From ghc-devs at haskell.org Thu Mar 1 02:41:21 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 02:41:21 -0000 Subject: [GHC] #14871: With process substitiution, ghc didn't read filedescriptor. Message-ID: <048.725b3d2df4357eed67fd8b8a75594876@haskell.org> #14871: With process substitiution, ghc didn't read filedescriptor. -------------------------------------+------------------------------------- Reporter: octaltree | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I ran ghc with process substitution as filename but ghc couldn't read the filedescriptor. I ran this script with bash and zsh, then I got the error. {{{#!sh #!/bin/sh H=''' main = putStrLn "Hello, World! ''' P=''' print("Hello, World!") ''' R=''' puts "Hello, World!" ''' stack ghc -- --version bash --version zsh --version cat --version python --version ruby --version echo '-----------------------' cat <(echo -n "$H") echo '-----------------------' stack ghc <(echo -n "$H") echo '-----------------------' python <(echo -n "$P") ruby <(echo -n "$R") }}} {{{ The Glorious Glasgow Haskell Compilation System, version 8.2.2 GNU bash, バージョン 4.4.19(1)-release (x86_64-unknown-linux-gnu) Copyright (C) 2016 Free Software Foundation, Inc. ライセンス GPLv3+: GNU GPL バージョン 3 またはそれ以降 This is free software; you are free to change and redistribute it. There is NO WARRANTY, to the extent permitted by law. zsh 5.4.2 (x86_64-unknown-linux-gnu) cat (GNU coreutils) 8.29 Copyright (C) 2017 Free Software Foundation, Inc. License GPLv3+: GNU GPL version 3 or later . This is free software: you are free to change and redistribute it. There is NO WARRANTY, to the extent permitted by law. 作者 Torbjorn Granlund および Richard M. Stallman。 Python 3.6.4 ruby 2.5.0p0 (2017-12-25 revision 61468) [x86_64-linux] ----------------------- main = putStrLn "Hello, World! ----------------------- target ‘/dev/fd/63’ is not a module name or a source file ----------------------- Hello, World! /dev/fd/63: No such file or directory @ realpath_rec - /proc/4024/fd/pipe:[1855404] (Errno::ENOENT) }}} I already reported to ruby. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 09:58:31 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 09:58:31 -0000 Subject: [GHC] #14862: Switching to Cabal 2.2 makes ghc unusable In-Reply-To: <048.eb29786956ab5b6f0a644e75f882323f@haskell.org> References: <048.eb29786956ab5b6f0a644e75f882323f@haskell.org> Message-ID: <063.45d52cb1209c5f285f777741faac2376@haskell.org> #14862: Switching to Cabal 2.2 makes ghc unusable -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: angerman Type: bug | Status: new Priority: high | Milestone: Component: None | Version: 8.4.1-alpha3 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 alpmestan): * owner: alpmestan => angerman Comment: Moritz is looking into the few small quirks left to handle for [https://phabricator.haskell.org/D4453 D4453] to be mergeable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 11:35:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 11:35:54 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.7b85c18a0bf8597f6d65b6878d01f74f@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): How can I reproduce this? I'm trying this on ghc-mini (ghc at df2c3b3364834d2fd038192c89348fc50a2e0475), `forkprocess01` passes every time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 13:14:00 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 13:14:00 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core Message-ID: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature | Status: new request | Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Sometimes, when I'm doing stuff that involves twiddling bits, it would be nicer to see integer literals in hexadecimal when I dump core with `-ddump-simpl`. For example, in a project I'm working on, I've got this: {{{ detectNull :: Word -> Word detectNull x = (x - repeatHexZeroOne) .&. complement x .&. repeatHexEightZero detectArtifact :: Word -> Word -> Word detectArtifact x artifact = detectNull (applyArtifact x artifact) applyArtifact :: Word -> Word -> Word applyArtifact = xor repeatHexZeroOne :: Word repeatHexZeroOne = div maxBound 255 repeatHexEightZero :: Word repeatHexEightZero = 128 * (div maxBound 255 :: Word) }}} Once everything gets unboxed and constant-folding happens, in GHC core, the places where I used `repeatHexZeroOne` show `72340172838076673##` (on a 64-bit machine). This is accurate, but it would be nice I could give a flag to make it show `0x0101010101010101##` instead. This would make it easier for me to confirm that the arithmetic I used to generate a bit pattern actually generated what I thought it did. Admittedly, we'd probably want leading zeroes to get chopped off so that small integer literals didn't show up with 15 zeroes in front of them. So, realistically, it might show up as `0x101010101010101##`. Or maybe it could always to padded with leading zeroes until the length was a power of two. Anyway, not important, but I thought it would be nice to have. Possible flag name: `-ddump-hex-literals`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 14:01:33 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 14:01:33 -0000 Subject: [GHC] #14856: GHC API: Linker failure on loading target multiple times In-Reply-To: <049.5d72fe6ce564adad9a42ef4e09990bc5@haskell.org> References: <049.5d72fe6ce564adad9a42ef4e09990bc5@haskell.org> Message-ID: <064.a4ccdf0a6e784a45d21425f3aba51501@haskell.org> #14856: GHC API: Linker failure on loading target multiple times -------------------------------+-------------------------------------- Reporter: fizzixnerd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: GHC API | Version: 8.4.1-alpha3 Resolution: | Keywords: GHC API Linker Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------+-------------------------------------- Changes (by fizzixnerd): * version: 8.2.2 => 8.4.1-alpha3 * architecture: Unknown/Multiple => x86_64 (amd64) * milestone: => 8.4.1 Comment: Checked this against ghc 8.4.0.20180224, and found it still exists. Updating ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 14:42:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 14:42:54 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.6033a40a6be40b39729c112ea89ea38f@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Fine with me. Maybe `Word#` should ''always'' be shown in hex? But yes, a flag to control is always good. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 15:06:53 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 15:06:53 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.ad0cf8dab6e88f4fc1e80a29254514a7@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 19:49:24 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 19:49:24 -0000 Subject: [GHC] #1831: reify never provides the declaration of variables In-Reply-To: <044.a26292943bffdeb4bdb3ded03525ce1f@haskell.org> References: <044.a26292943bffdeb4bdb3ded03525ce1f@haskell.org> Message-ID: <059.cde89d4b9fc2ab6faade7ae80a42ea0f@haskell.org> #1831: reify never provides the declaration of variables -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Template Haskell | Version: 6.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 parsonsmatt): I'd like to register interest in having this available :) My specific use case is walking the AST from a given point to capture uses of `throw`, `throwM`, `throwIO`, etc. and try to get a list of possible exception types that might arise from a given function. eg: {{{ openFile' :: FilePath -> IO (Either IOException String) openFile' f = [catch|openFile f|] }}} It seems like this would be useful for other sorts of static analysis, as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 19:56:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 19:56:35 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.e28899e137a03cdd27e1a2ac0eea550b@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, perhaps it only occurs under load? How many times did you run the test? I would set it in a loop and let it run for an hours or so before drawing any conclusions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 21:10:45 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 21:10:45 -0000 Subject: [GHC] #14873: GHC HEAD regression (piResultTy) Message-ID: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> #14873: GHC HEAD regression (piResultTy) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.5 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- (Originally noticed [https://travis- ci.org/goldfirere/singletons/jobs/347945148#L1179 here].) The following program typechecks on GHC 8.2.2 on GHC 8.4.1, but panics on GHC HEAD: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind (Type) data family Sing (a :: k) newtype instance Sing (f :: k1 ~> k2) = SLambda { applySing :: forall t. Sing t -> Sing (Apply f t) } data TyFun :: Type -> Type -> Type type a ~> b = TyFun a b -> Type infixr 0 ~> type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 class SingI (a :: k) where sing :: Sing a data ColSym1 :: f a -> a ~> Bool type instance Apply (ColSym1 x) y = Col x y class PColumn (f :: Type -> Type) where type Col (x :: f a) (y :: a) :: Bool class SColumn (f :: Type -> Type) where sCol :: forall (x :: f a) (y :: a). Sing x -> Sing y -> Sing (Col x y :: Bool) instance (SColumn f, SingI x) => SingI (ColSym1 (x :: f a) :: a ~> Bool) where sing = SLambda (sCol (sing @_ @x)) }}} {{{ $ /opt/ghc/head/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.5.20180201 for x86_64-unknown-linux): piResultTy k_aZU[tau:1] (a_aW8[sk:1] |> <*>_N) Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:947:35 in ghc:Type }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 23:16:11 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 23:16:11 -0000 Subject: [GHC] #14874: Trac: TypeError: can't compare datetime.datetime to str Message-ID: <046.4f845865a3bc11f2535cf0d6fa1fe078@haskell.org> #14874: Trac: TypeError: can't compare datetime.datetime to str -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: hvr Type: bug | Status: new Priority: normal | Milestone: Component: Trac & Git | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This problem appears when sorting closed tickets by their "modified" field. [https://ghc.haskell.org/trac/ghc/query?status=closed&col=id&col=changetime&desc=1&order=changetime Example]. The source of the problem appears to be that a few old tickets don't have a "modified" time (changetime). Instead their "changetime" field seems to be set to the empty string. Apparently similar issues have been known to the Trac developers for a while: https://trac.edgewall.org/ticket/12029. ==== How to Reproduce ==== While doing a GET operation on `/query`, Trac issued an internal error. ''(please provide additional details here)'' Request parameters: {{{ {u'col': [u'id', u'changetime'], u'desc': u'1', u'order': u'changetime', u'page': u'2', u'status': u'closed'} }}} User agent: `Mozilla/5.0 (X11; Linux x86_64) AppleWebKit/537.36 (KHTML, like Gecko) Ubuntu Chromium/64.0.3282.167 Chrome/64.0.3282.167 Safari/537.36` ==== System Information ==== ''System information not available'' ==== Enabled Plugins ==== ''Plugin information not available'' ==== Interface Customization ==== ''Interface customization information not available'' ==== Python Traceback ==== {{{ Traceback (most recent call last): File "/usr/local/lib/python2.7/dist-packages/trac/web/main.py", line 623, in _dispatch_request dispatcher.dispatch(req) File "/usr/local/lib/python2.7/dist-packages/trac/web/main.py", line 239, in dispatch resp = chosen_handler.process_request(req) File "/usr/local/lib/python2.7/dist-packages/trac/ticket/query.py", line 1000, in process_request return self.display_html(req, query) File "/usr/local/lib/python2.7/dist-packages/trac/ticket/query.py", line 1117, in display_html data = query.template_data(context, tickets, orig_list, orig_time, req) File "/usr/local/lib/python2.7/dist-packages/trac/ticket/query.py", line 776, in template_data elif ticket['changetime'] > orig_time: TypeError: can't compare datetime.datetime to str }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 23:30:47 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 23:30:47 -0000 Subject: [GHC] #12919: Equality not used for substitution In-Reply-To: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> References: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> Message-ID: <063.489140017292097a77c0b9edcc3369a9@haskell.org> #12919: Equality not used for substitution -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: patch Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T12919 Blocked By: | Blocking: 14441 Related Tickets: #13643 | Differential Rev(s): Phab:D3848 Wiki Page: | -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 23:47:55 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 23:47:55 -0000 Subject: [GHC] #3676: realToFrac doesn't sanely convert between floating types In-Reply-To: <046.c71a4f69a48e7e64e18a56e29c643e03@haskell.org> References: <046.c71a4f69a48e7e64e18a56e29c643e03@haskell.org> Message-ID: <061.6ff0028bd24b2a9a6f0d32f23c302c7a@haskell.org> #3676: realToFrac doesn't sanely convert between floating types -------------------------------------+------------------------------------- Reporter: draconx | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Core Libraries | Version: 6.12.1 Resolution: | Keywords: report-impact Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 23:56:39 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 23:56:39 -0000 Subject: [GHC] #9123: Need for higher kinded roles In-Reply-To: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> References: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> Message-ID: <061.7b5ad973cff33fc1b5f0fff8ae75644b@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) | Keywords: Roles, Resolution: | QuantifiedConstraints 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): Superclasses now working, I think, in `wip/T2893`: {{{ commit 910dfcfeadc4f132e887bc4adf5ac2e17a29d99b Author: Simon Peyton Jones Date: Thu Mar 1 23:32:29 2018 +0000 Add superclasses to quantified constraints This patch adds suppport for superclasses to quantified constraints. For example (contrived): f :: (forall a. Ord a => Ord (m a)) => m a -> m a -> Bool f x y = x==y Here we need (Eq (m a)); but the quantifed constraint deals only with Ord. But we can make it work by using its superclass. This behaviour finally delivers on the promise of comment:30 of Trac #9123: we can write an implication constraint that solves the problem of higher-kinded roles. Test quantified-constraints/T8123 demonstrates this in action. compiler/basicTypes/Id.hs | 2 +- compiler/typecheck/Inst.hs | 4 +- compiler/typecheck/TcCanonical.hs | 180 ++++++++++++++--------- compiler/typecheck/TcErrors.hs | 4 +- compiler/typecheck/TcEvTerm.hs | 5 +- compiler/typecheck/TcEvidence.hs | 74 ++++++---- compiler/typecheck/TcHsSyn.hs | 23 ++- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcInteract.hs | 61 ++++---- compiler/typecheck/TcMType.hs | 6 +- compiler/typecheck/TcPatSyn.hs | 7 +- compiler/typecheck/TcPluginM.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 62 ++++++-- compiler/typecheck/TcSMonad.hs | 119 +++++++-------- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcType.hs | 2 +- compiler/types/Class.hs | 54 ++++--- compiler/types/Kind.hs | 2 + testsuite/tests/quantified-constraints/T2893b.hs | 24 --- testsuite/tests/quantified-constraints/T2893c.hs | 15 ++ testsuite/tests/quantified-constraints/T9123.hs | 24 +++ testsuite/tests/quantified-constraints/T9123a.hs | 26 ++++ testsuite/tests/quantified-constraints/all.T | 5 + 23 files changed, 426 insertions(+), 279 deletions(-) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 1 23:57:41 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 01 Mar 2018 23:57:41 -0000 Subject: [GHC] #2893: Implement "Quantified constraints" proposal In-Reply-To: <045.2638646abdcf216191d07c9810407703@haskell.org> References: <045.2638646abdcf216191d07c9810407703@haskell.org> Message-ID: <060.9ec44f4b26e0d0a1447ab689b3007fbc@haskell.org> #2893: Implement "Quantified constraints" proposal -------------------------------------+------------------------------------- Reporter: porges | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.10.1 Resolution: | Keywords: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5927 | Differential Rev(s): Phab:D4353 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I've added the superclass stuff {{{ commit 910dfcfeadc4f132e887bc4adf5ac2e17a29d99b Author: Simon Peyton Jones Date: Thu Mar 1 23:32:29 2018 +0000 Add superclasses to quantified constraints This patch adds suppport for superclasses to quantified constraints. For example (contrived): f :: (forall a. Ord a => Ord (m a)) => m a -> m a -> Bool f x y = x==y Here we need (Eq (m a)); but the quantifed constraint deals only with Ord. But we can make it work by using its superclass. This behaviour finally delivers on the promise of comment:30 of Trac #9123: we can write an implication constraint that solves the problem of higher-kinded roles. Test quantified-constraints/T8123 demonstrates this in action. compiler/basicTypes/Id.hs | 2 +- compiler/typecheck/Inst.hs | 4 +- compiler/typecheck/TcCanonical.hs | 180 ++++++++++++++--------- compiler/typecheck/TcErrors.hs | 4 +- compiler/typecheck/TcEvTerm.hs | 5 +- compiler/typecheck/TcEvidence.hs | 74 ++++++---- compiler/typecheck/TcHsSyn.hs | 23 ++- compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcInteract.hs | 61 ++++---- compiler/typecheck/TcMType.hs | 6 +- compiler/typecheck/TcPatSyn.hs | 7 +- compiler/typecheck/TcPluginM.hs | 2 +- compiler/typecheck/TcRnTypes.hs | 62 ++++++-- compiler/typecheck/TcSMonad.hs | 119 +++++++-------- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcType.hs | 2 +- compiler/types/Class.hs | 54 ++++--- compiler/types/Kind.hs | 2 + testsuite/tests/quantified-constraints/T2893b.hs | 24 --- testsuite/tests/quantified-constraints/T2893c.hs | 15 ++ testsuite/tests/quantified-constraints/T9123.hs | 24 +++ testsuite/tests/quantified-constraints/T9123a.hs | 26 ++++ testsuite/tests/quantified-constraints/all.T | 5 + 23 files changed, 426 insertions(+), 279 deletions(-) }}} So now all the features I was planning are implemented. Give it a whirl! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 00:16:57 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 00:16:57 -0000 Subject: [GHC] #11382: Optimize Data.Char In-Reply-To: <046.07b85d059cbd81601867717299b83062@haskell.org> References: <046.07b85d059cbd81601867717299b83062@haskell.org> Message-ID: <061.6020da7bb810cf7718d53358191acae4@haskell.org> #11382: Optimize Data.Char -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9638, #1473 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 00:23:58 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 00:23:58 -0000 Subject: [GHC] #14873: GHC HEAD regression (piResultTy) In-Reply-To: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> References: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> Message-ID: <065.2fa9ef1725a288b89ccd48f2fed96e62@haskell.org> #14873: GHC HEAD regression (piResultTy) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: This regression was introduced in commit 0a12d92a8f65d374f9317af2759af2b46267ad5c (`Further improvements to well- kinded types`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 00:34:46 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 00:34:46 -0000 Subject: [GHC] #9123: Need for higher kinded roles In-Reply-To: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> References: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> Message-ID: <061.d52ff6b9c8a61372dd8724823e653d1f@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) | Keywords: Roles, Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): simonpj, that commit doesn't build for me. I get the following error when building stage 2: {{{ "inplace/bin/ghc-stage1" -hisuf hi -osuf o -hcsuf hc -static -O0 -H64m -Wall -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -this-unit-id ghc-8.5 -hide-all- packages -i -icompiler/backpack -icompiler/basicTypes -icompiler/cmm -icompiler/codeGen -icompiler/coreSyn -icompiler/deSugar -icompiler/ghci -icompiler/hsSyn -icompiler/iface -icompiler/llvmGen -icompiler/main -icompiler/nativeGen -icompiler/parser -icompiler/prelude -icompiler/profiling -icompiler/rename -icompiler/simplCore -icompiler/simplStg -icompiler/specialise -icompiler/stgSyn -icompiler/stranal -icompiler/typecheck -icompiler/types -icompiler/utils -icompiler/vectorise -icompiler/stage2/build -Icompiler/stage2/build -icompiler/stage2/build/./autogen -Icompiler/stage2/build/./autogen -Icompiler/. -Icompiler/parser -Icompiler/utils -Icompiler/../rts/dist/build -Icompiler/stage2 -optP-DGHCI -optP-include -optPcompiler/stage2/build/./autogen/cabal_macros.h -package-id base-4.11.0.0 -package-id deepseq-1.4.3.0 -package-id directory-1.3.1.5 -package-id process-1.6.2.0 -package-id bytestring-0.10.8.2 -package-id binary-0.8.5.1 -package-id time-1.8.0.2 -package-id containers-0.5.10.2 -package-id array-0.5.2.0 -package-id filepath-1.4.1.2 -package-id template-haskell-2.13.0.0 -package-id hpc-0.6.0.3 -package-id transformers-0.5.5.0 -package-id ghc-boot-8.5 -package-id ghc-boot-th-8.5 -package-id ghci-8.5 -package-id unix-2.7.2.2 -package-id terminfo-0.4.1.1 -Wall -Wno-name-shadowing -Wnoncanonical-monad-instances -Wnoncanonical- monadfail-instances -Wnoncanonical-monoid-instances -this-unit-id ghc -XHaskell2010 -XNoImplicitPrelude -optc-DTHREADED_RTS -DGHCI_TABLES_NEXT_TO_CODE -DSTAGE=2 -Rghc-timing -O0 -Wcpp-undef -no- user-package-db -rtsopts -Wnoncanonical-monad-instances -odir compiler/stage2/build -hidir compiler/stage2/build -stubdir compiler/stage2/build -dynamic-too -c compiler/typecheck/TcPluginM.hs -o compiler/stage2/build/TcPluginM.o -dyno compiler/stage2/build/TcPluginM.dyn_o compiler/typecheck/TcPluginM.hs:176:38: error: • Data constructor not in scope: EvExpr :: EvExpr -> TcEvidence.EvTerm • Perhaps you meant variable ‘TcM.ctEvExpr’ (imported from TcRnMonad) Perhaps you want to add ‘EvExpr’ to the import list in the import of ‘TcEvidence’ (compiler/typecheck/TcPluginM.hs:(72,1)-(73,51)). | 176 | setEvBind $ mkGivenEvBind new_ev (EvExpr evtm) | ^^^^^^ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 00:50:23 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 00:50:23 -0000 Subject: [GHC] #12706: Collecting type info is slow In-Reply-To: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> References: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> Message-ID: <063.5279eae545a48fff649187f40109542d@haskell.org> #12706: Collecting type info is slow -------------------------------------+------------------------------------- Reporter: vshabanov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 02:11:28 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 02:11:28 -0000 Subject: [GHC] #14875: -ddump-splices pretty-printing oddities with case statements Message-ID: <050.0e58dfe7bbe09336b7902dab619fac86@haskell.org> #14875: -ddump-splices pretty-printing oddities with case statements -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Debugging Unknown/Multiple | information is incorrect Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The latest installment in "Ryan finds minor bugs in `-ddump-splices`". Take this program: {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([d| f :: Bool -> Bool f x = case x of (True :: Bool) -> True (False :: Bool) -> False g :: Bool -> Bool g x = (case x of True -> True False -> False) :: Bool |]) }}} Compiling this gives: {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(6,3)-(15,6): Splicing declarations [d| f_a1sB :: Bool -> Bool f_a1sB x_a1sD = case x_a1sD of (True :: Bool) -> True (False :: Bool) -> False g_a1sC :: Bool -> Bool g_a1sC x_a1sE = (case x_a1sE of True -> True False -> False) :: Bool |] ======> f_a49Z :: Bool -> Bool f_a49Z x_a4a0 = case x_a4a0 of True :: Bool -> True False :: Bool -> False g_a49Y :: Bool -> Bool g_a49Y x_a4a1 = case x_a4a1 of True -> True False -> False :: Bool }}} Neither the `-ddump-splices` output for `f` nor `g` parse are legal Haskell: * In `f`, GHC fails to parenthesize the pattern signatures `True :: Bool` and `False :: Bool`. * In `g`, GHC fails to parenthesize the `case` expression which has an explicit `Bool` signature. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 06:51:16 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 06:51:16 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.a46b2ee27692e9b40610c2b7955624f8@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): > How many times did you run the test? I would set it in a loop and let it run for an hours or so before drawing any conclusions. I run it 100 times, passed every time. I'll keep it running for a few hours and see if that makes any difference. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 09:15:39 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 09:15:39 -0000 Subject: [GHC] #2893: Implement "Quantified constraints" proposal In-Reply-To: <045.2638646abdcf216191d07c9810407703@haskell.org> References: <045.2638646abdcf216191d07c9810407703@haskell.org> Message-ID: <060.f550c0a032573e7a6a6f049a0a807977@haskell.org> #2893: Implement "Quantified constraints" proposal -------------------------------------+------------------------------------- Reporter: porges | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.10.1 Resolution: | Keywords: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5927 | Differential Rev(s): Phab:D4353 Wiki Page: | -------------------------------------+------------------------------------- Comment (by AntC): > ... superclass stufff ... Give it a whirl! Terrific. I'd appreciate if someone could test my hypothesis of a use case [1]. Note this using QuantifiedConstraints purely as implications with nothing `forall`'d.: > Consider modelling the logic for somewhat-injective type functions. > Take type-level Boolean `And` [5]. > > `And` is not fully injective but: > > * If the result is True, the two arguments must be True. > > * If the result is False and one argument is True, the other must be False. {{{ class ( (b3 ~ True) => (b1 ~ True, b2 ~ True), (b3 ~ False, b1 ~ True) => b2 ~ False, (b3 ~ False, b2 ~ True) => b1 ~ False ) => And (b1 :: Bool) (b2 :: Bool) (b3 :: Bool) | b1 b2 -> b3 where {} instance And True b2 b2 instance And False b2 False x3 = undefined :: (And b1 b2 True) => (b1, b2) -- should infer x3's type as :: (True, True) }}} [https://mail.haskell.org/pipermail/glasgow-haskell- users/2018-February/026694.html [1]] [https://mail.haskell.org/pipermail/ghc-devs/2017-November/015073.html [5]] [https://mail.haskell.org/pipermail/glasgow-haskell- users/2017-November/026650.html continued] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 09:24:23 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 09:24:23 -0000 Subject: [GHC] #14876: Reading source files in text mode so that we get CRLF conversion under Windows? Message-ID: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> #14876: Reading source files in text mode so that we get CRLF conversion under Windows? -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- According to https://github.com/sol/interpolate/issues/9 the string passed to a quasi quoter contains CRLF line endings. I have observed the same things for Haddock comments (both in `haddock` and `doctest` when extracted through the GHC API). I haven't looked at any GHC code, but wouldn't the right thing be to read source files in text mode so that we get newline conversion? If we don't want / can't do that for some reason, then wouldn't we still want to handle this somewhere deep down the stack so that not every client has to deal with it separately? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 09:32:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 09:32:48 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.040178529919ea0e26e3752c924d34d8@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Here's a code path that may be causing this: - rts/Schedule.c `forkProcess()` (called by the library) acquires `all_tasks_mutex` (in line 1987) - `forkProcess()` calls `fork()` - If in parent process (which means all locks are still held), it releases a few locks (but not `all_tasks_mutex`) and calls `releaseCapability_` for all capabilities. - In rts/Capability.c `releaseCapability_()`, when these conditions hold 1. `cap->n_returning_tasks == 0` 2. There is not a pending sync 3. Next thread in the run queue is not a bound one 4. The capability has spare workers (`cap->spare_workers` is not `NULL`) 5. The capability's run queue is not empty (`cap->n_run_queue != 0`) and we're not shutting down (`sched_state != SCHED_SHUTTING_DOWN`) When all these hold `releaseCapability_()` calls `startWorkerTask()` (rts/Task.c), which in turn calls `newTask()`, which tries to take `all_tasks_mutex`, causing this bug. Btw, if I'm reading this correctly there is at least one more bug. The fork(2) man page says state of mutex is also replicated in the child process, so `all_tasks_mutex` will be acquired in the child process. However in the "child" branch of `forkProcess()` we initialize `all_tasks_mutex` without releasing it, and `pthread_mutex_init` man page says "Attempting to initialize an already initialized mutex results in undefined behavior.". So far I've run this test more than 1500 times on ghc-mini and it passed every time. I'll try to reproduce locally based on the information above. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 09:44:03 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 09:44:03 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.b632fb50c37a8a1717b186fd46baafb4@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I confirmed that if the code path described above is taken we get this error. gdb output: {{{ >>> call startWorkerTask(cap) Main: internal error: multiple ACQUIRE_LOCK: rts/Task.c 228 (GHC version 8.5.20180301 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Thread 1 "Main" received signal SIGABRT, Aborted. 0x00007ffff6c8d428 in __GI_raise (sig=sig at entry=6) at ../sysdeps/unix/sysv/linux/raise.c:54 54 ../sysdeps/unix/sysv/linux/raise.c: No such file or directory. }}}[ -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 09:53:15 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 09:53:15 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.74f9b3016ac44d05eddd8bb4cddc5ab7@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I manage to reproduce this locally on my Linux laptop: {{{ $ ./Main +RTS -N Main: internal error: multiple ACQUIRE_LOCK: rts/Task.c 228 (GHC version 8.5.20180301 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug in child process [2] 6823 abort (core dumped) ./Main +RTS -N $ ./Main +RTS -N in parent process in child process Just (Exited (ExitFailure 72)) $ ./Main +RTS -N Main: internal error: multiple ACQUIRE_LOCK: rts/Task.c 228 (GHC version 8.5.20180301 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug in child process [2] 6927 abort (core dumped) ./Main +RTS -N }}} reproducer: {{{ import System.Exit import System.Posix.Process import Control.Concurrent main = do p <- forkProcess $ putStrLn "in child process" >> exitWith (ExitFailure 72) putStrLn "in parent process" r <- getProcessStatus True False p yield print r }}} compile with: {{{ ghc-stage2 -O0 Main.hs -debug -rtsopts -threaded -fforce-recomp }}} run with `+RTS -N` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 10:30:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 10:30: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.b0abfd596385f0f5c6caa98114addb03@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) | Keywords: Roles, Resolution: | QuantifiedConstraints 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): Importing `EvTerm(..)` from `TcEvidence` in `compiler/typecheck/TcPluginM.hs` does the trick -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 11:09:13 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 11:09:13 -0000 Subject: [GHC] #12706: Collecting type info is slow In-Reply-To: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> References: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> Message-ID: <063.eb97a2c9804c26a2b03a75fc82b10661@haskell.org> #12706: Collecting type info is slow -------------------------------------+------------------------------------- Reporter: vshabanov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D4459 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alexbiehl): * differential: => D4459 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 11:19:26 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 11:19:26 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.b2e73751b7d468cde168e590d781f5fe@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #1391, #9295, | Differential Rev(s): #9296 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * related: => #1391, #9295, #9296 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 11:24:20 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 11:24:20 -0000 Subject: [GHC] #2893: Implement "Quantified constraints" proposal In-Reply-To: <045.2638646abdcf216191d07c9810407703@haskell.org> References: <045.2638646abdcf216191d07c9810407703@haskell.org> Message-ID: <060.c7554a794218b34fb736e6d6d14cc25c@haskell.org> #2893: Implement "Quantified constraints" proposal -------------------------------------+------------------------------------- Reporter: porges | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.10.1 Resolution: | Keywords: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5927 | Differential Rev(s): Phab:D4353 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): `f` should have an `Ord a` constraint right? {{{#!hs f :: (Ord a, forall x. Ord x => Ord (m x)) => m a -> m a -> Bool }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 11:48:38 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 11:48:38 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.afd4f02d36ae518745b18b3ba987e341@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #1391, #9295, | Differential Rev(s): Phab:D4460 #9296 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * failure: None/Unknown => Runtime crash * differential: => Phab:D4460 * os: MacOS X => Unknown/Multiple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 12:42:18 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 12:42:18 -0000 Subject: [GHC] #14697: Redundant computation in fingerprintDynFlags when compiling many modules In-Reply-To: <046.c781f4e812a45b7f1a7576c9d7db1ab8@haskell.org> References: <046.c781f4e812a45b7f1a7576c9d7db1ab8@haskell.org> Message-ID: <061.cd820be292298fca59e339fee8bebeb2@haskell.org> #14697: Redundant computation in fingerprintDynFlags when compiling many modules -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 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:D4445 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"b8f03bbe16af7a09b494a33fbbe523ecd82f1a50/ghc" b8f03bbe/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b8f03bbe16af7a09b494a33fbbe523ecd82f1a50" Cache the fingerprint of sOpt_P Before this change we would compute a hash of all the command line -optP flags once per file. With a lot of files and many -optP flags, that's a lot of repeated work. I added a new Note that explains the approach and rationale. Test Plan: new test Reviewers: simonmar, simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14697 Differential Revision: https://phabricator.haskell.org/D4445 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 12:43:49 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 12:43:49 -0000 Subject: [GHC] #14697: Redundant computation in fingerprintDynFlags when compiling many modules In-Reply-To: <046.c781f4e812a45b7f1a7576c9d7db1ab8@haskell.org> References: <046.c781f4e812a45b7f1a7576c9d7db1ab8@haskell.org> Message-ID: <061.290f782c6fe72505338946be1e96ea1a@haskell.org> #14697: Redundant computation in fingerprintDynFlags when compiling many modules -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): phab:D4445 Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 13:06:26 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 13:06:26 -0000 Subject: [GHC] #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' In-Reply-To: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> References: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> Message-ID: <066.8987f693767c109f43d875347de2ecfc@haskell.org> #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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): With the [https://ghc.haskell.org/trac/ghc/ticket/2893#comment:34 latest changes] `uncurryC2` works. Should this be closed? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 13:08:19 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 13:08:19 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.d4abc7ab3602bd99bd4698929b397a0d@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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:6 simonpj]: > What is "this program"? The one in comment:4 uses `CCategory` but does not define it. `ConstraintCategory` was meant to be `CCategory`, I changed it to reflect that -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 13:14:11 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 13:14:11 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.39e1753b74a890f6b9680de01286f576@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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:7 RyanGlScott]: > I'm referring to the original program itself: The original program still gives a stack overflow with [https://ghc.haskell.org/trac/ghc/ticket/2893#comment:34 latest changes]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 13:35:12 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 13:35:12 -0000 Subject: [GHC] #12706: Collecting type info is slow In-Reply-To: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> References: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> Message-ID: <063.7471da4412320dd6f997d61f5945fafa@haskell.org> #12706: Collecting type info is slow -------------------------------------+------------------------------------- Reporter: vshabanov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4459 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: D4459 => Phab:D4459 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 13:45:06 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 13:45:06 -0000 Subject: [GHC] #14831: QuantifiedConstraints: Odd superclass constraint In-Reply-To: <051.631b3f4dec55319ae6028526fc90fcb8@haskell.org> References: <051.631b3f4dec55319ae6028526fc90fcb8@haskell.org> Message-ID: <066.9f797ced7e9a68854fd8497e1f5b7e85@haskell.org> #14831: QuantifiedConstraints: Odd superclass constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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): Update: With [https://ghc.haskell.org/trac/ghc/ticket/2893#comment:34 latest changes] the original code compiles AND we can build this hierarchy for our own `Semigroup`-`Monoid`-`Group` hierarchy {{{#!hs instance semi ~=> Semigroup => Semigroup (Free semi a) where (<>) = liftFree2 (<>) sconcat = undefined stimes = undefined instance mon ~=> Monoid => Monoid (Free mon a) where mempty = liftFree0 mempty mappend = liftFree2 (<>) mconcat = undefined instance grp ~=> Group => Group (Free grp a) where inv = liftFree1 inv }}} but leaving out or inlining default methods `mconcat = foldr mappend mempty` fails. ---- {{{#!hs class Monoid a => Group a where inv :: a -> a type cls ~=> cls' = (forall xx. cls xx => cls' xx :: Constraint) liftFree0 :: (forall xx. cls xx => xx) -> Free cls a liftFree0 a = Free (pure a) liftFree1 :: (forall xx. cls xx => xx -> xx) -> (Free cls a -> Free cls a) liftFree1 f (Free xs) = Free (fmap f xs) liftFree2 :: (forall xx. cls xx => xx -> xx -> xx) -> (Free cls a -> Free cls a -> Free cls a) liftFree2 f (Free xs) (Free ys) = Free (liftA2 f xs ys) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 14:49:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 14:49:31 -0000 Subject: [GHC] #14877: QuantifiedConstraints: Can't deduce `xx' from `(xx => a, xx)' Message-ID: <051.a93bc7dc60f96bf37ae9f443b2fe178c@haskell.org> #14877: QuantifiedConstraints: Can't deduce `xx' from `(xx => a, xx)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This works with the [https://ghc.haskell.org/trac/ghc/ticket/2893#comment:34 latest change to the -XQuantifiedConstraints branch]. {{{#!hs {-# Language QuantifiedConstraints, FlexibleInstances, MultiParamTypeClasses, AllowAmbiguousTypes, RankNTypes, PolyKinds, ConstraintKinds, UndecidableInstances #-} class (forall xx. (xx => a) => Implies xx b) => F a b instance (forall xx. (xx => a) => Implies xx b) => F a b class (a => b) => Implies a b instance (a => b) => Implies a b }}} but replacing `Implies xx b` with `(xx => b)` causes it to fail. I don't know if the cause of this overlaps with an existing ticket. {{{#!hs class (forall xx. (xx => a) => (xx => b)) => F a b instance (forall xx. (xx => a) => (xx => b)) => F a b -- $ ghci -ignore-dot-ghci /tmp/ASD.hs -- GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help -- [1 of 1] Compiling Main ( /tmp/ASD.hs, interpreted ) -- -- /tmp/ASD.hs:4:10: error: -- • Could not deduce: xx0 -- arising from the superclasses of an instance declaration -- from the context: forall (xx :: Constraint). (xx => a, xx) => b -- bound by the instance declaration at /tmp/ASD.hs:4:10-53 -- or from: (xx => a, xx) -- bound by a quantified context at /tmp/ASD.hs:1:1 -- • In the instance declaration for ‘F a b’ -- | -- 4 | instance (forall xx. (xx => a) => (xx => b)) => F a b -- | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ -- Failed, no modules loaded. -- Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 14:49:43 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 14:49:43 -0000 Subject: [GHC] #14877: QuantifiedConstraints: Can't deduce `xx' from `(xx => a, xx)' In-Reply-To: <051.a93bc7dc60f96bf37ae9f443b2fe178c@haskell.org> References: <051.a93bc7dc60f96bf37ae9f443b2fe178c@haskell.org> Message-ID: <066.e6e3be3880415bbe7392314efbff336a@haskell.org> #14877: QuantifiedConstraints: Can't deduce `xx' from `(xx => a, xx)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * version: 8.2.2 => 8.5 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 15:47:06 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 15:47:06 -0000 Subject: [GHC] #14431: Peculiar RTS crash on OS X In-Reply-To: <046.50af1b780509b4198d8903bef0dbcaf2@haskell.org> References: <046.50af1b780509b4198d8903bef0dbcaf2@haskell.org> Message-ID: <061.65393ed2116345aaafc706bd6f58afe1@haskell.org> #14431: Peculiar RTS crash on OS X ---------------------------------+---------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14538 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * related: => #14538 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 15:47:17 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 15:47:17 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.b7842203b7f0597ed04a9ebfdb5e8a5a@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #1391, #9295, | Differential Rev(s): Phab:D4460 #9296, #14431 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: #1391, #9295, #9296 => #1391, #9295, #9296, #14431 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 15:54:46 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 15:54:46 -0000 Subject: [GHC] #14381: Consider making ghc-pkg fill in abi-depends based on depends In-Reply-To: <045.a757b4d974e51bd6ab6f6869ba65de4c@haskell.org> References: <045.a757b4d974e51bd6ab6f6869ba65de4c@haskell.org> Message-ID: <060.61b6eff472be948ed861f8c0fcbe0393@haskell.org> #14381: Consider making ghc-pkg fill in abi-depends based on depends -------------------------------------+------------------------------------- Reporter: ezyang | Owner: thoughtpolice Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: ghc-pkg | Version: 8.2.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:D4159 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => highest * milestone: 8.2.3 => 8.4.2 Comment: I have encountered this on quite a few occasions. Bumping priority. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 16:02:26 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 16:02:26 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.828fb096c256d619664840273a98d390@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.4.1 => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 16:16:58 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 16:16:58 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.6360f474cbfa86e4301d0943403bb5c3@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: highest | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #1391, #9295, | Differential Rev(s): Phab:D4460 #9296, #14431 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"e261b8523eb547b93b8b9e194bc2566350e7cc60/ghc" e261b852/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e261b8523eb547b93b8b9e194bc2566350e7cc60" forkProcess: fix task mutex release order `all_tasks_mutex` should be released before calling `releaseCapability_` in the parent process as `releaseCapability_` spawns worker tasks in some cases. Reviewers: bgamari, erikd, simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14538 Differential Revision: https://phabricator.haskell.org/D4460 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 16:29:14 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 16:29:14 -0000 Subject: [GHC] #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup In-Reply-To: <047.dbe3294939f168d779839dd776514e40@haskell.org> References: <047.dbe3294939f168d779839dd776514e40@haskell.org> Message-ID: <062.0b4a22e0caaa28381bf06177bb6d83f7@haskell.org> #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): I may have struck this problem too. {{{ [34 of 59] Compiling Published.Bedford ( /flare-timing/earth/test-suite-earth/Published/Bedford.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-apple-darwin): translateConPatVec: lookup }}} This [[https://github.com/BlockScope/flare- timing/commit/07ea720ec98c9c756f7ed63ee7b80f574eb00a07|revision]] introduced the problem from which I was able to [[https://github.com/BlockScope/flare- timing/commit/b3963f61f97d0c70d726319260241bbedbe45f7f|workaround]] by using qualified imports. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 17:33:34 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 17:33:34 -0000 Subject: [GHC] #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup In-Reply-To: <047.dbe3294939f168d779839dd776514e40@haskell.org> References: <047.dbe3294939f168d779839dd776514e40@haskell.org> Message-ID: <062.1e6fdcf0de356fbfcc804279d1eaa2ec@haskell.org> #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * priority: normal => high * resolution: => duplicate * milestone: => 8.4.2 Old description: > *Main> price Stock{name=name,ric=ric,price=price} = price > ghc: panic! (the 'impossible' happened) > (GHC version 8.0.1 for x86_64-unknown-mingw32): > translateConPatVec: lookup > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug New description: {{{ *Main> price Stock{name=name,ric=ric,price=price} = price ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-mingw32): translateConPatVec: lookup Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Comment: If I understand correctly, this is a duplicate of #13644 which should be fixed in the soon-to-be-released 8.4.1. Perhaps someone could verify this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 17:34:33 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 17:34:33 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.f9db6635e5c4220195db6db878056646@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: 8.4.2 Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #1391, #9295, | Differential Rev(s): Phab:D4460 #9296, #14431 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.4.2 Comment: Excellent sleuthing, osa1! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 17:35:39 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 17:35:39 -0000 Subject: [GHC] #9123: Need for higher kinded roles In-Reply-To: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> References: <046.743e1f5edf878b0ae2d2d6b5081e6a33@haskell.org> Message-ID: <061.eff19a734b62d55acb57010a2bf20397@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) | Keywords: Roles, Resolution: | QuantifiedConstraints 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): Sorry: fix pushed now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 17:40:06 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 17:40:06 -0000 Subject: [GHC] #2893: Implement "Quantified constraints" proposal In-Reply-To: <045.2638646abdcf216191d07c9810407703@haskell.org> References: <045.2638646abdcf216191d07c9810407703@haskell.org> Message-ID: <060.e2b13bdfac9e47dc783d44cc9aca5be6@haskell.org> #2893: Implement "Quantified constraints" proposal -------------------------------------+------------------------------------- Reporter: porges | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.10.1 Resolution: | Keywords: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5927 | Differential Rev(s): Phab:D4353 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:36 Iceland_jack]: > `f` should have an `Ord a` constraint right? You mean in the commit message? Yes, you're right. (Before putting this on master I'll squash all the commits and write a new message.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 17:41:13 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 17:41:13 -0000 Subject: [GHC] #14873: GHC HEAD regression (piResultTy) In-Reply-To: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> References: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> Message-ID: <065.97451f214aa8765b292f379a48c14877@haskell.org> #14873: GHC HEAD regression (piResultTy) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Urk! Patch coming -- but validation is not complete and I have to go home, so probably Monday. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 17:45:32 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 17:45:32 -0000 Subject: [GHC] #14876: Reading source files in text mode so that we get CRLF conversion under Windows? In-Reply-To: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> References: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> Message-ID: <065.985a44cd0748dc5bf6741b4c8f9c4148@haskell.org> #14876: Reading source files in text mode so that we get CRLF conversion under Windows? -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): GHC uses its `StringBuffer` abstraction, which is essentially just a bytestring, to read source files. `hGetStringBuffer` opens the file in binary mode, leaving UTF-8 decoding to `nextChar` and friends. In principle we could probably do newline conversion there. That being said, I'm a bit weary of changing this in fear of breaking someone relying on the current behavior. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 18:02:36 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 18:02:36 -0000 Subject: [GHC] #14878: Can't witness transitivity ((.)) of isomorphism of Constraints Message-ID: <051.a45c628270a13635f0d506c37084dcac@haskell.org> #14878: Can't witness transitivity ((.)) of isomorphism of Constraints -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This compiles, {{{#!hs {-# Language QuantifiedConstraints, GADTs, ConstraintKinds, TypeOperators, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-} data Dict c where Dict :: c => Dict c class (a => b) => Implies a b instance (a => b) => Implies a b type a -:- b = Dict (Implies a b, Implies b a) -- isomorphism of constraints, should be an equivalence relation id_ :: a-:-a id_ = Dict sym_ :: a-:-b -> b-:-a sym_ Dict = Dict -- comp_ :: a-:-b -> b-:-c -> a-:-c -- comp_ Dict Dict = Dict }}} but uncommenting `comp_` and GHC doesn't know how to deduce `b` (the location message is weird) {{{ $ ghci -ignore-dot-ghci hs/206-bug-quantified-constraints.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( hs/206-bug-quantified- constraints.hs, interpreted ) hs/206-bug-quantified-constraints.hs:1:1: error: Could not deduce: b from the context: (Implies a b, Implies b a) bound by a pattern with constructor: Dict :: forall (c :: Constraint). c => Dict c, in an equation for ‘comp_’ at hs/206-bug-quantified-constraints.hs:18:7-10 or from: (Implies b c, Implies c b) bound by a pattern with constructor: Dict :: forall (c :: Constraint). c => Dict c, in an equation for ‘comp_’ at hs/206-bug-quantified-constraints.hs:18:12-15 or from: c bound by a quantified context at hs/206-bug-quantified-constraints.hs:1:1 | 1 | {-# Language QuantifiedConstraints, GADTs, ConstraintKinds, TypeOperators, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-} | ^ hs/206-bug-quantified-constraints.hs:1:1: error: Could not deduce: b from the context: (Implies a b, Implies b a) bound by a pattern with constructor: Dict :: forall (c :: Constraint). c => Dict c, in an equation for ‘comp_’ at hs/206-bug-quantified-constraints.hs:18:7-10 or from: (Implies b c, Implies c b) bound by a pattern with constructor: Dict :: forall (c :: Constraint). c => Dict c, in an equation for ‘comp_’ at hs/206-bug-quantified-constraints.hs:18:12-15 or from: a bound by a quantified context at hs/206-bug-quantified-constraints.hs:1:1 | 1 | {-# Language QuantifiedConstraints, GADTs, ConstraintKinds, TypeOperators, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-} | ^ Failed, no modules loaded. Prelude> }}} simplifying and uncurrying we get a more minimal example {{{#!hs {-# Language QuantifiedConstraints, GADTs, ConstraintKinds, TypeOperators, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-} data Dict c where Dict :: c => Dict c f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a f = Dict }}} giving a different and longer error message {{{ GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( 206-bug-quantified-constraints.hs, interpreted ) 206-bug-quantified-constraints.hs:6:6: error: • Could not deduce: c0 from the context: (a => b, b => a, b => c, c => b, a => c, c) bound by the type signature for: f :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). (a => b, b => a, b => c, c => b, a => c, c) => Dict a at 206-bug-quantified-constraints.hs:6:6-58 • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | 6 | f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 206-bug-quantified-constraints.hs:6:6: error: • Could not deduce: (b, c0) from the context: (a => b, b => a, b => c, c => b, a => c, c) bound by the type signature for: f :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). (a => b, b => a, b => c, c => b, a => c, c) => Dict a at 206-bug-quantified-constraints.hs:6:6-58 or from: a bound by a quantified context at 206-bug-quantified-constraints.hs:6:6-58 • In the type signature: f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | 6 | f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 206-bug-quantified-constraints.hs:6:6: error: • Could not deduce: b0 from the context: (a => b, b => a, b => c, c => b, a => c, c) bound by the type signature for: f :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). (a => b, b => a, b => c, c => b, a => c, c) => Dict a at 206-bug-quantified-constraints.hs:6:6-58 or from: c0 bound by a quantified context at 206-bug-quantified-constraints.hs:6:6-58 • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | 6 | f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 206-bug-quantified-constraints.hs:6:6: error: • Could not deduce: c0 from the context: (a => b, b => a, b => c, c => b, a => c, c) bound by the type signature for: f :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). (a => b, b => a, b => c, c => b, a => c, c) => Dict a at 206-bug-quantified-constraints.hs:6:6-58 or from: b0 bound by a quantified context at 206-bug-quantified-constraints.hs:6:6-58 • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | 6 | f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 206-bug-quantified-constraints.hs:6:6: error: • Could not deduce: b from the context: (a => b, b => a, b => c, c => b, a => c, c) bound by the type signature for: f :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). (a => b, b => a, b => c, c => b, a => c, c) => Dict a at 206-bug-quantified-constraints.hs:6:6-58 or from: b0 bound by a quantified context at 206-bug-quantified-constraints.hs:6:6-58 • In the ambiguity check for ‘f’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | 6 | f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ 206-bug-quantified-constraints.hs:6:6: error: • Could not deduce: (b, b0) from the context: (a => b, b => a, b => c, c => b, a => c, c) bound by the type signature for: f :: forall (a :: Constraint) (b :: Constraint) (c :: Constraint). (a => b, b => a, b => c, c => b, a => c, c) => Dict a at 206-bug-quantified-constraints.hs:6:6-58 or from: a bound by a quantified context at 206-bug-quantified-constraints.hs:6:6-58 • In the type signature: f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | 6 | f :: (a => b, b => a, b => c, c => b, a => c, c) => Dict a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Failed, no modules loaded. Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 18:28:53 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 18:28:53 -0000 Subject: [GHC] #14879: QuantifiedConstraints: Big error message + can't substitute (=>) with a class alias Message-ID: <051.9b359bfca6701741c297f67cb37814d6@haskell.org> #14879: QuantifiedConstraints: Big error message + can't substitute (=>) with a class alias -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This compiles fine {{{#!hs {-# Language QuantifiedConstraints, FlexibleInstances, MultiParamTypeClasses, ConstraintKinds, UndecidableInstances, GADTs, TypeOperators #-} class (a => b) => Implies a b instance (a => b) => Implies a b data Dict c where Dict :: c => Dict c type a :- b = Dict (Implies a b) class (forall xx. Implies b xx => Implies a xx) => Yo a b instance (forall xx. Implies b xx => Implies a xx) => Yo a b yo :: Yo a b :- Implies a b yo = Dict }}} until you replace `(=>)` with `Implies` (which should be fine?) {{{#!hs class (forall xx. Implies b xx `Implies` Implies a xx) => Yo a b instance (forall xx. Implies b xx `Implies` Implies a xx) => Yo a b }}} and the error message blows up {{{ $ ghci -ignore-dot-ghci SD.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( SD.hs, interpreted ) SD.hs:15:6: error: • Reduction stack overflow; size = 201 When simplifying the following type: Implies b (Implies b (Implies -->8---->8----several-hundred-lines---->8---->8---- b))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))) Use -freduction-depth=0 to disable this check (any upper bound you could choose might fail unpredictably with minor updates to GHC, so disabling the check is recommended if you're sure that type checking should terminate) • In the expression: Dict In an equation for ‘yo’: yo = Dict | 15 | yo = Dict | ^^^^ Failed, no modules loaded. Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 19:11:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 19:11:48 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.324dbfbfc7950e9dde8de05383058b0a@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.6.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, | Phab:D1396, Phab:D1457, Phab:D1468, Wiki Page: | Phab:D1487, Phab:D1504, Phab:D1508, DeterministicBuilds | Phab:D4388 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d8e47a2ea89dbce647b06132ec10c39a2de67437/ghc" d8e47a2e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d8e47a2ea89dbce647b06132ec10c39a2de67437" Make cost centre symbol names deterministic. Previously, non-CAF cost centre symbol names contained a unique, leading to non-deterministic object files which, among other issues, can lead to an inconsistency causing linking failure when using cached builds sourced from multiple machines, such as with nix. Now, each cost centre symbol is annotated with the type of cost centre it is (CAF, expression annotation, declaration annotation, or HPC) and, when a single module has multiple cost centres with the same name and type, a 0-based index. Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: niteria, simonmar, RyanGlScott, osa1, rwbarton, thomie, carter GHC Trac Issues: #4012, #12935 Differential Revision: https://phabricator.haskell.org/D4388 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 19:11:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 19:11:48 -0000 Subject: [GHC] #12935: Object code produced by GHC is non-deterministic In-Reply-To: <046.8f3dd2cbcacc5f9595e0dfae3817822d@haskell.org> References: <046.8f3dd2cbcacc5f9595e0dfae3817822d@haskell.org> Message-ID: <061.78b9a386314060acfc59ea402379af65@haskell.org> #12935: Object code produced by GHC is non-deterministic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4388 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d8e47a2ea89dbce647b06132ec10c39a2de67437/ghc" d8e47a2e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d8e47a2ea89dbce647b06132ec10c39a2de67437" Make cost centre symbol names deterministic. Previously, non-CAF cost centre symbol names contained a unique, leading to non-deterministic object files which, among other issues, can lead to an inconsistency causing linking failure when using cached builds sourced from multiple machines, such as with nix. Now, each cost centre symbol is annotated with the type of cost centre it is (CAF, expression annotation, declaration annotation, or HPC) and, when a single module has multiple cost centres with the same name and type, a 0-based index. Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: niteria, simonmar, RyanGlScott, osa1, rwbarton, thomie, carter GHC Trac Issues: #4012, #12935 Differential Revision: https://phabricator.haskell.org/D4388 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 20:12:13 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 20:12:13 -0000 Subject: [GHC] #14880: GHC panic: updateRole Message-ID: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: Roles | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program panics on GHC 8.0.2, 8.2.2, 8.4.1, and HEAD: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind import Data.Type.Equality ((:~:)(..)) type SameKind (a :: k) (b :: k) = (() :: Constraint) data TyFun :: Type -> Type -> Type type a ~> b = TyFun a b -> Type infixr 0 ~> type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 type f @@ x = f `Apply` x infixl 9 @@ type family WhyCong (x :: Type) (y :: Type) (f :: x ~> y) (a :: x) (z :: x) (e :: a :~: z) :: Type where WhyCong _ _ f a z _ = f @@ a :~: f @@ z data WhyCongSym1 (x :: Type) :: forall (a :: x) (y :: Type) (z :: x). Type ~> (x ~> y) ~> x ~> x ~> a :~: z ~> Type data WhyCongSym0 :: forall (x :: Type) (a :: x) (y :: Type) (z :: x). Type ~> Type ~> (x ~> y) ~> x ~> x ~> a :~: z ~> Type where WhyCongSym0KindInference :: forall x arg. SameKind (Apply WhyCongSym0 arg) (WhyCongSym1 arg) => WhyCongSym0 x }}} {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): updateRole WhyCongSym0 arg_aYV[sk:1] [aYU :-> 4, a22o :-> 0, a22p :-> 1, a22q :-> 2, a22r :-> 3] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcTyDecls.hs:656:23 in ghc:TcTyDecls }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:07:30 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:07:30 -0000 Subject: [GHC] #14767: Move Data.Functor.Contravariant into base In-Reply-To: <049.b50afcae0d7c6cf3237575f5b3450e51@haskell.org> References: <049.b50afcae0d7c6cf3237575f5b3450e51@haskell.org> Message-ID: <064.95fa35f2031e71b949cca2c5d653066f@haskell.org> #14767: Move Data.Functor.Contravariant into base -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: base 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:"8c7a1551fcd004c37f4ccd99c7c10395179519f1/ghc" 8c7a1551/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8c7a1551fcd004c37f4ccd99c7c10395179519f1" Move Data.Functor.Contravariant from the contravariant package to base. Move Data.Functor.Contravariant from the contravariant package to base. Since base is the bottom of the dependency hierarchy, several instances have been removed. They will need to be added to the following packages: transformers, StateVar, and possibly tagged. There may not actually have been any types from tagged that previous had instanced provided by this module though, since it may have only been used for Data.Proxy. Additionally, all CPP has been removed. Derived Typeable instances have been removed (since Typeable is now automatically derived for everything). The language extension Safe is still used, although it is unclear to ATM whether or not it is necessary. This resolves trac issue #14767. Test Plan: validate Reviewers: RyanGlScott, ekmett, hvr, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, thomie, ekmett, carter, RyanGlScott GHC Trac Issues: #14767 Differential Revision: https://phabricator.haskell.org/D4399 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:07:30 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:07:30 -0000 Subject: [GHC] #14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall In-Reply-To: <050.74a33b64a09712cb22148568a57e17c8@haskell.org> References: <050.74a33b64a09712cb22148568a57e17c8@haskell.org> Message-ID: <065.e324543fc030d3281148bdc99e624659@haskell.org> #14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: sighingnow Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | T14773a,T14773b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4400 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"e8e9f6a7a6d857efe6e3b2aec0c4964f9a8fa09a/ghc" e8e9f6a7/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e8e9f6a7a6d857efe6e3b2aec0c4964f9a8fa09a" Improve exhaustive checking for guards in pattern bindings and MultiIf. Previously we didn't do exhaustive checking on MultiIf expressions and guards in pattern bindings. We can construct the `LMatch` directly from GRHSs or [LHsExpr] (MultiIf's alts) then feed it to checkMatches, without construct the MatchGroup and using function `matchWrapper`. Signed-off-by: HE, Tao Test Plan: make test TEST="T14773a T14773b" Reviewers: bgamari, RyanGlScott, simonpj Reviewed By: bgamari, simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14773 Differential Revision: https://phabricator.haskell.org/D4400 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:07:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:07:31 -0000 Subject: [GHC] #12790: GHC 8.0.1 uses copious amounts of RAM and time when trying to compile lambdabot-haskell-plugins In-Reply-To: <044.6c4a4edd18cfc656391e8adc9c55d93a@haskell.org> References: <044.6c4a4edd18cfc656391e8adc9c55d93a@haskell.org> Message-ID: <059.e3ca14d2401c633341393f16d8f4522b@haskell.org> #12790: GHC 8.0.1 uses copious amounts of RAM and time when trying to compile lambdabot-haskell-plugins -------------------------------------+------------------------------------- Reporter: clint | Owner: (none) Type: bug | Status: patch 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): Phab:D4412 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"125d15181c7ac8d8fbaa43f799f9e3876dc2f57b/ghc" 125d1518/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="125d15181c7ac8d8fbaa43f799f9e3876dc2f57b" Add regression test for #12790 Test Plan: make test TEST=T12790 Reviewers: bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, dfeuer, rwbarton, thomie, carter GHC Trac Issues: #12790 Differential Revision: https://phabricator.haskell.org/D4412 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:07:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:07:31 -0000 Subject: [GHC] #14819: GHC 8.2 does not accept British {-# LANGUAGE GeneralisedNewtypeDeriving #-} spelling In-Reply-To: <046.3cff902adb709d7e7df64a2fe7e8f873@haskell.org> References: <046.3cff902adb709d7e7df64a2fe7e8f873@haskell.org> Message-ID: <061.e2b175c5b4fd2f9585a2e97554109808@haskell.org> #14819: GHC 8.2 does not accept British {-# LANGUAGE GeneralisedNewtypeDeriving #-} spelling -------------------------------------+------------------------------------- Reporter: clinton | Owner: (none) Type: bug | Status: patch Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 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:D4422 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"17739645ce5a5d4b46b1de8d43e87b318a98ae6b/ghc" 17739645/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="17739645ce5a5d4b46b1de8d43e87b318a98ae6b" DynFlags: Support British spelling of GeneralisedNewtypeDeriving Reviewers: dfeuer Reviewed By: dfeuer Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #14819 Differential Revision: https://phabricator.haskell.org/D4422 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:07:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:07:31 -0000 Subject: [GHC] #14817: GHC 8.4.1 pretty-prints data family instances with redundant kind signatures using -ddump-splices In-Reply-To: <050.79b05eb6509492d423346b61e70e23a4@haskell.org> References: <050.79b05eb6509492d423346b61e70e23a4@haskell.org> Message-ID: <065.a73f27fd696f37f360895e471704802f@haskell.org> #14817: GHC 8.4.1 pretty-prints data family instances with redundant kind signatures using -ddump-splices -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 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:D4418 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"aef2b429072e3d3bbdbcb9e4082a0d86ba329d9e/ghc" aef2b429/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="aef2b429072e3d3bbdbcb9e4082a0d86ba329d9e" Fix #14817 by not double-printing data family instance kind signatures Within `pprDataFamInstDecl`, we were invoking `pprFamInstLHS` to pretty-print a data family instance header, and we were passing `Just` a kind signature to `pprFamInstLHS` to make it pretty-print the kind signature alongside it (this is a consequence of commit d1ef223cfebd23c25489a4b0c67fbaa2f91c1ec6). But this is silly, because then invoke `pp_data_defn`, which //also// pretty-prints the kind signature, resulting in the kind signature being printed twice by mistake. This fix is simple—pass `Nothing` to `pprFamInstLHS` instead. Test Plan: make test TEST=T14817 Reviewers: alanz, bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, rwbarton, thomie, carter GHC Trac Issues: #14817 Differential Revision: https://phabricator.haskell.org/D4418 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:08:19 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:08:19 -0000 Subject: [GHC] #14819: GHC 8.2 does not accept British {-# LANGUAGE GeneralisedNewtypeDeriving #-} spelling In-Reply-To: <046.3cff902adb709d7e7df64a2fe7e8f873@haskell.org> References: <046.3cff902adb709d7e7df64a2fe7e8f873@haskell.org> Message-ID: <061.aa71da157152e6857bd178805e91542d@haskell.org> #14819: GHC 8.2 does not accept British {-# LANGUAGE GeneralisedNewtypeDeriving #-} spelling -------------------------------------+------------------------------------- Reporter: clinton | Owner: (none) Type: bug | Status: closed Priority: lowest | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | 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:D4422 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:08:47 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:08:47 -0000 Subject: [GHC] #14817: GHC 8.4.1 pretty-prints data family instances with redundant kind signatures using -ddump-splices In-Reply-To: <050.79b05eb6509492d423346b61e70e23a4@haskell.org> References: <050.79b05eb6509492d423346b61e70e23a4@haskell.org> Message-ID: <065.fc748f0744e0f8e318c54d3d492475eb@haskell.org> #14817: GHC 8.4.1 pretty-prints data family instances with redundant kind signatures using -ddump-splices -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.1-alpha3 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:D4418 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:09:28 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:09:28 -0000 Subject: [GHC] #12790: GHC 8.0.1 uses copious amounts of RAM and time when trying to compile lambdabot-haskell-plugins In-Reply-To: <044.6c4a4edd18cfc656391e8adc9c55d93a@haskell.org> References: <044.6c4a4edd18cfc656391e8adc9c55d93a@haskell.org> Message-ID: <059.2309746c438af8b5f725a8dd13afbba8@haskell.org> #12790: GHC 8.0.1 uses copious amounts of RAM and time when trying to compile lambdabot-haskell-plugins -------------------------------------+------------------------------------- Reporter: clint | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4412 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.1 Comment: It looks like this is probably fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:09:56 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:09:56 -0000 Subject: [GHC] #14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall In-Reply-To: <050.74a33b64a09712cb22148568a57e17c8@haskell.org> References: <050.74a33b64a09712cb22148568a57e17c8@haskell.org> Message-ID: <065.02f4477dbf878c10d9daa6758a611fcb@haskell.org> #14773: MultiWayIf makes it easy to write partial programs that are not catched by -Wall -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: sighingnow Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | T14773a,T14773b Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4400 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:10:18 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:10:18 -0000 Subject: [GHC] #14767: Move Data.Functor.Contravariant into base In-Reply-To: <049.b50afcae0d7c6cf3237575f5b3450e51@haskell.org> References: <049.b50afcae0d7c6cf3237575f5b3450e51@haskell.org> Message-ID: <064.6f6c22159336a96db132da6f14699cd5@haskell.org> #14767: Move Data.Functor.Contravariant into base -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: base Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:49:40 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:49:40 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.30dbb6734822f2b9775812e1ea29af4a@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by aosivitz): * cc: aosivitz (added) Comment: Sorry for the delay- I forgot to add myself to CC and didn't see your message. So I have now successfully reproduced the problem in a clean environment with bitemyapp's help. The missing piece is that it fails during template haskell compilation, but I'm a little confused at to why. It makes sense, of course, that template-haskell compilation would involve some dynamic linking in order to run the code, but if the number of dependencies is the problem, doesn't that imply TH links all of its dependencies dynamically? What is the advantage of dynamic linking here instead of just statically linking for TH? Here's a github gist for a shell script that generates a giant stack project (with 150 generated dependencies) that triggers the panic: https://gist.github.com/asivitz/f4b983b2374a6155ac4faaf9b61aca59 I'm not sure the best way to do the same thing without using stack, but if you have an idea I can do that. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #12706: Collecting type info is slow In-Reply-To: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> References: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> Message-ID: <063.1a1253c858e50239a726f997abca7a1b@haskell.org> #12706: Collecting type info is slow -------------------------------------+------------------------------------- Reporter: vshabanov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4459 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"969e747f67f57f7dd57c2e549d6a007505671158/ghc" 969e747/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="969e747f67f57f7dd57c2e549d6a007505671158" GHCi info: Use src file for cache invalidation Prior to this patch GHCi used the modification time of a module's object file to invalidate the info cache. We now look at the modification time of the source file, if present. This addresses part of https://ghc.haskell.org/trac/ghc/ticket/12706#comment:3. Reviewers: bgamari Reviewed By: bgamari Subscribers: lelf, alpmestan, rwbarton, thomie, carter GHC Trac Issues: #12706 Differential Revision: https://phabricator.haskell.org/D4459 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #11767: Add @since annotations for base instances In-Reply-To: <046.80486230653199e8f5fef1dcd513180c@haskell.org> References: <046.80486230653199e8f5fef1dcd513180c@haskell.org> Message-ID: <061.39d1c29cf17418f7620a2957b07f24ed@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11768 | Differential Rev(s): Phab:D2277 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"5c28ee88dd66617b0fd5dbe0d90142ce983a547e/ghc" 5c28ee8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5c28ee88dd66617b0fd5dbe0d90142ce983a547e" Add @since annotations for derived instances in base Test Plan: ./validate Reviewers: hvr, goldfire, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: rwbarton, thomie, carter GHC Trac Issues: #11767 Differential Revision: https://phabricator.haskell.org/D4452 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #14843: Can't splice a partially applied PromoteTupleT type from Template Haskell In-Reply-To: <050.3a3c674a7e7086c9c05579f6851de573@haskell.org> References: <050.3a3c674a7e7086c9c05579f6851de573@haskell.org> Message-ID: <065.e66382c311ac4a0e6cfa34af33aec62e@haskell.org> #14843: Can't splice a partially applied PromoteTupleT type from Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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:D4442 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"68357020b1cf29d4306e769b3366feb9a65ae78c/ghc" 6835702/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="68357020b1cf29d4306e769b3366feb9a65ae78c" Permit conversion of partially applied PromotedTupleTs Summary: We were simply missing a case in `Convert` for when have a `PromotedTupleT` that wasn't fully saturated. Easily fixed. Test Plan: make test TEST=T14843 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14843 Differential Revision: https://phabricator.haskell.org/D4442 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #14675: GHC 8.4.1 regression: segfault when loading doctest on a module with ANNs on Ubuntu 16.04 or later In-Reply-To: <050.c5c190ffbc3e4175e84536f4424d1ad2@haskell.org> References: <050.c5c190ffbc3e4175e84536f4424d1ad2@haskell.org> Message-ID: <065.e5eefc0588e171e44d7b5848fca3e355@haskell.org> #14675: GHC 8.4.1 regression: segfault when loading doctest on a module with ANNs on Ubuntu 16.04 or later -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: bgamari Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: GHC API | Version: 8.4.1-alpha1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #14603 | Differential Rev(s): Phab:D4431 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"bc1bcaa2c0c66fb247d1338d6d0055a833918a7f/ghc" bc1bcaa/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bc1bcaa2c0c66fb247d1338d6d0055a833918a7f" configure: Enable LD_NO_GOLD is set in all codepaths Test Plan: `./configure --disable-ld-override; make; make install` Reviewers: trofi, hvr Reviewed By: trofi Subscribers: rwbarton, thomie, erikd, carter, simonmar GHC Trac Issues: #14675 Differential Revision: https://phabricator.haskell.org/D4448 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #14838: missing "incomplete-patterns" warning for TH-generated functions In-Reply-To: <046.404359ac761dc94d2a50e36ab6ec4ae4@haskell.org> References: <046.404359ac761dc94d2a50e36ab6ec4ae4@haskell.org> Message-ID: <061.2ffa1db15cbf0d19ca0e62e3946a5cca@haskell.org> #14838: missing "incomplete-patterns" warning for TH-generated functions -------------------------------------+------------------------------------- Reporter: gelisam | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4440 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"ffb2738f86c4e4c3f0eaacf0a95d7326fdd2e383/ghc" ffb2738f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ffb2738f86c4e4c3f0eaacf0a95d7326fdd2e383" Fix #14838 by marking TH-spliced code as FromSource Previously, any Template Haskell code that was spliced would be marked as `Generated`, which would completely suppress pattern- match coverage warnings for it, which several folks found confusing. Indeed, Template Haskell-spliced code is "source" code in some sense, as users specifically request that it be put into their program, so changing its designation to `FromSource` makes sense from that perspective. Test Plan: make test TEST=T14838 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14838 Differential Revision: https://phabricator.haskell.org/D4440 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #5: fails if library has main() In-Reply-To: <045.5aafe47c7b47732eda828244576abf66@haskell.org> References: <045.5aafe47c7b47732eda828244576abf66@haskell.org> Message-ID: <060.15e989f3337b5823f5f5fd495d47875d@haskell.org> #5: fails if library has main() --------------------------------+---------------------- Reporter: cwitty | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: Driver | Version: 5.02 Resolution: Wont Fix | Keywords: Type of failure: None/Unknown | --------------------------------+---------------------- Changes (by Ben Gamari ): * failure: => None/Unknown Comment: In [changeset:"5f6fcf7808b16d066ad0fb2068225b3f2e8363f7/ghc" 5f6fcf78/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5f6fcf7808b16d066ad0fb2068225b3f2e8363f7" Compile with `--via-asm` when cross compiling. This bumps `hsc2hs` and adds the new `--via-asm` flag, which allows to successfully cross compile the win32 lirbary. - Compile with `--via-asm` when cross compiling. This requires haskell/hsc2hs#5 (https://github.com/haskell/hsc2hs/pull/5) Test Plan: ./validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4439 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #14544: doCorePass has at least one missing case In-Reply-To: <049.4d90cc3cc6b5380801189db1b57310d5@haskell.org> References: <049.4d90cc3cc6b5380801189db1b57310d5@haskell.org> Message-ID: <064.5ecc974d6c3506a7718678989e97f13a@haskell.org> #14544: doCorePass has at least one missing case -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4435 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"44ba60fe9bce298cfa41c4505d029c1a2c6e5671/ghc" 44ba60fe/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="44ba60fe9bce298cfa41c4505d029c1a2c6e5671" doCorePass: Expand catch-all This doesn't remedy problem, but at least it's more explicit than the catch-all Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14544 Differential Revision: https://phabricator.haskell.org/D4435 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #14098: Incorrect pattern match warning on nested GADTs In-Reply-To: <047.9af3deedeaeda4254147ac374e749c5f@haskell.org> References: <047.9af3deedeaeda4254147ac374e749c5f@haskell.org> Message-ID: <062.c3b80c98ee70fc4b6a8f478a44216b1c@haskell.org> #14098: Incorrect pattern match warning on nested GADTs -------------------------------------+------------------------------------- Reporter: jmgrosen | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11984 | Differential Rev(s): Phab:D4434 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a2d03c69b782212e6c476cfc1870bae493a4ac89/ghc" a2d03c6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a2d03c69b782212e6c476cfc1870bae493a4ac89" Fix the coverage checker's treatment of existential tyvars Previously, the pattern-match coverage checker was far too eager to freshen the names of existentially quantified type variables, which led to incorrect sets of type constraints that misled GHC into thinking that certain programs that involve nested GADT pattern matches were non-exhaustive (when in fact they were). Now, we generate extra equality constraints in the ConCon case of the coverage algorithm to ensure that these fresh tyvars align with existing existential tyvars. See `Note [Coverage checking and existential tyvars]` for the full story. Test Plan: make test TEST="T11984 T14098" Reviewers: gkaracha, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #11984, #14098 Differential Revision: https://phabricator.haskell.org/D4434 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:53:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:53:55 -0000 Subject: [GHC] #11984: Pattern match incompleteness / inaccessibility discrepancy In-Reply-To: <047.1cf132bd89a1199ee00c683072ed7b2c@haskell.org> References: <047.1cf132bd89a1199ee00c683072ed7b2c@haskell.org> Message-ID: <062.94a88ebb1cb8913466724d05e2cda06b@haskell.org> #11984: Pattern match incompleteness / inaccessibility discrepancy -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14098 | Differential Rev(s): Phab:D4434 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a2d03c69b782212e6c476cfc1870bae493a4ac89/ghc" a2d03c6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a2d03c69b782212e6c476cfc1870bae493a4ac89" Fix the coverage checker's treatment of existential tyvars Previously, the pattern-match coverage checker was far too eager to freshen the names of existentially quantified type variables, which led to incorrect sets of type constraints that misled GHC into thinking that certain programs that involve nested GADT pattern matches were non-exhaustive (when in fact they were). Now, we generate extra equality constraints in the ConCon case of the coverage algorithm to ensure that these fresh tyvars align with existing existential tyvars. See `Note [Coverage checking and existential tyvars]` for the full story. Test Plan: make test TEST="T11984 T14098" Reviewers: gkaracha, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #11984, #14098 Differential Revision: https://phabricator.haskell.org/D4434 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:56:50 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:56:50 -0000 Subject: [GHC] #12706: Collecting type info is slow In-Reply-To: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> References: <048.46558b94dab961bc2f1f1afabbe58413@haskell.org> Message-ID: <063.580403d7d54238547a22321501bcd452@haskell.org> #12706: Collecting type info is slow -------------------------------------+------------------------------------- Reporter: vshabanov | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4459 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): comment:7 should help significantly but there is still more to be done here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:57:29 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:57:29 -0000 Subject: [GHC] #14843: Can't splice a partially applied PromoteTupleT type from Template Haskell In-Reply-To: <050.3a3c674a7e7086c9c05579f6851de573@haskell.org> References: <050.3a3c674a7e7086c9c05579f6851de573@haskell.org> Message-ID: <065.af4d8a5589fa80bfcbf2552055ad111c@haskell.org> #14843: Can't splice a partially applied PromoteTupleT type from Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: T14843 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4442 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * testcase: => T14843 * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:57:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:57:55 -0000 Subject: [GHC] #14838: missing "incomplete-patterns" warning for TH-generated functions In-Reply-To: <046.404359ac761dc94d2a50e36ab6ec4ae4@haskell.org> References: <046.404359ac761dc94d2a50e36ab6ec4ae4@haskell.org> Message-ID: <061.8cc0eeeaf6207e8c32e19e45b53c88a0@haskell.org> #14838: missing "incomplete-patterns" warning for TH-generated functions -------------------------------------+------------------------------------- Reporter: gelisam | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.2.2 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: T14838 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4440 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => T14838 * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:58:12 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:58:12 -0000 Subject: [GHC] #14544: doCorePass has at least one missing case In-Reply-To: <049.4d90cc3cc6b5380801189db1b57310d5@haskell.org> References: <049.4d90cc3cc6b5380801189db1b57310d5@haskell.org> Message-ID: <064.8b2005d87a74501026d6b8deeafe0b5c@haskell.org> #14544: doCorePass has at least one missing case -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4435 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:58:46 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:58:46 -0000 Subject: [GHC] #14098: Incorrect pattern match warning on nested GADTs In-Reply-To: <047.9af3deedeaeda4254147ac374e749c5f@haskell.org> References: <047.9af3deedeaeda4254147ac374e749c5f@haskell.org> Message-ID: <062.a6151db90a9de84c9aaeba63909b5247@haskell.org> #14098: Incorrect pattern match warning on nested GADTs -------------------------------------+------------------------------------- Reporter: jmgrosen | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11984 | Differential Rev(s): Phab:D4434 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:59:05 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:59:05 -0000 Subject: [GHC] #14098: Incorrect pattern match warning on nested GADTs In-Reply-To: <047.9af3deedeaeda4254147ac374e749c5f@haskell.org> References: <047.9af3deedeaeda4254147ac374e749c5f@haskell.org> Message-ID: <062.35e69c5a46bbad0052e675b30b2db745@haskell.org> #14098: Incorrect pattern match warning on nested GADTs -------------------------------------+------------------------------------- Reporter: jmgrosen | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: T11984, error/warning at compile-time | T14098 Blocked By: | Blocking: Related Tickets: #11984 | Differential Rev(s): Phab:D4434 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => T11984, T14098 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 21:59:50 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 21:59:50 -0000 Subject: [GHC] #11984: Pattern match incompleteness / inaccessibility discrepancy In-Reply-To: <047.1cf132bd89a1199ee00c683072ed7b2c@haskell.org> References: <047.1cf132bd89a1199ee00c683072ed7b2c@haskell.org> Message-ID: <062.00ffea6e2825eea6e9cfb2119f88a315@haskell.org> #11984: Pattern match incompleteness / inaccessibility discrepancy -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T11984 Blocked By: | Blocking: Related Tickets: #14098 | Differential Rev(s): Phab:D4434 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * testcase: => T11984 * resolution: => fixed * milestone: => 8.6.1 Old description: > Consider this module: > > {{{ > {-# LANGUAGE PolyKinds, TypeOperators, DataKinds, TypeFamilies, GADTs #-} > > module Bug where > > data family Sing (a :: k) > > data Schema = Sch [Bool] > > data instance Sing (x :: Schema) where > SSch :: Sing x -> Sing ('Sch x) > > data instance Sing (x :: [k]) where > SNil :: Sing '[] > SCons :: Sing a -> Sing b -> Sing (a ': b) > > data G a where > GCons :: G ('Sch (a ': b)) > > eval :: G s -> Sing s -> () > eval GCons s = > case s of > -- SSch SNil -> undefined > SSch (SCons _ _) -> undefined > }}} > > Upon seeing this, GHC says > > {{{ > Bug.hs:21:9: warning: [-Wincomplete-patterns] > Pattern match(es) are non-exhaustive > In a case alternative: Patterns not matched: (SSch SNil) > }}} > > So I uncomment the second-to-last line, inducing GHC to say > > {{{ > Bug.hs:22:16: error: > • Couldn't match type ‘a : b’ with ‘'[]’ > Inaccessible code in > a pattern with constructor: SNil :: forall k. Sing '[], > in a case alternative > • In the pattern: SNil > In the pattern: SSch SNil > In a case alternative: SSch SNil -> undefined > }}} > > Thankfully, this pattern is much rarer than it once was, but it's a bit > sad that it's still possible. New description: Consider this module: {{{#!hs {-# LANGUAGE PolyKinds, TypeOperators, DataKinds, TypeFamilies, GADTs #-} module Bug where data family Sing (a :: k) data Schema = Sch [Bool] data instance Sing (x :: Schema) where SSch :: Sing x -> Sing ('Sch x) data instance Sing (x :: [k]) where SNil :: Sing '[] SCons :: Sing a -> Sing b -> Sing (a ': b) data G a where GCons :: G ('Sch (a ': b)) eval :: G s -> Sing s -> () eval GCons s = case s of -- SSch SNil -> undefined SSch (SCons _ _) -> undefined }}} Upon seeing this, GHC says {{{ Bug.hs:21:9: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: (SSch SNil) }}} So I uncomment the second-to-last line, inducing GHC to say {{{ Bug.hs:22:16: error: • Couldn't match type ‘a : b’ with ‘'[]’ Inaccessible code in a pattern with constructor: SNil :: forall k. Sing '[], in a case alternative • In the pattern: SNil In the pattern: SSch SNil In a case alternative: SSch SNil -> undefined }}} Thankfully, this pattern is much rarer than it once was, but it's a bit sad that it's still possible. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 22:37:59 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 22:37:59 -0000 Subject: [GHC] #14881: Consistent labeling of redundant, qualified imports Message-ID: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> #14881: Consistent labeling of redundant, qualified imports -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ import Data.Map as M (Map, adjust, lookup, fromList) foo :: Map Int Int foo = fromList [] }}} GHC helpfully suggests: {{{ Bug.hs:3:1: warning: [-Wunused-imports] The import of `adjust, M.lookup' from module `Data.Map' is redundant | 3 | import Data.Map as M (Map, adjust, lookup, fromList) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} However, this message can be improved. Notice that in the line "The import of ...", `adjust` is *not* qualified, while `lookup` *is* qualified. It would be better if this was consistent. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 22:48:02 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 22:48:02 -0000 Subject: [GHC] #14881: Consistent labeling of redundant, qualified imports In-Reply-To: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> References: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> Message-ID: <062.43997d6abf7ca45ae32c9d5841935168@haskell.org> #14881: Consistent labeling of redundant, qualified imports -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Currently this is by design. * `adjust` (unqualified) is unambiguous in this scope * But `lookup` is ambiguous -- it is not clear whether you mean `M.lookup` or `Prelude.lookup`. But I suppose that in the context of this error message we can ''only'' mean the `lookup` imported from `Data.Map` so we could unconditinally print unqualified. Any volunteers? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 22:54:25 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 22:54:25 -0000 Subject: [GHC] #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' In-Reply-To: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> References: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> Message-ID: <066.920de9b404abebd68fdce12551b1b5f5@haskell.org> #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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; and I've added a test case {{{ commit 32e8499889d314e9efd0747b4053290a2dc237d5 Author: Simon Peyton Jones Date: Fri Mar 2 22:53:27 2018 +0000 Test Trac #14863 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:08:37 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:08:37 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.7c28ff9ac2545b7cfc8a0ae9fcbdead5@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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 original program still gives a stack overflow with ​latest changes. And so it should. You have a "given" `(Trans rel)`, where {{ type Trans rel = (forall xx yy zz. (rel xx yy, rel yy zz) => rel xx zz :: Constraint) }}} So if you want to solve `[W] rel t1 t2` (for some type `t1` or `t2`, this local instance (quantified constraint) matches. We can solve it by solving {{{ [W] rel t1 alpha [W] rel alpha t2 }}} where `alpha` is a fresh unification variable (corresponding to `yy` in the definition of `Trans rel`. But then each of those two constraints can be solved once more with this over-general local instance -- and now we hare four constraints. And so on. You used `UndecidableInstances` and sure enough you wrote an infinite loop. I say there is no bug here. The same thing wold happen if you wrote {{{ instance (C a x, C x b) => C a b }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:11:02 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:11:02 -0000 Subject: [GHC] #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' In-Reply-To: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> References: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> Message-ID: <066.d918e15e0e33f7ef602770e2dfff1806@haskell.org> #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:15:45 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:15:45 -0000 Subject: [GHC] #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' In-Reply-To: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> References: <051.903b58847c266d2c5a5e433b5aee3bbf@haskell.org> Message-ID: <066.14fb30bf3642a68b8046ea59bf3e2162@haskell.org> #14863: QuantifiedConstraints: Can't deduce `c' from `(a, b)' and `a |- b |- c' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | QuantifiedConstraints wipT2893 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 great work thanks! For those interested these examples came from [https://www.reddit.com/r/haskell/comments/6k86je/constraint_unions_bringing_or_to_the_language_of/djlghz8/ Edward Kmett's encoding of sums of Constraints]. This may be a milestone, since `curryC` / `uncurryC` mean that the "category of entailment" `(:-)` is a Cartesian closed `Constraint` category (which means we could get [https://www.reddit.com/r/haskell/comments/73lp4m/higherorder_abstract_syntax_for_any/ HOAS syntax for constraints]?). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:29:15 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:29:15 -0000 Subject: [GHC] #14882: memchr# Message-ID: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It would be neat if we had a primitive for calling memchr on a ByteArray#. Something like this: {{{ memchr :: ByteArray# -> Word# -> Int# -> Int# -> Int# }}} The integer arguments are a starting index and length. I have a hunch that copyByteArray# and friends are just wrappers for memcpy that somehow prohibit the array from being moved by the GC while they are running. I would be happy to try to implement memchr# if it seems like an alright idea. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:34:07 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:34:07 -0000 Subject: [GHC] #14849: Add Applicative, Semigroup and Monoid instances in GHC.Generics In-Reply-To: <044.8f485efed694e393dbe4d64e7f5d45ed@haskell.org> References: <044.8f485efed694e393dbe4d64e7f5d45ed@haskell.org> Message-ID: <059.a549034477460c00e2768ac7dcbc6097@haskell.org> #14849: Add Applicative, Semigroup and Monoid instances in GHC.Generics -------------------------------------+------------------------------------- Reporter: lyxia | Owner: lyxia Type: task | Status: closed Priority: normal | Milestone: 8.6.1 Component: libraries/base | Version: 8.2.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:D4447 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Fixed in 7782b47c4193975123edd3af630e6fe59ac7ef73 (`Add Applicative, Semigroup, and Monoid instances in GHC.Generics`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:56:23 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:56:23 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.b741073f3f8df194a53f857b437ed76f@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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): Is there hope for the user to guide this process and leaving the definition of `Trans` intact (not having to create `CCategory`)? If this were a rank-2 function we can explicitly instantiate `xx` `yy` `zz` {{{#!hs foo :: R X Y -> R Y Z -> (forall xx yy zz. (R xx yy, R yy zz) => R xx zz) -> R X Y foo xy yz f = f @X @Y @Z (xy, yz) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 2 23:58:49 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 02 Mar 2018 23:58:49 -0000 Subject: [GHC] #10412: isAlphaNum includes mark characters, but neither isAlpha nor isNumber do In-Reply-To: <051.04054b116946e9bf810283d6d73d9ff5@haskell.org> References: <051.04054b116946e9bf810283d6d73d9ff5@haskell.org> Message-ID: <066.8cd2f8e5c8b2247a00df4d472de4a3af@haskell.org> #10412: isAlphaNum includes mark characters, but neither isAlpha nor isNumber do -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: unicode 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 lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 00:05:06 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 00:05:06 -0000 Subject: [GHC] #14767: Move Data.Functor.Contravariant into base In-Reply-To: <049.b50afcae0d7c6cf3237575f5b3450e51@haskell.org> References: <049.b50afcae0d7c6cf3237575f5b3450e51@haskell.org> Message-ID: <064.85ac078ab3d15ba799d8f726b57a3838@haskell.org> #14767: Move Data.Functor.Contravariant into base -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: base Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4399 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D4399 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 00:59:32 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 00:59:32 -0000 Subject: [GHC] #393: functions without implementations In-Reply-To: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> References: <047.8e9c859b4db83c0d687094f53af0d886@haskell.org> Message-ID: <062.e73b9583e2fef20769039c1ce2efcfcc@haskell.org> #393: functions without implementations -------------------------------------+------------------------------------- Reporter: c_maeder | Owner: Iceland_jack 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 sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 01:08:30 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 01:08:30 -0000 Subject: [GHC] #9251: ghc does not expose branchless max/min operations as primops In-Reply-To: <045.e29eb1e7c055c049cd093a2df9caa8db@haskell.org> References: <045.e29eb1e7c055c049cd093a2df9caa8db@haskell.org> Message-ID: <060.5a3fc815ec261a06c210bbda3852afd1@haskell.org> #9251: ghc does not expose branchless max/min operations as primops -------------------------------------+------------------------------------- Reporter: carter | Owner: osa1 Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9246 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 01:12:06 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 01:12:06 -0000 Subject: [GHC] #2269: Word type to Double or Float conversions are slower than Int conversions In-Reply-To: <043.be417919ffcce10010ccb473704f0755@haskell.org> References: <043.be417919ffcce10010ccb473704f0755@haskell.org> Message-ID: <058.a19acbe2bbac8c4c7683ec81cb632a84@haskell.org> #2269: Word type to Double or Float conversions are slower than Int conversions -------------------------------------+------------------------------------- Reporter: dons | Owner: dons@… Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 6.8.2 Resolution: | Keywords: rules, | performance, double, newcomer 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 sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 02:07:45 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 02:07:45 -0000 Subject: [GHC] #14880: GHC panic: updateRole In-Reply-To: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> References: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> Message-ID: <065.880f963d8d7896fdc07aca495e89d639@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Roles Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description: > The following program panics on GHC 8.0.2, 8.2.2, 8.4.1, and HEAD: > > {{{#!hs > {-# LANGUAGE ConstraintKinds #-} > {-# LANGUAGE GADTs #-} > {-# LANGUAGE ScopedTypeVariables #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE TypeInType #-} > {-# LANGUAGE TypeOperators #-} > module Bug where > > import Data.Kind > import Data.Type.Equality ((:~:)(..)) > > type SameKind (a :: k) (b :: k) = (() :: Constraint) > > data TyFun :: Type -> Type -> Type > type a ~> b = TyFun a b -> Type > infixr 0 ~> > > type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 > type f @@ x = f `Apply` x > infixl 9 @@ > > type family WhyCong (x :: Type) (y :: Type) (f :: x ~> y) > (a :: x) (z :: x) (e :: a :~: z) :: Type where > WhyCong _ _ f a z _ = f @@ a :~: f @@ z > > data WhyCongSym1 (x :: Type) :: forall (a :: x) > (y :: Type) > (z :: x). > Type ~> (x ~> y) ~> x ~> x ~> a :~: z ~> > Type > > data WhyCongSym0 :: forall (x :: Type) > (a :: x) > (y :: Type) > (z :: x). > Type ~> Type ~> (x ~> y) ~> x ~> x ~> a :~: z ~> Type > where > WhyCongSym0KindInference :: forall x arg. > SameKind (Apply WhyCongSym0 arg) > (WhyCongSym1 arg) => > WhyCongSym0 x > }}} > > {{{ > $ /opt/ghc/8.2.2/bin/ghc Bug.hs > [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) > ghc: panic! (the 'impossible' happened) > (GHC version 8.2.2 for x86_64-unknown-linux): > updateRole > WhyCongSym0 > arg_aYV[sk:1] > [aYU :-> 4, a22o :-> 0, a22p :-> 1, a22q :-> 2, a22r :-> 3] > Call stack: > CallStack (from HasCallStack): > prettyCurrentCallStack, called at > compiler/utils/Outputable.hs:1133:58 in ghc:Outputable > callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in > ghc:Outputable > pprPanic, called at compiler/typecheck/TcTyDecls.hs:656:23 in > ghc:TcTyDecls > }}} New description: The following program panics on GHC 8.0.2, 8.2.2, 8.4.1, and HEAD: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} module Bug where import Data.Kind import Data.Type.Equality ((:~:)) type SameKind (a :: k) (b :: k) = (() :: Constraint) data TyFun :: Type -> Type -> Type type a ~> b = TyFun a b -> Type infixr 0 ~> type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 data WhyCongSym1 (x :: Type) :: forall (a :: x) (y :: Type) (z :: x). Type ~> (x ~> y) ~> x ~> x ~> (a :~: z) ~> Type data WhyCongSym0 :: forall (x :: Type) (a :: x) (y :: Type) (z :: x). Type ~> Type ~> (x ~> y) ~> x ~> x ~> (a :~: z) ~> Type where WhyCongSym0KindInference :: forall x arg. SameKind (Apply WhyCongSym0 arg) (WhyCongSym1 arg) => WhyCongSym0 x }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): updateRole WhyCongSym0 arg_a1A6[sk:1] [a1A5 :-> 4, a2Cy :-> 0, a2Cz :-> 1, a2CA :-> 2, a2CB :-> 3] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcTyDecls.hs:656:23 in ghc:TcTyDecls }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 02:25:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 02:25:55 -0000 Subject: [GHC] #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# In-Reply-To: <048.a76989facca9d2ef0c59d6b7bfd86029@haskell.org> References: <048.a76989facca9d2ef0c59d6b7bfd86029@haskell.org> Message-ID: <063.3f6ebfae57e0892066195b57083b2bb9@haskell.org> #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4433 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sjakobi): bgamari commented on [Phab:D4433]: > If I'm not mistaken this also needs to take care to avoid unaligned loads and stores on architectures that do not support such things. I could need some guidance on how to do that. Is there an existing machinery for working around unaligned operations that I could use? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 02:29:09 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 02:29:09 -0000 Subject: [GHC] #14880: GHC panic: updateRole In-Reply-To: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> References: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> Message-ID: <065.54676e18b2f3eb08c861f4a9152eef3d@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Roles Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's as minimal of an example as I can conjure up: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeInType #-} module Bug where import Data.Kind import Data.Proxy data Foo (x :: Type) :: forall (a :: x). Proxy a -> Type data Bar :: Type -> Type where MkBar :: forall x arg. -- Commenting out the line below makes the issue go away Foo arg ~ Foo arg => Bar x }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): updateRole Bar arg_a1vT[sk:1] [a1vS :-> 0] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcTyDecls.hs:656:23 in ghc:TcTyDecls }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 02:57:24 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 02:57:24 -0000 Subject: [GHC] #14831: QuantifiedConstraints: Odd superclass constraint In-Reply-To: <051.631b3f4dec55319ae6028526fc90fcb8@haskell.org> References: <051.631b3f4dec55319ae6028526fc90fcb8@haskell.org> Message-ID: <066.0a4fd19ff7200a05faef9655cecbc8bd@haskell.org> #14831: QuantifiedConstraints: Odd superclass constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): You didn't post the full code that you're alluding to in comment:5, but my hunch is that you're experiencing the same bug as in https://ghc.haskell.org/trac/ghc/ticket/5927#comment:32. This probably deserves its own ticket regardless. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 03:10:01 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 03:10:01 -0000 Subject: [GHC] #14881: Consistent labeling of redundant, qualified imports In-Reply-To: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> References: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> Message-ID: <062.019e106f7884da8bbea6fbec6de9cbd7@haskell.org> #14881: Consistent labeling of redundant, qualified imports -------------------------------------+------------------------------------- Reporter: crockeea | Owner: sighingnow Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * owner: (none) => sighingnow -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 03:10:54 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 03:10:54 -0000 Subject: [GHC] #14883: QuantifiedConstraints don't kick in when used in TypeApplications Message-ID: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> #14883: QuantifiedConstraints don't kick in when used in TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 (Type checker) | Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Bug where import Data.Coerce import Data.Kind type Representational1 m = (forall a b. Coercible a b => Coercible (m a) (m b) :: Constraint) class Representational1 f => Functor' f where fmap' :: (a -> b) -> f a -> f b class Functor' f => Applicative' f where pure' :: a -> f a (<*>@) :: f (a -> b) -> f a -> f b class Functor' t => Traversable' t where traverse' :: Applicative' f => (a -> f b) -> t a -> f (t b) -- Typechecks newtype T1 m a = MkT1 (m a) deriving Functor' instance Traversable' m => Traversable' (T1 m) where traverse' :: forall f a b. (Applicative' f) => (a -> f b) -> T1 m a -> f (T1 m b) traverse' = coerce @((a -> f b) -> m a -> f (m b)) @((a -> f b) -> T1 m a -> f (T1 m b)) traverse' -- Doesn't typecheck newtype T2 m a = MkT2 (m a) deriving Functor' instance Traversable' m => Traversable' (T2 m) where traverse' = coerce @(forall f a b. Applicative' f => (a -> f b) -> m a -> f (m b)) @(forall f a b. Applicative' f => (a -> f b) -> T2 m a -> f (T2 m b)) traverse' }}} This defines a variant of `Functor` that has `forall a b. Coercible a b. Coercible (m a) (m b)` as a superclass, and also defines versions of `Applicative` and `Traversable` that use this `Functor` variant. This is towards the ultimate goal of defining `Traversable'` à la `GeneralizedNewtypeDeriving`. This attempt (using `InstanceSigs`) typechecks: {{{#!hs newtype T1 m a = MkT1 (m a) deriving Functor' instance Traversable' m => Traversable' (T1 m) where traverse' :: forall f a b. (Applicative' f) => (a -> f b) -> T1 m a -> f (T1 m b) traverse' = coerce @((a -> f b) -> m a -> f (m b)) @((a -> f b) -> T1 m a -> f (T1 m b)) traverse' }}} However, this version (which is closer to what `GeneralizedNewtypeDeriving` would actually create) does //not// typecheck: {{{#!hs newtype T2 m a = MkT2 (m a) deriving Functor' instance Traversable' m => Traversable' (T2 m) where traverse' = coerce @(forall f a b. Applicative' f => (a -> f b) -> m a -> f (m b)) @(forall f a b. Applicative' f => (a -> f b) -> T2 m a -> f (T2 m b)) traverse' }}} {{{ $ ghc-cq/inplace/bin/ghc-stage2 --interactive Bug.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:38:15: error: • Couldn't match representation of type ‘f1 (m b1)’ with that of ‘f1 (T2 m b1)’ arising from a use of ‘coerce’ NB: We cannot know what roles the parameters to ‘f1’ have; we must assume that the role is nominal • In the expression: coerce @(forall f a b. Applicative' f => (a -> f b) -> m a -> f (m b)) @(forall f a b. Applicative' f => (a -> f b) -> T2 m a -> f (T2 m b)) traverse' In an equation for ‘traverse'’: traverse' = coerce @(forall f a b. Applicative' f => (a -> f b) -> m a -> f (m b)) @(forall f a b. Applicative' f => (a -> f b) -> T2 m a -> f (T2 m b)) traverse' In the instance declaration for ‘Traversable' (T2 m)’ • Relevant bindings include traverse' :: (a -> f b) -> T2 m a -> f (T2 m b) (bound at Bug.hs:38:3) | 38 | traverse' = coerce @(forall f a b. Applicative' f => (a -> f b) -> m a -> f (m b)) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} Shouldn't it, though? These instance declarations out to be equivalent (morally, at least). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 03:17:38 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 03:17:38 -0000 Subject: [GHC] #14883: QuantifiedConstraints don't kick in when used in TypeApplications In-Reply-To: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> References: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> Message-ID: <065.753c29ca77ec028a3db540037576d665@haskell.org> #14883: QuantifiedConstraints don't kick in when used in TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Another example in the same vein: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Bug where import Data.Coerce import Data.Kind type Phantom1 p = (forall a b. Coercible (p a) (p b) :: Constraint) class Foo a where bar :: Phantom1 proxy => proxy a -> Int instance Foo Int where bar _ = 42 -- Typecheck newtype Age1 = MkAge1 Int instance Foo Age1 where bar :: forall proxy. Phantom1 proxy => proxy Age1 -> Int bar = coerce @(proxy Int -> Int) @(proxy Age1 -> Int) bar -- Doesn't typecheck newtype Age2 = MkAge2 Int instance Foo Age2 where bar = coerce @(forall proxy. Phantom1 proxy => proxy Int -> Int) @(forall proxy. Phantom1 proxy => proxy Age2 -> Int) bar }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 08:00:32 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 08:00:32 -0000 Subject: [GHC] #14884: Type holes cause assertion failure in ghc-stage2 compiler during type checking Message-ID: <049.e0dc234c0a117697c411dc48fa40d3fb@haskell.org> #14884: Type holes cause assertion failure in ghc-stage2 compiler during type checking -------------------------------------+------------------------------------- Reporter: sighingnow | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- ghc-stage2 panic! due to assertion failure when compiling the following code with `ghc-stage2 Bug.hs` {{{#!hs module Bug where x :: IO () x = _ print "abc" }}} Callstack: {{{ λ inplace\bin\ghc-stage2 Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180225 for x86_64-unknown-mingw32): ASSERT failed! t_a4ec[tau:2] 2 1 Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler\utils\Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler\utils\Outputable.hs:1206:5 in ghc:Outputable assertPprPanic, called at compiler\\typecheck\\TcType.hs:1187:83 in ghc:TcType CallStack (from -prof): TcInteract.solve_loop (compiler\typecheck\TcInteract.hs:(247,9)-(254,44)) TcInteract.solveSimples (compiler\typecheck\TcInteract.hs:(241,5)-(243,21)) TcRnDriver.simplifyTop (compiler\typecheck\TcRnDriver.hs:408:25-39) TcRnDriver.tcRnSrcDecls (compiler\typecheck\TcRnDriver.hs:254:25-65) }}} The failed assertion is `checkTcLevelInvariant ctxt_tclvl tv_tclvl` in `isTouchableMetaTyVar`: {{{#!hs isTouchableMetaTyVar :: TcLevel -> TcTyVar -> Bool isTouchableMetaTyVar ctxt_tclvl tv | isTyVar tv -- See Note [Coercion variables in free variable lists] = ASSERT2( tcIsTcTyVar tv, ppr tv ) case tcTyVarDetails tv of MetaTv { mtv_tclvl = tv_tclvl } -> ASSERT2( checkTcLevelInvariant ctxt_tclvl tv_tclvl, ppr tv $$ ppr tv_tclvl $$ ppr ctxt_tclvl ) tv_tclvl `sameDepthAs` ctxt_tclvl _ -> False | otherwise = False }}} Notice that the ghc-stage1 compiler doesn't panic and report the type hole correctly. This seems a regression and I have checked that ghc-8.2.2 also works well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 09:38:03 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 09:38:03 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.1b88ef82bf7b49c328d5f2cb2e1aad76@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.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 osa1): So the bug here is not related with inlining. In general, any flag that effects generated Core (or analysis passes like the demand analysis) can effect inlining decisions. In particular, -XStrict can lead to more case expressions to evaluate intermediate results eagerly, which may cause larger code, which effects inlining decisions. Also, because some part of inlining decisions are done in the use site we'd also need to see the code that uses your `primitive` function. That being said, the bug here is that `-XStrict` shouldn't have any effect on generated Core because you only have one binding (`a` in your `primitive` function), and that has a laziness annotation. [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html #strict-by-default-pattern-bindings GHC user manual on -XStrict] says that adding `~` in front of bindings gives us the regular lazy behavior. So really there's nothing `-XStrict` can do in this module. However the desugared code really changes with `-XStrict` in GHC 8.2.2, and that's the bug. I just tested with HEAD and 8.4 RC1 and this is fixed in both versions so you just have to update GHC when 8.4 released. (I don't know if there will be another 8.2 release, if so maybe we can include the fix in that version) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 10:50:28 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 10:50:28 -0000 Subject: [GHC] #14883: QuantifiedConstraints don't kick in when used in TypeApplications In-Reply-To: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> References: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> Message-ID: <065.3cacae85826b782ee31ea5f30bb552ff@haskell.org> #14883: QuantifiedConstraints don't kick in when used in TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints, wipT2893 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 Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 12:15:15 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 12:15:15 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.ac4b89a2aad9ef067cbf0d0f120592b8@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 12:45:33 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 12:45:33 -0000 Subject: [GHC] #14881: Consistent labeling of redundant, qualified imports In-Reply-To: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> References: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> Message-ID: <062.5d461502ccba893a54920ceb9f5b474d@haskell.org> #14881: Consistent labeling of redundant, qualified imports -------------------------------------+------------------------------------- Reporter: crockeea | Owner: sighingnow Type: bug | Status: patch Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4461 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * status: new => patch * differential: => Phab:D4461 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 13:11:10 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 13:11:10 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.77ab33684e1cdd3f3d05288d873da0a8@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): I'm working on this now. I should have something up on phabricator soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 13:14:57 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 13:14:57 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.1c4aabb2aaa0ff156b57d96ed8576c60@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: andrewthad Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ulysses4ever): * owner: (none) => andrewthad -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 14:08:41 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 14:08:41 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.bccbc465858be3097c1fd57cc1a1aa34@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: andrewthad Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): I went ahead and pushed it up to github in case I somehow destroy it by accident: https://github.com/andrewthad/ghc/tree/dump-word-hex-literals I'll get this on phabricator soon. I'm getting a weird linking error late in compilation, but I suspect that's from failing to update submodules. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 14:11:00 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 14:11:00 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.656de68a25000220e4f86fb94c2f9317@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: andrewthad Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): In case anyone has seen this error before: {{{ "@LdNoGoldCmd@" -r -o libraries/ghc-prim/dist-install/build/HSghc- prim-0.5.2.0.o libraries/ghc-prim/dist-install/build/GHC/CString.o libraries/ghc-prim/dist-install/build/GHC/Classes.o libraries/ghc-prim /dist-install/build/GHC/Debug.o libraries/ghc-prim/dist- install/build/GHC/IntWord64.o libraries/ghc-prim/dist- install/build/GHC/Magic.o libraries/ghc-prim/dist- install/build/GHC/PrimopWrappers.o libraries/ghc-prim/dist- install/build/GHC/Tuple.o libraries/ghc-prim/dist- install/build/GHC/Types.o libraries/ghc-prim/dist- install/build/cbits/atomic.o libraries/ghc-prim/dist- install/build/cbits/bswap.o libraries/ghc-prim/dist- install/build/cbits/clz.o libraries/ghc-prim/dist- install/build/cbits/ctz.o libraries/ghc-prim/dist- install/build/cbits/debug.o libraries/ghc-prim/dist- install/build/cbits/longlong.o libraries/ghc-prim/dist- install/build/cbits/pdep.o libraries/ghc-prim/dist- install/build/cbits/pext.o libraries/ghc-prim/dist- install/build/cbits/popcnt.o libraries/ghc-prim/dist- install/build/cbits/word2float.o /bin/bash: @LdNoGoldCmd@: command not found libraries/ghc-prim/ghc.mk:4: recipe for target 'libraries/ghc-prim/dist- install/build/HSghc-prim-0.5.2.0.o' failed }}} I'll try blowing out the directory later today and reapplying the patch to master if this isn't something that anyone else knows a simple fix for. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 15:12:14 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 15:12:14 -0000 Subject: [GHC] #14546: -Woverlapping-patterns warns on wrong patterns for Int In-Reply-To: <046.65cf2f969bf40f1f8653cdbe0242cf31@haskell.org> References: <046.65cf2f969bf40f1f8653cdbe0242cf31@haskell.org> Message-ID: <061.7c573bf1dc80d7edd95a57bddb13df99@haskell.org> #14546: -Woverlapping-patterns warns on wrong patterns for Int -------------------------------------+------------------------------------- Reporter: Lemming | Owner: sighingnow Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: Resolution: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * owner: (none) => sighingnow -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 16:09:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 16:09:55 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced Message-ID: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.2.2 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: -------------------------------------+------------------------------------- Consider the following program: {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where class Foo1 a where bar1 :: forall b. a -> b -> b bar1 _ x = (x :: b) $([d| class Foo2 a where bar2 :: forall b. a -> b -> b bar2 _ x = (x :: b) |]) }}} `Foo1` typechecks, so naturally you'd expect `Foo2` to typecheck as well. Prepare to be surprised: {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:(10,3)-(13,6): Splicing declarations [d| class Foo2_aoA a_aoC where bar2_aoB :: forall b_aoD. a_aoC -> b_aoD -> b_aoD bar2_aoB _ x_aoE = (x_aoE :: b_aoD) |] ======> class Foo2_a3JQ a_a3JS where bar2_a3JR :: forall b_a3JT. a_a3JS -> b_a3JT -> b_a3JT bar2_a3JR _ x_a3JU = x_a3JU :: b_aoD Bug.hs:10:3: error: • Couldn't match expected type ‘b1’ with actual type ‘b’ ‘b’ is a rigid type variable bound by the type signature for: bar2 :: forall b. a0 -> b -> b at Bug.hs:(10,3)-(13,6) ‘b1’ is a rigid type variable bound by an expression type signature: forall b1. b1 at Bug.hs:(10,3)-(13,6) • In the expression: x_a3JU :: b In an equation for ‘bar2’: bar2 _ x_a3JU = x_a3JU :: b • Relevant bindings include x_a3JU :: b (bound at Bug.hs:10:3) bar2 :: a0 -> b -> b (bound at Bug.hs:10:3) | 10 | $([d| class Foo2 a where | ^^^^^^^^^^^^^^^^^^^^^^... }}} Notice how in the quoted `Foo2` declaration, the scoping is correct: `b_a0D` is used in both the type signature for `bar2_a0B` as well as in its default implementation. But after splicing, there are now two different `b`s: the one in the type signature (`b_a3JT`), and the one in the default implementation (`b_aoD`)! This causes the resulting type error. This is a regression that was introduced somewhere between 7.10.3 and 8.0.1, since it works in 7.10.3: {{{ $ /opt/ghc/7.10.3/bin/ghci Bug.hs GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(10,3)-(13,6): Splicing declarations [d| class Foo2_awn a_awp where bar2_awo :: forall b_awq. a_awp -> b_awq -> b_awq bar2_awo _ x_awr = (x_awr :: b_awq) |] ======> class Foo2_a3zs a_a3zu where bar2_a3zt :: forall b_awq. a_a3zu -> b_awq -> b_awq bar2_a3zt _ x_a3zv = x_a3zv :: b_awq Ok, modules loaded: Bug. }}} But not in any version of GHC since 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 16:37:49 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 16:37:49 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced In-Reply-To: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> References: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> Message-ID: <065.2c02a5bb6a9a357c8f96be8f62d08e0d@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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 RyanGlScott): It's not just class declarations that are broken. Pattern synonyms are similarly broken: {{{#!hs {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where pattern P1 :: forall a. a -> Maybe a pattern P1 x <- Just x where P1 x = Just (x :: a) $([d| pattern P2 :: forall a. a -> Maybe a pattern P2 x <- Just x where P2 x = Just (x :: a) |]) }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(11,3)-(14,6): Splicing declarations [d| pattern P2_a1t7 :: forall a_a1t8. a_a1t8 -> Maybe a_a1t8 pattern P2_a1t7 x_a1t9 <- Just x_a1t9 where P2_a1t7 x_a1ta = Just (x_a1ta :: a_a1t8) |] ======> pattern P2_a4aA :: forall a_a4aB. a_a4aB -> Maybe a_a4aB pattern P2_a4aA x_a4aC <- Just x_a4aC where P2_a4aA x_a4aD = Just (x_a4aD :: a_a1t8) Bug.hs:11:3: error: • Couldn't match expected type ‘a1’ with actual type ‘a’ ‘a’ is a rigid type variable bound by the signature for pattern synonym ‘P2’ at Bug.hs:(11,3)-(14,6) ‘a1’ is a rigid type variable bound by an expression type signature: forall a1. a1 at Bug.hs:(11,3)-(14,6) • In the first argument of ‘Just’, namely ‘(x_a4aD :: a)’ In the expression: Just (x_a4aD :: a) In an equation for ‘P2’: P2 x_a4aD = Just (x_a4aD :: a) • Relevant bindings include x_a4aD :: a (bound at Bug.hs:11:3) $bP2 :: a -> Maybe a (bound at Bug.hs:11:3) | 11 | $([d| pattern P2 :: forall a. a -> Maybe a | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} As well as `DefaultSignatures`: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where class Foo1 a where foo1 :: forall b. a -> b -> b default foo1 :: forall b. a -> b -> b foo1 _ x = (x :: b) $([d| class Foo2 a where foo2 :: forall b. a -> b -> b default foo2 :: forall b. a -> b -> b foo2 _ x = (x :: b) |]) }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(12,3)-(16,6): Splicing declarations [d| class Foo2_a1tO a_a1tQ where foo2_a1tP :: forall b_a1tR. a_a1tQ -> b_a1tR -> b_a1tR default foo2_a1tP :: forall b_a1tS. a_a1tQ -> b_a1tS -> b_a1tS foo2_a1tP _ x_a1tT = (x_a1tT :: b_a1tS) |] ======> class Foo2_a4bq a_a4bs where foo2_a4br :: forall b_a4bt. a_a4bs -> b_a4bt -> b_a4bt default foo2_a4br :: forall b_a4bu. a_a4bs -> b_a4bu -> b_a4bu foo2_a4br _ x_a4bv = x_a4bv :: b_a1tS Bug.hs:12:3: error: • Couldn't match expected type ‘b1’ with actual type ‘b’ ‘b’ is a rigid type variable bound by the type signature for: foo2 :: forall b. a0 -> b -> b at Bug.hs:(12,3)-(16,6) ‘b1’ is a rigid type variable bound by an expression type signature: forall b1. b1 at Bug.hs:(12,3)-(16,6) • In the expression: x_a4bv :: b In an equation for ‘foo2’: foo2 _ x_a4bv = x_a4bv :: b • Relevant bindings include x_a4bv :: b (bound at Bug.hs:12:3) foo2 :: a0 -> b -> b (bound at Bug.hs:12:3) | 12 | $([d| class Foo2 a where | ^^^^^^^^^^^^^^^^^^^^^^... }}} And `InstanceSigs`: {{{#!hs {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where class Foo1 a where foo1 :: forall b. a -> b -> b instance Foo1 (Maybe a) where foo1 :: forall b. Maybe a -> b -> b foo1 _ x = (x :: b) $([d| class Foo2 a where foo2 :: forall b. a -> b -> b instance Foo2 (Maybe a) where foo2 :: forall b. Maybe a -> b -> b foo2 _ x = (x :: b) |]) }}} {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(14,3)-(20,6): Splicing declarations [d| class Foo2_a1tR a_a1tT where foo2_a1tS :: forall b_a1tU. a_a1tT -> b_a1tU -> b_a1tU instance Foo2_a1tR (Maybe a_a1tV) where foo2_a1tS :: forall b_a1tW. Maybe a_a1tV -> b_a1tW -> b_a1tW foo2_a1tS _ x_a1tX = (x_a1tX :: b_a1tW) |] ======> class Foo2_a4c2 a_a4c4 where foo2_a4c3 :: forall b_a4c5. a_a4c4 -> b_a4c5 -> b_a4c5 instance Foo2_a4c2 (Maybe a_a4c6) where foo2_a4c3 :: forall b_a4c8. Maybe a_a4c6 -> b_a4c8 -> b_a4c8 foo2_a4c3 _ x_a4c7 = x_a4c7 :: b_a1tW Bug.hs:14:3: error: • Couldn't match expected type ‘b1’ with actual type ‘b’ ‘b’ is a rigid type variable bound by the type signature for: foo2 :: forall b. Maybe a -> b -> b at Bug.hs:(14,3)-(20,6) ‘b1’ is a rigid type variable bound by an expression type signature: forall b1. b1 at Bug.hs:(14,3)-(20,6) • In the expression: x_a4c7 :: b In an equation for ‘foo2’: foo2 _ x_a4c7 = x_a4c7 :: b In the instance declaration for ‘Foo2 (Maybe a)’ • Relevant bindings include x_a4c7 :: b (bound at Bug.hs:14:3) foo2 :: Maybe a -> b -> b (bound at Bug.hs:14:3) | 14 | $([d| class Foo2 a where | ^^^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 16:39:19 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 16:39:19 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced In-Reply-To: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> References: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> Message-ID: <065.230bc931462a15d27ff4bd2b6b6dff29@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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 RyanGlScott): Strangely, one thing that is //not// broken is good ol' top-level type signatures. This works just fine: {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where f1 :: forall a. a -> a f1 x = (x :: a) $([d| f2 :: forall a. a -> a f2 x = (x :: a) |]) }}} In that case, what secret sauce do top-level functions have that `InstanceSigs` //et al.// do not have? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 16:53:27 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 16:53:27 -0000 Subject: [GHC] #14874: Trac: TypeError: can't compare datetime.datetime to str In-Reply-To: <046.4f845865a3bc11f2535cf0d6fa1fe078@haskell.org> References: <046.4f845865a3bc11f2535cf0d6fa1fe078@haskell.org> Message-ID: <061.489f2e191f171bedcaf55c7b72b4b8d5@haskell.org> #14874: Trac: TypeError: can't compare datetime.datetime to str -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: hvr Type: bug | Status: new Priority: normal | Milestone: Component: Trac & Git | Version: 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 sjakobi): The following workaround was suggested in https://trac.edgewall.org/ticket/12029#comment:14: > Trac doesn't expect NULL in changetime column, which is lead by issue in first version of sourceforge2trac.py. > > Please update changetime column with value of time column for records which have NULL in the changetime column. > {{{#!sql > UPDATE ticket SET changetime = time WHERE changetime IS NULL > }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 16:53:32 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 16:53:32 -0000 Subject: [GHC] #14886: Add max GC pause to GHC.Stats/-t --machine-readable Message-ID: <047.0641890e447a41b5694f0694e508f86b@haskell.org> #14886: Add max GC pause to GHC.Stats/-t --machine-readable -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Sometimes we're interested in latency of our programs. Often the upper highest percentiles are by garbage collector pauses due to stop-the-world implementation. It seems that currently the only way to see the highest pause is to use the {{{-s}}} flag or alternatively {{{-S}}}. This is problematic in two scenarios: 1. You don't have a human at the monitor parsing the {{{-s}}} output. 2. You are unable to get the maximum pause statistic programmatically inside the program itself. We do have {{{-t -machine-readable}}} which is nearly what I'd want but missing the actual pause information. Either that should include all the extra info from {{{-s}}} or {{{-s}}} should have machine-readable output format too. There is the {{{-S}}} option which will print garbage collections as they happen. We could parse and manually track the highest pause time but it requires an external process and a parser. If you want to get that information back into the process then you have to do even more work. {{{GHC.Stats}}} is of no help. It does not track or expose pause values. Even the "last GC info" APIs don't provide this (and they are not a solution anyway as you can only get info on last GC). I would therefore like to request two similar features: * Add relevant information from {{{-s}}} to {{{-t}}} machine readable output or add machine readable format option to {{{-s}}}. * Add maximum pause information to GHC.Stats interface. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 17:46:40 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 17:46:40 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.804c5ac43f47c0b6b6a4085ef880a649@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I just tested with HEAD and 8.4 RC1 and this is fixed in both versions Can you offer a test case to add to our regression suite? Thanks! Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 18:21:47 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 18:21:47 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.0627e82d941da655c6fa79a6f2d92454@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: andrewthad Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): Differential is on phabricator now: https://phabricator.haskell.org/D4465 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 18:51:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 18:51:55 -0000 Subject: [GHC] #14796: Pretty Printing: GHC doesn't parenthesise (() :: Constraint) In-Reply-To: <051.7c740abd2da79f78e6b41c16e1857e91@haskell.org> References: <051.7c740abd2da79f78e6b41c16e1857e91@haskell.org> Message-ID: <066.75ac01df3522e3cf71e17f6f43546064@haskell.org> #14796: Pretty Printing: GHC doesn't parenthesise (() :: Constraint) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14808 | Differential Rev(s): Phab:D4408 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"99c556d2bb0594fd718622906168d2ea25a0bf06/ghc" 99c556d2/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="99c556d2bb0594fd718622906168d2ea25a0bf06" Parenthesize (() :: Constraint) in argument position Summary: A simple oversight in the pretty-printer lead to a special case for `() :: Constraint` not being parenthesized correctly when used in an argument position. Easily fixed with a `maybeParen`. Test Plan: make test TEST=T14796 Reviewers: alanz, goldfire, bgamari, simonpj Reviewed By: bgamari, simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14796 Differential Revision: https://phabricator.haskell.org/D4408 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 18:54:06 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 18:54:06 -0000 Subject: [GHC] #14796: Pretty Printing: GHC doesn't parenthesise (() :: Constraint) In-Reply-To: <051.7c740abd2da79f78e6b41c16e1857e91@haskell.org> References: <051.7c740abd2da79f78e6b41c16e1857e91@haskell.org> Message-ID: <066.54a5a6faf8abd30480bc1052830baf43@haskell.org> #14796: Pretty Printing: GHC doesn't parenthesise (() :: Constraint) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T14796 Blocked By: | Blocking: Related Tickets: #14808 | Differential Rev(s): Phab:D4408 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => ghci/scripts/T14796 * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 19:56:31 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 19:56:31 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.bda822bd4b8c516cba01c6729542c2e1@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 sjakobi): * owner: (none) => sjakobi -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 22:06:02 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 22:06:02 -0000 Subject: [GHC] #14701: Investigate the performance impact of code alignment In-Reply-To: <042.e11dda7ab3eddd9e4c88a6b0f72299d7@haskell.org> References: <042.e11dda7ab3eddd9e4c88a6b0f72299d7@haskell.org> Message-ID: <057.f63741f8ba30c62bce326f132de178e1@haskell.org> #14701: Investigate the performance impact of code alignment -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AndreasK): Code where this could be relevant is for example the binary searches we generate for case statements. {{{ some_func(bits64 r2) { bits64 var; _L1: if (r2 > 4) (likely: False) {goto _L9;} else {goto _L2;} _L2: if (r2 < 2) (likely: False) {goto _L6;} else {goto _L3;} _L3: if (r2 < 3) {goto _L5;} else {goto _L4;} _L4: var = 322; return (var); _L5: var = 222; return (var); _L6: if (r2 < 1) (likely: False) {goto _L8;} else {goto _L7;} _L7: var = 111; return (var); _L8: var = -1; return (var); _L9: if (r2 > 6) (likely: False) {goto _L8;} else {goto _L10;} _L10: if (r2 < 5) {goto _L12;} else {goto _L11;} _L11: var = 522; return (var); _L12: var = 422; return (var); } }}} This is a pretty straight forward binary search and at the outside of the range returns -1. The last two blocks don't fit into a 64 Byte cache line. Doing anything useful in this example would be hard. One option would be to push the unlikely leaves of the search which usually represent an exceptional result like a match failure towards the end. But this would require assigning a weight to each block and seems like a lot of effort. {{{ ==================== Asm code ==================== 2018-03-03 18:34:09.5530413 UTC .section .text .align 8 .globl kasdf kasdf: _cx: cmpq $4,%rbx ja _c4 _c6: cmpq $2,%rbx jb _c8 _ca: cmpq $3,%rbx jb _cc _ce: movl $322,%ebx jmp *(%rbp) _c4: cmpq $6,%rbx ja _cm _cq: cmpq $5,%rbx jb _cs _cu: movl $522,%ebx jmp *(%rbp) _cs: movl $422,%ebx jmp *(%rbp) _cm: movq $-1,%rbx jmp *(%rbp) _c8: cmpq $1,%rbx jb _cm _ck: movl $111,%ebx jmp *(%rbp) _cc: movl $222,%ebx jmp *(%rbp) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 23:20:16 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 23:20:16 -0000 Subject: [GHC] #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# In-Reply-To: <048.a76989facca9d2ef0c59d6b7bfd86029@haskell.org> References: <048.a76989facca9d2ef0c59d6b7bfd86029@haskell.org> Message-ID: <063.d120a3457404bafc0c37833fc13981b9@haskell.org> #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4433 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: Jaffacake (added) Comment: I don't believe so; this is one of the reasons the primops look like they do: they allow us to avoid dealing with alignment headaches. Frankly, I'm not even sure what sort of alignment guarantees our current C-- load and store nodes expect. Jaffacake, could you comment on this? We do have a list of architectures for which we need to worry about alignment (essentially everything but amd64; see `PprC.cLoad`). To figure out how to lower these operations I would likely just use a C compiler. For instance, compile a test program like, {{{#!c #include struct { uint32_t x; } __attribute__((packed)) *x; void store() { x->x = 42; } }}} with a cross-compiler and see what gets produced. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 23:25:08 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 23:25:08 -0000 Subject: [GHC] #10412: isAlphaNum includes mark characters, but neither isAlpha nor isNumber do In-Reply-To: <051.04054b116946e9bf810283d6d73d9ff5@haskell.org> References: <051.04054b116946e9bf810283d6d73d9ff5@haskell.org> Message-ID: <066.6f0977ba43d1e14f4edc38ed16aea084@haskell.org> #10412: isAlphaNum includes mark characters, but neither isAlpha nor isNumber do -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: unicode, | 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 bgamari): * keywords: unicode => unicode, newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 23:27:06 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 23:27:06 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.cb1f118071723b38594399e0952dedfc@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): If the goal is really to just call the C `memchr` implementation then you might also simply use an unsafe foreign call. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 3 23:53:46 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 03 Mar 2018 23:53:46 -0000 Subject: [GHC] #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck Message-ID: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: TypeFamilies, | Operating System: Unknown/Multiple TypeInType | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -fprint-explicit-kinds #-} module Bug where import Data.Kind import Data.Type.Equality type family Foo1 (e :: (a :: k) :~: (a :: k)) :: Type where Foo1 (e :: a :~: a) = a :~: a type family Foo2 (k :: Type) (e :: (a :: k) :~: (a :: k)) :: Type where Foo2 k (e :: a :~: a) = a :~: a }}} `Foo2` is wholly equivalent to `Foo1`, except that in `Foo2`, the `k` kind variable is explicitly quantified. However, `Foo1` typechecks, but `Foo2` does not! {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs -fprint-explicit-kinds GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ryanglscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:13:10: error: • Couldn't match kind ‘k’ with ‘k1’ When matching the kind of ‘a’ Expected kind ‘(:~:) k a a’, but ‘e’ has kind ‘(:~:) k a a’ • In the second argument of ‘Foo2’, namely ‘(e :: a :~: a)’ In the type family declaration for ‘Foo2’ | 13 | Foo2 k (e :: a :~: a) = a :~: a | ^^^^^^^^^^^^^^ }}} (Moreover, there seems to be a tidying bug, since GHC claims that `(:~:) k a a` is not the same kind as `(:~:) k a a`.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 03:10:34 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 03:10:34 -0000 Subject: [GHC] #14888: The (->) type doesn't survive a TH quote-splice roundtrip Message-ID: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> #14888: The (->) type doesn't survive a TH quote-splice roundtrip -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.2.2 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: -------------------------------------+------------------------------------- You can roundtrip function types like `Bool -> Bool` through Template Haskell splicing: {{{ $ /opt/ghc/8.2.2/bin/ghci -XTemplateHaskell GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci λ> :m + Language.Haskell.TH λ> :k $([t| Bool -> Bool |]) $([t| Bool -> Bool |]) :: * }}} However, GHC doesn't offer the same courtesy to `(->)` applied prefix, as in the following example: {{{ λ> :k $([t| (->) Bool Bool |]) :1:3: error: • Illegal type constructor or class name: ‘(->)’ When splicing a TH type: GHC.Prim.(->) GHC.Types.Bool GHC.Types.Bool • In the untyped splice: $([t| (->) Bool Bool |]) }}} One way to fix this would be to consistently desugar `(->)` to `ArrowT` in `DsMeta` (instead of leaving it as `GHC.Prim.(->)`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 03:50:26 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 03:50:26 -0000 Subject: [GHC] #14840: QuantifiedConstraints: Can't define class alias In-Reply-To: <051.efc0726cd0630f1f9a6cfd923f4eea44@haskell.org> References: <051.efc0726cd0630f1f9a6cfd923f4eea44@haskell.org> Message-ID: <066.df731964144e5d531a119901655552d5@haskell.org> #14840: QuantifiedConstraints: Can't define class alias -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | QuantifiedConstraints wipT2893 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'm thinking of these as Church encoding, I wanted to see how close I could get to something like a sum or existential constraints {{{#!hs type Sum a b = forall sum. (a -> sum) -> (b -> sum) -> sum }}} and actually, both of these definitions work-for-some-definition-of! (with judicious aliasing.) Here is an example that works today, I can Church encode `(a, b)` {{{#!hs {-# Language TypeOperators, GADTs, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, ConstraintKinds, RankNTypes, QuantifiedConstraints #-} data Dict c where Dict :: c => Dict c class (a => b) => (a |- b) instance (a => b) => (a |- b) }}} We define a type class constraint of church encoded products (`forall pair. (a -> b -> pair) -> pair`) {{{#!hs class (forall pair. (a |- b |- pair) |- pair) => ChurchPair a b instance (forall pair. (a |- b |- pair) |- pair) => ChurchPair a b }}} And amazingly GHC can conclude `ChurchPair a b` from `(a, b)`! {{{#!hs type a :- b = Dict (a |- b) wit :: (a, b) :- ChurchPair a b wit = Dict }}} the other half of the isomorphism is too much for GHC {{{#!hs reductionStackOverflow :: ChurchPair a b :- (a, b) reductionStackOverflow = Dict }}} which is as expected, from your response to one of the other tickets -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 04:02:20 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 04:02:20 -0000 Subject: [GHC] #14888: The (->) type doesn't survive a TH quote-splice roundtrip In-Reply-To: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> References: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> Message-ID: <065.91c9d93f1e7ee6e430d75bd51fd57fc9@haskell.org> #14888: The (->) type doesn't survive a TH quote-splice roundtrip -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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:D4466 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4466 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 04:58:48 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 04:58:48 -0000 Subject: [GHC] #10412: isAlphaNum includes mark characters, but neither isAlpha nor isNumber do In-Reply-To: <051.04054b116946e9bf810283d6d73d9ff5@haskell.org> References: <051.04054b116946e9bf810283d6d73d9ff5@haskell.org> Message-ID: <066.97042bef7c5ef41fd4681cb83c5258cd@haskell.org> #10412: isAlphaNum includes mark characters, but neither isAlpha nor isNumber do -------------------------------------+------------------------------------- Reporter: Artyom.Kazak | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: unicode, | 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 sighingnow): `GENCAT_MC|GENCAT_ME|GENCAT_MN` has been included in `u_iswalnum` since more than 10 years ago. However the documentation of `isAlphaNum` says "Selects alphabetic or numeric digit Unicode characters" and doesn't mention the "mark" characters. Should we fix the documentation of `isAlphaNum` to include "mark" characters or keep the documentation as it is and fix `u_iswalnum`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 05:19:43 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 05:19:43 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced In-Reply-To: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> References: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> Message-ID: <065.7424372ddeb773eb8fbb084c6e4bf703@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: sighingnow Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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 sighingnow): * owner: (none) => sighingnow Comment: We didn't consider the association of signatures and default implementations when representing TH declarations, rather than use `hsSigTvBinders` to handle scoped type variables (as in `repBinds`). {{{#!hs repTyClD (L loc (ClassDecl { tcdCtxt = cxt, tcdLName = cls, tcdTyVars = tvs, tcdFDs = fds, tcdSigs = sigs, tcdMeths = meth_binds, tcdATs = ats, tcdATDefs = atds })) = do { cls1 <- lookupLOcc cls -- See note [Binders and occurrences] ; dec <- addTyVarBinds tvs $ \bndrs -> do { cxt1 <- repLContext cxt ; sigs1 <- rep_sigs sigs ; binds1 <- rep_binds meth_binds ; fds1 <- repLFunDeps fds ; ats1 <- repFamilyDecls ats ; atds1 <- repAssocTyFamDefaults atds ; decls1 <- coreList decQTyConName (ats1 ++ atds1 ++ sigs1 ++ binds1) ; repClass cxt1 cls1 bndrs fds1 decls1 } ; return $ Just (loc, dec) } }}} I think I could try on this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 10:38:30 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 10:38:30 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch Message-ID: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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: -------------------------------------+------------------------------------- Commit http://git.haskell.org/ghc.git/commitdiff/5f6fcf7808b16d066ad0fb2068225b3f2e8363f7 enables '''--via-asm''' for all targets: {{{ ifeq "$(CrossCompiling)" "YES" -SRC_HSC2HS_OPTS_STAGE1 += --cross-compile -SRC_HSC2HS_OPTS_STAGE2 += --cross-compile +# We'll assume we compile with gcc or clang, and both support `-S` and can as such use the +# --via-asm pass, which should be faster and is required for cross compiling to windows, as +# the c compiler complains about non-constant expressions even though they are constant and +# end up as constants in the assembly. +SRC_HSC2HS_OPTS_STAGE1 += --cross-compile --via-asm +SRC_HSC2HS_OPTS_STAGE2 += --cross-compile --via-asm endif }}} But the discussion in original submission https://github.com/haskell/hsc2hs/pull/5 talks about opt-in and mostly x86 assembly support. Before this change targets like sparc were cross-compiling just fine. Now '''sparc-unknown-linux-gnu''' fails as: {{{ hsc2hs: Failed to extract integer CallStack (from HasCallStack): error, called at utils/hsc2hs/CrossCodegen.hs:606:27 in main:CrossCodegen make[1]: *** [libraries/unix/ghc.mk:4: libraries/unix/dist- install/build/System/Posix/Files.hs] Error 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 10:42:31 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 10:42:31 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch In-Reply-To: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> References: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> Message-ID: <060.4285fe6b4e3932af848b8a079cf2dbe8@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 angerman): Will look into this tomorrow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 11:08:21 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 11:08:21 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch In-Reply-To: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> References: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> Message-ID: <060.b2aecfb3c056125937f2683713987d55@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 slyfox): More debugging: The command is: {{{ $ "inplace/bin/hsc2hs" '--cc=sparc-unknown-linux-gnu-gcc' '--ld=sparc- unknown-linux-gnu-gcc' --cross-safe --cflag=-O2 --cflag=-pipe --cflag=-Wall --cflag=-fno-stack-protector --cross-compile --via-asm --cflag=-Dsparc_HOST_ARCH --cflag=-Dlinux_HOST_OS --cflag=-D__GLASGOW_HASKELL__=805 '--cflag=-fno-stack-protector' '-- cflag=-O2' '--cflag=-pipe' '--cflag=-Wall' '--cflag=-Ilibraries/ghci/dist- install/build/./autogen' '--cflag=-Ilibraries/ghci/.' '--cflag=-DGHCI' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/directory/.' '--cflag=-I/tmp/portage- tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/directory/dist-install/build/.' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/unix/include' '--cflag=-I/tmp /portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/unix/dist-install/build/include' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/unix/dist-install/build/include' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/unix/dist-install/build/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/time/lib/include' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/time/lib/dist-install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/time/dist-install/build/lib/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/time/dist-install/build/lib/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/containers/include' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/containers/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/containers/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/containers/dist- install/build/dist-install/build/include' '--cflag=-I/tmp/portage- tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/bytestring/include' '--cflag=-I/tmp /portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/bytestring/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/bytestring/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/bytestring/dist- install/build/dist-install/build/include' '--cflag=-I/tmp/portage- tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/base/include' '--cflag=-I/tmp /portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/base/dist-install/build/include' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/base/dist-install/build/include' '-- cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/base/dist-install/build/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/integer-gmp/include' ' --cflag=-I/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/libraries/integer-gmp/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/integer-gmp/dist- install/build/include' '--cflag=-I/tmp/portage-tmpdir/portage/cross-sparc- unknown-linux-gnu/ghc-9999/work/ghc-9999/libraries/integer-gmp/dist- install/build/dist-install/build/include' '--cflag=-I/tmp/portage- tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/rts/dist/build' '--cflag=-I/tmp/portage- tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/includes' '--cflag=-I/tmp/portage- tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/includes/dist-derivedconstants/header' '-- cflag=-Werror=unused-but-set-variable' '--cflag=-Wno-error=inline' '-- lflag=-Wl,-O1' --cflag=-Ilibraries/ghci/dist-install/build/./autogen --cflag=-include --cflag=libraries/ghci/dist- install/build/./autogen/cabal_macros.h libraries/ghci/./GHCi/FFI.hsc -o libraries/ghci/dist-install/build/GHCi/FFI.hs }}} Adding '''-k -v''': {{{ ... libraries/ghci/GHCi/FFI.hsc:111 computing FFI_OK executing: sparc-unknown-linux-gnu-gcc -S -c libraries/ghci/dist- install/build/GHCi/FFI_hsc_test10.c -o libraries/ghci/dist- install/build/GHCi/FFI_hsc_test10.s ... }}} Generated files are: {{{ // FFI_hsc_test10.c #include "/tmp/portage-tmpdir/portage/cross-sparc-unknown-linux- gnu/ghc-9999/work/ghc-9999/inplace/lib/template-hsc.h" #line 9 "FFI.hsc" #include #line 71 "FFI.hsc" #if defined(mingw32_HOST_OS) && defined(i386_HOST_ARCH) #line 73 "FFI.hsc" #endif extern unsigned long long ___hsc2hs_BOM___; unsigned long long ___hsc2hs_BOM___ = 0x100000000; extern unsigned long long ___hsc2hs_int_test___hsc2hs_sign___; unsigned long long ___hsc2hs_int_test___hsc2hs_sign___ = (FFI_OK) < 0; extern unsigned long long ___hsc2hs_int_test; unsigned long long ___hsc2hs_int_test = (FFI_OK); #line 119 "FFI.hsc" #if defined(mingw32_HOST_OS) && defined(i386_HOST_ARCH) #line 122 "FFI.hsc" #endif }}} {{{ ; FFI_hsc_test10.s .file "FFI_hsc_test10.c" .global ___hsc2hs_int_test .section ".bss" .align 8 .type ___hsc2hs_int_test, #object .size ___hsc2hs_int_test, 8 ___hsc2hs_int_test: .skip 8 .global ___hsc2hs_int_test___hsc2hs_sign___ .align 8 .type ___hsc2hs_int_test___hsc2hs_sign___, #object .size ___hsc2hs_int_test___hsc2hs_sign___, 8 ___hsc2hs_int_test___hsc2hs_sign___: .skip 8 .global ___hsc2hs_BOM___ .section ".data" .align 8 .type ___hsc2hs_BOM___, #object .size ___hsc2hs_BOM___, 8 ___hsc2hs_BOM___: .long 1 .long 0 .ident "GCC: (Gentoo 7.2.0-r1 p1.1) 7.2.0" .section .note.GNU-stack,"", at progbits }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 11:10:56 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 11:10:56 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch In-Reply-To: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> References: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> Message-ID: <060.2256d9e0a22a1319b39a2bdff3a922b9@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 slyfox): * cc: hvr, bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 11:22:08 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 11:22:08 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.0c1778c04d46c58b9b6fd2c12d2f5e4f@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): That does work. However, I prefer to avoid using the FFI where possible. My reasons (which I’ll admit are not entirely compelling) are: it’s syntactically unappealing, it prevents optimizations (barely relevant in this case though), and it doesn’t work with GHCJS. I noticed from looking at the source for Data.Primitive.ByteArray that copyByteArray# and friends weren’t always provided by GHC.Prim. https://hackage.haskell.org/package/primitive-0.6.3.0/docs/src/Data- Primitive-ByteArray.html#MutableByteArray For super old GHCs, they were just an FFI call to memcpy. But these were eventually brought into GHC.Prim. I don’t know why this decision was made, but I’m glad that it was. I would like more ByteArray operations that correspond to manually super optimized standard c library functions to be made available as primitives. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 11:28:15 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 11:28:15 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.372d133bb4733273cf41493287abf980@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 sjakobi): I have [https://github.com/sjakobi/ghc/tree/T13362 a branch] that works for me on Windows 10 and Linux using an i7-4790K CPU. It would be great if y'all could test this on: * macOS / OS X * FreeBSD * ARM and other non-x86 architectures * Intel Haswell and Broadwell CPUs with L4 cache To ensure that the code works as intended, run a "Hello world"-program with `+RTS -s` and check that the report shows `(N+1) MB total memory in use` where `N` MB is the size of your largest cache. PRs to support other operating systems are also very welcome! :) Open design questions as of now: 1. If we only find an L1 cache, should we really go with an allocation area of typically just 32 or 64 kB? IMHO it might be better to ignore any L1 caches and to simply default to the old 1 MB in these cases. 2. What if we find an L4 cache with 64 or 128 **MB**? This would easier to decide if we got some benchmark results, for example in the style of [comment:7 varosi's]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 11:58:08 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 11:58:08 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch In-Reply-To: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> References: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> Message-ID: <060.31afadf1dc82b551bddb9eeec079c390@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 slyfox): Meanwhile I've added example outputs for a few targets here: https://github.com/haskell/hsc2hs/pull/7 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 14:11:28 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 14:11:28 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.053999a0d48d36c5594b0d211f52b862@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 varosi): Great! Is it possible to share your Windows executable so I could experiment on a few machines from a few cores up to close to hundred? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 18:10:43 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 18:10:43 -0000 Subject: [GHC] #14699: Core library status for 8.4.1 In-Reply-To: <046.12f775ea02060174a5ac178f457055aa@haskell.org> References: <046.12f775ea02060174a5ac178f457055aa@haskell.org> Message-ID: <061.0fc4cce1621d54aebb8fbcad2866dce2@haskell.org> #14699: Core library status for 8.4.1 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): For the record, 8.4 will be shipping with a `unix` from the 2.7 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 20:48:04 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 20:48:04 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.8cc7a49451b1169cd5a35a3f1c26e9c4@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Right, indeed we have been gradually moving simple operations like this into primops and this is certainly something we can consider doing in the case of `memchr`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 22:57:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 22:57:55 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.d5dd00366936b727162aa049434a03d1@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): Gotcha. Out of curiosity, who is the "we" that you refer to? Lately, I've been trying to improve my understanding of who has the authority to make certain decisions concerning important components of the GHC haskell ecosystem. According to the core libraries maintainership page (1), `ghc- prim` is maintained by GHC HQ, but I cannot figure out who GHC HQ is. Is there a page somewhere that lists who comprises this group? (1) https://wiki.haskell.org/Library_submissions#The_Core_Libraries -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 23:03:19 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 23:03:19 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.f2e4447b8604c21916cab3c1af69f9ee@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): Sorry, just reread my comment after submitting it. I realized that the first two sentences may be read with a snarky tone to them that I didn't intend. Also, I'm glad that `memchr` could be considered for being moved into `ghc-prim`, and I'm happy to try implementing it if it's approved. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 23:13:31 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 23:13:31 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.cbcc527b51ad4c04afd8e65cc73fbb63@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): Nevermind my earlier question. I just found the answer on the very page I had linked to: > The maintainer "GHC HQ" means Simon Marlow, Simon Peyton Jones, Herbert Valerio Riedel and Ben Gamari. Daniel Fischer has taken responsibility for numeric stuff. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 4 23:58:44 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 04 Mar 2018 23:58:44 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.1ed7bbb847f07295e2d51d49a47045a2@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 ulysses4ever): As it seems to stale for a while, I'd like to give it a try. IIUC, the strategy laid by Simon suggests developing a `Tc`-less version of `lookupGlobal`. For this we need to identify ties to `Tc` inside it and then try to cut those. First tie (also spelled by Simon above) is “`tcg_type_env`, which was initialised by `initTcForLookup`”. I looked at `initTcForLookup` and its dependencies, and it seems to me that `tcg_type_env`is initialized with `emptyNameEnv` there. A question: does that mean that corresponding part of the `tcLookupGlobal` which queries `tcg_type_env` is not needed at all and can be omitted in the `Tc`-less version of `lookupGlobal`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 00:59:31 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 00:59:31 -0000 Subject: [GHC] #13573: Add Foldable1 to base In-Reply-To: <051.5343934480dda921b1b6981f18b39763@haskell.org> References: <051.5343934480dda921b1b6981f18b39763@haskell.org> Message-ID: <066.657d1cf32411343c40f9a24c218a71a5@haskell.org> #13573: Add Foldable1 to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10365 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): The name of the typeclass is a little unfortunate since the similarly named `Eq1`, `Show1`, etc. use the same suffix but with a very different meaning. Also, it's a little unfortunate that `Foldable1` doesn't have `foldl1`, `foldr1`, etc. Although there are already functions of the same name in `Foldable`, and there's no burning need to remove them any time soon, it would be nice to have a long-term plan to deprecate and remove them since they are a wart in the typeclass design. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 01:01:16 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 01:01:16 -0000 Subject: [GHC] #13573: Add Foldable1 to base In-Reply-To: <051.5343934480dda921b1b6981f18b39763@haskell.org> References: <051.5343934480dda921b1b6981f18b39763@haskell.org> Message-ID: <066.ebe974bc5286b2c43c17b8ae56aed607@haskell.org> #13573: Add Foldable1 to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10365 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): Those things aside, in general, I am in favor of getting `Foldable1` into `base` (with the same name that it currently has). I would like for the typeclass to have more methods though, and I'd like for there to be a longer-term plan around fixing `Foldable`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 02:06:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 02:06:51 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.41e2b730d1b4f1d63736e29f8d1ea477@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Should this ticket be a release blocker? As shown in #14868, this issue can cause an outright miscompilation when `-g` is used and Core Lint is disabled. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 02:07:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 02:07:13 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.4a41cc6504b6bcf77a2c95b5fa1952da@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 03:05:14 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 03:05:14 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.001a79b91bdbf68d2b52162dda2fc1ac@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * version: => 8.3 * milestone: => 8.4.2 Comment: I'm afraid that it's too late for 8.4.1; it will have to wait for 8.4.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 03:25:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 03:25:46 -0000 Subject: [GHC] #14890: Make Linux slow validate green Message-ID: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> #14890: Make Linux slow validate green -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Now since we will soon have a nightly slow validation, let's finally get it passing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 03:38:59 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 03:38:59 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.d698a2203a0fd3a1abe5aa2b02b7d692@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): That being said, your question is a very reasonable one and one that doesn't have a particularly clear meaning. "GHC HQ" is a rather vague entity which has historically meant some subset of the Simons, hvr, me/Austin/Ian, and perhaps some unnamed others. I generally try to avoid using the phrase for that reason but there are still plenty of references to be found on the wiki. Regarding `ghc-prim`, it's really an implementation detail of GHC and therefore Simon PJ has the ultimate say. In general if there's uncertainty on his part we just send the proposal to the proposal process. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 06:11:59 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 06:11:59 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.f0e1cc79cd0c284b69a4627ee83baece@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 sjakobi): Replying to [comment:12 varosi]: > Great! Is it possible to share your Windows executable so I could experiment on a few machines from a few cores up to close to hundred? You can download a binary distribution [https://drive.google.com/file/d/1sNf93dZ9KEZT6yYdfSCM3fAVxn7YyFil/view?usp=sharing here]. It's not an optimized build though, so at least building with it should be slower than with official releases. Regarding running on Windows machines with close to a hundred cores, the current implementation will only detect caches within its current processor group of at most 64 logical processors (see "Remarks" [https://msdn.microsoft.com/en- us/library/windows/desktop/ms683194(v=vs.85).aspx here]). As long as there aren't any larger caches outside of the processor group it will still set the allocation area to the correct size. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 07:47:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 07:47:10 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.deca58accd2bb46f5d6f7725fd38e69f@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.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 osa1): I'm not sure how to write a test for this. The problem is in GHC 8.2 for the `primitive` function shown in the bug report we generate a desugared function with `RHS size: {terms: 16, types: 52, coercions: 15, joins: 0/1}` without `-XStrict`, and with `-XStrict` it becomes `-- RHS size: {terms: 16, types: 58, coercions: 15, joins: 1/2}` even though there should be no difference (as is already the case with GHC 8.4 and GHC HEAD). It's hard to write a program that generates different outputs based on the term size, so I guess I have to compare desugarer outputs with and without `-XStrict`, but even then I get different variables generated in each run, so I need equality modulo renaming.. bgamari, do you know how to implement such a test? Do we have any similar tests in the test suite already? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 08:51:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 08:51:01 -0000 Subject: [GHC] #14873: GHC HEAD regression (piResultTy) In-Reply-To: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> References: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> Message-ID: <065.aaf77708e8762514a36e1d056dac6053@haskell.org> #14873: GHC HEAD regression (piResultTy) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"3d252037234ce48f9bdada7d5c9b1d8eba470829/ghc" 3d252037/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3d252037234ce48f9bdada7d5c9b1d8eba470829" Respect Note [The tcType invariant] I tried to do this with commit 0a12d92a8f65d374f9317af2759af2b46267ad5c Author: Simon Peyton Jones Date: Wed Dec 13 12:53:26 2017 +0000 Further improvements to well-kinded types The typechecker has the invariant that every type should be well- kinded as it stands, without zonking. See Note [The well-kinded type invariant] in TcType. That invariant was not being upheld, which led to Trac #14174. I fixed part of it, but T14174a showed that there was more. This patch finishes the job. But I didn't get it quite right as Trac #14873 showed. This patch fixes the problem; although I am still a bit unhappy. (See "A worry" in the HsApp case of tc_infer_hs_type.) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 08:51:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 08:51:01 -0000 Subject: [GHC] #14808: GHC HEAD regression: GADT constructors no longer quantify tyvars in topological order In-Reply-To: <050.90702c1fad16a72a2e55cb4eeb0cc78a@haskell.org> References: <050.90702c1fad16a72a2e55cb4eeb0cc78a@haskell.org> Message-ID: <065.3b6be2941e8e4cddc9a65549c5527a16@haskell.org> #14808: GHC HEAD regression: GADT constructors no longer quantify tyvars in topological order -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.5 checker) | Resolution: | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14529, #14796 | Differential Rev(s): Phab:D4413 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"e7653bc3c4f57d2282e982b9eb83bd1fcbae6e30/ghc" e7653bc/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e7653bc3c4f57d2282e982b9eb83bd1fcbae6e30" Wombling around in Trac #14808 Comment:4 in Trac #14808 explains why I'm unhappy with the current state of affairs -- at least the lack of documentation. This smallpatch does nothing major: * adds comments * uses existing type synonyms more (notably FreeKiTyVarsWithDups) * adds another test case to T14808 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 08:51:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 08:51:01 -0000 Subject: [GHC] #14174: GHC panic with TypeInType and type family In-Reply-To: <045.87c0508a41a6d0d9834ba40ef8506297@haskell.org> References: <045.87c0508a41a6d0d9834ba40ef8506297@haskell.org> Message-ID: <060.6ff42302d25845d007a089f5213b74ba@haskell.org> #14174: GHC panic with TypeInType and type family -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.3 Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | polykinds/T14174.hs, T14174a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"3d252037234ce48f9bdada7d5c9b1d8eba470829/ghc" 3d252037/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3d252037234ce48f9bdada7d5c9b1d8eba470829" Respect Note [The tcType invariant] I tried to do this with commit 0a12d92a8f65d374f9317af2759af2b46267ad5c Author: Simon Peyton Jones Date: Wed Dec 13 12:53:26 2017 +0000 Further improvements to well-kinded types The typechecker has the invariant that every type should be well- kinded as it stands, without zonking. See Note [The well-kinded type invariant] in TcType. That invariant was not being upheld, which led to Trac #14174. I fixed part of it, but T14174a showed that there was more. This patch finishes the job. But I didn't get it quite right as Trac #14873 showed. This patch fixes the problem; although I am still a bit unhappy. (See "A worry" in the HsApp case of tc_infer_hs_type.) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 08:52:20 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 08:52:20 -0000 Subject: [GHC] #14873: GHC HEAD regression (piResultTy) In-Reply-To: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> References: <050.432390dbdc6a6bf0129a45fcc689c7e7@haskell.org> Message-ID: <065.9e17c1151e868bf632705d8f874e53cf@haskell.org> #14873: GHC HEAD regression (piResultTy) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: (none) => goldfire Comment: OK done. Richard: could you have a look, to check my work? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 09:12:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 09:12:52 -0000 Subject: [GHC] #12935: Object code produced by GHC is non-deterministic In-Reply-To: <046.8f3dd2cbcacc5f9595e0dfae3817822d@haskell.org> References: <046.8f3dd2cbcacc5f9595e0dfae3817822d@haskell.org> Message-ID: <061.55270c7b5d947b714adaa006341d0479@haskell.org> #12935: Object code produced by GHC is non-deterministic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4388 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): As I mentioned over on #14769, I don't think relying on the compilation order of modules for determinism is the right way to do this. The rationale is that the compilation order can change for other reasons: the user may invoke GHC on a different set of modules, without changing anything about the source code or dependencies of any particular module. The determinism property we want is that the output depends only on * The source code of a module, * Its dependencies, * compiler flags that affect the generated code -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 09:49:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 09:49:08 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.1cf7f569a34dec8719612df02069aef6@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 hvr): Fwiw, I can see the appeal to abstract over the basic low-level ISO C99 memory primitives (`memcmp`, `memchr`, `memcpy`, `memset` etc, some of which may have a LLVM primitive op counterpart), which makes it easier for projects like ghcjs, eta, or the upcoming ghc/wasm if `ghc-prim` already provides the primitives in a single central place, than having to patch N packages which FFI call themselves. It seems to me, that `memchr(3)` may be the only one left from the ISO C99 set of `mem*` family of functions operating on byte arrays we haven't yet wrapped. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 11:02:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 11:02:09 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.772baa17832afd6ad5a9503ee1a8796e@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.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 ulysses4ever): Couldn't Joachim's library [https://github.com/nomeata/inspection-testing inspection-testing] help here somehow? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 11:20:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 11:20:22 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.8b592d4297a030a4750439b4d5be34d9@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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): > Is there hope for the user to guide this process You want to write a ''term-level'' function that can be used a theorem in solving ''type-level'' constraints. This also came up, I think, in #14822. Of course, this is much what happens in many proof assistants. Perhaps we can learn from them. Personally, I don't see a direct way to do this; but perhaps others with a broader perspective, and a bit more time, might do so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 11:31:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 11:31:10 -0000 Subject: [GHC] #14877: QuantifiedConstraints: Can't deduce `xx' from `(xx => a, xx)' In-Reply-To: <051.a93bc7dc60f96bf37ae9f443b2fe178c@haskell.org> References: <051.a93bc7dc60f96bf37ae9f443b2fe178c@haskell.org> Message-ID: <066.69d1c35b2039ff7eea3d1c654da6fac5@haskell.org> #14877: QuantifiedConstraints: Can't deduce `xx' from `(xx => a, xx)' -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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): Consider the quantified constraint (QC) in {{{ instance (forall xx. (xx => a) => Implies xx b) => F a b }}} It serves as a local instance declaration. To construct the dictionary for `(F a b)` I may need to to solve a constraint `(Implies xx b)`. The QC says "if you want to solve `Implies xx b`, then it suffices to prove `xx => a`". And to prove `xx => a`, the built-in rules assume `xx` and try to prove `a`. It's quite different to say {{{ instance (forall xx. (xx => a) => (xx => b) => F a b }}} That is precisely equivalant to {{{ instance (forall xx. (xx => a, xx) => b) => F a b }}} Now the QC says "if you want to solve the goal `b`, then conjure up some constraint `xx`, and prove `(xx => a, xx)`. But how can we guess `xx`? Each QC has an instance "head", usually headed by a type constructor, sometimes by a type variable. That head is the pattern the QC can solve. `Implies xx b` is a good instance head: it matches things of that form. Plain `b` is not a good instance head! In short, I see nothing wrong here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 11:32:41 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 11:32:41 -0000 Subject: [GHC] #14869: Documentation for isLiftedTypeKind is incorrect In-Reply-To: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> References: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> Message-ID: <065.abe77dfe0977da9f279f1f9c1bb48829@haskell.org> #14869: Documentation for isLiftedTypeKind is incorrect -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | 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 simonpj): > I propose that we: Yes that sounds reasonable. Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 11:52:32 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 11:52:32 -0000 Subject: [GHC] #8772: ghci should save history more often In-Reply-To: <046.7de96bdd9c1f26a5cddbf4d5489fb344@haskell.org> References: <046.7de96bdd9c1f26a5cddbf4d5489fb344@haskell.org> Message-ID: <061.5b04bb8fb6e839ed9923fe392088041f@haskell.org> #8772: ghci should save history more often -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: feature request | Status: upstream Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 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 sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 12:06:29 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 12:06:29 -0000 Subject: [GHC] #13193: Integer (gmp) performance regression? In-Reply-To: <049.413a0b17762ed375a5821293dec1ac28@haskell.org> References: <049.413a0b17762ed375a5821293dec1ac28@haskell.org> Message-ID: <064.5812b1fbc2f6fe516fce565d0aee2373@haskell.org> #13193: Integer (gmp) performance regression? -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 12:08:43 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 12:08:43 -0000 Subject: [GHC] #10854: Remove recursive uses of `pprParendHsExpr` from `HsExpr.ppr_expr` In-Reply-To: <047.e2e165b0a37a7097edcf4a218b419974@haskell.org> References: <047.e2e165b0a37a7097edcf4a218b419974@haskell.org> Message-ID: <062.15d3a3abe44d472c68957ae551b6164a@haskell.org> #10854: Remove recursive uses of `pprParendHsExpr` from `HsExpr.ppr_expr` -------------------------------------+------------------------------------- Reporter: goldfire | Owner: kseo Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13238 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 12:15:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 12:15:04 -0000 Subject: [GHC] #14884: Type holes cause assertion failure in ghc-stage2 compiler during type checking In-Reply-To: <049.e0dc234c0a117697c411dc48fa40d3fb@haskell.org> References: <049.e0dc234c0a117697c411dc48fa40d3fb@haskell.org> Message-ID: <064.9fa8d0f73be762d251e02ce655893f46@haskell.org> #14884: Type holes cause assertion failure in ghc-stage2 compiler during type checking -------------------------------------+------------------------------------- Reporter: sighingnow | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I've seen this before. It arises during error reporting, when the (now quite elaborate) `TcErrors.validSubstitutions` code invokes the constraint solver. To avoid the assertion error we need to set the level correctly, and we aren't doing that yet. It's unsatisfactory, but I think harmless. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 12:33:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 12:33:09 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.56c54ddd1ea26c5ba0d4f6d3786853cb@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): @bgamari Thanks for the clarification. It is much appreciated. @hvr I think that `memcmp` is also missing. Also, thanks for pointing out eta and wasm, which I'd forgotten about. I agree that this would be helpful for those as well. Also, that's a cool blog post. Thanks for linking. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 13:11:06 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 13:11:06 -0000 Subject: [GHC] #14706: T11489 fails if run as root In-Reply-To: <046.a14b90f533f833e4ef6e5c85c8add140@haskell.org> References: <046.a14b90f533f833e4ef6e5c85c8add140@haskell.org> Message-ID: <061.69a500eba287f28a9d2da840974ad733@haskell.org> #14706: T11489 fails if run as root -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Continuous | Version: 8.5 Integration | 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:D4360 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mrkkrp): * owner: bgamari => mrkkrp -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 13:11:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 13:11:46 -0000 Subject: [GHC] #14598: 32-bit Linux environment In-Reply-To: <046.d2f4ecc843f7c7bed1054ebabaec5cff@haskell.org> References: <046.d2f4ecc843f7c7bed1054ebabaec5cff@haskell.org> Message-ID: <061.f31edab73d1594d6dbc972ac7b323ee0@haskell.org> #14598: 32-bit Linux environment -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: bug | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.1 Integration | 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 mrkkrp): * owner: bgamari => mrkkrp -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 13:12:43 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 13:12:43 -0000 Subject: [GHC] #14706: T11489 fails if run as root In-Reply-To: <046.a14b90f533f833e4ef6e5c85c8add140@haskell.org> References: <046.a14b90f533f833e4ef6e5c85c8add140@haskell.org> Message-ID: <061.68cc4ce0d8dcb74c130be5a3a4943753@haskell.org> #14706: T11489 fails if run as root -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Continuous | Version: 8.5 Integration | 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:D4360 Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * cc: facundo.dominguez (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 13:31:18 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 13:31:18 -0000 Subject: [GHC] #14862: Switching to Cabal 2.2 makes ghc unusable In-Reply-To: <048.eb29786956ab5b6f0a644e75f882323f@haskell.org> References: <048.eb29786956ab5b6f0a644e75f882323f@haskell.org> Message-ID: <063.b14c2aa34dab81a3683d7f60974b42f3@haskell.org> #14862: Switching to Cabal 2.2 makes ghc unusable -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: angerman Type: bug | Status: closed Priority: high | Milestone: Component: None | Version: 8.4.1-alpha3 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 alpmestan): * status: new => closed * resolution: => fixed Comment: [https://phabricator.haskell.org/D4453 D4453] has been merged. Thanks hvr/angerman! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 13:48:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 13:48:35 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.6af36f6664074b56e6720e6cbb678c3b@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): I've hit a small snag trying to follow: https://ghc.haskell.org/trac/ghc/ticket/14779#comment:15 I expected top level primitive strings (things of type `Addr#`) to be either `Lit (MachStr _)` or `Lit (MachStr _)`wrapped in any number of allowed `Tick t _`. Running the `T9583` after reverting f5b275a239d2554c4da0b7621211642bf3b10650, revealed top level bindings of the form: {{{ $tT_sas7 :: Addr# [LclId] $tT_sas7 = src src $tcT_sahj $tcT_sahj :: Addr# [LclId] $tcT_sahj = "T"# }}} This appears to be a variant of a problem from the original "allow top level primitive strings" patch. Changing CSE similarly to https://phabricator.haskell.org/D2605#inline-23997 may be what I need to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:00:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:00:04 -0000 Subject: [GHC] #14888: The (->) type doesn't survive a TH quote-splice roundtrip In-Reply-To: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> References: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> Message-ID: <065.0df37006c8213e9af493c203527766d8@haskell.org> #14888: The (->) type doesn't survive a TH quote-splice roundtrip -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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:D4466 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"6ee831f279c91888ee5815f8eee473bcd6fd25c6/ghc" 6ee831f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6ee831f279c91888ee5815f8eee473bcd6fd25c6" Fix #14888 by adding more special cases for ArrowT Summary: There were previously some situations where `(->)` would not be desugared or reified as `ArrowT`, leading to various oddities such as those observed in #14888. We now uniformly treat `(->)` as `ArrowT` in Template Haskell–world by checking for any tycon that has the same name as `(->)`, and converting that to `ArrowT`. Test Plan: make test TEST=T14888 Reviewers: goldfire, bgamari, simonpj Reviewed By: goldfire, simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14888 Differential Revision: https://phabricator.haskell.org/D4466 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:01:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:01:01 -0000 Subject: [GHC] #14888: The (->) type doesn't survive a TH quote-splice roundtrip In-Reply-To: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> References: <050.33ec4f5b4c8ee4ddfb72368dd47e7c8a@haskell.org> Message-ID: <065.e897a1f600748ace7b411c39175b9db7@haskell.org> #14888: The (->) type doesn't survive a TH quote-splice roundtrip -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: th/T14888 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4466 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => th/T14888 * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:02:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:02:08 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.8b1d2748e55e2c521c4057a70f8743a3@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): Relying on correctness with CSE seems a bit brittle though. If I `-fno- cse` I'm back to the original problem. That leads me to believe that 2 things need to happen: 1. CoreLint (and probably CoreToSTG) needs to accept Core like above. 2. CSE should fix it. Alternatively we could figure out how it happens and never let it happen. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:27:31 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:27:31 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.2dafcabd985d1f4954188d19cc610aaa@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): Fixing `tryForCSE` to look through ticks here: {{{ tryForCSE :: Bool -> CSEnv -> InExpr -> OutExpr tryForCSE toplevel env expr | toplevel && exprIsLiteralString expr = expr -- See Note [Take care with literal strings] | Just e <- lookupCSEnv env expr'' = mkTicks ticks e | otherwise = expr' }}} Appears to take care of the problem from 2 previous comments. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:32:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:32:19 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin Message-ID: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Since a9f680f631e2 the testsuite has been failing with [[https://phabricator.haskell.org/harbormaster/build/42193|broken ext- interp tests]] on Darwin. I also see this on the ghc-8.4 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:32:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:32:52 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin In-Reply-To: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> References: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> Message-ID: <061.2fda802a7192ce0b86a14f5838ea426c@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Strangely enough when preparing the final release tarball I noticed that the failure manifested as a linker error, {{{ =====> T9262(ext-interp) 1 of 1 [0, 0, 0] cd "./th/T9262.run" && "/Users/bgamari/bin- dist-8.4.1-Darwin/ghc/inplace/bin/ghc-stage2" -c T9262.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show- caret -dno-debug-output -XTemplateHaskell -package template-haskell -fexternal-interpreter -v0 Compile failed (exit code 1) errors were: ghc-iserv.bin: lookupSymbol failed in relocateSection (RELOC_GOT) /Users/bgamari/bin-dist-8.4.1-Darwin/ghc/libraries/integer-gmp/dist- install/build/HSinteger-gmp-1.0.1.0.o: unknown symbol `___gmp_rands' ghc-stage2: unable to load package `integer-gmp-1.0.1.0' }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 14:45:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 14:45:36 -0000 Subject: [GHC] #13324: Allow PartialTypeSignatures in the instance context of a standalone deriving declaration In-Reply-To: <050.05d716a2c5be2cade611e1ab44e0e3c6@haskell.org> References: <050.05d716a2c5be2cade611e1ab44e0e3c6@haskell.org> Message-ID: <065.d99cb1a47c38e0fb4e84037af4516e7b@haskell.org> #13324: Allow PartialTypeSignatures in the instance context of a standalone deriving declaration -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10607 | Differential Rev(s): Phab:D4383 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"1c062b794bf71a329f65813ce7b72fe2bd3935f0/ghc" 1c062b79/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1c062b794bf71a329f65813ce7b72fe2bd3935f0" Simplify rnLHsInstType This patch is preparatory for the main fix for Trac #13324 Here, we simplify rnLHsInstType so that it does not try to figure out the class name. This turns out to have a good (rather than bad) effect on error messages, and it prepares the way for the main event. Plus, less code! }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 15:07:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 15:07:35 -0000 Subject: [GHC] #12506: Compile time regression in GHC 8. In-Reply-To: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> References: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> Message-ID: <059.628309121621f67752e4a25295bf23b8@haskell.org> #12506: Compile time regression in GHC 8. -------------------------------------+------------------------------------- Reporter: deech | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:28 simonpj]: > > I can confirm that this *is* a regression; I'm seeing ~34 seconds overall compilation time on 7.10.3, vs. ~341 seconds on GHC HEAD. > > Aha! Excellent. Does that show on (some version of) the repro case test.hs? > > PS: maybe comment:27 answers that affirmatively; I missed that. Yes on both; `test1000.hs` is pretty much an exact replica of the code in the original test case, I really just unrolled the imports to get it into one file, and played with the number of repetitions in `main`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 15:20:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 15:20:12 -0000 Subject: [GHC] #14890: Make Linux slow validate green In-Reply-To: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> References: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> Message-ID: <061.d3482ea8cddd0a27dcf05ee0075bf9f9@haskell.org> #14890: Make Linux slow validate green -------------------------------------+------------------------------------- Reporter: bgamari | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => alpmestan -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 15:32:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 15:32:05 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced In-Reply-To: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> References: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> Message-ID: <065.f280bec36c8c86c1d66e1c9b3671985e@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: sighingnow Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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:D4469 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * status: new => patch * differential: => Phab:D4469 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 15:32:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 15:32:57 -0000 Subject: [GHC] #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup In-Reply-To: <047.dbe3294939f168d779839dd776514e40@haskell.org> References: <047.dbe3294939f168d779839dd776514e40@haskell.org> Message-ID: <062.4e6049c700d2ce40ecb8e8f657d99a99@haskell.org> #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): I tried verifying this in place by updating stack to use [[https://gist.github.com/DanBurton/ba6fcf6b54491436fe8c98d2b2dc702b|ghc-8.4.1-alpha2]]. I set `allow-newer: true` and then hit problems with libraries that I worked through by adding specific packages references until I hit `refex- tdfa` that doesn't compile with this version of ghc. {{{ - location: git: https://github.com/haskell/primitive.git commit: 53f72ce69a4dfde5345cf5809a8b4a1993523367 extra-dep: true - location: git: https://github.com/haskell/text.git commit: 9fac5db9b048b7d68fa2fb68513ba86c791b3630 extra-dep: true - location: git: https://github.com/ChrisKuklewicz/regex-tdfa commit: f1b671946ee573f86d72484f3ab56487d456e735 }}} I think it may be better to try to get a minimal test case going with fewer dependencies. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 16:34:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 16:34:10 -0000 Subject: [GHC] #14170: 8.2.1 regression: GHC fails to simplify `natVal` In-Reply-To: <048.f68d481a7069080ef2825e023292b3f7@haskell.org> References: <048.f68d481a7069080ef2825e023292b3f7@haskell.org> Message-ID: <063.a5174f270b4317cc69c06b3ef1c579e6@haskell.org> #14170: 8.2.1 regression: GHC fails to simplify `natVal` -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Bodigrim Type: bug | Status: patch Priority: high | Milestone: 8.2.3 Component: Compiler | Version: 8.2.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:D4212 Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * status: new => patch * differential: => Phab:D4212 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 16:35:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 16:35:13 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.a15bbfd0f3e37422b91704d4eaa9662c@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by aosivitz): Here's another idea: instead of dynamically linking each dep separately for TH codegen, we could combine all the modules into one and then dynamically link in that large blob. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 16:51:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 16:51:57 -0000 Subject: [GHC] #13205: Run `validate --slow` during CI at least sometimes. In-Reply-To: <047.9b52b4440ebca44d5a2343fbe8a3a428@haskell.org> References: <047.9b52b4440ebca44d5a2343fbe8a3a428@haskell.org> Message-ID: <062.d27d1d594976e1112e9903228f2d5338@haskell.org> #13205: Run `validate --slow` during CI at least sometimes. -------------------------------------+------------------------------------- Reporter: dobenour | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Continuous | Version: 8.0.1 Integration | 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:D4354 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D4354 * milestone: => 8.6.1 Comment: I have a differential up adding a nightly slow validate to the CircleCI infrastructure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 16:53:15 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 16:53:15 -0000 Subject: [GHC] #13205: Run `validate --slow` during CI at least sometimes. In-Reply-To: <047.9b52b4440ebca44d5a2343fbe8a3a428@haskell.org> References: <047.9b52b4440ebca44d5a2343fbe8a3a428@haskell.org> Message-ID: <062.29d4ca4dcd8ba192154e800a18ae728e@haskell.org> #13205: Run `validate --slow` during CI at least sometimes. -------------------------------------+------------------------------------- Reporter: dobenour | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Continuous | Version: 8.0.1 Integration | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14890 | Differential Rev(s): Phab:D4354 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #14890 Comment: We also need to fix the (numerous) known failures. See #14890. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 16:57:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 16:57:36 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.7a97068e05ca0ed504be558c626fd643@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Fixing tryForCSE to look through ticks here: I don't get it. You've added a case to `tryForCSE` that looks a the original expression `expr`, not the stripped one `expr''`. How does that differ from the existing code where the test is in `cse_bind`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 16:59:42 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 16:59:42 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.d902251f3a3b173451840746caf4a9d3@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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): > does that mean that corresponding part of the tcLookupGlobal which queries tcg_type_env is not needed at all and can be omitted Yes I think so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:09:44 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:09:44 -0000 Subject: [GHC] #14892: Field imposters with DuplicateRecordFields Message-ID: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> #14892: Field imposters with DuplicateRecordFields -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: MacOS X Architecture: x86_64 | Type of failure: GHC accepts (amd64) | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: 13644 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- There's a [[https://github.com/BlockScope/ghc-panic-12158|test case]] for this ghc panic. If I use `NamedFieldPuns` I wish this could more delicately pick the right field. If my record use is qualified then please restrict the set of candidate field names to use punned. {{{ {-# LANGUAGE DuplicateRecordFields #-} module Geodesy (X(..), Y(..)) where data X a = X {x :: a} data Y a = Y {x :: a} }}} {{{ {-# LANGUAGE NamedFieldPuns #-} module GhcPanic12158 where import qualified Geodesy as G (X(..)) import Geodesy (Y(..)) update :: G.X a -> G.X a update G.X{x} = G.X{x = x} }}} {{{ > stack build ghc-panic-translateConPatVec-lookup-0.1.0: build (lib) Preprocessing library for ghc-panic-translateConPatVec-lookup-0.1.0.. Building library for ghc-panic-translateConPatVec-lookup-0.1.0.. [1 of 3] Compiling Geodesy [2 of 3] Compiling GhcPanic12158 ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-apple-darwin): translateConPatVec: lookup Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} There are some fixes; 1. Add DuplicateRecordFields. {{{ {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE DuplicateRecordFields #-} module GhcPanic12158 where import qualified Geodesy as G (X(..)) import Geodesy (Y(..)) update :: G.X a -> G.X a update G.X{x} = G.X{x = x} }}} 2. Use qualified field names. {{{ {-# LANGUAGE NamedFieldPuns #-} module GhcPanic12158 where import qualified Geodesy as G (X(..)) import Geodesy (Y(..)) update :: G.X a -> G.X a update G.X{G.x} = G.X{G.x = x} }}} Interestingly, if I don't import the record with the clashing field name then GHC complains. {{{ {-# LANGUAGE NamedFieldPuns #-} module GhcPanic12158 where import qualified Geodesy as G (X(..)) update :: G.X a -> G.X a update G.X{x} = G.X{x = x} }}} {{{ > stack build ghc-panic-translateConPatVec-lookup-0.1.0: unregistering ghc-panic-translateConPatVec-lookup-0.1.0: build (lib) Preprocessing library for ghc-panic-translateConPatVec-lookup-0.1.0.. Building library for ghc-panic-translateConPatVec-lookup-0.1.0.. [3 of 3] Compiling GhcPanic12158 /ghc-panic-12158/earth/library/GhcPanic12158.hs:8:12: error: Not in scope: ‘x’ | 8 | update G.X{x} = G.X{x = x} | ^ /ghc-panic-12158/earth/library/GhcPanic12158.hs:8:21: error: Not in scope: ‘x’ | 8 | update G.X{x} = G.X{x = x} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:11:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:11:56 -0000 Subject: [GHC] #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup In-Reply-To: <047.dbe3294939f168d779839dd776514e40@haskell.org> References: <047.dbe3294939f168d779839dd776514e40@haskell.org> Message-ID: <062.c149aafcc0bb7362723d31dc367e8375@haskell.org> #12158: ghc: panic! (the 'impossible' happened) translateConPatVec: lookup -------------------------------------+------------------------------------- Reporter: wozgonon | Owner: gkaracha Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): The minimal test case I ended up with seemed different enough to warrant its own case, see #14892. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:13:15 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:13:15 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.919f3e56f9617d81399dd969ee52aa39@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): > I don't get it. You've added a case to tryForCSE that looks a the original expression expr, not the stripped one expr''. How does that differ from the existing code where the test is in cse_bind? Sorry, perhaps I was imprecise. I pointed to code before the change, the code after the change is: {{{ tryForCSE :: Bool -> CSEnv -> InExpr -> OutExpr tryForCSE toplevel env expr | toplevel && exprIsMbTickedLitString expr = expr -- See Note [Take care with literal strings] | Just e <- lookupCSEnv env expr'' = mkTicks ticks e | otherwise }}} Where `exprIsMbTickedLitString` looks through allowed ticks. I'm not married to the name by the way, I have a hard time coming up with a better one. For completeness: {{{ exprIsMbTickedLitString :: CoreExpr -> Bool exprIsMbTickedLitString = isJust . exprIsMbTickedLitString_maybe exprIsMbTickedLitString_maybe :: CoreExpr -> Maybe CoreExpr exprIsMbTickedLitString_maybe e@(Lit (MachStr _)) = Just e exprIsMbTickedLitString_maybe (Tick t e) | tickishPlace t == PlaceCostCentre = Nothing | otherwise = exprIsMbTickedLitString_maybe e exprIsMbTickedLitString_maybe _ = Nothing }}} I should be able to put up a complete phab patch soon and discussing the details should be easier. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:13:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:13:19 -0000 Subject: [GHC] #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. (was: Field imposters with DuplicateRecordFields) In-Reply-To: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> References: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> Message-ID: <066.797d1448efa74190c7ba0f87da07ce48@haskell.org> #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC accepts | (amd64) invalid program | Test Case: Blocked By: | Blocking: Related Tickets: 13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:15:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:15:12 -0000 Subject: [GHC] #14600: Work out why Hadrian builds routinely fail In-Reply-To: <046.d1a91fc8ce0240183a8fe557b52881a5@haskell.org> References: <046.d1a91fc8ce0240183a8fe557b52881a5@haskell.org> Message-ID: <061.4c13d9f8c3fefe5acf8475ce4164c953@haskell.org> #14600: Work out why Hadrian builds routinely fail -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.1 Integration | 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): Here is a recent instance of this failure: https://circleci.com/gh/ghc/ghc/2028 I've tried reproducing this locally and over SSH but have been unable to reproduce it thusfar. It seems quite non-deterministic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:19:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:19:08 -0000 Subject: [GHC] #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. In-Reply-To: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> References: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> Message-ID: <066.64138ac0a6072e9309668f108dd4a9f8@haskell.org> #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 Resolution: | Keywords: ORF Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC accepts | (amd64) invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: adamgundry (added) * keywords: => ORF * version: 8.2.2 => 8.4.1-alpha3 * related: 13644 => #13644 Comment: FWIW, this does not panic on GHC 8.4.1 (after #13644 was fixed), but instead gives an incorrect error message: {{{ $ /opt/ghc/8.4.1/bin/ghci GhcPanic12158.hs GHCi, version 8.4.0.20180224: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 2] Compiling Geodesy ( Geodesy.hs, interpreted ) [2 of 2] Compiling GhcPanic12158 ( GhcPanic12158.hs, interpreted ) GhcPanic12158.hs:8:12: error: • Constructor ‘G.X’ does not have field ‘x’ • In the pattern: G.X {x} In an equation for ‘update’: update G.X {x} = G.X {x = x} | 8 | update G.X{x} = G.X{x = x} | ^ }}} I believe this lines up with Adam's work on overloaded record fields, so I'll label this ticket as such. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:32:33 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:32:33 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.6018f9896d5aea95aa438443da5a36e3@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > Here's another idea: instead of dynamically linking each dep separately for TH codegen, we could combine all the modules into one and then dynamically link in that large blob. I fear that may increase compilation time rather significantly, however. Linking tends to be quite expensive. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:33:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:33:13 -0000 Subject: [GHC] #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. In-Reply-To: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> References: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> Message-ID: <066.af695c5affd15e2e2f8336b8a840d220@haskell.org> #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 Resolution: | Keywords: ORF Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC accepts | (amd64) invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Thanks for reducing this, philderbeast! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:33:38 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:33:38 -0000 Subject: [GHC] #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. In-Reply-To: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> References: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> Message-ID: <066.5097e3c702868d10ada2c5893b74cb8d@haskell.org> #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 Resolution: | Keywords: ORF Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC accepts | (amd64) invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): You beat me to the test with a later GHC version, something Ben asked me to do on #12158. I too am seeing the problem of GHC's panic fixed. I do wish however that the compiler here would pick the one `x` pun that fits. {{{ # stack.yaml resolver: ghc-8.4.0.20180118 compiler: ghc-8.4.0.20180118 compiler-check: match-exact }}} {{{ > stack build ghc-panic-translateConPatVec-lookup-0.1.0: build (lib) Preprocessing library for ghc-panic-translateConPatVec-lookup-0.1.0.. Building library for ghc-panic-translateConPatVec-lookup-0.1.0.. [2 of 3] Compiling GhcPanic12158 /earth/library/GhcPanic12158.hs:9:12: error: • Constructor ‘G.X’ does not have field ‘x’ • In the pattern: G.X {x} In an equation for ‘update’: update G.X {x} = G.X {x = x} | 9 | update G.X{x} = G.X{x = x} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:37:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:37:09 -0000 Subject: [GHC] #10946: Typed hole inside typed Template Haskell bracket causes panic In-Reply-To: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> References: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> Message-ID: <063.ef052719db3059001d5a66967380dce3@haskell.org> #10946: Typed hole inside typed Template Haskell bracket causes panic -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T10946 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): So in f64f7c36ef9395da1cc7b686aaf1b019204cd0fc, we added a test case for this that was marked as `expect_broken`. However, that program now loops infinitely on GHC HEAD! {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.5.20180305: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci λ> :set -XTemplateHaskell λ> m :: a -> a; m x = $$([||_||]) -- Loops infinitely ^CInterrupted. }}} Should we disable the test case entirely in the meantime? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:43:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:43:26 -0000 Subject: [GHC] #14880: GHC panic: updateRole In-Reply-To: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> References: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> Message-ID: <065.6ec4fff8dffe7c7d358d01390df58b8c@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Roles Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Even simpler {{{ data Foo (x :: Type) :: forall (a :: x). Proxy a -> Type data Bar :: Type -> Type where MkBar :: forall x arg. -- Commenting out the line below makes the issue go away Proxy (Foo arg) -> Bar x }}} The panic is caused because the existentials for `MkBar` are messed up; {{{ {- MkBar univ_tvs: (x :: *) ex_tvs: (a :: arg_aZv) (arg_XZx :: *) arg ty: Proxy @arg_XZx a result ty: Foo @arg_XZx a }}} Note the confusion of two `arg` variables. Ran out of time at that point. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 17:50:06 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 17:50:06 -0000 Subject: [GHC] #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck In-Reply-To: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> References: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> Message-ID: <065.3246e1e26dd464dbc0681680846e34fd@haskell.org> #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: TypeFamilies, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): A slight twist on this is if you leave out the type family equations. For instance: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# OPTIONS_GHC -fprint-explicit-kinds #-} module Bug where import Data.Kind import Data.Proxy type family Foo1 (e :: Proxy (a :: k)) :: Type where {} type family Foo2 (k :: Type) (e :: Proxy (a :: k)) :: Type where {} }}} `Foo1` typechecks, but `Foo2` does not: {{{ $ ghci Bug.hs -fprint-explicit-kinds GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:10:1: error: • These kind and type variables: k (e :: Proxy k a) are out of dependency order. Perhaps try this ordering: k (a :: k) (e :: Proxy k a) NB: Implicitly declared kind variables are put first. • In the type family declaration for ‘Foo2’ | 10 | type family Foo2 (k :: Type) (e :: Proxy (a :: k)) :: Type where {} | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} I have no idea why GHC is complaining about the scoping order here—that looks well-scoped to me! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 18:32:16 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 18:32:16 -0000 Subject: [GHC] #14878: Can't witness transitivity ((.)) of isomorphism of Constraints In-Reply-To: <051.a45c628270a13635f0d506c37084dcac@haskell.org> References: <051.a45c628270a13635f0d506c37084dcac@haskell.org> Message-ID: <066.e0cd486a9479ef33e4976775e57a4e0b@haskell.org> #14878: Can't witness transitivity ((.)) of isomorphism of Constraints -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I don't think this is a bug. Consider this example: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE QuantifiedConstraints #-} data Dict c where Dict :: c => Dict c f :: ( c , c => d ) => Dict d f = Dict }}} This works, because there is exactly one matching local instance (`c => d`) for `d`. What about this example, which is closer to what you are writing? {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE QuantifiedConstraints #-} data Dict c where Dict :: c => Dict c f :: ( a, b , a => c, b => c , c => d ) => Dict d f = Dict }}} There is one matching local instance (`c => d`) for `d`, so we try to deduce `c`. But there are multiple matching local instances for `c`: `a => c` and `b => c`. Which one does GHC pick? As noted in the [https://github.com/Gertjan423/ghc- proposals/blob/e16828dbcd59d0ca58573c81fc6cea671875e6e2/proposals/0000 -quantified-constraints.rst#125overlap quantified constraints proposal], if GHC is ever in doubt about which local instance to pick, it simply rejects the code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 18:34:18 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 18:34:18 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin In-Reply-To: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> References: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> Message-ID: <061.acb7b3c66d374195a866a36ff6afe705@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: hvr Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => hvr -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 18:53:33 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 18:53:33 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.1d757b38577c0e16939ab3bd67538060@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423, #8472, #14406 | phab:D4470 Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * differential: phab:D4423 => phab:D4423, phab:D4470 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 19:06:20 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 19:06:20 -0000 Subject: [GHC] #10946: Typed hole inside typed Template Haskell bracket causes panic In-Reply-To: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> References: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> Message-ID: <063.69fc18ed9bfb8942ce2a763a846991f8@haskell.org> #10946: Typed hole inside typed Template Haskell bracket causes panic -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T10946 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): A correction to comment:9—it doesn't loop infinitely, but it does take a full five minutes to complete that test case on my machine. Still, that's quite severe—we should find out what caused this to regress. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 19:32:07 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 19:32:07 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.2a977c8c7fc4a902443edfd449354929@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by aosivitz): Hm, so- as I understand it. We create a single libghc_XX.dylib for use by TH, which in turn references each of its dependencies and loads them with 'load commands' (of which there is a hard total size limit on MacOS). What's the reason we take this step instead of just loading each dependency directly? Is that also for performance? If so, could we generate two of these libghc_XX.dylibs? Or 1 per every 50 dependencies? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 19:34:07 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 19:34:07 -0000 Subject: [GHC] #14878: Can't witness transitivity ((.)) of isomorphism of Constraints In-Reply-To: <051.a45c628270a13635f0d506c37084dcac@haskell.org> References: <051.a45c628270a13635f0d506c37084dcac@haskell.org> Message-ID: <066.52c291f68b87c71e69255cdb635c958c@haskell.org> #14878: Can't witness transitivity ((.)) of isomorphism of Constraints -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * status: new => closed * resolution: => invalid Comment: Ah that's sensible, and not too difficult to work around: {{{#!hs {-# Language QuantifiedConstraints, GADTs, ConstraintKinds, TypeOperators, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, TypeApplications, ScopedTypeVariables #-} import Data.Kind data Dict c where Dict :: c => Dict c class (a => b) => Implies a b instance (a => b) => Implies a b type a :- b = Dict (Implies a b) type a -:- b = Dict (Implies a b, Implies b a) type Iso s t a b = Dict (Implies a b, Implies s t) comp_ :: forall a b c. a-:-b -> b-:-c -> a-:-c comp_ Dict Dict = comp__ @c @b @a @b @a @c b1 a1 a2 b2 where a1 :: a:-b a1 = Dict a2 :: b:-a a2 = Dict b1 :: c:-b b1 = Dict b2 :: b:-c b2 = Dict comp__ :: s:-t -> a:-b -> t:-i -> b:-c -> Iso s i a c comp__ Dict Dict Dict Dict = Dict }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 19:49:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 19:49:22 -0000 Subject: [GHC] #10946: Typed hole inside typed Template Haskell bracket causes panic In-Reply-To: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> References: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> Message-ID: <063.42cfae831e26d608f36a983689512f12@haskell.org> #10946: Typed hole inside typed Template Haskell bracket causes panic -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T10946 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: Tritlo (added) Comment: It looks like much of the slowdown was introduced in commit cbdea95938bf09e8e3e7be31918549224d171873 (`Sort valid substitutions for typed holes by "relevance"`). Tritlo, do you have any idea what might be happening here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 19:54:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 19:54:19 -0000 Subject: [GHC] #14878: Can't witness transitivity ((.)) of isomorphism of Constraints In-Reply-To: <051.a45c628270a13635f0d506c37084dcac@haskell.org> References: <051.a45c628270a13635f0d506c37084dcac@haskell.org> Message-ID: <066.57fe432b309ffadf4cb164f1bd9fff12@haskell.org> #14878: Can't witness transitivity ((.)) of isomorphism of Constraints -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 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 can additionally be witnessed by carrying the witness and composing it explicitly {{{#!hs type Cat ob = ob -> ob -> Type data ImpliesC :: Cat Constraint where ImpliesC :: (a => b) => ImpliesC a b data IsoC :: Cat Constraint where IsoC :: ImpliesC a b -> ImpliesC b a -> IsoC a b instance Category ImpliesC where id :: ImpliesC a a id = ImpliesC (.) :: ImpliesC b c -> ImpliesC a b -> ImpliesC a c ImpliesC . ImpliesC = ImpliesC instance Category IsoC where id :: IsoC a a id = IsoC id id (.) :: IsoC b c -> IsoC a b -> IsoC a c IsoC bc cb . IsoC ab ba = IsoC (bc . ab) (ba . cb) }}} `IsoC` can be parameterised by the category `IsoC :: Cat ob -> Cat ob`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 20:22:34 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 20:22:34 -0000 Subject: [GHC] #10946: Typed hole inside typed Template Haskell bracket causes panic In-Reply-To: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> References: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> Message-ID: <063.f940898df885226b0c77028cadb196be@haskell.org> #10946: Typed hole inside typed Template Haskell bracket causes panic -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T10946 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): RyanGlScott: It seems like what's happening is that since the variable has no constraints on it at all, then it's matching everything in scope (including everything in scope in TemplateHaskell), and then doing the subsumption graph sorting on that, which takes a very long time. I'll give it some thought, but it seems like the right way to go would be to not try to find valid substitutions for this too general case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 20:23:17 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 20:23:17 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.47864fbe02fb0fa5a46c83590adc8af2@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > instead of just loading each dependency directly? Do you mean directly calling `dlopen` on each dependency? I suppose we could do this and it might even work. The problem is that it does nothing for the case of executables. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 20:31:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 20:31:09 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.7ad5cfdf2c171b671e3b71b9212ffd24@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by aosivitz): Yea, dlopen for each dependency. Are you saying there's still a problem with executables that this wouldn't fix? How can I reproduce that? I was only able to reproduce the panic using template haskell. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 20:34:07 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 20:34:07 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin In-Reply-To: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> References: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> Message-ID: <061.ec0b12f0cfd4e68eb526b03003a67c4c@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: hvr Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.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 Herbert Valerio Riedel ): In [changeset:"df7ac37d43bdbabbde9b09344f9425e8e5a879ff/ghc" df7ac37d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="df7ac37d43bdbabbde9b09344f9425e8e5a879ff" Fixup include of gmp/config.mk to use new location This wasn't spotted rightaway in 8f0b2f5eadf0fcb47c581907205a9db686214a69 because the include-site deliberately ignored include-errors as a Hack with the justification below: > Hack. The file gmp/config.mk doesn't exist yet after running ./configure in > the toplevel (ghc) directory. To let some toplevel make commands such as > sdist go through, right after ./configure, don't consider this an error. This may have contributed to #14891. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 20:39:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 20:39:04 -0000 Subject: [GHC] #14868: -O -g breaks string literals In-Reply-To: <043.b85ddd9da71a7b040ce01bef4d2ffb0c@haskell.org> References: <043.b85ddd9da71a7b040ce01bef4d2ffb0c@haskell.org> Message-ID: <058.efdecd211df565e0e2441aafeb5cc042@haskell.org> #14868: -O -g breaks string literals -------------------------------------+------------------------------------- Reporter: akio | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14779, #14123 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): Nice test case, I added it to https://phabricator.haskell.org/D4470. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 20:55:43 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 20:55:43 -0000 Subject: [GHC] #10946: Typed hole inside typed Template Haskell bracket causes panic In-Reply-To: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> References: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> Message-ID: <063.6e4c1da74f668f77a6892e95ada2d206@haskell.org> #10946: Typed hole inside typed Template Haskell bracket causes panic -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T10946 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Or just to limit the maximum number of substitutions to ten, or something arbitrary like that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:05:37 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:05:37 -0000 Subject: [GHC] #14893: GHC hangs while producing error message for incorrect TypeFamilies application Message-ID: <047.c7bdc37997d8c9a8bfb76bc219cbd46f@haskell.org> #14893: GHC hangs while producing error message for incorrect TypeFamilies application -------------------------------------+------------------------------------- Reporter: coopercm | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Linux Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's a minimally reproducible example: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} module Main where newtype Token f a = Token { unToken :: f a } class Class x (f :: * -> *) where type Meta x f :: * type Body x f :: * type Body x f = Token f Meta main :: IO () main = return () }}} This hangs like so {{{ [2 of 2] Compiling Main ( app/Main.hs, .stack- work/dist/x86_64-linux/Cabal-2.0.1.0/build/foo-exe/foo-exe-tmp/Main.o ) }}} I tested on 8.2.2 and 8.0.2 and got the same behavior. The closest existing bug report I could find was https://ghc.haskell.org/trac/ghc/ticket/12386. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:13:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:13:27 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.afb9b3a01264247cf51b92f14fe37e11@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423, #8472, #14406 | phab:D4470 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): D4423 is marked abandoned, in favour of Phab:D4470. Is that right? If so, let's remove it from the Differential Revs field. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:14:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:14:13 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.30a55b5519bf75017765cd15ce1843bc@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4423, #8472, #14406 | phab:D4470 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): In Phab:D4470 I see no change in `tryForCSE`. Are we good without it now? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:21:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:21:36 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.c9ca86c5ecc674a1dbb42e18bd296336@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4470 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * differential: phab:D4423, phab:D4470 => phab:D4470 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:21:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:21:46 -0000 Subject: [GHC] #14840: QuantifiedConstraints: Can't define class alias In-Reply-To: <051.efc0726cd0630f1f9a6cfd923f4eea44@haskell.org> References: <051.efc0726cd0630f1f9a6cfd923f4eea44@haskell.org> Message-ID: <066.d1702ae50e4372b644a3bc8368a26850@haskell.org> #14840: QuantifiedConstraints: Can't define class alias -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | QuantifiedConstraints wipT2893 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): Given this [wiki:QuantifiedConstraints interesting collection of tickets on quantified constraints] it'd be great if someone (Iceland Jack? Ryan?) wanted to write a blog post or even a paper about what you can and cannot do; and why. These examples make my head hurt! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:24:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:24:55 -0000 Subject: [GHC] #10946: Typed hole inside typed Template Haskell bracket causes panic In-Reply-To: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> References: <048.bb931422119631f05ab09abe14bd4c46@haskell.org> Message-ID: <063.7a81f9be321219258d0a8068d49f4829@haskell.org> #10946: Typed hole inside typed Template Haskell bracket causes panic -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: th/T10946 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Tritlo): On the other hand, this is the right behavior, since a type variable with no constraints on it could be substituted with any identifier of any type. So the time it is taking is really due to the bug giving the hole a too general type. simonpj: Yes, that's a good point. When we don't try to sort the substitution, that is indeed what happens. We should set some limit for how many substitutions we attempt to sort by the subsumption graph method, and default to some other method otherwise (like e.g. sorting by module). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:26:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:26:51 -0000 Subject: [GHC] #14840: QuantifiedConstraints: Can't define class alias In-Reply-To: <051.efc0726cd0630f1f9a6cfd923f4eea44@haskell.org> References: <051.efc0726cd0630f1f9a6cfd923f4eea44@haskell.org> Message-ID: <066.208226e540132ecfe396007ebd998b23@haskell.org> #14840: QuantifiedConstraints: Can't define class alias -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: | QuantifiedConstraints wipT2893 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 will write a blog post, I would love to expand it into a paper but I'd probably require some guidance. I have a good idea what you can/cannot do but not always why. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:30:42 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:30:42 -0000 Subject: [GHC] #14831: QuantifiedConstraints: Odd superclass constraint In-Reply-To: <051.631b3f4dec55319ae6028526fc90fcb8@haskell.org> References: <051.631b3f4dec55319ae6028526fc90fcb8@haskell.org> Message-ID: <066.bc6989100eb76510aa4fd6761fb3f531@haskell.org> #14831: QuantifiedConstraints: Odd superclass constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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 my hunch is that you're experiencing the same bug as in... Indeed: see comment:4 above, which gives exactly the same diagnosis as I gave in https://ghc.haskell.org/trac/ghc/ticket/5927#comment:33. In both comments I point out that a local instance declaration that claims to produce evidence for `Semigroup xx` '''for any xx''' is very suspicious (comment:4 above). Now you have two ways of proving `SemiGroup (Free ...)`: from the top- level instance or from the local instance (QC). And currently the local one "wins". For now I'm saying "not a bug" and "you probably didn't really want that program anyway". But I could obviously be wrong about the latter. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:32:48 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:32:48 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.79e08ce835ed2a554bc6ae14ef1371eb@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4470 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): > In ​Phab:D4470 I see no change in tryForCSE. Are we good without it now? Looks like I confused everyone, myself included. The code for `tryForCSE` that I copied comes from https://phabricator.haskell.org/D2605. It has been refactored since (9304df5230a7a29d3e992916d133e462b854e55f) and `cse_bind` is the equivalent place that needed to be fixed. I'm sorry for the confusion. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:37:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:37:03 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.33a0b63db819f529f727ad947fcfd7c5@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 ulysses4ever): One more question. Consider a part of `tcImportDecl_maybe`: {{{ initIfaceTcRn (importDecl name) }}} You said that it is necessary to create a variant of `initIfaceTcRn`. That sounds fine. But here is another thing: `importDecl` has `IfM` in its type. And `IfM` is defined in `TcRnTypes`, so leaving it doesn't bring us decoupling from the typechecker. Should we also replace `importDecl`? This sounds like a lot of work, because it depends on `loadInterface` which is >100 LOCs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:39:30 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:39:30 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 Message-ID: <046.3db25c336062f0dea40eba4721995b57@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: Debugging (amd64) | information is incorrect Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I wanted to see how `-g1` vs `-g2` impact compile speed. Unfortunately I get linking errors trying to build GHC with `-g`. Steps: 1) Add {{{ GhcLibHcOpts += -g1 GhcRtsHcOpts += -g1 }}} to `mk/build.mk`. I used devel2 flavor. 2) `./boot && ./configure && make -j` 3) Observe failure The failure (trimmed): {{{ /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1c94): error: undefined refe rence to '.LcbG2_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cc7): error: undefined refe rence to '.LcbGL_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cfa): error: undefined refe rence to '.LcbI0_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1d2d): error: undefined refe rence to '.LcbIh_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21a4): error: undefined refe rence to '.LcbSn_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21d1): error: undefined refe rence to '.LcbTc_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x234f): error: undefined refe rence to '.Lcc18_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2c76): error: undefined refe rence to '.Lccmj_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2dff): error: undefined refe rence to '.LccsV_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2e2f): error: undefined refe rence to '.Lcct6_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f38): error: undefined refe rence to '.Lccv1_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f66): error: undefined refe rence to '.Lccve_die' }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:39:53 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:39:53 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 In-Reply-To: <046.3db25c336062f0dea40eba4721995b57@haskell.org> References: <046.3db25c336062f0dea40eba4721995b57@haskell.org> Message-ID: <061.26c46aa1c931b44b3c64ff8fba760010@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Debugging | (amd64) information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by niteria: Old description: > I wanted to see how `-g1` vs `-g2` impact compile speed. Unfortunately I > get linking errors trying to build GHC with `-g`. > > Steps: > 1) Add {{{ > GhcLibHcOpts += -g1 > GhcRtsHcOpts += -g1 > }}} > to `mk/build.mk`. I used devel2 flavor. > 2) `./boot && ./configure && make -j` > 3) Observe failure > > The failure (trimmed): > {{{ > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1c94): > error: undefined refe > rence to '.LcbG2_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cc7): > error: undefined refe > rence to '.LcbGL_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cfa): > error: undefined refe > rence to '.LcbI0_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1d2d): > error: undefined refe > rence to '.LcbIh_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21a4): > error: undefined refe > rence to '.LcbSn_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21d1): > error: undefined refe > rence to '.LcbTc_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x234f): > error: undefined refe > rence to '.Lcc18_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2c76): > error: undefined refe > rence to '.Lccmj_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2dff): > error: undefined refe > rence to '.LccsV_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2e2f): > error: undefined refe > rence to '.Lcct6_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f38): > error: undefined refe > rence to '.Lccv1_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f66): > error: undefined refe > rence to '.Lccve_die' > }}} New description: I wanted to see how `-g1` vs `-g2` impact compile speed. Unfortunately I get linking errors trying to build GHC with `-g1`. Steps: 1) Add {{{ GhcLibHcOpts += -g1 GhcRtsHcOpts += -g1 }}} to `mk/build.mk`. I used devel2 flavor. 2) `./boot && ./configure && make -j` 3) Observe failure The failure (trimmed): {{{ /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1c94): error: undefined refe rence to '.LcbG2_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cc7): error: undefined refe rence to '.LcbGL_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cfa): error: undefined refe rence to '.LcbI0_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1d2d): error: undefined refe rence to '.LcbIh_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21a4): error: undefined refe rence to '.LcbSn_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21d1): error: undefined refe rence to '.LcbTc_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x234f): error: undefined refe rence to '.Lcc18_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2c76): error: undefined refe rence to '.Lccmj_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2dff): error: undefined refe rence to '.LccsV_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2e2f): error: undefined refe rence to '.Lcct6_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f38): error: undefined refe rence to '.Lccv1_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f66): error: undefined refe rence to '.Lccve_die' }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:41:25 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:41:25 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 In-Reply-To: <046.3db25c336062f0dea40eba4721995b57@haskell.org> References: <046.3db25c336062f0dea40eba4721995b57@haskell.org> Message-ID: <061.93a7f620288b3435b4c3dda95ad3af1f@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Debugging | (amd64) information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by niteria: Old description: > I wanted to see how `-g1` vs `-g2` impact compile speed. Unfortunately I > get linking errors trying to build GHC with `-g1`. > > Steps: > 1) Add {{{ > GhcLibHcOpts += -g1 > GhcRtsHcOpts += -g1 > }}} > to `mk/build.mk`. I used devel2 flavor. > 2) `./boot && ./configure && make -j` > 3) Observe failure > > The failure (trimmed): > {{{ > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1c94): > error: undefined refe > rence to '.LcbG2_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cc7): > error: undefined refe > rence to '.LcbGL_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cfa): > error: undefined refe > rence to '.LcbI0_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1d2d): > error: undefined refe > rence to '.LcbIh_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21a4): > error: undefined refe > rence to '.LcbSn_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21d1): > error: undefined refe > rence to '.LcbTc_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x234f): > error: undefined refe > rence to '.Lcc18_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2c76): > error: undefined refe > rence to '.Lccmj_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2dff): > error: undefined refe > rence to '.LccsV_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2e2f): > error: undefined refe > rence to '.Lcct6_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f38): > error: undefined refe > rence to '.Lccv1_info_die' > /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- > install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f66): > error: undefined refe > rence to '.Lccve_die' > }}} New description: I wanted to see how `-g1` vs `-g2` impact compile speed. Unfortunately I get linking errors trying to build GHC with `-g1`. Steps: 1. Add: {{{ GhcLibHcOpts += -g1 GhcRtsHcOpts += -g1 }}} to `mk/build.mk`. I used devel2 flavor. 2. `./boot && ./configure && make -j` 3. Observe failure The failure (trimmed): {{{ /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1c94): error: undefined refe rence to '.LcbG2_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cc7): error: undefined refe rence to '.LcbGL_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1cfa): error: undefined refe rence to '.LcbI0_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x1d2d): error: undefined refe rence to '.LcbIh_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21a4): error: undefined refe rence to '.LcbSn_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x21d1): error: undefined refe rence to '.LcbTc_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x234f): error: undefined refe rence to '.Lcc18_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2c76): error: undefined refe rence to '.Lccmj_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2dff): error: undefined refe rence to '.LccsV_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2e2f): error: undefined refe rence to '.Lcct6_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f38): error: undefined refe rence to '.Lccv1_info_die' /data/users/bnitka/ghc-HEAD-dwarf-lint-fixes-g/libraries/base/dist- install/build/libHSbase-4.11.0.0.a(Internals.o)(.debug_info+0x2f66): error: undefined refe rence to '.Lccve_die' }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:42:25 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:42:25 -0000 Subject: [GHC] #14895: STG CSE makes dead binders undead Message-ID: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> #14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Debugging Unknown/Multiple | information is incorrect Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following example: {{{#!hs go :: (a -> b) -> Either String a -> Either String b go f (Right a) = Right (f a) go _ (Left e) = Left e }}} GHC with `-O2` converts it into the following STG: {{{#!hs TestUndead.go :: forall a b. (a -> b) -> Data.Either.Either GHC.Base.String a -> Data.Either.Either GHC.Base.String b [GblId, Arity=2, Caf=NoCafRefs, Str=, Unf=OtherCon []] = \r [f_s17n ds_s17o] case ds_s17o of { Data.Either.Left e_s17q [Occ=Once] -> wild_s17p; Data.Either.Right a1_s17r [Occ=Once] -> let { sat_s17s [Occ=Once] :: b_aVN [LclId] = \u [] f_s17n a1_s17r; } in Data.Either.Right [sat_s17s]; }; }}} Notice that the dead binder `wild_s17p` is now alive (in the first alternative) but it isn't shown in `case ds_s17o of {` because the pretty- printer still assumes it is dead. I think that in `stgCseExpr .. (StgCase ...)` (simplStg/StgCse.hs) we should check if the new binder is alive in the new alternatives, just like we do in `coreToStgExpr (Case ...)` (stgSyn/CoreToStg.hs), and use `setIdOccInfo (ManyOccs NoTailCallInfo)` on the new binder if necessary. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 21:46:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 21:46:26 -0000 Subject: [GHC] #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. In-Reply-To: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> References: <051.c44ceae1fcaef369d2f65097af0253ee@haskell.org> Message-ID: <066.bf7b528cc300d9ffa2338beec8034603@haskell.org> #14892: Field imposters with DuplicateRecordFields and NamedFieldPuns. -------------------------------------+------------------------------------- Reporter: philderbeast | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 Resolution: | Keywords: ORF Operating System: MacOS X | Architecture: x86_64 Type of failure: GHC accepts | (amd64) invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #13644 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): I think you want `DisambiguateRecordFields`. Without it, the 8.4 behaviour is correct, isn't it? Indeed `G.X` does not have a field `x` in scope (although it does have `G.x`). The error message could be better, perhaps suggesting `DisambiguateRecordFields`. Note that `DuplicateRecordFields` implies `DisambiguateRecordFields`, which is why enabling the former fixes the problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 22:03:15 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 22:03:15 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 In-Reply-To: <046.3db25c336062f0dea40eba4721995b57@haskell.org> References: <046.3db25c336062f0dea40eba4721995b57@haskell.org> Message-ID: <061.e8ff8b2d6fa3345877d6030c1db36425@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Debugging | (amd64) information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by niteria): Actually, building GHC is overkill. This reproduces on many tests when `-g1` is used. For example: {{{ =====> simplCore.oneShot(optasm) 1 of 1 [0, 0, 0] cd "./prog003/simplCore.oneShot.run" && "/data/users/bnitka/ghc-HEAD- dwarf-lint-fixes-validate/inplace/test spaces/ghc-stage2" --make -o simplCore.oneShot OneShot2 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -g1 -dno-debug- output -O -fasm -v0 Compile failed (exit code 1) errors were: OneShot2.o(.debug_info+0x1bb): error: undefined reference to '.Lc5rU_die' OneShot2.o(.debug_info+0x1e3): error: undefined reference to '.Lc5rU_die' OneShot2.o(.debug_info+0x291): error: undefined reference to '.Lc5w8_die' OneShot2.o(.debug_info+0x2b9): error: undefined reference to '.Lc5wf_die' collect2: error: ld returned 1 exit status `gcc' failed in phase `Linker'. (Exit code: 1) *** unexpected failure for simplCore.oneShot(optasm) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 22:23:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 22:23:27 -0000 Subject: [GHC] #14893: GHC hangs while producing error message for incorrect TypeFamilies application In-Reply-To: <047.c7bdc37997d8c9a8bfb76bc219cbd46f@haskell.org> References: <047.c7bdc37997d8c9a8bfb76bc219cbd46f@haskell.org> Message-ID: <062.aa6d298cf2c479a108508780b0e6b5b4@haskell.org> #14893: GHC hangs while producing error message for incorrect TypeFamilies application -------------------------------------+------------------------------------- Reporter: coopercm | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12386 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #12386 Comment: Thanks for the bug report. I believe this is in fact a duplicate of #12386, as this gives a proper error on GHC 8.4.1: {{{ $ /opt/ghc/8.4.1/bin/ghci Bug.hs GHCi, version 8.4.0.20180224: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:11:27: error: • Expecting two more arguments to ‘Meta’ Expected a type, but ‘Meta’ has kind ‘* -> (* -> *) -> *’ • In the second argument of ‘Token’, namely ‘Meta’ In the type ‘Token f Meta’ In the default type instance declaration for ‘Body’ | 11 | type Body x f = Token f Meta | ^^^^ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 22:44:50 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 22:44:50 -0000 Subject: [GHC] #14880: GHC panic: updateRole In-Reply-To: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> References: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> Message-ID: <065.b52fea0356a3fe7b7a532c2b60a36282@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: Roles => TypeInType * owner: (none) => goldfire Comment: The trouble is that the type of `MkBar` should really be {{{ MkBar :: forall (x:Type) (arg:Type) {a:arg}. Proxy @(Proxy @arg a -> Type) (Foo arg @a) -> Bar x }}} where I have put in all the kind applications. The trouble is that `MkBar` has an ''implicit'' forall's variable `a`, whose kind mentions an ''explicit'' type variable `arg`. So the implicit argument must appear later in the telescope. But `tcConDecl` (the `ConDeclGADT` case) doesn't allow that: {{{ tkv_bndrs = mkTyVarBinders Inferred tkvs' user_tv_bndrs = mkTyVarBinders Specified user_tvs' all_user_bndrs = tkv_bndrs ++ user_tv_bndrs }}} Notice that the inferred ones always come first. But here they can't! Solution: do a topo-sort of the tyvars that is allowed to interleave the `Inferred` and `Specified` ones. But is that the only place? If we try something like this with a function type signature thus {{{ f :: forall (v :: *) (a :: Proxy (k :: v)). Proxy a f = f }}} we get the error message {{{ T14880.hs:24:6: error: * The kind of variable `k', namely `v', depends on variable `v' from an inner scope Perhaps bind `k' sometime after binding `v' NB: Implicitly-bound variables always come before other ones. * In the type signature: f :: forall (v :: *) (a :: Proxy (k :: v)). Proxy a }}} But is there anything really wrong with this signature? It we topo-sorted the type variables we'd be fine. There are other places (exp in `TcTyClsDecls`) where we seem to put all the inferred variables around the outside. I don't know how to be sure in which, if any, of these case we have a bug. Maybe we need more topo-sorts? Amnother oddd thing about this ticket is the data decl for `Foo`: {{{ data Foo (v :: Type) :: forall (a :: v). Proxy a -> Type }}} That is a strange kind signature. I don't expect to see foralls to the right of the `::` in such a decl. So, more questions * Is it valuable to permit TyCons whose kinds are not in prenex form (i.e. all foralls at the front)? If so, we should document it. Meanwhile I'm not going to fix this because it may all come out in the wash of Richards's upcoming kind-inference patch. It's nothing to do with roles! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 22:45:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 22:45:05 -0000 Subject: [GHC] #14893: GHC hangs while producing error message for incorrect TypeFamilies application In-Reply-To: <047.c7bdc37997d8c9a8bfb76bc219cbd46f@haskell.org> References: <047.c7bdc37997d8c9a8bfb76bc219cbd46f@haskell.org> Message-ID: <062.4431adf68d4b7be5219ede408751c7c0@haskell.org> #14893: GHC hangs while producing error message for incorrect TypeFamilies application -------------------------------------+------------------------------------- Reporter: coopercm | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #12386 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by coopercm): Thanks! Looking forward to the release of 8.4.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 22:51:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 22:51:12 -0000 Subject: [GHC] #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck In-Reply-To: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> References: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> Message-ID: <065.f2d7eae36576a9fda16e5ec5cb7cfe02@haskell.org> #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: TypeFamilies, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: (none) => goldfire Comment: Interesting bug, thanks. But not much point in looking at this until Richard's "solveEqualities" patch lands. Richard? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 5 22:58:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 05 Mar 2018 22:58:57 -0000 Subject: [GHC] #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck In-Reply-To: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> References: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> Message-ID: <065.a5622fdf6a8c83535ec36e3a007f7c2b@haskell.org> #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: TypeFamilies, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 00:44:59 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 00:44:59 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 In-Reply-To: <046.3db25c336062f0dea40eba4721995b57@haskell.org> References: <046.3db25c336062f0dea40eba4721995b57@haskell.org> Message-ID: <061.4dc8c5ca5afe70f77b9a91aa57db7405@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Debugging | (amd64) information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Oh dear; we should add a test to ensure that at least "hello world" is compiled with `-g` when the testsuite is run. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 01:10:10 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 01:10:10 -0000 Subject: [GHC] #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck In-Reply-To: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> References: <050.26e9faa4d4a29b625c8bfcdef0d31364@haskell.org> Message-ID: <065.f2030b7a500b390d3f87ad9840eb0490@haskell.org> #14887: Explicitly quantifying a kind variable causes a type family to fail to typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: TypeFamilies, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): That patch is held up on the #12919 patch, which is under review at Phab:D4451. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 01:20:31 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 01:20:31 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.3173755517069c774579009b2aab1411@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): @hvr You're right, `memcmp` has already been implemented as `compareByteArrays#`. It just hasn't been released yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 01:21:49 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 01:21:49 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.7c5ac92306cac64d1ab9e24920aade06@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 andrewthad): I'm giving this a shot right now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 01:38:52 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 01:38:52 -0000 Subject: [GHC] #14880: GHC panic: updateRole In-Reply-To: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> References: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> Message-ID: <065.5373155c506948a849784bdd2ff69e1d@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The `updateRole` panic triggers on various invalid-tycon problems. I'm not surprised that roles aren't involved. Yes, a `forall` to the right of the `::` in a data declaration makes fine sense. For example, here is one way to define heterogeneous equality: {{{#!hs data (:~~:) :: forall k1. k1 -> forall k2. k2 -> Type where HRefl :: a :~~: a }}} This definition is actually a touch more general than one where `k1` and `k2` are quantified prenex, as the "Practical Type Inference" paper explains. I don't see a need to document this specially. As for the toposorting suggestions: I've considered it a design principle that implicit quantification comes before all explicit quantification. Of course, we can't panic when something goes wrong here, but I think this design is a good one, just to have some rules that users can rely on. My existing patch still panics on this case, but I agree that no one should spend time on this until that patch lands. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 06:24:48 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 06:24:48 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.38f650ff37c9c0f9f0ca3c124b36c27c@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 tysonzero): It seems like the same issue is (probably?) occurring with persistent- postgresql on windows (https://github.com/yesodweb/persistent/issues/794#issuecomment-370539509), and `-fexternal-interpreter` does not seem to help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 08:29:43 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 08:29:43 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.a07b0b629433b755ad9d3bae5b42550e@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4472 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alexbiehl): * differential: => Phab:D4472 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 08:40:34 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 08:40:34 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.113e89a04b63626a38e77d4d088cd3df@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4472 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I'm not all that convinced that we need `memchr#` to be a primitive. The reason we brought in `memcmp` and `memcpy` were for performance in the `unordered-containers` package, as I recall, and they were a pretty important performance win in that case. Do we have any similar motivation for `memchr`? Where does it stop? These primitives are pretty complicated to implement in the compiler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 10:04:37 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 10:04:37 -0000 Subject: [GHC] #14895: STG CSE makes dead binders undead In-Reply-To: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> References: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> Message-ID: <060.b52571161abc8c8636913e552969ad64@haskell.org> #14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Good catch. I had observed this when debugging some other tickets, but couldn't figure why it was happening. I ended up enabling some debug flags that make printer print all variables. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 12:17:38 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 12:17:38 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.3229374c7a24692f2d9e44b7e082f5ce@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4472 Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): It's good to hear what the actual motivation was for bringing `memcpy` in. I cannot provide a similarly compelling performance-oriented reason for `memchr`. I think that in https://ghc.haskell.org/trac/ghc/ticket/14882#comment:8, hvr makes the best argument I could offer: that all of the other C99 memory primitives are already wrapped by `ghc-prim` and this one would complete the set. I disagree that `memchr` is difficult to implement a wrapper for in the compiler. In the differential I linked, the actual implementation is about 20 lines code. Some of the others are certainly more complicated though. The fact `memcpy` takes two arrays means the GHC needs several variants of it dealing with various combinations of `ByteArray#`, `MutableByteArray#`, and `Addr#`, (GHC has 5 variants of `copyByteArray#`) but `memchr` only takes a single array, so even the most complete wrapping of it possible would only need three implementations. I've only done one so far since it was the only one I needed. > Where does it stop? I think that it would stop where the C99 memory primitives stop. So, nothing like `memset_s`, `rawmemchr`, etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 13:31:26 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 13:31:26 -0000 Subject: [GHC] #14895: STG CSE makes dead binders undead In-Reply-To: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> References: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> Message-ID: <060.f4f11cef02aa371474facdf10db05d9e@haskell.org> #14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I am not sure if the dead-ness info is use for anything except pretty- printing. Perhaps not.... but worth a check. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 13:49:23 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 13:49:23 -0000 Subject: [GHC] #14896: QuantifiedConstraints: GHC does doesn't discharge constraints if they are quantified Message-ID: <051.1cc6b03dde1d531c03c6cbc0cd468d33@haskell.org> #14896: QuantifiedConstraints: GHC does doesn't discharge constraints if they are quantified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This came up on a [https://www.reddit.com/r/haskell/comments/8257mz/how_quantifiedconstraints_can_let_us_put_join/dv8hfxb/ reddit thread], {{{#!hs {-# Language QuantifiedConstraints #-} class (forall aa. Functor (bi aa)) => Bifunctor bi where first :: (a -> a') -> (bi a b -> bi a' b) bimap :: Bifunctor bi => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') bimap f g = first f . fmap g }}} This is the type we want for `bimap` even if we mix & match `Bifunctor` and `Functor`. We already know that we can `fmap @(bi xx)` for any `xx` but this is not the inferred type. Instead GHC infers a type (tidied up) with a superfluous `Functor` constraint {{{#!hs bimap :: (Bifunctor bi, Functor (bi a)) => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') }}} Indeed post-composing with a superfluous `fmap @(bi a')` incurs yet another `Functor` constraint {{{#!hs bimap :: (Bifunctor bi, Functor (bi a), Functor (bi a')) => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') bimap f g = fmap id . first f . fmap g }}} A terminology question, I'm not sure how to phrase what GHC isn't doing to the `Functor` constraints: ‘discharge’? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 13:51:01 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 13:51:01 -0000 Subject: [GHC] #14896: QuantifiedConstraints: GHC does doesn't discharge constraints if they are quantified In-Reply-To: <051.1cc6b03dde1d531c03c6cbc0cd468d33@haskell.org> References: <051.1cc6b03dde1d531c03c6cbc0cd468d33@haskell.org> Message-ID: <066.20fd7ec6edb9854e20cf60d337bdd703@haskell.org> #14896: QuantifiedConstraints: GHC does doesn't discharge constraints if they are quantified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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: Old description: > This came up on a > [https://www.reddit.com/r/haskell/comments/8257mz/how_quantifiedconstraints_can_let_us_put_join/dv8hfxb/ > reddit thread], > > {{{#!hs > {-# Language QuantifiedConstraints #-} > > class (forall aa. Functor (bi aa)) => Bifunctor bi where > first :: (a -> a') -> (bi a b -> bi a' b) > > bimap :: Bifunctor bi => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') > bimap f g = first f . fmap g > }}} > > This is the type we want for `bimap` even if we mix & match `Bifunctor` > and `Functor`. We already know that we can `fmap @(bi xx)` for any `xx` > but this is not the inferred type. > > Instead GHC infers a type (tidied up) with a superfluous `Functor` > constraint > > {{{#!hs > bimap :: (Bifunctor bi, Functor (bi a)) => (a -> a') -> (b -> b') -> (bi > a b -> bi a' b') > }}} > > Indeed post-composing with a superfluous `fmap @(bi a')` incurs yet > another `Functor` constraint > > {{{#!hs > bimap :: (Bifunctor bi, Functor (bi a), Functor (bi a')) => (a -> a') -> > (b -> b') -> (bi a b -> bi a' b') > bimap f g = fmap id . first f . fmap g > }}} > > A terminology question, I'm not sure how to phrase what GHC isn't doing > to the `Functor` constraints: ‘discharge’? New description: This came up on a [https://www.reddit.com/r/haskell/comments/8257mz/how_quantifiedconstraints_can_let_us_put_join/dv8hfxb/ reddit thread], {{{#!hs {-# Language QuantifiedConstraints #-} class (forall aa. Functor (bi aa)) => Bifunctor bi where first :: (a -> a') -> (bi a b -> bi a' b) bimap :: Bifunctor bi => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') bimap f g = first f . fmap g }}} This is the type we want for `bimap` even if we mix & match `Bifunctor` and `Functor`. We already know that we can `fmap @(bi xx)` for any `xx` but this is not the inferred type. Instead GHC infers a type (tidied up) with a superfluous `Functor` constraint {{{#!hs bimap :: (Bifunctor bi, Functor (bi a)) => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') }}} Indeed post-composing with a superfluous `fmap @(bi a') id` incurs yet another `Functor` constraint {{{#!hs bimap :: (Bifunctor bi, Functor (bi a), Functor (bi a')) => (a -> a') -> (b -> b') -> (bi a b -> bi a' b') bimap f g = fmap id . first f . fmap g }}} A terminology question, I'm not sure how to phrase what GHC isn't doing to the `Functor` constraints: ‘discharge’? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 13:57:01 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 13:57:01 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.0c8309335a1a7ee495c146ffae872528@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4470 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"5bc195a2caddc5c29cf24e9c731dd8d5050f2c66/ghc" 5bc195a2/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5bc195a2caddc5c29cf24e9c731dd8d5050f2c66" Allow top level ticked string literals This reverts f5b275a239d2554c4da0b7621211642bf3b10650 and changes the places that looked for `Lit (MachStr _))` to use `exprIsMbTickedLitString_maybe` to unwrap ticks as necessary. Also updated relevant comments. Test Plan: I added 3 new tests that previously reproduced. GHC HEAD now builds with -g Reviewers: simonpj, simonmar, bgamari, hvr, goldfire Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14779 Differential Revision: https://phabricator.haskell.org/D4470 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 14:01:35 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 14:01:35 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.df451f4c2071adc65bc221eee38ce3b7@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4470 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 14:47:06 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 14:47:06 -0000 Subject: [GHC] #14897: QuantifiedConstraints: Can't print type of quantified constraint Message-ID: <051.b509630009c40df070f071bb7f5dfd8f@haskell.org> #14897: QuantifiedConstraints: Can't print type of quantified constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language QuantifiedConstraints, FlexibleInstances, UndecidableInstances, MonoLocalBinds #-} class (forall xx. Functor (f xx)) => Functor' f instance (forall xx. Functor (f xx)) => Functor' f fmap' :: Functor' f => (b -> b') -> (f a b -> f a b') fmap' = fmap }}} load in ghci and check the type of `fmap'` {{{ $ ... -ignore-dot-ghci Bug2.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Bug2.hs, interpreted ) Ok, one module loaded. *Main> :t fmap' :1:1: error: No instance for (Functor (f xx)) arising from a use of ‘fmap'’ *Main> }}} Simpler example {{{ GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help Prelude> :set -XRankNTypes -XQuantifiedConstraints Prelude> let a :: (forall xx. Monoid (f xx)) => f a; a = mempty Prelude> :t a :1:1: error: No instance for (Monoid (f xx)) arising from a use of ‘a’ Prelude> }}} I expected the same output as `:t +v` {{{ Prelude> :t +v a a :: (forall xx. Monoid (f xx)) => f a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 14:51:01 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 14:51:01 -0000 Subject: [GHC] #14897: QuantifiedConstraints: Can't print type of quantified constraint In-Reply-To: <051.b509630009c40df070f071bb7f5dfd8f@haskell.org> References: <051.b509630009c40df070f071bb7f5dfd8f@haskell.org> Message-ID: <066.53e2c8d2d9b069be715047d1526515e9@haskell.org> #14897: QuantifiedConstraints: Can't print type of quantified constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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 know printing isn't the problem, “over-eagerly resolves quantified constraint...” something -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 15:13:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 15:13:33 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.36d3077a779c9a9b3513063758f300e6@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4472 Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): Also, I just realized that I never linked to the differential on phab. Here it is: https://phabricator.haskell.org/D4472 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 16:29:20 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 16:29:20 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.a9606b10fd21d68496db64369fd3698f@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): tysonzero, I am unable to reproduce the segfault you're experiencing. Is this the program you're using from https://github.com/yesodweb/persistent/issues/794#issuecomment-370539509 ? (I had to guess some details you left out.) {{{#!hs {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PackageImports #-} {-# LANGUAGE TypeApplications #-} module Main where import "monad-logger" Control.Monad.Logger import "transformers" Control.Monad.Trans.Reader import "persistent-postgresql" Database.Persist.Postgresql main :: IO () main = runNoLoggingT . withPostgresqlConn "" . runReaderT @SqlBackend $ pure () }}} {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.2.2 $ ghc -- Bug.hs -O2 -fforce-recomp [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Linking Bug.exe ... $ ./Bug.exe Bug.exe: SqlError {sqlState = "", sqlExecStatus = FatalError, sqlErrorMsg = "missing \"=\" after \" GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 17:31:21 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 17:31:21 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.8134b0c05cf04ca11e96f3b5e052b7bd@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by aosivitz): Oh, I understand. By default GHC will statically link exes, but you can force it to be dynamic and in that case it will fail. Well, I personally am less concerned about that case because I'm not trying to dynamically link any exes, but I see why you would want both to work equally well. It seems to me like the TH problem (building an extra dynamic lib unnecessarily which happens to cause bad behavior on Mac) is separate from the dynamic exe problem (how can we dynamically link a bunch of libs into an exe on Mac). Is there some implementation reason why those two problems are more tied together than I assume? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 17:59:00 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 17:59:00 -0000 Subject: [GHC] #14105: ApplicativeDo causes GHC panic on irrefutable list pattern match In-Reply-To: <050.11e02ba42db9ddcb8fd7d6aa7559f6ed@haskell.org> References: <050.11e02ba42db9ddcb8fd7d6aa7559f6ed@haskell.org> Message-ID: <065.b163deda2c34c28880165381dbd9e45e@haskell.org> #14105: ApplicativeDo causes GHC panic on irrefutable list pattern match -------------------------------------+------------------------------------- Reporter: BoteboTsebo | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: ApplicativeDo Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: 8.2.3 => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 17:59:55 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 17:59:55 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.da714089b470303715825d26050e07ea@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.3 (Debugging) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4470 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: 8.4.2 => 8.4.1 Comment: Merged as 2753d8903129ffec94253f99c3904248274053cd. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 18:33:44 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 18:33:44 -0000 Subject: [GHC] #14785: accumArray is too lazy In-Reply-To: <045.3d70ccf693988ad2d3ddc47afd2f8ad1@haskell.org> References: <045.3d70ccf693988ad2d3ddc47afd2f8ad1@haskell.org> Message-ID: <060.745f47ae94db3d95cee98620de26d62a@haskell.org> #14785: accumArray is too lazy -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.2.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:D4403 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"08345bd0e8d237ec3929aaee7613c4f76e07e131/ghc" 08345bd/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="08345bd0e8d237ec3929aaee7613c4f76e07e131" Make accumArray and accum stricter `accumArray` was lazier than documented. `accum` did not have documented strictness. The extra laziness allowed thunks to build up in the array. Force the results of applying the accumulating function to resolve. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: alpmestan, rwbarton, thomie, carter GHC Trac Issues: #14785 Differential Revision: https://phabricator.haskell.org/D4403 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 18:34:15 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 18:34:15 -0000 Subject: [GHC] #14705: ghc-iserv sometimes segfaults in profiled way In-Reply-To: <046.be67f06c8a68b32fb302ce316ee26108@haskell.org> References: <046.be67f06c8a68b32fb302ce316ee26108@haskell.org> Message-ID: <061.f5767ecb4dba8dc2c2bbef6dcb4b0539@haskell.org> #14705: ghc-iserv sometimes segfaults in profiled way -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: new Priority: highest | Milestone: 8.4.1 Component: Profiling | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4437 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"488d63d6899d223ef87c26c218f0cf81ac670a90/ghc" 488d63d6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="488d63d6899d223ef87c26c218f0cf81ac670a90" Fix interpreter with profiling This was broken by D3746 and/or D3809, but unfortunately we didn't notice because CI at the time wasn't building the profiling way. Test Plan: ``` cd testsuite/test/profiling/should_run make WAY=ghci-ext-prof ``` Reviewers: bgamari, michalt, hvr, erikd Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14705 Differential Revision: https://phabricator.haskell.org/D4437 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 20:00:07 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 20:00:07 -0000 Subject: [GHC] #14878: Can't witness transitivity ((.)) of isomorphism of Constraints In-Reply-To: <051.a45c628270a13635f0d506c37084dcac@haskell.org> References: <051.a45c628270a13635f0d506c37084dcac@haskell.org> Message-ID: <066.6bdaa27872e9eb66ce80367226919fe4@haskell.org> #14878: Can't witness transitivity ((.)) of isomorphism of Constraints -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): To be clear this is not a bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 20:10:22 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 20:10:22 -0000 Subject: [GHC] #14869: Documentation for isLiftedTypeKind is incorrect In-Reply-To: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> References: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> Message-ID: <065.568aa51d9e6efac7429bd4329d57bc1f@haskell.org> #14869: Documentation for isLiftedTypeKind is incorrect -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4474 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4474 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 20:45:24 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 20:45:24 -0000 Subject: [GHC] #14508: Bring up Appveyor for Windows CI In-Reply-To: <046.b1e7fd0356de10b29814d8db318f756c@haskell.org> References: <046.b1e7fd0356de10b29814d8db318f756c@haskell.org> Message-ID: <061.9f062c3a294b7fc56b1c778af57bc67d@haskell.org> #14508: Bring up Appveyor for Windows CI -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: task | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.1 Integration | 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 facundo.dominguez): * owner: bgamari => mrkkrp -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 20:48:11 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 20:48:11 -0000 Subject: [GHC] #14508: Bring up Appveyor for Windows CI In-Reply-To: <046.b1e7fd0356de10b29814d8db318f756c@haskell.org> References: <046.b1e7fd0356de10b29814d8db318f756c@haskell.org> Message-ID: <061.add3a39354f6895ad9d213926844fb56@haskell.org> #14508: Bring up Appveyor for Windows CI -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: task | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.1 Integration | 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 facundo.dominguez): The plan is now to use GCE and a premium account from appveyor. https://mail.haskell.org/pipermail/ghc-devops-group/2018-March/000168.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 20:57:09 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 20:57:09 -0000 Subject: [GHC] #12959: GHC doesn't warn about missing implementations for class methods beginning with an underscore In-Reply-To: <050.f1c049718f4b94fba939144b405d48bc@haskell.org> References: <050.f1c049718f4b94fba939144b405d48bc@haskell.org> Message-ID: <065.49c46a07c5843f1b322d957c7bed65e2@haskell.org> #12959: GHC doesn't warn about missing implementations for class methods beginning with an underscore -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) 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: Other | Test Case: | warnings/minimal/WarnMinimal.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2849, Wiki Page: | Phab:D4476 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: Phab:D2849 => Phab:D2849, Phab:D4476 Comment: It looks like we forgot to update the users' guide about this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 6 22:12:30 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 06 Mar 2018 22:12:30 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.ff60c8aa0e5ae3587be9cdc2fb164407@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 ulysses4ever): Ok, after some more thinking it seems to me that importing just `TcRnTypes` is not big deal. Now I'm wondering if it is legit to deal with `initIfaceTcRn` by just repalacing it with `TcRnMonad.initIfaceLoad`. If so, do we need to move it to some less `Tc`-heavy place? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 02:07:27 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 02:07:27 -0000 Subject: [GHC] #14444: Linker limit on OS X Sierra breaks builds for big projects In-Reply-To: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> References: <049.ef1cbd3eecd105a31deac573ded19c35@haskell.org> Message-ID: <064.260bec6d5f950fa9e41a0cf76cb2ff87@haskell.org> #14444: Linker limit on OS X Sierra breaks builds for big projects -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: angerman Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 (Linking) | Resolution: | Keywords: Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by angerman): > Here's a github gist for a shell script that generates a giant stack project (with 150 generated dependencies) that triggers the panic: ​https://gist.github.com/asivitz/f4b983b2374a6155ac4faaf9b61aca59 I'm not sure the best way to do the same thing without using stack, but if you have an idea I can do that. This will generate 150 direct dependencies. As such any dylib that will reference those, will have to reference 150 libraries, in the load commands section. I don't think we can do much about this case. If this was 150 transitive dependencies spread over a few levels. we might. For 150 direct, we could potentially only work around this by using the splitting approach from nix. For 150 transitive dependencies, I still believe recursive linking could solve this. (See https://github.com/angerman/dylib-linking) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 05:32:01 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 05:32:01 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys Message-ID: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I get a GHC panic while compiling a rather large module that contains a fairly simple function: {{{#!hs import Control.Monad.Reader usingReader :: (Monad m) => r -> (a -> ReaderT r m b) (a -> m b) usingReader r f = flip runReaderT r . f }}} Unfortunately, that function alone in a module does not trigger the panic. The error message is: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.2.1 for x86_64-unknown-linux): repSplitAppTys a_ahFs[sk:1] ReaderT r_ahFr[sk:1] m_ahFq[sk:1] b_ahFt[sk:1] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:808:9 in ghc:Type }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 05:36:52 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 05:36:52 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys In-Reply-To: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> References: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> Message-ID: <063.d3128dd1e025925a0d5db5b8a326de66@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryanreich): Replying to [ticket:14898 ryanreich]: > {{{#!hs > import Control.Monad.Reader > usingReader :: > (Monad m) => > r -> > (a -> ReaderT r m b) > (a -> m b) > usingReader r f = flip runReaderT r . f > }}} > > Unfortunately, that function alone in a module does not trigger the panic. Note the error in the above type signature: there is a missing arrow on the line with ReaderT. If I fix that error, the panic goes away. However, a standalone module still does not trigger the panic; the type error is correctly reported. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 05:41:49 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 05:41:49 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys In-Reply-To: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> References: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> Message-ID: <063.837a98b540e25d29da8e4d20b33818ca@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Could this be a dup of #13819, #14568, #14371, etc? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 07:30:22 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 07:30:22 -0000 Subject: [GHC] #14785: accumArray is too lazy In-Reply-To: <045.3d70ccf693988ad2d3ddc47afd2f8ad1@haskell.org> References: <045.3d70ccf693988ad2d3ddc47afd2f8ad1@haskell.org> Message-ID: <060.8a7df9c9e94151fe32b31258b3c63843@haskell.org> #14785: accumArray is too lazy -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.2.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:D4403 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 07:31:19 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 07:31:19 -0000 Subject: [GHC] #14705: ghc-iserv sometimes segfaults in profiled way In-Reply-To: <046.be67f06c8a68b32fb302ce316ee26108@haskell.org> References: <046.be67f06c8a68b32fb302ce316ee26108@haskell.org> Message-ID: <061.c4205ea1de45b5e0708d8bf7b2f9e89d@haskell.org> #14705: ghc-iserv sometimes segfaults in profiled way -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Profiling | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4437 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Merged for 8.4.1 as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 08:01:08 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 08:01:08 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.2f85d46893f3804d563d8baf169e2351@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * owner: (none) => osa1 * related: => #11547 Comment: I think regardless of the performance problems, #11547 (Phab:D2447) should just be reverted. I think there were some misunderstanding in the ticket, and some questions are left unanswered in Phab:D2447, and I think there's really no utility of this patch. While I agree that having ~1000 shadowed names take ~40s to load is a problem, I also think that keeping shadowed variables is unnecessary. Here are some facts: - GHCi prompt works like `do` block, as noted by Ben in Phab:D2447, in [https://stackoverflow.com/questions/14052093/ghci-let-what-does-it-do this SO thread], in the [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html #using-do-notation-at-the-prompt user manual] etc. so it's only expected to have the same shadowing behavior in the GHCi prompt. - Simon says in comment:1 in #11547 that we should be consistent in shadowing. I think we were already consistent previously. Values are shadowed, types are also shadowed, but shadowed types are still accessible in the promopt. His example: {{{ > data A = A > let f A = Int > data A = XX > :type f }}} already worked on GHC 8.0.1: {{{ $ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/omer/rcbackup/.ghci λ:1> data A = A λ:2> let f A = 123 λ:3> data A = XX λ:4> :t f f :: Num t => Ghci1.A -> t λ:5> :info Ghci1.A data Ghci1.A = A -- Defined at :1:1 }}} The question > But what is the user-facing specification? We need user-manual stuff explaining what all this Ghci4.foo stuff means. How would you know whether to say :t Ghci2.foo or :t Ghci3.foo? Can you list all the foo functions? Etc. is left unanswered. Ben also asks about the specification in Phab:D2447, and that also goes unanswered, but somehow the patch gets merged later on. We should at least have a motivating example, otherwise #11547 can also be fixed with a better error message and that'd cost us nothing in terms of performance and implementation simplicity and gives us the same benefits. After this ideas in comment:10 can still be implemented as an improvement (I'm still digesting that comment). Simon, in this sentence: > I can't work out why we keep the shadowed x's in the ic_rn_gbl_env. If we simply deleted them, all would be well. After all, we do not expect the user to be able to refer to an old x with a qualified name Ghci1.x. Why do you think we don't expect user to be able to refer shadowed x with qualified name? That was the motivation for #11547 and Phab:D2447. Secondly, the example in comment:10 worked fine with GHC 8.0.1: {{{ $ ghci M.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/omer/rcbackup/.ghci [1 of 1] Compiling M ( M.hs, interpreted ) Ok, modules loaded: M. λ:1> import M λ:2> M.x 0 λ:3> x 0 λ:4> let x = 1 λ:5> x 1 λ:6> M.x 0 }}} so there were really no problems that Phab:D2447 solved. I'll again claim that there's no utility of that patch and it should be reverted. I'll add a perf test for this ticket, and then try to digest comment:10. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 08:47:42 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 08:47:42 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys In-Reply-To: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> References: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> Message-ID: <063.5ee46221956ffa79d1cb35ee4f02bca6@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): In other words, can you test your program on GHC 8.2.2? The panic should be fixed on that version. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 09:01:03 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 09:01:03 -0000 Subject: [GHC] #7206: Implement cheap build In-Reply-To: <046.231132dc13e5eec24b09b65a3836eff3@haskell.org> References: <046.231132dc13e5eec24b09b65a3836eff3@haskell.org> Message-ID: <061.b7c1bd2f92d3f4110761009ca30b9421@haskell.org> #7206: Implement cheap build -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.4.2 Resolution: | Keywords: FloatOut Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8763, #13422 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): > Some examples/tickets (which specifically?) really do improve. I don't know which examples/tickets improve. Perhaps @dfeuer knows? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 09:14:34 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 09:14:34 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.f184054aed1e787b51abf3ce3e86de23@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ömer Sinan Ağacan ): In [changeset:"40c4313a8729cbd0873c16ae69434919343b551f/ghc" 40c4313/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="40c4313a8729cbd0873c16ae69434919343b551f" Add perf test for #14052 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 10:19:34 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 10:19:34 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.464f646844881384f798ad2fb2af394b@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Here's an even simpler reproducer: just repeat this line a few thousand times in a .script file: {{{ let x = 1 :: Int }}} Then run {{{ $ time (echo ":quit" | ghci -ghci-script Example.script Foo.hs >/dev/null 2>&1) }}} Results: {{{ GHC 8.0.2 2000 repetitions: 1,04s GHC 8.0.2 4000 repetitions: 2,06s GHC 8.0.2 8000 repetitions: 4,02s GHC 8.2.2 2000 repetitions: 2,17s GHC 8.2.2 4000 repetitions: 6,31s GHC 8.2.2 8000 repetitions: 21,39s }}} Demonstrates that adding a new shadowing binding is a constant time operation in GHC 8.0.2, but it's not constant time in GHC 8.2.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 11:11:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 11:11:10 -0000 Subject: [GHC] #14742: Unboxed sums can treat Word#s as Int#s In-Reply-To: <043.f2ad58847922732aad4c3d717b7bb370@haskell.org> References: <043.f2ad58847922732aad4c3d717b7bb370@haskell.org> Message-ID: <058.4ac696259359eca3a66811d1f8b48b86@haskell.org> #14742: Unboxed sums can treat Word#s as Int#s -------------------------------------+------------------------------------- Reporter: duog | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: UnboxedSums Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): Somewhat related ticket: https://ghc.haskell.org/trac/ghc/ticket/14562 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 11:42:08 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 11:42:08 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.3ca47dd58b6a3c2c94a722057b8c3739@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I think regardless of the performance problems, #11547 (​Phab:D2447) should just be reverted. Reviewing this, I agree with you. I see that in my original review of Phab:D2447 I wrote "I don't think I fully understand all the consequences, but I don't want to stand in the way". This ticket shows some bad consequences. And I don't think anyone is actively arguing for access to previously in-scope versions of `x`. It'd be polite to tell the original author of the patch ([https://phabricator.haskell.org/p/mniip/ mniip] I believe), in case he has reasons for wanting (some revised version of) his patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 11:43:45 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 11:43:45 -0000 Subject: [GHC] #12506: Compile time regression in GHC 8. In-Reply-To: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> References: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> Message-ID: <059.457149bb61dbbfc99099b9cffd1ca0bd@haskell.org> #12506: Compile time regression in GHC 8. -------------------------------------+------------------------------------- Reporter: deech | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): The problem persists with D4394 applied, so the idea that that particular nonlinearity in the coercion handling has anything to do with it doesn't hold. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 11:49:22 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 11:49:22 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.1d5326a960e8b8464dfd49fa90cf83fa@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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): > importDecl has IfM in its type. And IfM is defined in TcRnTypes, so leaving it doesn't bring us decoupling from the typechecker. Should we also replace importDecl? No, leave all that. The point is as follows (please document this in your patch): * `TcEnv.lookupGlobal` may look up an `Id` that one one has previously looked up. * If so, we are going to read its interface file, and add its bindings to the `ExternalPackageTable`, which is a persistent in-memory cache of information about other modules. * Loading that interface file does quite a bit of work, but we don't consider that as "part of the typechecker"; it's essentially just de- serialising interface-file data on disk. For example, any failures are not user errors; they represent messed-up files or GHC bugs, so can legitimatelly raise an exception. * The entire mechanism of `importDecl` and `loadInterface` is part of this. Don't duplicate it! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 11:53:03 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 11:53:03 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.cb169249802dbd1a54014abeedc818a8@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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): > I'm wondering if it is legit to deal with initIfaceTcRn by just repalacing it with TcRnMonad.initIfaceLoad Yes that sounds just right. > If so, do we need to move it to some less Tc-heavy place? We might indeed want to do this. But you might want to keep the moving- code-around work in a separate patch, lest the diffs from that refactoring obscure the main payload -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 11:57:46 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 11:57:46 -0000 Subject: [GHC] #12506: Compile time regression in GHC 8. In-Reply-To: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> References: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> Message-ID: <059.3c683d71822eda98f2184e2db29e49f9@haskell.org> #12506: Compile time regression in GHC 8. -------------------------------------+------------------------------------- Reporter: deech | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > The problem persists with D4394 applied I was not expecting that D4394 would help. The problem here is that the coercions are too big. The encouraging news is that 7.10.3 didn't have that problem, so it's an existence proof that we don't ''need'' big coercions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 13:22:40 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 13:22:40 -0000 Subject: [GHC] #14770: Allow static pointer expressions to have static pointer free variables In-Reply-To: <048.bed690b6ed6632ceb9361aef80b57ffb@haskell.org> References: <048.bed690b6ed6632ceb9361aef80b57ffb@haskell.org> Message-ID: <063.77b25df30b8e77bfe1a0b242931ea2cc@haskell.org> #14770: Allow static pointer expressions to have static pointer free variables -------------------------------------+------------------------------------- Reporter: TheKing01 | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | StaticPointers 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 facundo.dominguez): I don't understand how this works yet. Static pointers are put in the static pointer table (SPT) before the program executes. What is put in the SPT if the static form is allowed to have free variables? Before executing the program, the values of the free variables might be still unknown. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 14:17:55 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 14:17:55 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys In-Reply-To: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> References: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> Message-ID: <063.5ab3fe87ece14c2ddb02d3a4b04a7e47@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 14:42:38 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 14:42:38 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.415a0dcf7c097ce3864e46fb61ab1180@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Phab:D4478 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D4478 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 15:09:45 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 15:09:45 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.59446ea56a4c6c330e977a96deff65a9@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * related: => #7206 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 15:13:24 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 15:13:24 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.16bafe720495df22c3910bb62991a35d@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I confirmed that #7206 fixes this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 15:18:07 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 15:18:07 -0000 Subject: [GHC] #7206: Implement cheap build In-Reply-To: <046.231132dc13e5eec24b09b65a3836eff3@haskell.org> References: <046.231132dc13e5eec24b09b65a3836eff3@haskell.org> Message-ID: <061.3d40b7bb11373af7e259b9a08a6bf6cc@haskell.org> #7206: Implement cheap build -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 7.4.2 Resolution: | Keywords: FloatOut Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8763, #13422 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I confirmed that this fixes #8763. I had not encountered this in practice myself, but I was surprised to see this function used in another bug report: {{{ ireplicateA_ :: Applicative m => Int -> (Int -> m a) -> m () ireplicateA_ cnt0 f = loop cnt0 0 where loop !cnt !n | cnt <= 0 = pure () | otherwise = f n *> (loop (cnt - 1) (n + 1)) }}} when I tried using `forM_ [1 .. n] ...` instead of this function I realized that the program gets much slower. However with `cheapBuild` the generated code is identical. I'll submit a patch with cheap build later today with a perf test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 15:28:31 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 15:28:31 -0000 Subject: [GHC] #12506: Compile time regression in GHC 8. In-Reply-To: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> References: <044.1c66d98985dc3977bc33250e284e20f8@haskell.org> Message-ID: <059.e6247f45b4deea41d3563f508414e699@haskell.org> #12506: Compile time regression in GHC 8. -------------------------------------+------------------------------------- Reporter: deech | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I've had a look. I don't think it's fruitful for you to investigate further, Tobias, until I or Richard have had a look at the constraints generated etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 15:31:07 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 15:31:07 -0000 Subject: [GHC] #11330: Test `dynamic-paper` fails with core lint error (hpc) and "Simplifier ticks exhausted" (optasm) In-Reply-To: <045.051b0256ab9a07b148a027389e8de3e1@haskell.org> References: <045.051b0256ab9a07b148a027389e8de3e1@haskell.org> Message-ID: <060.e368017a6f0b7cf35591143fa60e4bae@haskell.org> #11330: Test `dynamic-paper` fails with core lint error (hpc) and "Simplifier ticks exhausted" (optasm) -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonpj Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/dynamic- | paper Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): I tried a `./validate --slow` with the `master` branch from today and this `dynamic-paper` test shows up as an "unexpected pass" for optasm and optllvm. I suppose one of the commits referenced here or even some other ones somehow make GHC use less ticks on that example? Should we now expect this test to pass? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 15:38:04 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 15:38:04 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys In-Reply-To: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> References: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> Message-ID: <063.5a640c6d427dc3b1d7172625678430a9@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sighingnow): I have confirmed that the program in description doesn't trigger panic with ghc-8.2.2. The error message is as follows: {{{#!hs [1 of 1] Compiling T ( T.hs, T.o ) T.hs:313:3: error: ? Expecting one fewer arguments to ‘a -> ReaderT r m b’ Expected kind ‘* -> *’, but ‘a -> ReaderT r m b’ has kind ‘*’ ? In the type signature: usingReader :: (Monad m) => r -> (a -> ReaderT r m b) (a -> m b) | 313 | (a -> ReaderT r m b) | ^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 16:00:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 16:00:10 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.f0941b3db8c8a8e4f576d2d0c7d999c3@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => infoneeded Comment: Sorry for the confusion -- it turns out GHC 8.2.2 already optimizes this. Perhaps this can be closed or we may need a new reproducer. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 16:01:07 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 16:01:07 -0000 Subject: [GHC] #14898: Panic with repSplitAppTys In-Reply-To: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> References: <048.6eb8422d8f4e52b06c26781f8fdec562@haskell.org> Message-ID: <063.f5668ac964eddd202e9972b139d9d234@haskell.org> #14898: Panic with repSplitAppTys -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #13819 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: infoneeded => closed * resolution: => duplicate * related: => #13819 Comment: Now that you mention it, despite ryanreich's message to the contrary, that code alone //does// panic on GHC 8.2.1 when put into its own module: {{{ $ /opt/ghc/8.2.1/bin/ghci Bug.hsGHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.1 for x86_64-unknown-linux): repSplitAppTys a_a1Ah[sk:1] ReaderT r_a1Ag[sk:1] m_a1Af[sk:1] b_a1Ai[sk:1] [] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:808:9 in ghc:Type }}} But does not with 8.2.2, as sighingnow noted in comment:5. So this really is a duplicate of #13819. Hooray! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 17:41:07 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 17:41:07 -0000 Subject: [GHC] #14048: Data instances of kind Constraint In-Reply-To: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> References: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> Message-ID: <066.84d146c67e0e7b70675b5bbf75e3663b@haskell.org> #14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D4479 Comment: Until we've agreed to actually allow this feature, Phab:D4479 properly catches uses of data types with return kind `Constraint` and rejects them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 18:16:40 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 18:16:40 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.74aceee8c459d688d0e8319444873165@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 tysonzero): I should have made it more clear that "" should be replaced with a working connection string to reproduce the access violation error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 18:17:35 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 18:17:35 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.5533f0f603395e840eed1c7c0aa1b255@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): OK. I'm completely unfamiliar with `persistent-postgresql`—can you walk me through the exact steps I'd need to take to set up such a connection string? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 18:24:09 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 18:24:09 -0000 Subject: [GHC] #14883: QuantifiedConstraints don't kick in when used in TypeApplications In-Reply-To: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> References: <050.9ae7dfd18c1aed745c56cdebbc78f3e8@haskell.org> Message-ID: <065.29f47ec55a39aca2b3201f2676317583@haskell.org> #14883: QuantifiedConstraints don't kick in when used in TypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a simpler version of the original program, if `Traversable` is too dense: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ImpredicativeTypes #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Bug where import Data.Coerce import Data.Kind type Representational1 m = (forall a b. Coercible a b => Coercible (m a) (m b) :: Constraint) class Distributive g where distribute :: Representational1 f => f (g a) -> g (f a) -- Typechecks newtype T1 g a = MkT1 (g a) instance Distributive g => Distributive (T1 g) where distribute :: forall f a. Representational1 f => f (T1 g a) -> T1 g (f a) distribute = coerce @(f (g a) -> g (f a)) @(f (T1 g a) -> T1 g (f a)) distribute -- Doesn't typecheck newtype T2 g a = MkT2 (g a) instance Distributive g => Distributive (T2 g) where distribute = coerce @(forall f a. Representational1 f => f (g a) -> g (f a)) @(forall f a. Representational1 f => f (T2 g a) -> T2 g (f a)) distribute }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 19:53:59 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 19:53:59 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.18fa16247e97d0b27b4f7eb47d8fb06a@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: fixed | Keywords: seq, evaluate 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:D615 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): A recent `./validate --slow` run I did revealed that this test doesn't pass anymore. I found out that something changed between `8.0.2` and `8.2.1`: {{{#!sh $ nix-shell -p haskell.compiler.ghc821 --run 'ghc-8.2.1 -O -fforce-recomp ~/ghc/testsuite/tests/codeGen/should_run/T5129.hs && /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129' [1 of 1] Compiling Main ( /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129.hs, /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129.o ) Linking /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129 ... T5129: HUnitFailure "must throw when given a negative number" $ nix-shell -p haskell.compiler.ghc802 --run 'ghc-8.0.2 -O -fforce-recomp ~/ghc/testsuite/tests/codeGen/should_run/T5129.hs && /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129' [1 of 1] Compiling Main ( /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129.hs, /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129.o ) Linking /home/alp/ghc/testsuite/tests/codeGen/should_run/T5129 ... $ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 20:50:41 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 20:50:41 -0000 Subject: [GHC] #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking Message-ID: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple PatternMatchWarnings | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where data family Sing (z :: k) class SEq k where (%==) :: forall (a :: k) (b :: k). Sing a -> Sing b -> () infix 4 %== data Foo a b c d = A a b c d | B a b c d | C a b c d | D a b c d | E a b c d | F a b c d data instance Sing (z_awDE :: Foo a b c d) where SA :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('A a b c d) SB :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('B a b c d) SC :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('C a b c d) SD :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('D a b c d) SE :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('E a b c d) SF :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('F a b c d) $([d| instance (SEq a, SEq b, SEq c, SEq d) => SEq (Foo a b c d) where (%==) (SA _ _ _ _) (SA _ _ _ _) = () (%==) (SA _ _ _ _) (SB _ _ _ _) = () (%==) (SA _ _ _ _) (SC _ _ _ _) = () (%==) (SA _ _ _ _) (SD _ _ _ _) = () (%==) (SA _ _ _ _) (SE _ _ _ _) = () (%==) (SA _ _ _ _) (SF _ _ _ _) = () (%==) (SB _ _ _ _) (SA _ _ _ _) = () (%==) (SB _ _ _ _) (SB _ _ _ _) = () (%==) (SB _ _ _ _) (SC _ _ _ _) = () (%==) (SB _ _ _ _) (SD _ _ _ _) = () (%==) (SB _ _ _ _) (SE _ _ _ _) = () (%==) (SB _ _ _ _) (SF _ _ _ _) = () (%==) (SC _ _ _ _) (SA _ _ _ _) = () (%==) (SC _ _ _ _) (SB _ _ _ _) = () (%==) (SC _ _ _ _) (SC _ _ _ _) = () (%==) (SC _ _ _ _) (SD _ _ _ _) = () (%==) (SC _ _ _ _) (SE _ _ _ _) = () (%==) (SC _ _ _ _) (SF _ _ _ _) = () (%==) (SD _ _ _ _) (SA _ _ _ _) = () (%==) (SD _ _ _ _) (SB _ _ _ _) = () (%==) (SD _ _ _ _) (SC _ _ _ _) = () (%==) (SD _ _ _ _) (SD _ _ _ _) = () (%==) (SD _ _ _ _) (SE _ _ _ _) = () (%==) (SD _ _ _ _) (SF _ _ _ _) = () (%==) (SE _ _ _ _) (SA _ _ _ _) = () (%==) (SE _ _ _ _) (SB _ _ _ _) = () (%==) (SE _ _ _ _) (SC _ _ _ _) = () (%==) (SE _ _ _ _) (SD _ _ _ _) = () (%==) (SE _ _ _ _) (SE _ _ _ _) = () (%==) (SE _ _ _ _) (SF _ _ _ _) = () (%==) (SF _ _ _ _) (SA _ _ _ _) = () (%==) (SF _ _ _ _) (SB _ _ _ _) = () (%==) (SF _ _ _ _) (SC _ _ _ _) = () (%==) (SF _ _ _ _) (SD _ _ _ _) = () (%==) (SF _ _ _ _) (SE _ _ _ _) = () (%==) (SF _ _ _ _) (SF _ _ _ _) = () |]) }}} It takes significantly longer to compile this program on 8.4 and HEAD: {{{ $ /opt/ghc/8.4.1/bin/ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.1 $ time /opt/ghc/8.4.1/bin/ghc Bug.hs -fforce-recomp [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) real 0m0.285s user 0m0.236s sys 0m0.036s $ /opt/ghc/head/bin/ghc --version The Glorious Glasgow Haskell Compilation System, version 8.5.20180306 $ time /opt/ghc/head/bin/ghc Bug.hs -fforce-recomp [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) real 0m29.684s user 0m29.656s sys 0m0.060s }}} The reason for this regression is somewhat incidental—it's due to commit ffb2738f86c4e4c3f0eaacf0a95d7326fdd2e383 (`Fix #14838 by marking TH- spliced code as FromSource`). Before that commit, we were supressing pattern-match coverage checking entirely on TH-quoted code. We no longer do this, which means that we coverage-check the TH-quoted instance in that program, which appears to be why it takes so long to compile. This is a serious issue in practice because a good chunk of `singletons`-generated code is of this form, which means that a good amount of code is effectively uncompilable on GHC HEAD now. (See, for instance, this [https://travis- ci.org/goldfirere/singletons/jobs/350483543#L1182 Travis failure] on GHC HEAD.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 20:57:20 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 20:57:20 -0000 Subject: [GHC] #14770: Allow static pointer expressions to have static pointer free variables In-Reply-To: <048.bed690b6ed6632ceb9361aef80b57ffb@haskell.org> References: <048.bed690b6ed6632ceb9361aef80b57ffb@haskell.org> Message-ID: <063.a37e44cdef73786a04fe2c70fb507b6f@haskell.org> #14770: Allow static pointer expressions to have static pointer free variables -------------------------------------+------------------------------------- Reporter: TheKing01 | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | StaticPointers 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 TheKing01): The code surrounding the free variables is put in the SPT. A static pointer then points to that code, as well as separate static pointers for the free variables. This makes static pointers a recursive data type. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 20:58:58 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 20:58:58 -0000 Subject: [GHC] #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking In-Reply-To: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> References: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> Message-ID: <065.5c75d8aa29314c4797f15b991a5c66d6@haskell.org> #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Curiously, data family instances seem to play a role in this. If I replace the data family formulation of `Sing` with a normal datatype: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where class SEq k where (%==) :: forall (a :: k) (b :: k). Sing a -> Sing b -> () infix 4 %== data Foo a b c d = A a b c d | B a b c d | C a b c d | D a b c d | E a b c d | F a b c d data Sing (z_awDE :: k) where SA :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('A a b c d) SB :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('B a b c d) SC :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('C a b c d) SD :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('D a b c d) SE :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('E a b c d) SF :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('F a b c d) $([d| instance (SEq a, SEq b, SEq c, SEq d) => SEq (Foo a b c d) where (%==) (SA _ _ _ _) (SA _ _ _ _) = () (%==) (SA _ _ _ _) (SB _ _ _ _) = () (%==) (SA _ _ _ _) (SC _ _ _ _) = () (%==) (SA _ _ _ _) (SD _ _ _ _) = () (%==) (SA _ _ _ _) (SE _ _ _ _) = () (%==) (SA _ _ _ _) (SF _ _ _ _) = () (%==) (SB _ _ _ _) (SA _ _ _ _) = () (%==) (SB _ _ _ _) (SB _ _ _ _) = () (%==) (SB _ _ _ _) (SC _ _ _ _) = () (%==) (SB _ _ _ _) (SD _ _ _ _) = () (%==) (SB _ _ _ _) (SE _ _ _ _) = () (%==) (SB _ _ _ _) (SF _ _ _ _) = () (%==) (SC _ _ _ _) (SA _ _ _ _) = () (%==) (SC _ _ _ _) (SB _ _ _ _) = () (%==) (SC _ _ _ _) (SC _ _ _ _) = () (%==) (SC _ _ _ _) (SD _ _ _ _) = () (%==) (SC _ _ _ _) (SE _ _ _ _) = () (%==) (SC _ _ _ _) (SF _ _ _ _) = () (%==) (SD _ _ _ _) (SA _ _ _ _) = () (%==) (SD _ _ _ _) (SB _ _ _ _) = () (%==) (SD _ _ _ _) (SC _ _ _ _) = () (%==) (SD _ _ _ _) (SD _ _ _ _) = () (%==) (SD _ _ _ _) (SE _ _ _ _) = () (%==) (SD _ _ _ _) (SF _ _ _ _) = () (%==) (SE _ _ _ _) (SA _ _ _ _) = () (%==) (SE _ _ _ _) (SB _ _ _ _) = () (%==) (SE _ _ _ _) (SC _ _ _ _) = () (%==) (SE _ _ _ _) (SD _ _ _ _) = () (%==) (SE _ _ _ _) (SE _ _ _ _) = () (%==) (SE _ _ _ _) (SF _ _ _ _) = () (%==) (SF _ _ _ _) (SA _ _ _ _) = () (%==) (SF _ _ _ _) (SB _ _ _ _) = () (%==) (SF _ _ _ _) (SC _ _ _ _) = () (%==) (SF _ _ _ _) (SD _ _ _ _) = () (%==) (SF _ _ _ _) (SE _ _ _ _) = () (%==) (SF _ _ _ _) (SF _ _ _ _) = () |]) }}} Then the compilation time for GHC HEAD goes back to being the same as in 8.4.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 21:08:36 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 21:08:36 -0000 Subject: [GHC] #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking In-Reply-To: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> References: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> Message-ID: <065.a3eaa4cbe9311905a0139600b00b71f5@haskell.org> #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This is bad. Really bad. I looked briefly into the GHC source, and found [http://git.haskell.org/ghc.git/blob/d9d463289fe20316cff12a8f0dbf414db678fa72:/compiler/deSugar/Check.hs#l1105 this ominous Note]: {{{ Note [Translate CoPats] ~~~~~~~~~~~~~~~~~~~~~~~ The pattern match checker did not know how to handle coerced patterns `CoPat` efficiently, which gave rise to #11276. The original approach translated `CoPat`s: pat |> co ===> x (pat <- (e |> co)) Instead, we now check whether the coercion is a hole or if it is just refl, in which case we can drop it. Unfortunately, data families generate useful coercions so guards are still generated in these cases and checking data families is not really efficient. }}} If that is to be believed, then is coverage-checking data family instances really doomed to be slow? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 7 21:37:06 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 07 Mar 2018 21:37:06 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.c7404885c5c171cf4ceedf474387a379@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nh2): If the problem is gone in 8.2.2, do we know what commit fixed it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 00:22:22 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 00:22:22 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.635cd07074a4f5941a47bc87a8c8ffb0@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): I haven't confirmed, but it looks like 2effe18ab51d66474724d38b20e49cc1b8738f60 may have fixed this. Now fusion happens during the "gentle" phase of simplifier, which happens before any of the float-out passes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 01:09:26 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 01:09:26 -0000 Subject: [GHC] #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking In-Reply-To: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> References: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> Message-ID: <065.15840de4bf7130c82057a3e4ef9a75ea@haskell.org> #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To make the data type version of the program as slow to compile as the data family instance version, you can use explicit guards: {{{#!hs {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} module Bug where class SEq k where (%==) :: forall (a :: k) (b :: k). Sing a -> Sing b -> () infix 4 %== data Foo a b c d = A a b c d | B a b c d | C a b c d | D a b c d | E a b c d | F a b c d data Sing (z_awDE :: k) where SA :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('A a b c d) SB :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('B a b c d) SC :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('C a b c d) SD :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('D a b c d) SE :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('E a b c d) SF :: Sing a -> Sing b -> Sing c -> Sing d -> Sing ('F a b c d) instance (SEq a, SEq b, SEq c, SEq d) => SEq (Foo a b c d) where (%==) x y | SA {} <- x , SA {} <- y = () | SA {} <- x , SB {} <- y = () | SA {} <- x , SC {} <- y = () | SA {} <- x , SD {} <- y = () | SA {} <- x , SE {} <- y = () | SA {} <- x , SF {} <- y = () | SB {} <- x , SA {} <- y = () | SB {} <- x , SB {} <- y = () | SB {} <- x , SC {} <- y = () | SB {} <- x , SD {} <- y = () | SB {} <- x , SE {} <- y = () | SB {} <- x , SF {} <- y = () | SC {} <- x , SA {} <- y = () | SC {} <- x , SB {} <- y = () | SC {} <- x , SC {} <- y = () | SC {} <- x , SD {} <- y = () | SC {} <- x , SE {} <- y = () | SC {} <- x , SF {} <- y = () | SD {} <- x , SA {} <- y = () | SD {} <- x , SB {} <- y = () | SD {} <- x , SC {} <- y = () | SD {} <- x , SD {} <- y = () | SD {} <- x , SE {} <- y = () | SD {} <- x , SF {} <- y = () | SE {} <- x , SA {} <- y = () | SE {} <- x , SB {} <- y = () | SE {} <- x , SC {} <- y = () | SE {} <- x , SD {} <- y = () | SE {} <- x , SE {} <- y = () | SE {} <- x , SF {} <- y = () | SF {} <- x , SA {} <- y = () | SF {} <- x , SB {} <- y = () | SF {} <- x , SC {} <- y = () | SF {} <- x , SD {} <- y = () | SF {} <- x , SE {} <- y = () | SF {} <- x , SF {} <- y = () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 01:47:10 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 01:47:10 -0000 Subject: [GHC] #14900: Calling isByteArrayPinned# on compact ByteArray Message-ID: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> #14900: Calling isByteArrayPinned# on compact ByteArray -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The documentation explaining the relationship between pinnedness and compact regions is incomplete. From `Data.Compact`: > Pinned ByteArray# objects cannot be compacted. This is for a good reason: the memory is pinned so that it can be referenced by address (the address might be stored in a C data structure, for example), so we can't make a copy of it to store in the Compact. This is half-way true since it only considers one a the ways in which the GHC runtime tracks the pinnedness of an object. From experimenting with compact regions, it seems like there are two different notions of pinnedness: 1. Did the user explicitly ask for the `ByteArray` to be pinned? 2. Is the `ByteArray` pinned? If (1) is true, then (2) must always be true, but if (1) is false, then could be true or false. `ByteArray`s over 3KB are pinned, and `ByteArray`s under 3KB are not (or somewhere around that number). With that background information in place, here's the scenario I've encountered: {{{ {-# LANGUAGE MagicHash #-} import Data.Primitive import Data.Compact import GHC.Int import GHC.Prim main :: IO () main = do ByteArray arr1# <- fmap getCompact $ newByteArray 65000 >>= unsafeFreezeByteArray >>= compact ByteArray arr2# <- newByteArray 65000 >>= unsafeFreezeByteArray print (I# (isByteArrayPinned# arr1#)) print (I# (isByteArrayPinned# arr2#)) putStrLn "Finished" }}} When compiled and run, this gives: {{{ 0 1 Finished }}} We can see that the 65KiB `ByteArray` that was not compacted let's the user know that it is pinned. The compacted `ByteArray` claims to not be pinned, but this is not true. The docs in `Data.Compact` claim: > Data in a compact doesn't ever move, so compacting data is also a way to pin arbitrary data structures in memory. I propose that the behavior of `compact` be modified to accurately convey the pinnedness of the `ByteArray`s that copies. This would mean that even small, previously unpinned, `ByteArray`s would also be designated as pinned. It's a small change, but it makes the information the runtime gives us more accurate. This is occasionally handy when dealing with the FFI. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 06:37:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 06:37:35 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.62638a9f9d2cd0ebfa03c7eb773c4477@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Phab:D4478 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I told mniip about this ticket on IRC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 07:44:00 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 07:44:00 -0000 Subject: [GHC] #4114: Add a flag to remove/delete intermediate files generated by GHC In-Reply-To: <044.5bde4abfdaa56d5ae586d71d6ff93b9d@haskell.org> References: <044.5bde4abfdaa56d5ae586d71d6ff93b9d@haskell.org> Message-ID: <059.087e56fc8dd428bd5a1bfb536d361246@haskell.org> #4114: Add a flag to remove/delete intermediate files generated by GHC -------------------------------------+------------------------------------- Reporter: guest | Owner: kaiha Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 6.10.4 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | driver/T4114a,b,c,d Blocked By: | Blocking: Related Tickets: #2258 | Differential Rev(s): Phab:D2021 Wiki Page: | Phab:D2050 -------------------------------------+------------------------------------- Comment (by alpmestan): With master from yesterday, T4114c and T4114d are failing with the `ghci` way: {{{ =====> T4114c(ghci) 1 of 2 [0, 0, 0] cd "./driver/T4114c.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T4114c.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output -fobject-code --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -no- keep-o-files< T4114c.genscript Wrong exit code for T4114c(ghci) (expected 0 , actual 1 ) Stderr ( T4114c ): T4114c: error: intermediate 'T4114cSub.o' exists CallStack (from HasCallStack): error, called at ./T4114cSub.hs:9:8 in main:T4114cSub *** unexpected failure for T4114c(ghci) =====> T4114d(ghci) 2 of 2 [0, 1, 0] cd "./driver/T4114d.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T4114d.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output -fobject-code --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -hisuf .myhi -osuf .myo -no-keep-o-files< T4114d.genscript Wrong exit code for T4114d(ghci) (expected 0 , actual 1 ) Stderr ( T4114d ): T4114d: error: intermediate 'T4114dSub.myo' exists CallStack (from HasCallStack): error, called at ./T4114dSub.hs:9:8 in main:T4114dSub *** unexpected failure for T4114d(ghci) }}} So it looks like `--interactive` does not honor `-no-keep-o-files` anymore. Shall I push a patch that expects just this way to fail, or shall I look into this somewhat soon to fix it instead? Or both I guess? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 08:28:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 08:28:57 -0000 Subject: [GHC] #14900: Calling isByteArrayPinned# on compact ByteArray In-Reply-To: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> References: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> Message-ID: <064.82b8c59ee502589443b3a2ba71380daa@haskell.org> #14900: Calling isByteArrayPinned# on compact ByteArray -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 08:35:13 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 08:35:13 -0000 Subject: [GHC] #14900: Calling isByteArrayPinned# on compact ByteArray In-Reply-To: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> References: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> Message-ID: <064.3cffce5fc86190ee8c61e81801d3459d@haskell.org> #14900: Calling isByteArrayPinned# on compact ByteArray -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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): Yes, we could make all `ByteArray#` in a compact region return true for `isByteArrayPinned#`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 08:58:19 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 08:58:19 -0000 Subject: [GHC] #14900: Calling isByteArrayPinned# on compact ByteArray In-Reply-To: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> References: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> Message-ID: <064.bb4d64a0adf49653d4dc748ac0034595@haskell.org> #14900: Calling isByteArrayPinned# on compact ByteArray -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4485 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * owner: (none) => simonmar * differential: => Phab:D4485 * component: Compiler => Runtime System * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 09:33:10 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 09:33:10 -0000 Subject: [GHC] #8542: Suggest NegativeLiterals In-Reply-To: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> References: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> Message-ID: <062.37be7d5dc8e3b0a47463eaff914a965f@haskell.org> #8542: Suggest NegativeLiterals -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | numeric/should_fail/T8542 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): The `hpc` way fails on `T8542`: {{{ =====> T8542(hpc) 1 of 1 [0, 0, 0] cd "./numeric/should_compile/T8542.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" -c T8542.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -O -fhpc Actual stderr output differs from expected: diff -uw "./numeric/should_compile/T8542.run/T8542.stderr.normalised" "./numeric/should_compile/T8542.run/T8542.comp.stderr.normalised" --- ./numeric/should_compile/T8542.run/T8542.stderr.normalised 2018-03-08 10:24:05.303965000 +0100 +++ ./numeric/should_compile/T8542.run/T8542.comp.stderr.normalised 2018-03-08 10:24:05.303965000 +0100 @@ -1,4 +1,8 @@ +T8542.hs:6:6: warning: [-Woverflowed-literals (in -Wdefault)] + Literal 128 is out of the Int8 range -128..127 + If you are trying to write a large negative literal, use NegativeLiterals + T8542.hs:9:5: warning: [-Woverflowed-literals (in -Wdefault)] Literal 128 is out of the Int8 range -128..127 If you are trying to write a large negative literal, use NegativeLiterals *** unexpected failure for T8542(hpc) }}} Somehow, unlike all the other ways, it ends up warning us about both occurences of `128` in: {{{#!hs module T8542 where import GHC.Int x :: Int8 x = -128 y :: Int8 y = 128 }}} instead of realizing that the first literal is `-128` directly, which _is_ within the `[-128 .. 127]` range but supposedly not considered because `NegativeLiterals` is not on? It does sound like a little bug, and I'm curious as to why we don't see it with any of the other ways, even though to be honest I'm not familiar with the `hpc` way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 10:50:51 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 10:50:51 -0000 Subject: [GHC] #2783: RTS -K/-M options not honored In-Reply-To: <049.63d82e75e6191178fe162ae9a73c2fd3@haskell.org> References: <049.63d82e75e6191178fe162ae9a73c2fd3@haskell.org> Message-ID: <064.c031c08c920ffcea297bda581a007469@haskell.org> #2783: RTS -K/-M options not honored -----------------------------------+------------------------------ Reporter: j.waldmann | Owner: igloo Type: merge | Status: closed Priority: normal | Milestone: 6.10.2 Component: Runtime System | Version: 6.10.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+------------------------------ Changes (by alpmestan): * failure: => None/Unknown Comment: When running `./validate --slow` yesterday, I saw the test for this ticket failing with the `threaded1` way. Instead of detecting the loop and aborting with an informative message, we get an assertion failure in the `rts/ThreadPaused.c:threadPaused` function. The program: {{{#!hs main = print $ do x <- [ 0 .. 5 ] ; let { y = 5 - y } ; return y }}} The output: {{{ =====> T2783(threaded1) 1 of 1 [0, 0, 0] cd "./rts/T2783.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" -o T2783 T2783.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output -threaded -debug cd "./rts/T2783.run" && ./T2783 Wrong exit code for T2783(threaded1)(expected 1 , actual 134 ) Stderr ( T2783 ): T2783: internal error: ASSERTION FAILED: file rts/ThreadPaused.c, line 314 (GHC version 8.5.20180306 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) *** unexpected failure for T2783(threaded1) }}} The code for the corresponding assertion: {{{#!c // We should never have made it here in the event of blackholes that // we already own; they should have been marked when we blackholed // them and consequently we should have stopped our stack walk // above. ASSERT(!((bh_info == &stg_BLACKHOLE_info) && (((StgInd*)bh)->indirectee == (StgClosure*)tso))); }}} This actually is unexpected _ang_ a bug, right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 13:04:15 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 13:04:15 -0000 Subject: [GHC] #12870: Allow completely disabling +RTS options parsing In-Reply-To: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> References: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> Message-ID: <057.3cc295216027fd0cad6845f5af85e39e@haskell.org> #12870: Allow completely disabling +RTS options parsing -------------------------------------+------------------------------------- Reporter: nh2 | Owner: AndreasK Type: feature request | Status: closed Priority: normal | Milestone: 8.4.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): Phab:D3740 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): I'm seeing quite a few failures related to the `T12870*` tests in a run of `./validate --slow` with master from yesterday. First, _all_ those tests fail with the `ghci` way, because `ghci` doesn't see that those modules are declared as `module Main where ...` and have a `main` function, and reports an error about this. {{{ =====> T12870a(ghci) 1 of 8 [0, 0, 0] cd "./rts/flags/T12870a.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T12870 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts -main-is T12870< T12870a.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./rts/flags/T12870a.run/T12870a.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/flags/T12870a.run/T12870a.run.stderr.normalised 2018-03-08 13:56:21.487965000 +0100 @@ -0,0 +1,4 @@ + +T12870a:6:30: + Not in scope: ‘Main.main’ + No module named ‘Main’ is imported. *** unexpected failure for T12870a(ghci) =====> T12870b(ghci) 2 of 8 [0, 1, 0] cd "./rts/flags/T12870b.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T12870 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts=none -main-is T12870< T12870b.genscript Wrong exit code for T12870b(ghci) (expected 1 , actual 0 ) Stderr ( T12870b ): T12870b:6:30: error: Not in scope: ‘Main.main’ No module named ‘Main’ is imported. *** unexpected failure for T12870b(ghci) =====> T12870c(ghci) 3 of 8 [0, 2, 0] cd "./rts/flags/T12870c.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T12870 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts=some -main-is T12870< T12870c.genscript Wrong exit code for T12870c(ghci) (expected 1 , actual 0 ) Stderr ( T12870c ): T12870c:6:30: error: Not in scope: ‘Main.main’ No module named ‘Main’ is imported. *** unexpected failure for T12870c(ghci) =====> T12870d(ghci) 4 of 8 [0, 3, 0] cd "./rts/flags/T12870d.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T12870 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -main-is T12870< T12870d.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./rts/flags/T12870d.run/T12870d.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/flags/T12870d.run/T12870d.run.stderr.normalised 2018-03-08 13:56:22.091965000 +0100 @@ -0,0 +1,4 @@ + +T12870d:6:30: + Not in scope: ‘Main.main’ + No module named ‘Main’ is imported. *** unexpected failure for T12870d(ghci) =====> T12870e(ghci) 5 of 8 [0, 4, 0] cd "./rts/flags/T12870e.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T12870 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts=ignore -main-is T12870< T12870e.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./rts/flags/T12870e.run/T12870e.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/flags/T12870e.run/T12870e.run.stderr.normalised 2018-03-08 13:56:22.307965000 +0100 @@ -0,0 +1,4 @@ + +T12870e:6:30: + Not in scope: ‘Main.main’ + No module named ‘Main’ is imported. *** unexpected failure for T12870e(ghci) =====> T12870f(ghci) 6 of 8 [0, 5, 0] cd "./rts/flags/T12870f.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" T12870 -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno- warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts=ignoreAll -main-is T12870< T12870f.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./rts/flags/T12870f.run/T12870f.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/flags/T12870f.run/T12870f.run.stderr.normalised 2018-03-08 13:56:22.547965000 +0100 @@ -0,0 +1,4 @@ + +T12870f:6:30: + Not in scope: ‘Main.main’ + No module named ‘Main’ is imported. *** unexpected failure for T12870f(ghci) =====> T12870g(ghci) 7 of 8 [0, 6, 0] cd "./rts/flags/T12870g.run" && GHCRTS=-G7 "/home/alp/ghc/inplace/test spaces/ghc-stage2" T12870g -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts -main-is T12870g -with-rtsopts="-G3"< T12870g.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./rts/flags/T12870g.run/T12870g.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/flags/T12870g.run/T12870g.run.stderr.normalised 2018-03-08 13:56:22.799965000 +0100 @@ -0,0 +1,4 @@ + +T12870g:6:30: + Not in scope: ‘Main.main’ + No module named ‘Main’ is imported. *** unexpected failure for T12870g(ghci) =====> T12870h(ghci) 8 of 8 [0, 7, 0] cd "./rts/flags/T12870h.run" && GHCRTS=-G7 "/home/alp/ghc/inplace/test spaces/ghc-stage2" T12870g -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -rtsopts=ignoreAll -main-is T12870g -with-rtsopts="-G3"< T12870h.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./rts/flags/T12870h.run/T12870h.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/flags/T12870h.run/T12870h.run.stderr.normalised 2018-03-08 13:56:23.031965000 +0100 @@ -0,0 +1,4 @@ + +T12870h:6:30: + Not in scope: ‘Main.main’ + No module named ‘Main’ is imported. *** unexpected failure for T12870h(ghci) }}} I also see failures with `threaded2`, because of additional RTS options passed to all tests executed in the `threaded2` way, I suppose: {{{ =====> T12870e(threaded2) 1 of 2 [0, 0, 0] cd "./rts/flags/T12870e.run" && "/home/alp/ghc/inplace/test spaces /ghc-stage2" --make -o T12870e T12870 -dcore-lint -dcmm-lint -no-user- package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -O -threaded -eventlog -rtsopts=ignore -main-is T12870 cd "./rts/flags/T12870e.run" && ./T12870e +RTS -N2 -ls -RTS +RTS -G2 -RTS arg1 --RTS +RTS arg2 Actual stdout output differs from expected: diff -uw "./rts/flags/T12870e.run/T12870e.stdout.normalised" "./rts/flags/T12870e.run/T12870e.run.stdout.normalised" --- ./rts/flags/T12870e.run/T12870e.stdout.normalised 2018-03-08 13:37:41.099965000 +0100 +++ ./rts/flags/T12870e.run/T12870e.run.stdout.normalised 2018-03-08 13:37:41.099965000 +0100 @@ -1 +1 @@ -["+RTS","-G2","-RTS","arg1","--RTS","+RTS","arg2"] +["+RTS","-N2","-ls","-RTS","+RTS","-G2","-RTS","arg1","-- RTS","+RTS","arg2"] *** unexpected failure for T12870e(threaded2) =====> T12870f(threaded2) 2 of 2 [0, 1, 0] cd "./rts/flags/T12870f.run" && "/home/alp/ghc/inplace/test spaces /ghc-stage2" --make -o T12870f T12870 -dcore-lint -dcmm-lint -no-user- package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -O -threaded -eventlog -rtsopts=ignoreAll -main-is T12870 cd "./rts/flags/T12870f.run" && ./T12870f +RTS -N2 -ls -RTS +RTS -G2 -RTS arg1 --RTS +RTS arg2 Actual stdout output differs from expected: diff -uw "./rts/flags/T12870f.run/T12870f.stdout.normalised" "./rts/flags/T12870f.run/T12870f.run.stdout.normalised" --- ./rts/flags/T12870f.run/T12870f.stdout.normalised 2018-03-08 13:37:41.671965000 +0100 +++ ./rts/flags/T12870f.run/T12870f.run.stdout.normalised 2018-03-08 13:37:41.671965000 +0100 @@ -1 +1 @@ -["+RTS","-G2","-RTS","arg1","--RTS","+RTS","arg2"] +["+RTS","-N2","-ls","-RTS","+RTS","-G2","-RTS","arg1","-- RTS","+RTS","arg2"] *** unexpected failure for T12870f(threaded2) }}} I'm also not sure what `-rtsopts=ignoreAll` is about, I don't see anything being ignored, only some more options being given to the program and reported. This makes it hard to expect the same output from a test executed under different ways. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 13:20:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 13:20:35 -0000 Subject: [GHC] #13543: Improve demand analysis for join points In-Reply-To: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> References: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> Message-ID: <061.c3591568cd6a9770dc46f4659921c860@haskell.org> #13543: Improve demand analysis for join points -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): When running `./validate --slow`, I found out that the `T13543` test fails with all 3 of these ways: `hpc`, `optasm`, `optllvm`. {{{ =====> T13543(hpc) 1 of 1 [0, 0, 0] cd "./simplCore/should_compile/T13543.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" -c T13543.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -O -fhpc -ddump-str-signatures Actual stderr output differs from expected: diff -uw "./simplCore/should_compile/T13543.run/T13543.stderr.normalised" "./simplCore/should_compile/T13543.run/T13543.comp.stderr.normalised" --- ./simplCore/should_compile/T13543.run/T13543.stderr.normalised 2018-03-08 14:13:19.867965000 +0100 +++ ./simplCore/should_compile/T13543.run/T13543.comp.stderr.normalised 2018-03-08 14:13:19.867965000 +0100 @@ -1 +1,12 @@ +==================== Strictness signatures ==================== +Foo.$trModule: m +Foo.f: m +Foo.g: m + + + +==================== Strictness signatures ==================== +Foo.$trModule: m +Foo.f: m +Foo.g: m *** unexpected failure for T13543(hpc) }}} {{{ =====> T13543(optasm) 1 of 1 [0, 0, 0] cd "./simplCore/should_compile/T13543.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" -c T13543.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -O -fasm -ddump-str-signatures Actual stderr output differs from expected: diff -uw "./simplCore/should_compile/T13543.run/T13543.stderr.normalised" "./simplCore/should_compile/T13543.run/T13543.comp.stderr.normalised" --- ./simplCore/should_compile/T13543.run/T13543.stderr.normalised 2018-03-08 14:16:02.367965000 +0100 +++ ./simplCore/should_compile/T13543.run/T13543.comp.stderr.normalised 2018-03-08 14:16:02.367965000 +0100 @@ -1 +1,12 @@ +==================== Strictness signatures ==================== +Foo.$trModule: m +Foo.f: m +Foo.g: m + + + +==================== Strictness signatures ==================== +Foo.$trModule: m +Foo.f: m +Foo.g: m *** unexpected failure for T13543(optasm) }}} {{{ =====> T13543(optllvm) 1 of 1 [0, 0, 0] cd "./simplCore/should_compile/T13543.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" -c T13543.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -O -fllvm -ddump-str-signatures Actual stderr output differs from expected: diff -uw "./simplCore/should_compile/T13543.run/T13543.stderr.normalised" "./simplCore/should_compile/T13543.run/T13543.comp.stderr.normalised" --- ./simplCore/should_compile/T13543.run/T13543.stderr.normalised 2018-03-08 14:16:28.627965000 +0100 +++ ./simplCore/should_compile/T13543.run/T13543.comp.stderr.normalised 2018-03-08 14:16:28.627965000 +0100 @@ -1 +1,12 @@ +==================== Strictness signatures ==================== +Foo.$trModule: m +Foo.f: m +Foo.g: m + + + +==================== Strictness signatures ==================== +Foo.$trModule: m +Foo.f: m +Foo.g: m *** unexpected failure for T13543(optllvm) }}} In all 3 cases, we're expecting an empty stderr (that we get with other ways like `normal`) but we instead get the strictness signatures dumped there, because of the flag that we pass to ghc: {{{ test('T13543', normal, compile, ['-ddump-str-signatures']) }}} Should I just strip that flag so that these tests pass? It's still odd that say `normal` and `optasm` dump things in different places, isn't it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 13:55:46 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 13:55:46 -0000 Subject: [GHC] #13366: addCStub doesn't allow control over compiler flags or source file file In-Reply-To: <046.e4d0ff069ca721205cf186e478fec23b@haskell.org> References: <046.e4d0ff069ca721205cf186e478fec23b@haskell.org> Message-ID: <061.7a69d83ca365b4488465b8e54a62d036@haskell.org> #13366: addCStub doesn't allow control over compiler flags or source file file -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: closed Priority: high | 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): Phab:D3280 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): The `T13366` test fails on master from yesterday, when executed with the `ghci` way: {{{ =====> T13366(ghci) 1 of 1 [0, 0, 0] cd "./th/T13366.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" T13366.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn- missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output -XTemplateHaskell -package template-haskell --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS -lstdc++ -v0< T13366.genscript Actual stderr output differs from expected: diff -uw "/dev/null" "./th/T13366.run/T13366.run.stderr.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./th/T13366.run/T13366.run.stderr.normalised 2018-03-08 14:49:20.583965000 +0100 @@ -0,0 +1,13 @@ +ghc: ^^ Could not load 'fcxx', dependency unresolved. See top entry above. + + +ByteCodeLink: can't find label +During interactive linking, GHCi couldn't find the following symbol: + fcxx +This may be due to you not asking GHCi to load extra object files, +archives or DLLs needed by your current session. Restart GHCi, specifying +the missing library using the -L/path/to/object/dir and -lmissinglibname +flags, or simply by naming the relevant files on the GHCi command line. +Alternatively, this link failure might indicate a bug in GHCi. +If you suspect the latter, please send a bug report to: + glasgow-haskell-bugs at haskell.org *** unexpected failure for T13366(ghci) }}} where the aforementionned symbol is defined in a snippet of C++ code that TH adds to the build through `addForeignFile`: {{{#!hs foreign import ccall fcxx :: Int -> IO Int do addForeignFile LangCxx $ unlines [ "#include " , "extern \"C\" {" , " int fcxx(int x) {" , " std::cout << \"calling fcxx(\" << x << \")\" << std::endl;" , " std::cout.flush();" , " return A_MACRO + x;" , " }" , "}" ] return [] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 15:30:44 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 15:30:44 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.03494ea0ca5b88504251b60bcf88799a@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate 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:D615 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: simonmar => (none) * status: closed => new * resolution: fixed => Comment: Let's reopen this (or open a new ticket to track these). These competing bottoms are tricky! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 15:49:47 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 15:49:47 -0000 Subject: [GHC] #2783: RTS -K/-M options not honored In-Reply-To: <049.63d82e75e6191178fe162ae9a73c2fd3@haskell.org> References: <049.63d82e75e6191178fe162ae9a73c2fd3@haskell.org> Message-ID: <064.c7a3bc22d14eba2c7af9fb5fd7eed52c@haskell.org> #2783: RTS -K/-M options not honored -----------------------------------+------------------------------ Reporter: j.waldmann | Owner: igloo Type: merge | Status: closed Priority: normal | Milestone: 6.10.2 Component: Runtime System | Version: 6.10.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+------------------------------ Old description: > I have this program > > main = print $ do x <- [ 0 .. 5 ] ; let { y = 5 - y } ; return y > > I compile with ghc-6.10.1 --make > > and I execute with +RTS -M10m -K10m > > but still the executable quickly eats up all my memory. > > (I know the program is silly but still it should crash > gracefully.) > > When I do the same thing with ghc-6.8.3, > I get "Heap exhausted", as it should be. New description: I have this program {{{#!hs main = print $ do x <- [ 0 .. 5 ] ; let { y = 5 - y } ; return y }}} I compile with `ghc-6.10.1 --make` and I execute with `+RTS -M10m -K10m` but still the executable quickly eats up all my memory. (I know the program is silly but still it should crash gracefully.) When I do the same thing with ghc-6.8.3, I get "Heap exhausted", as it should be. -- Comment (by bgamari): Sounds like a bug to me, but it's not the bug covered by this ticket. Let's open a new ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:04:52 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:04:52 -0000 Subject: [GHC] #13543: Improve demand analysis for join points In-Reply-To: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> References: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> Message-ID: <061.207292b6cca7d99b1532a7a78413bf7c@haskell.org> #13543: Improve demand analysis for join points -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, I think the expected test output might just be wrong: the stderr output is empty in the `normal` way because GHC is invoked without optimisation enabled in that way. I believe the test was supposed to expect non-empty output. I suspect we should only be running this test in the `optasm` way (since the other ways will inevitably differ in their strictness signatures) and update the output accordingly. We should ask Simon to look over the new output before committing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:42:46 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:42:46 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.e090ec16106eb5ec58b0f7c62fe44fbc@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.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: | -------------------------------------+------------------------------------- Old description: > Hi, let's consider the following code: > > {{{ > > {-# LANGUAGE Strict #-} -- Comment/uncommenting this > {-# LANGUAGE MultiParamTypeClasses #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > > module K where > > import Control.Monad.Trans > import qualified Control.Monad.State.Strict as S > import Control.Monad.Primitive > > newtype StateT s m a = StateT (S.StateT s m a) -- S is > Control.Monad.State.Strict > deriving (Functor, Applicative, Monad, MonadTrans) > > instance PrimMonad m => PrimMonad (StateT s m) where > type PrimState (StateT s m) = PrimState m > primitive ~a = lift (primitive a) ; {-# INLINE primitive #-} > }}} > > If compiled with `-XStrict` this code is not inlined properly and it > badly affects the performance. While discussing it on Haskell IRC `lyxia` > helped very much with discovering the CORE differences. The lazy version > has couple of things which the strict version is missing in form of > `[InlPrag=INLINE (sat-args=0)]` on toplevel identifiers. > > Core: https://gist.github.com/Lysxia/34684c9ca9fe4772ea38a5065414f542 New description: Hi, let's consider the following code: {{{#!hs {-# LANGUAGE Strict #-} -- Comment/uncommenting this {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module K where import Control.Monad.Trans import qualified Control.Monad.State.Strict as S import Control.Monad.Primitive newtype StateT s m a = StateT (S.StateT s m a) -- S is Control.Monad.State.Strict deriving (Functor, Applicative, Monad, MonadTrans) instance PrimMonad m => PrimMonad (StateT s m) where type PrimState (StateT s m) = PrimState m primitive ~a = lift (primitive a) ; {-# INLINE primitive #-} }}} If compiled with `-XStrict` this code is not inlined properly and it badly affects the performance. While discussing it on Haskell IRC `lyxia` helped very much with discovering the CORE differences. The lazy version has couple of things which the strict version is missing in form of `[InlPrag=INLINE (sat-args=0)]` on toplevel identifiers. Core: https://gist.github.com/Lysxia/34684c9ca9fe4772ea38a5065414f542 -- Comment (by bgamari): Indeed it sounds like testing this would be fiddly at best. That being said, it does seem quite unfortunate to simply close this. A user enabled `-XStrict` thinking that it would improve program performance and it got significantly worse, leaving the user with little recourse. I'm not sure what we can do better here, but this doesn't seem like much of a resolution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:45:18 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:45:18 -0000 Subject: [GHC] #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic In-Reply-To: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> References: <046.6179459a606dda455f09a96c2a4bfb98@haskell.org> Message-ID: <061.adede673c7f3c5741abeca20021e47da@haskell.org> #14538: forkprocess01 fails occassionally on with multiple ACQUIRE_LOCK panic -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Runtime System | Version: 8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #1391, #9295, | Differential Rev(s): Phab:D4460 #9296, #14431 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: 8.4.2 => 8.4.1 Comment: Merged in 0dc2a358a954b0b858e91843ade52bb0a28c392d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:45:55 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:45:55 -0000 Subject: [GHC] #14431: Peculiar RTS crash on OS X In-Reply-To: <046.50af1b780509b4198d8903bef0dbcaf2@haskell.org> References: <046.50af1b780509b4198d8903bef0dbcaf2@haskell.org> Message-ID: <061.202969164890e310c1202a86befd79b6@haskell.org> #14431: Peculiar RTS crash on OS X ---------------------------------+---------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14538 | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * milestone: => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:47:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:47:35 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin In-Reply-To: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> References: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> Message-ID: <061.54e9bd46b4e9c4f0c78e16a433105eb4@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: hvr Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:47:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:47:54 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.ccaae43667b28252048c2cb1f2e7c9e4@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate 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:D615 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 16:48:17 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 16:48:17 -0000 Subject: [GHC] #14251: LLVM Code Gen messes up registers In-Reply-To: <047.9ece2514d7c7f668525c93ec15fb841a@haskell.org> References: <047.9ece2514d7c7f668525c93ec15fb841a@haskell.org> Message-ID: <062.18d79ac0dd460dffc467a1a5fe8ca171@haskell.org> #14251: LLVM Code Gen messes up registers -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (LLVM) | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): What happened to this? It sounds like this bug is still at large. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 17:12:31 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 17:12:31 -0000 Subject: [GHC] #14901: dsrun004 fails with most ways Message-ID: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> #14901: dsrun004 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: dsrun004 | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The `dsrun004` test doesn't seem to pass for a whole bunch of ways, as a recent `./validate --slow` (against yesterday's master) revealed. {{{#!py # the test options test('dsrun014', normal, compile_and_run, ['-fobject-code']) }}} {{{#!hs -- the haskell program we build & run {-# LANGUAGE UnboxedTuples #-} module Main where import Debug.Trace {-# NOINLINE f #-} f :: a -> b -> (# a,b #) f x y = x `seq` y `seq` (# x,y #) g :: Int -> Int -> Int g v w = case f v w of (# a,b #) -> a+b main = print (g (trace "one" 1) (trace "two" 2)) -- The args should be evaluated in the right order! }}} {{{ # the failing ways /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (hpc) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (optasm) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (threaded2) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (dyn) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (optllvm) }}} With those 5 ways, the program's trace is `two` then `one` while with some other ways (like ghci or normal) we get (as expected by the testsuite) `one` first and `two` afterwards. I'm not sure whether the expectation is too strong or whether there's something fishy going on with those 5 ways. Simon, could you perhaps comment on this? Is this a "proper" bug? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 18:58:31 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 18:58:31 -0000 Subject: [GHC] #14902: GHC HEAD cannot be booted GHC 8.4.1 Message-ID: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> #14902: GHC HEAD cannot be booted GHC 8.4.1 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 get this when I try to boot GHC HEAD with GHC 8.4.1 (using official binaries): {{{ $ make ===--- building phase 0 make --no-print-directory -f ghc.mk phase=0 phase_0_builds utils/genprimopcode/ghc.mk:19: utils/genprimopcode/dist/package-data.mk: No such file or directory utils/deriveConstants/ghc.mk:19: utils/deriveConstants/dist/package- data.mk: No such file or directory utils/genapply/ghc.mk:23: utils/genapply/dist/package-data.mk: No such file or directory libraries/hpc/ghc.mk:3: libraries/hpc/dist-boot/package-data.mk: No such file or directory libraries/binary/ghc.mk:3: libraries/binary/dist-boot/package-data.mk: No such file or directory libraries/text/ghc.mk:3: libraries/text/dist-boot/package-data.mk: No such file or directory libraries/transformers/ghc.mk:3: libraries/transformers/dist-boot/package- data.mk: No such file or directory libraries/mtl/ghc.mk:3: libraries/mtl/dist-boot/package-data.mk: No such file or directory libraries/parsec/ghc.mk:3: libraries/parsec/dist-boot/package-data.mk: No such file or directory libraries/Cabal/Cabal/ghc.mk:3: libraries/Cabal/Cabal/dist-boot/package- data.mk: No such file or directory libraries/ghc-boot-th/ghc.mk:3: libraries/ghc-boot-th/dist-boot/package- data.mk: No such file or directory libraries/ghc-boot/ghc.mk:3: libraries/ghc-boot/dist-boot/package-data.mk: No such file or directory libraries/template-haskell/ghc.mk:3: libraries/template-haskell/dist-boot /package-data.mk: No such file or directory libraries/terminfo/ghc.mk:3: libraries/terminfo/dist-boot/package-data.mk: No such file or directory libraries/ghci/ghc.mk:3: libraries/ghci/dist-boot/package-data.mk: No such file or directory compiler/ghc.mk:446: compiler/stage1/package-data.mk: No such file or directory utils/hsc2hs/ghc.mk:21: utils/hsc2hs/dist/package-data.mk: No such file or directory utils/ghc-pkg/ghc.mk:70: utils/ghc-pkg/dist/package-data.mk: No such file or directory ghc/ghc.mk:111: ghc/stage1/package-data.mk: No such file or directory "inplace/bin/ghc-cabal" configure libraries/binary dist-boot --with- ghc="/home/omer/ghc_bins/ghc-8.4.1-bin/bin/ghc" --with-ghc- pkg="/home/omer/ghc_bins/ghc-8.4.1-bin/bin/ghc-pkg" --package- db=/home/omer/haskell/ghc/libraries/bootstrapping.conf --disable-library- for-ghci --enable-library-vanilla --enable-library-for-ghci --disable- library-profiling --disable-shared --configure-option=CFLAGS="-Wall -fno- stack-protector -Werror=unused-but-set-variable -Wno-error=inline" --configure- option=LDFLAGS=" " --configure-option=CPPFLAGS=" " --gcc-options="-Wall -fno-stack-protector -Werror=unused-but-set-variable -Wno-error=inline " --constraint "binary == 0.8.5.1" --constraint "text == 1.2.3.0" --constraint "transformers == 0.5.5.0" --constraint "mtl == 2.2.2" --constraint "parsec == 3.1.13.0" --constraint "Cabal == 2.2.0.0" --constraint "hpc == 0.6.0.3" --constraint "ghc-boot-th == 8.5" --constraint "ghc-boot == 8.5" --constraint "template-haskell == 2.13.0.0" --constraint "ghci == 8.5" --constraint "terminfo == 0.4.1.1" --with-gcc="gcc" --with-ld="ld.gold" --with-ar="ar" --with- alex="/home/omer/.local/bin/alex" --with- happy="/home/omer/.local/bin/happy" Warning: binary.cabal:19:24: unexpected unknown build-type: 'Simple' Simple ghc-cabal: dieVerbatim: user error (ghc-cabal: Failed parsing "./binary.cabal". ) libraries/binary/ghc.mk:3: recipe for target 'libraries/binary/dist-boot /package-data.mk' failed make[1]: *** [libraries/binary/dist-boot/package-data.mk] Error 1 Makefile:122: recipe for target 'all' failed make: *** [all] Error 2 }}} Switching to 8.2.1 works fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:00:52 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:00:52 -0000 Subject: [GHC] #14902: GHC HEAD cannot be booted GHC 8.4.1 In-Reply-To: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> References: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> Message-ID: <058.464275891cdde93ea6f8ca5ad0504092@haskell.org> #14902: GHC HEAD cannot be booted GHC 8.4.1 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 osa1): * version: 8.5 => 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:01:50 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:01:50 -0000 Subject: [GHC] #14902: GHC HEAD cannot be booted with GHC 8.4.1 (was: GHC HEAD cannot be booted GHC 8.4.1) In-Reply-To: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> References: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> Message-ID: <058.843e8708e246774e211a445d31b40008@haskell.org> #14902: GHC HEAD cannot be booted with GHC 8.4.1 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:03:06 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:03:06 -0000 Subject: [GHC] #14903: RISC-V port Message-ID: <046.3830c4aba1ac1c459127346e87521431@haskell.org> #14903: RISC-V port -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- At least three people recently mentioned interest in a RISC-V port of GHC. As it turns out, I started down this road one weekend last year. This ticket will track this effort. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:03:50 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:03:50 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.3489b3f2c8898b13dd57420e5e6950ec@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Phab:D4478 Wiki Page: | -------------------------------------+------------------------------------- Comment (by mniip): I don't hold any strong opinion on how the shadowed identifiers should behave, but whichever way it is, I don't think an error similar to one in #11547 is appropriate. Perhaps it is best to hide the `Ghci#` modules in renamer too? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:06:05 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:06:05 -0000 Subject: [GHC] #14902: GHC HEAD cannot be booted with GHC 8.4.1 In-Reply-To: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> References: <043.016a3788cb924dba7d82567fd39dedeb@haskell.org> Message-ID: <058.2219c6e1f1cb8e3ad9109024e3919f2f@haskell.org> #14902: GHC HEAD cannot be booted with GHC 8.4.1 -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 hvr): Strange, I wasn't able to reproduce this -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:07:03 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:07:03 -0000 Subject: [GHC] #14903: RISC-V port In-Reply-To: <046.3830c4aba1ac1c459127346e87521431@haskell.org> References: <046.3830c4aba1ac1c459127346e87521431@haskell.org> Message-ID: <061.6865f00a59bbfedd1cd83e1d86c33b48@haskell.org> #14903: RISC-V port -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I rebased my [[https://github.com/bgamari/ghc/tree/riscv|branch]] which sets the groundwork for building GHC targetting RISC-V using the LLVM backend. When I started this effort in Fall of 2016 there was no usable LLVM support for RISC-V. Today the situation is a bit better with the [[LowRISC port|https://github.com/lowRISC/riscv-llvm/]]. Someone will need to add support for the GHC calling convention to this port. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:10:52 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:10:52 -0000 Subject: [GHC] #14699: Core library status for 8.4.1 In-Reply-To: <046.12f775ea02060174a5ac178f457055aa@haskell.org> References: <046.12f775ea02060174a5ac178f457055aa@haskell.org> Message-ID: <061.96c54dbccc6a584db2ff98528f9985f2@haskell.org> #14699: Core library status for 8.4.1 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: The release is out! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:18:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:18:54 -0000 Subject: [GHC] #12870: Allow completely disabling +RTS options parsing In-Reply-To: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> References: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> Message-ID: <057.c7c50c8886970a62e02573624d2ad3a8@haskell.org> #12870: Allow completely disabling +RTS options parsing -------------------------------------+------------------------------------- Reporter: nh2 | Owner: AndreasK Type: feature request | Status: closed Priority: normal | Milestone: 8.4.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): Phab:D3740 Wiki Page: | -------------------------------------+------------------------------------- Comment (by AndreasK): Replying to [comment:8 alpmestan]: > I'm seeing quite a few failures related to the `T12870*` tests in a run of `./validate --slow` with master from yesterday. > > First, _all_ those tests fail with the `ghci` way, because `ghci` doesn't see that those modules are declared as `module Main where ...` and have a `main` function, and reports an error about this. > > I'm also not sure what `-rtsopts=ignoreAll` is about, I don't see anything being ignored, only some more options being given to the program and reported. This makes it hard to expect the same output from a test executed under different ways. I didn't test these using the slow run when I wrote these tests. https://phabricator.haskell.org/D4486 should fix the tests. Thanks for reporting this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:19:27 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:19:27 -0000 Subject: [GHC] #12870: Allow completely disabling +RTS options parsing In-Reply-To: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> References: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> Message-ID: <057.9f9cf6ec04dc7c49138b923ec91219aa@haskell.org> #12870: Allow completely disabling +RTS options parsing -------------------------------------+------------------------------------- Reporter: nh2 | Owner: AndreasK Type: feature request | Status: closed Priority: normal | Milestone: 8.4.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): Phab:D3740 Wiki Page: | Phab:D4486 -------------------------------------+------------------------------------- Changes (by AndreasK): * differential: Phab:D3740 => Phab:D3740 Phab:D4486 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:34:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:34:57 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.6a24dca7833f472b0a40f7bb14280f8d@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Phab:D4478 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ömer Sinan Ağacan ): In [changeset:"98c7749cd360293bee96034056e260d70224cef6/ghc" 98c7749/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="98c7749cd360293bee96034056e260d70224cef6" Revert "GHCi: Don't remove shadowed bindings from typechecker scope." This reverts commit 59d7ee53906b9cee7f279c1f9567af7b930f8636 and enables the test for #14052. (See #14052 for the discussion) Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14052 Differential Revision: https://phabricator.haskell.org/D4478 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 19:38:29 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 19:38:29 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.8cd66912057354b79b607e8e749929d5@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: merge Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Phab:D4478 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: patch => merge Comment: Agreed that the error message is bad. We should probably reopen #11547 or open a new ticket to improve it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 20:25:18 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 20:25:18 -0000 Subject: [GHC] #14740: Unboxed tuple allowed in context: ((##)) => () In-Reply-To: <051.8b8e98ba0843035c110393441bb1b895@haskell.org> References: <051.8b8e98ba0843035c110393441bb1b895@haskell.org> Message-ID: <066.88a212f2c7fc1843733ba4f9aa38cadd@haskell.org> #14740: Unboxed tuple allowed in context: ((##)) => () -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: sighingnow Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.5 (Parser) | Resolution: | Keywords: UnboxedTuples Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T14740 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4359 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: 8.6.1 => 8.4.2 Comment: It looks like this didn't make it into 8.4.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 21:48:42 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 21:48:42 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.21661fae0e01fe10f136e48504021a11@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 ulysses4ever): * owner: (none) => ulysses4ever Comment: I have one more question about `tcLookupGlobal` (hope the last one for it). Here its part: {{{ if nameIsLocalOrFrom (tcg_semantic_mod env) name then notFound name -- Internal names can happen in GHCi else }}} I have trouble with `notFound` part which essentially does careful error- reporting inside `Tc` monad. I'm lost on how to port this to IO with the same amount of precision. So far I come up with dumb solution (to be placed in the `then` branch): {{{ pprPanic "lookupGlobal" (ppr name) }}} It is probably not good enough. Or is it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 22:05:21 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 22:05:21 -0000 Subject: [GHC] #14335: Plugins don't work with -fexternal-interpreter In-Reply-To: <046.25c38c823cb7fca986641ffde5e3cbd0@haskell.org> References: <046.25c38c823cb7fca986641ffde5e3cbd0@haskell.org> Message-ID: <061.e82dcb4d689ac0d893c61e2051b95d1f@haskell.org> #14335: Plugins don't work with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T14335 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4456 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"bc95fedc0b1f45b62ba279f7df834c490c2e53b6/ghc" bc95fedc/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bc95fedc0b1f45b62ba279f7df834c490c2e53b6" Error message and doc improvements for #14335 - Show a more friendly error message when -fplugin is used with -fexternal-interpreter - Add a few words to users guide about the interaction with -fplugin and -fexternal-interpreter - Update test for #14335 Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14335 Differential Revision: https://phabricator.haskell.org/D4456 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 22:06:03 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 22:06:03 -0000 Subject: [GHC] #12959: GHC doesn't warn about missing implementations for class methods beginning with an underscore In-Reply-To: <050.f1c049718f4b94fba939144b405d48bc@haskell.org> References: <050.f1c049718f4b94fba939144b405d48bc@haskell.org> Message-ID: <065.c48458d704f10923ef55c55a9079e597@haskell.org> #12959: GHC doesn't warn about missing implementations for class methods beginning with an underscore -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) 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: Other | Test Case: | warnings/minimal/WarnMinimal.hs Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2849, Wiki Page: | Phab:D4476 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"47e2a28d8c8c80aa9309ceb195ee8671b5a76d3e/ghc" 47e2a28/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="47e2a28d8c8c80aa9309ceb195ee8671b5a76d3e" Remove outdated documentation bits concerning -Wmissing-methods In commit 503219e3e1667ac39607021b2d9586260fbab32b, we stopped suppressing `-Wmissing-methods` warnings on class methods whose names begin with an underscore. However, it seems the users' guide documentation concerning this was never updated. Let's do so. Test Plan: Read it Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #12959 Differential Revision: https://phabricator.haskell.org/D4476 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 8 22:07:06 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 08 Mar 2018 22:07:06 -0000 Subject: [GHC] #14335: Plugins don't work with -fexternal-interpreter In-Reply-To: <046.25c38c823cb7fca986641ffde5e3cbd0@haskell.org> References: <046.25c38c823cb7fca986641ffde5e3cbd0@haskell.org> Message-ID: <061.8f53c4170df709b9d45f72b760ba6ae1@haskell.org> #14335: Plugins don't work with -fexternal-interpreter -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T14335 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4456 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 00:22:21 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 00:22:21 -0000 Subject: [GHC] #14904: Compiler panic (piResultTy) Message-ID: <047.da803a71fb92b792256c7a85e0a6a6bc@haskell.org> #14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: 14873 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Type-checking the following type family {{{#!hs type family F (f :: forall a. g a) :: Type where F (f :: forall a. g a) = Int }}} panics with the message: {{{#!txt ghc: panic! (the 'impossible' happened) (GHC version 8.4.0.20180118 for x86_64-apple-darwin): piResultTy k_aVM[tau:1] a_aVF[sk:1] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:950:35 in ghc:Type }}} The panic happens with HEAD, 8.4 and 8.2. 8.0 rejects the program with an error message, but even it panics on the following version: {{{#!hs type family F f :: Type where F ((f :: forall a. g a) :: forall a. g a) = Int }}} #14873 seemed somewhat related, so I tried with the patch implemented in 3d252037234ce48f9bdada7d5c9b1d8eba470829, but that fails with the same panic too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 00:23:44 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 00:23:44 -0000 Subject: [GHC] #14904: Compiler panic (piResultTy) In-Reply-To: <047.da803a71fb92b792256c7a85e0a6a6bc@haskell.org> References: <047.da803a71fb92b792256c7a85e0a6a6bc@haskell.org> Message-ID: <062.f43e26833bb29d8395500635bc4343e2@haskell.org> #14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kcsongor): * Attachment "Bug.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 02:16:45 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 02:16:45 -0000 Subject: [GHC] #3353: Add CLDouble support In-Reply-To: <044.199bb36c514cf1226e0efa905a8fa4ca@haskell.org> References: <044.199bb36c514cf1226e0efa905a8fa4ca@haskell.org> Message-ID: <059.46cb6f5f19e4ab267a55839d95aaf09f@haskell.org> #3353: Add CLDouble support -------------------------------------+------------------------------------- Reporter: igloo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.12.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 claude): Replying to [comment:8 simonmar]: > As a workaround, code that needs `CLDouble` can go via a C wrapper that takes a `CLDouble *`. Avoid manipulating `CLDouble` directly in Haskell, just talk in terms of pointers to `CLDouble`. I recently had such a need, so wrote a small package to help: https://hackage.haskell.org/package/long-double -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 02:53:41 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 02:53:41 -0000 Subject: [GHC] #14904: Compiler panic (piResultTy) In-Reply-To: <047.da803a71fb92b792256c7a85e0a6a6bc@haskell.org> References: <047.da803a71fb92b792256c7a85e0a6a6bc@haskell.org> Message-ID: <062.b7e9cfde9f86db5e2b7dea1838cd12c2@haskell.org> #14904: Compiler panic (piResultTy) -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 14873 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType Comment: This is clearly in my wheelhouse... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 06:27:08 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 06:27:08 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.4ccfe53f42802164b4764a8132ed59f1@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Confirmed on 8.4.1 and HEAD (8.5.20180308). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 07:44:54 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 07:44:54 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin In-Reply-To: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> References: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> Message-ID: <061.07a8a66ecab8fd168be966d2230ced26@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: hvr Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:1 bgamari]: > {{{ > =====> T9262(ext-interp) 1 of 1 [0, 0, 0] > cd "./th/T9262.run" && "/Users/bgamari/bin- dist-8.4.1-Darwin/ghc/inplace/bin/ghc-stage2" -c T9262.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show- caret -dno-debug-output -XTemplateHaskell -package template-haskell -fexternal-interpreter -v0 > Compile failed (exit code 1) errors were: > ghc-iserv.bin: > lookupSymbol failed in relocateSection (RELOC_GOT) > /Users/bgamari/bin-dist-8.4.1-Darwin/ghc/libraries/integer-gmp/dist- install/build/HSinteger-gmp-1.0.1.0.o: unknown symbol `___gmp_rands' > ghc-stage2: unable to load package `integer-gmp-1.0.1.0' > }}} Alex discovered, this had been reported already some time ago at https://mail.haskell.org/pipermail/ghc-devs/2017-June/014325.html I also noticed that GHC 8.4.1 for OSX uses the in-tree GMP library; while all tests/validation I did on OSX, where with some system-installed libgmp 6.x -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 09:27:46 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 09:27:46 -0000 Subject: [GHC] #14900: Calling isByteArrayPinned# on compact ByteArray In-Reply-To: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> References: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> Message-ID: <064.5634e9595fb14f1b9f925ab5a9b94677@haskell.org> #14900: Calling isByteArrayPinned# on compact ByteArray -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4485 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"df2ea10655984234924ad9f2c237289ab8f4baa6/ghc" df2ea106/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="df2ea10655984234924ad9f2c237289ab8f4baa6" Compacted arrays are pinned for isByteArrayPinned# Test Plan: New unit test Reviewers: andrewthad, niteria, bgamari, erikd Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14900 Differential Revision: https://phabricator.haskell.org/D4485 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 09:32:03 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 09:32:03 -0000 Subject: [GHC] #14900: Calling isByteArrayPinned# on compact ByteArray In-Reply-To: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> References: <049.9fb383d33a5d4236e45fb3d51a2074e8@haskell.org> Message-ID: <064.7a8c5379a00838fa01ea2b8382cbb022@haskell.org> #14900: Calling isByteArrayPinned# on compact ByteArray -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.2.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:D4485 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 10:14:05 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 10:14:05 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.4f593ac1e8c39e2e3321e462c9722233@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => debugger -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 10:22:49 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 10:22:49 -0000 Subject: [GHC] #4009: can newtype be extended to permit GADT-like declarations In-Reply-To: <041.a1e8d53315c3ae56ae87418383fc51e1@haskell.org> References: <041.a1e8d53315c3ae56ae87418383fc51e1@haskell.org> Message-ID: <056.7a3ee6512aabab177c0d3693fb19850a@haskell.org> #4009: can newtype be extended to permit GADT-like declarations -------------------------------------+------------------------------------- Reporter: nr | Owner: simonpj Type: feature request | Status: closed Priority: normal | Milestone: 7.0.1 Component: Compiler (Type | Version: 6.12.1 checker) | Resolution: invalid | Keywords: newtype GADT Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sighingnow): In ghc-8.2.1 and ghc-head, `newtype` definition in comment:2 is disallowed. But The following definition is accepted by GHC: {{{#!hs newtype T a where MkT :: a -> T a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 12:10:20 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 12:10:20 -0000 Subject: [GHC] #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint Message-ID: <043.599dc42c545c1acae74a2386e576be96@haskell.org> #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.5 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Steps to reproduce: - Compile stage2 with `-debug` - Run GHCi with `+RTS -Di` - Load an interpreted module with a definition, set a breakpoint on the definition - Evaluate the definition GHCi crashes with a segfault. Backtrace: {{{ #0 0x00007ffff18bcaa9 in disInstr (bco=0x4200013f30, pc=1) at rts/Disassembler.c:71 #1 0x00007ffff18c89e9 in interpretBCO (cap=0x7ffff19431c0 ) at rts/Interpreter.c:986 #2 0x00007ffff18d19fe in schedule (initialCapability=0x7ffff19431c0 , task=0x7fffe0000910) at rts/Schedule.c:471 #3 0x00007ffff18d4ee2 in scheduleWorker (cap=0x7ffff19431c0 , task=0x7fffe0000910) at rts/Schedule.c:2553 #4 0x00007ffff18ccab8 in workerStart (task=0x7fffe0000910) at rts/Task.c:444 #5 0x00007ffff0c3c6ba in start_thread (arg=0x7fffee9aa700) at pthread_create.c:333 #6 0x00007ffff06f241d in clone () at ../sysdeps/unix/sysv/linux/x86_64/clone.S:109 }}} in this line: {{{ 71 debugBelch(" %s\n", ((CostCentre*)(literals[instrs[pc+3]]))->label); }}} `literals[instrs[pc+3]]` is null. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 12:42:33 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 12:42:33 -0000 Subject: [GHC] #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint In-Reply-To: <043.599dc42c545c1acae74a2386e576be96@haskell.org> References: <043.599dc42c545c1acae74a2386e576be96@haskell.org> Message-ID: <058.43aee3e8654962423bb63c77d00c078f@haskell.org> #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 8.5 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:D4490 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D4490 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 13:46:16 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 13:46:16 -0000 Subject: [GHC] #14906: Release notes have wrong version of base package Message-ID: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> #14906: Release notes have wrong version of base package -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Documentation | Version: 8.4.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 library version table introduced in the release notes in e4dc2cd51902a8cd83476f861cf52996e5adf157 claims that GHC 8.4.1 includes `base-2.1`. See https://downloads.haskell.org/~ghc/8.4.1/docs/html/users_guide/8.4.1-notes.html #included-libraries. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 14:09:34 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 14:09:34 -0000 Subject: [GHC] #14907: Error message: (%, %) shows up when with accidental paren Message-ID: <051.2e9709c3004b74af6c52b8b012de4b6f@haskell.org> #14907: Error message: (%,%) shows up when with accidental paren -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I accidentally wrote an extra closing parens in instance declaration {{{#!hs $ ghci -ignore-dot-ghci -XRankNTypes GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Prelude> class (Category (Src f), forall xx. xx => Eq xx)) => Functor f :1:8: error: Unexpected type ‘Category (Src f)’ In the class declaration for ‘GHC.Classes.(%,%)’ A class declaration should have form class GHC.Classes.(%,%) a b where ... Prelude> }}} `(%,%)` shouldn't show up here, same happens on 8.5.20180105 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 14:09:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 14:09:48 -0000 Subject: [GHC] #14907: Error message: (%, %) shows up when with accidental paren In-Reply-To: <051.2e9709c3004b74af6c52b8b012de4b6f@haskell.org> References: <051.2e9709c3004b74af6c52b8b012de4b6f@haskell.org> Message-ID: <066.e30c0e29d656252315f4db6a474d836e@haskell.org> #14907: Error message: (%,%) shows up when with accidental paren -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: Old description: > I accidentally wrote an extra closing parens in instance declaration > > {{{#!hs > $ ghci -ignore-dot-ghci -XRankNTypes > GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help > Prelude> class (Category (Src f), forall xx. xx => Eq xx)) => Functor f > > :1:8: error: > Unexpected type ‘Category (Src f)’ > In the class declaration for ‘GHC.Classes.(%,%)’ > A class declaration should have form > class GHC.Classes.(%,%) a b where ... > Prelude> > }}} > > `(%,%)` shouldn't show up here, same happens on 8.5.20180105 New description: I accidentally wrote an extra closing parens in instance declaration {{{ $ ghci -ignore-dot-ghci -XRankNTypes GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Prelude> class (Category (Src f), forall xx. xx => Eq xx)) => Functor f :1:8: error: Unexpected type ‘Category (Src f)’ In the class declaration for ‘GHC.Classes.(%,%)’ A class declaration should have form class GHC.Classes.(%,%) a b where ... Prelude> }}} `(%,%)` shouldn't show up here, same happens on 8.5.20180105 -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 14:21:25 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 14:21:25 -0000 Subject: [GHC] #14769: The RecompBecause [TH] check is not resume-build-safe In-Reply-To: <042.f54ba8f2fbf63135b78d7e32176ce748@haskell.org> References: <042.f54ba8f2fbf63135b78d7e32176ce748@haskell.org> Message-ID: <057.a75085bb77b4ba6b9f72633bdb3ef3b4@haskell.org> #14769: The RecompBecause [TH] check is not resume-build-safe -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #481 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): > I'd argue that removing the possibility to access an unsafePerformIO- based number generator at all would be an even stronger guarantee that non-determinism cannot be introduced, is that not accurate? Certainly, but there is a reason we use uniques: they allow very cheap comparison. Recovering this in a language with no sense of identity of pure values is not easy and I don't believe we are willing to eat the compile time regressions that would likely come from dropping uniques from the compiler. Of course, if you can show a rework of a subset of the compiler that doesn't regress in performance while avoiding a unique source, we would be quite interested. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 14:34:47 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 14:34:47 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.fa3b0445a77035f833a24ead8042df89@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4472 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): So I'm a bit unsure of how to proceed. On one hand, I can see the argument for consistency and having a uniform interface to these primitives across Haskell implementations (e.g. GHC, GHCJS, an eventual WebAssembly implementation, Eta) is nice. On the other, this uniform interface could likely be as-easily provided in a library. Given the relatively small size of the patch and the fact that we seem to agree that this will be the last such primop (since this is indeed the only C99 memory primitive that we lack), I'm not particularly opposed to merging it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 17:49:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 17:49:31 -0000 Subject: [GHC] #14890: Make Linux slow validate green In-Reply-To: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> References: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> Message-ID: <061.a12b11a44aca83fc782e68d86cdcedc9@haskell.org> #14890: Make Linux slow validate green -------------------------------------+------------------------------------- Reporter: bgamari | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 alpmestan): I have a preliminary summary in a gist [https://gist.github.com/alpmestan/c371840968f086c8dc5b56af8325f0a9 here]. I've started taking actions to address the failures I've looked at (unexpected passes & failures, haven't looked at the stats failures yet), I'll update the gist with links to tickets etc as I address each unexpected test result. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 18:58:10 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 18:58:10 -0000 Subject: [GHC] #14907: Error message: (%, %) shows up when with accidental paren In-Reply-To: <051.2e9709c3004b74af6c52b8b012de4b6f@haskell.org> References: <051.2e9709c3004b74af6c52b8b012de4b6f@haskell.org> Message-ID: <066.cce11a6e77f234996b40c06938b617a8@haskell.org> #14907: Error message: (%,%) shows up when with accidental paren -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): An even simpler example: {{{#!hs class (A, B) }}} {{{ $ /opt/ghc/8.2.2/bin/ghc Bug.hs [1 of 1] Compiling Main ( Bug.hs, Bug.o ) Bug.hs:1:8: error: Unexpected type ‘A’ In the class declaration for ‘GHC.Classes.(%,%)’ A class declaration should have form class GHC.Classes.(%,%) a b where ... | 1 | class (A, B) | ^ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 19:31:21 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 19:31:21 -0000 Subject: [GHC] #14906: Release notes have wrong version of base package In-Reply-To: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> References: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> Message-ID: <061.ae563147948c75eeb4be8b22094b63a7@haskell.org> #14906: Release notes have wrong version of base package -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: Documentation | Version: 8.4.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:D4491 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D4491 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 9 20:51:45 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 09 Mar 2018 20:51:45 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.be4509105fe7245c0c561dbec4974f74@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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:12 simonpj]: > You want to write a ''term-level'' function that can be used a theorem in solving ''type-level'' constraints. That's right. Here are some thoughts I have on a [https://gist.github.com/ekmett/b26363fc0f38777a637d#file-categories- hs-L84 meatier example] I just ran into. Each category in `hask` has an associated constraint for objects (`Ob cat a`). If `a` is an object of `Dom f` and `f` is a functor then `f a` must be an object of `Cod f` {{{#!hs ob :: Functor f => Ob (Dom f) a :- Ob (Cod f) (f a) ob = Sub (source (fmap id)) }}} Constructing this relies crucially on `fmap` and friends at the term level. The user has to pry `ob` open (at the right type) (here they just wanted to write `id = Nat id`) {{{#!hs id = Nat id1 where id1 :: forall f x. (Functor f, Ob (Dom f) x) => Cod f (f x) (f x) id1 = id \\ (ob :: Ob (Dom f) x :- Ob (Cod f) (f x)) }}} It actually works today to add this implication to the superclass context of `Functor f` but GHC will not use it and refuses to take our (term- level) `ob` into account {{{#!hs type MapOb f = (forall x. Ob (Dom f) x => Ob (Cod f) (f x) :: Constraint) class (MapOb f, ..) => Functor f .. }}} I see several issues for what I just presented 1. `Dom` / `Cod` are type families (#14860) 2. We can't convert from `a :- b` to `Dict (a => b)` (#14822) 3. Ignoring **1.** / **2.** for now, how can we even use `ob` to witness `MapOb f`? One idea is to allow pattern matching outside of `case` expressions or indeed outside any definition, so we could write {{{#!hs reifyC :: (a :- b) -> Dict (a => b) reifyC = error "let's assume this for a second" class MapOb f => Functor f where -- This brings `MapOb f' into scope for the whole instance Dict <- reifyC (ob @_ @_ @f) }}} Am I off base here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 05:03:10 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 05:03:10 -0000 Subject: [GHC] #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL In-Reply-To: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> References: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> Message-ID: <061.de519f7e9e00468752a625507f94603f@haskell.org> #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.3 Component: Build System | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13304 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by arvindd): I am just trying to install iHaskell on WSL, and in the process, I am hit also by this bug. The bug specifically occurs when I am installing one of its dependencies via stack: "stack install gtk2hs-buildtools". The error I get is: ghc-cabal: Cannot find the program 'ghc'. User-specified path '/home/athas/sandbox/ghc-8.2.2/inplace/bin/ghc-stage1' does not refer to an executable and the program is not on the system path. Is there some possibility that this bug is solved in the near future? (GHC 8.4.1 is just released, and I assume the problem still exists there - although I am yet to install the same on my machine.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 06:59:59 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 06:59:59 -0000 Subject: [GHC] #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint In-Reply-To: <043.599dc42c545c1acae74a2386e576be96@haskell.org> References: <043.599dc42c545c1acae74a2386e576be96@haskell.org> Message-ID: <058.e0cf3dcec1148207c908d832d15406f8@haskell.org> #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 8.5 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:D4490 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ömer Sinan Ağacan ): In [changeset:"8e3410134bd7419db638988d74fcc600b03e2a1a/ghc" 8e341013/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8e3410134bd7419db638988d74fcc600b03e2a1a" Fix a debug print in disassembler (#14905) When interpreter is not profiled (see `interpreterProfiled` in `DynFlags`) bytecode generator generates a NULL pointer as the cost centre of a `BRK_FUN` instruction: let cc | interpreterProfiled dflags = cc_arr ! tick_no | otherwise = toRemotePtr nullPtr let breakInstr = BRK_FUN (fromIntegral tick_no) (getUnique this_mod) cc return $ breakInstr `consOL` code We now take this into account when disassembling `BRK_FUN`. Reviewers: bgamari, simonmar, erikd Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4490 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 07:01:17 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 07:01:17 -0000 Subject: [GHC] #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint In-Reply-To: <043.599dc42c545c1acae74a2386e576be96@haskell.org> References: <043.599dc42c545c1acae74a2386e576be96@haskell.org> Message-ID: <058.504929271c380182fd93a41f0c79be38@haskell.org> #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: GHCi | Version: 8.5 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:D4490 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 10:57:08 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 10:57:08 -0000 Subject: [GHC] #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL In-Reply-To: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> References: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> Message-ID: <061.25caf636ef195aa37abf282f54937514@haskell.org> #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.3 Component: Build System | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13304 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sjakobi): Replying to [comment:13 arvindd]: I can't shed any light on the bug, but in case you're just looking for a working setup, you should give hvr's [https://launchpad.net/~hvr/+archive/ubuntu/ghc-wsl ghc-wsl PPA] a try. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 16:58:15 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 16:58:15 -0000 Subject: [GHC] #4442: Add unaligned version of indexWordArray# In-Reply-To: <044.4c85d11a3d9c22b5e6021cb85ad43106@haskell.org> References: <044.4c85d11a3d9c22b5e6021cb85ad43106@haskell.org> Message-ID: <059.aad515b63474640e48be3e583846b4c5@haskell.org> #4442: Add unaligned version of indexWordArray# -------------------------------------+------------------------------------- Reporter: tibbe | Owner: reinerp Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #14447 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by reinerp): * owner: (none) => reinerp -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 17:17:26 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 17:17:26 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.70a4c8144b1b288487bed287517b9654@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): I tried to reproduce this on GHC 8.2.1, but it builds cleanly, both with `__impossible` and `undefined`. I'm using the current `master` branch though, because the specified commit doesn't seem to exist in any of the exposed branches anymore. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 17:21:21 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 17:21:21 -0000 Subject: [GHC] #14908: Compiling using O1 works but panic using O2 or O3 Message-ID: <047.c822350a57bec20839dcef893a4ae20d@haskell.org> #14908: Compiling using O1 works but panic using O2 or O3 -------------------------------------+------------------------------------- Reporter: josejuan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 17:28:35 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 17:28:35 -0000 Subject: [GHC] #14908: Compiling using O1 works but panic using O2 or O3 In-Reply-To: <047.c822350a57bec20839dcef893a4ae20d@haskell.org> References: <047.c822350a57bec20839dcef893a4ae20d@haskell.org> Message-ID: <062.bb0aa09e6319a834cbe31ff9b523d09a@haskell.org> #14908: Compiling using O1 works but panic using O2 or O3 -------------------------------------+------------------------------------- Reporter: josejuan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by josejuan): * Attachment "panic_files.tar.gz" added. Complete project folder and reproducible behavior. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 17:46:09 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 17:46:09 -0000 Subject: [GHC] #14908: Compiling using O1 works but panic using O2 or O3 In-Reply-To: <047.c822350a57bec20839dcef893a4ae20d@haskell.org> References: <047.c822350a57bec20839dcef893a4ae20d@haskell.org> Message-ID: <062.e6736c1aac0d038df54f79d20c32a422@haskell.org> #14908: Compiling using O1 works but panic using O2 or O3 -------------------------------------+------------------------------------- Reporter: josejuan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To be clear, this is the panic that results: {{{ $ $(pwd)/../../../Software/ghc-8.0.2/bin/ghc Bug.hs -O2 -fforce-recomp [1 of 1] Compiling Main ( Bug.hs, Bug.o ) ghc.exe: panic! (the 'impossible' happened) (GHC version 8.0.2 for x86_64-unknown-mingw32): Simplifier ticks exhausted When trying UnfoldingDone $srec_s9Kw To increase the limit, use -fsimpl-tick-factor=N (default 100) If you need to do this, let GHC HQ know, and what factor you needed To see detailed counts use -ddump-simpl-stats Total ticks: 59242 }}} I can't reproduce this panic with GHC 8.2.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 18:18:08 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 18:18:08 -0000 Subject: [GHC] #4442: Add unaligned version of indexWordArray# In-Reply-To: <044.4c85d11a3d9c22b5e6021cb85ad43106@haskell.org> References: <044.4c85d11a3d9c22b5e6021cb85ad43106@haskell.org> Message-ID: <059.1ddedcd87f82a67d2ffa97f974b288c4@haskell.org> #4442: Add unaligned version of indexWordArray# -------------------------------------+------------------------------------- Reporter: tibbe | Owner: reinerp Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #14447 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 18:20:25 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 18:20:25 -0000 Subject: [GHC] #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# In-Reply-To: <048.a76989facca9d2ef0c59d6b7bfd86029@haskell.org> References: <048.a76989facca9d2ef0c59d6b7bfd86029@haskell.org> Message-ID: <063.4be6df9a0bfb18d3e87c7397237fff99@haskell.org> #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #4442 | Differential Rev(s): Phab:D4433 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * related: => #4442 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 19:07:00 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 19:07:00 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.8cb161853052dcb8571c129ff2adeb7d@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): As it turns out, the bug that tysonzero discovered has nothing to do with TH whatsoever (which is ostensibly what this bug report is about), but instead with a deficiency of `ld`. See [https://github.com/yesodweb/persistent/issues/794#issuecomment-372056256 here] for the full story. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 19:09:22 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 19:09:22 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.412732774d336bc574b06629a5cd99a5@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 ulysses4ever): So far I've replaced error-reporting for `TcM` (`notFound`, `failWithTc`) with `pprPanic`. Now I have full version of `lookupGlobal` in `IO` ([https://gist.github.com/ulysses4ever/2b1f3eb7bf0e2779cb1cd30249ec735c link]). It doesn't seem to break any test (besides already broken ones). Should I submit it to the Phabricator or proceed with the second part pointed out by Joachim, `thNameToGhcName`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 10 19:46:58 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 10 Mar 2018 19:46:58 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.7404bd0de5784bfa71384ae9f982fbaf@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): As far as the original ticket goes, I'm stumped. I tried to construct a minimal Template Haskell program which should eat up memory by causing a space leak: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where $(let f :: Int -> a f x = f (x + 1) in f 0) }}} I tried compiling this on GHC 8.2.2 with and without `-O2`, but despite it using all of my 8GB of memory available, this didn't trigger a segfault. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 01:14:09 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 01:14:09 -0000 Subject: [GHC] #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL In-Reply-To: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> References: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> Message-ID: <061.cd9fc226b9e252d42dd478af7624b7c8@haskell.org> #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.3 Component: Build System | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13304 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by arvindd): Thanks, let me try. I notice that the packages are for Ubuntu, and I am using OpenSUSE on WSL. I just need to figure out a way to rebuild those sources on OpenSUSE / find a similar thing on the rpm repositories. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 01:16:07 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 01:16:07 -0000 Subject: [GHC] #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL In-Reply-To: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> References: <046.d4cadd0de18785a85fd44eaf74dce48e@haskell.org> Message-ID: <061.991ad408226eac42ea667d4e5d94732f@haskell.org> #14021: 8.2.1 deb8 bindist fails to install on Windows 10 WSL -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.3 Component: Build System | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13304 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by arvindd): Replying to [comment:14 sjakobi]: > Replying to [comment:13 arvindd]: > > I can't shed any light on the bug, but in case you're just looking for a working setup, you should give hvr's [https://launchpad.net/~hvr/+archive/ubuntu/ghc-wsl ghc-wsl PPA] a try. Thanks, let me try. I notice that the packages are for Ubuntu, and I am using OpenSUSE on WSL. I just need to figure out a way to rebuild those sources on OpenSUSE / find a similar thing on the rpm repositories. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 01:51:04 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 01:51:04 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.68ee111a07302aeee9c9ed73e57c84c8@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 sighingnow): Replying to [comment:26 RyanGlScott]: > which should eat up memory by causing a space leak If we put a strictness annotations on `x` then the space leak will disappear. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 01:54:06 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 01:54:06 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.0850b997205dca6ea4c46c69f9d0120a@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 RyanGlScott): I think you misinterpreted my comment. I'm //deliberately// writing a program with a space leak, in hopes of triggering the segfault that was originally reported. (I wasn't successful, but that's beside the point.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 02:31:35 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 02:31:35 -0000 Subject: [GHC] #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. In-Reply-To: <044.8846313dfa837f257582237983583132@haskell.org> References: <044.8846313dfa837f257582237983583132@haskell.org> Message-ID: <059.b355bdbe05524fbee5ef4ca4897361c4@haskell.org> #13112: Windows 64-bit GHC HEAD segfaults on the code with a lot of TH stuff. ---------------------------------+-------------------------------------- Reporter: awson | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.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 sighingnow): Opps, my bad, sorry for the nise. I have deleted my previous comment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 03:40:22 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 03:40:22 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.06c7b3f556a6e59a7a9e1bffbf6290d8@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by zilinc): Replying to [comment:11 tdammers]: > I tried to reproduce this on GHC 8.2.1, but it builds cleanly, both with `__impossible` and `undefined`. I'm using the current `master` branch though, because the specified commit doesn't seem to exist in any of the exposed branches anymore. The commit is still there. But I totally believe that you could not reproduce it on an arbitrary commit, otherwise it would be easier to figure out what crashed the compiler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 04:17:07 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 04:17:07 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.8eb39210cf43bca5b05855144fd95451@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by zilinc: Old description: > The error message I got from GHC was: > > {{{ > : error: > ghc: panic! (the 'impossible' happened) > (GHC version 8.2.2 for x86_64-unknown-linux): > idInfo > t_XG0J > Call stack: > CallStack (from HasCallStack): > prettyCurrentCallStack, called at > compiler/utils/Outputable.hs:1133:58 in ghc:Outputable > callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in > ghc:Outputable > pprPanic, called at compiler/basicTypes/Var.hs:526:34 in ghc:Var > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} > > How was it triggerred (in short): > There's function definition, `f x = undefined`. If I change it to `f x = > __impossible "Oops!"`, ghc crashes. If I change it to `f x = error > "Oops!"`, it's OK. The definition of `__impossible` is simply > `__impossible s = error $ s ++ "some text"`. > > The code can be found here: > https://github.com/NICTA/cogent/blob/92c40530cbcbac77469865e096dab3228a2fb92f/cogent/src/Cogent/Desugar.hs#L482 > and > https://github.com/NICTA/cogent/blob/92c40530cbcbac77469865e096dab3228a2fb92f/cogent/src/Cogent/Compiler.hs#L30 > > It seems that this bug is not limited to 8.2.2; it also happened in > 8.2.1. > > I'm happy to provide more information, if someone can advice me what is > needed. I'll also try to shrink it to a small test case. New description: The error message I got from GHC was: {{{ : error: ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): idInfo t_XG0J Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Var.hs:526:34 in ghc:Var Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} How was it triggerred (in short): There's function definition, `f x = undefined`. If I change it to `f x = __impossible "Oops!"`, ghc crashes. If I change it to `f x = error "Oops!"`, it's OK. The definition of `__impossible` is simply `__impossible s = error $ s ++ "some text"`. The code can be found here: https://github.com/NICTA/cogent/blob/9420861128a8c445138aa6a48c62140d8c5f72eb/cogent/src/Cogent/Desugar.hs#L482 and https://github.com/NICTA/cogent/blob/9420861128a8c445138aa6a48c62140d8c5f72eb/cogent/src/Cogent/Compiler.hs#L30 It seems that this bug is not limited to 8.2.2; it also happened in 8.2.1. I'm happy to provide more information, if someone can advice me what is needed. I'll also try to shrink it to a small test case. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 10:27:54 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 10:27:54 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.c59d022b19f3fe01302db1377c1733d8@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 ulysses4ever): Actually, I don't see `thNameToGhcName` used anywhere (on master). So it could be (relatively) freely moved. Maybe `TcSplice`, which it depends upon, is the right place for it? In that case the return type's monad, probably, should be changed from `CoreM` to plain `IO`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 10:38:21 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 10:38:21 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.85411173e2aa6cd5c285282053ce4d0b@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate 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:D615 Wiki Page: | -------------------------------------+------------------------------------- Changes (by michalt): * cc: michalt (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 11:45:25 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 11:45:25 -0000 Subject: [GHC] #4459: Polymorphic Data.Dynamic In-Reply-To: <045.440a383f1785f051b223292e48377c3f@haskell.org> References: <045.440a383f1785f051b223292e48377c3f@haskell.org> Message-ID: <060.34721c7ad2b5074625b6f87716ed94a2@haskell.org> #4459: Polymorphic Data.Dynamic -------------------------------------+------------------------------------- Reporter: vivian | Owner: vivian Type: feature request | Status: new Priority: low | Milestone: Component: GHC API | Version: 7.1 Resolution: | Keywords: polymorphic, | dynamic, class, linking Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 4316 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mentheta): * cc: mentheta (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 14:24:17 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 14:24:17 -0000 Subject: [GHC] #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking In-Reply-To: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> References: <050.9e589019d6eb1fc4987004e5aa20a3e4@haskell.org> Message-ID: <065.66bc4a3192a7c1c5620d648f9a3b231a@haskell.org> #14899: Significant compilation time regression between 8.4 and HEAD due to coverage checking -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): (Warning: half-baked thoughts follow.) For reasons that I don't fully understand, it seems that coverage-checking guards is not nearly as efficient as coverage-checking raw constructor patterns. In that case, a question arises: why are we desugaring coercion patterns (like what data family constructors give you) to guards? It seems that we could handle coercion patterns in a fairly natural way by extending the algorithm from [https://www.microsoft.com/en-us/research/wp- content/uploads/2016/08/gadtpm-acm.pdf GADTs Meet Their Match] slightly. First, we could extend the pattern syntax (figure 2 from the GADTs Meet Their Match paper) to include coercion patterns directly: {{{ p,x ::= x | K p_1 ... p_n | G | (p |> co) }}} Where `co : τ_1 ~ τ_2` is a coercion. Then, we could extend the coverage checking algorithm in figure 3 to include a case for coercion patterns. For instance: {{{ C ((p |> co) q_1 ... q_n) (Γ ⊢ u_0 u_1 ... u_n ⊳ Δ) = C (p q_1 ... q_n) (Γ, y : τ_1 ⊢ y u_0 u_1 ... u_n ⊳ Δ') where Γ ⊢ p : τ_1 Γ ⊢ u_o : τ_2 Γ ⊢ c : τ_1 ~ τ_2 y#Γ Δ' = Δ ∪ u ≈ (p |> co) }}} And similarly for U and D. That way, we wouldn't need guards at all here—we'd just have an extra case for coercion patterns that "pushes through" the types as necessary. Does this sound plausible? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 15:19:20 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 15:19:20 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.f97d4783d2e36c2de01c412a508f3e42@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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 nomeata): `thNameToGhcName` is useful for GHC plugins, so any module reexported by `GhcPlugins` (or maybe even that module itself) is a good place. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 16:49:19 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 16:49:19 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.ad9ac981d82047fd015744e2955ea799@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * Attachment "T14774.zip" added. Self-contained test case for T14777 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 16:49:50 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 16:49:50 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.24ec69de405e42f55c70edcf60429d12@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sighingnow): I have create a self-contained minimal case (still have several files but only depends on base, mtl and containers) that can trigger this panic. I **can** reproduce this panic with ghc-8.2.1 (nightly-2017-11-24) and ghc-8.2.2 (lts-10.3/lts-10.4) but **cannot** with ghc-8.4.1 and ghc-head. Maybe it has already been fixed. I also have test with with ghc-8.0.1 (lts-9.4) but also failed to trigger the panic with this minimal case. Step to reproduce with ghc-8.2.2: unzip and enter `src`, then {{{ stack exec --resolver=lts-10.4 -- ghc Cogent.Desugar -fforce-recomp -O2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 17:44:10 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 17:44:10 -0000 Subject: [GHC] #14909: Change default armhf target to a newer architecture Message-ID: <044.27d87d6827047d9a351acb29d7974fea@haskell.org> #14909: Change default armhf target to a newer architecture -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: arm | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently the default [https://github.com/ghc/ghc/blob/60b06456ddef08bd8a8a47497a6cbefbb5e359fb /llvm-targets#L4 llvm-targets] file specifies the default `arm-unknown- linux-gnueabihf` target to be using `-mcpu=arm1176jzf-s`. Which is an `Armv6` architecture. This has the problem that it's generating memory barriers using `CP15` instructions that are deprecated in `Armv7` and removed in `Armv8`. Because of this there's no way to run the binaries being produced by GHC HQ on Armv8 CPUs without having kernel support for `CP15 Barrier emulation.` which is slow. We're also not taking advantage of new Armv8 instructions this way. The debian folks have a bug report about this as well https://bugs.debian.org/cgi-bin/bugreport.cgi?bug=864847 This means that GHC cannot work on most boards people have/can easily buy today. I think the default target should be an `Armv7` architecture at the very least. But realistically `Armv8` would probably be ok as well as I doubt many people use GHC to compile on older cores. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 17:49:24 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 17:49:24 -0000 Subject: [GHC] #14909: Change default armhf target to a newer architecture In-Reply-To: <044.27d87d6827047d9a351acb29d7974fea@haskell.org> References: <044.27d87d6827047d9a351acb29d7974fea@haskell.org> Message-ID: <059.3f13be18962a047015a83f4166a741b5@haskell.org> #14909: Change default armhf target to a newer architecture ---------------------------------------+------------------------------ Reporter: Phyx- | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler (CodeGen) | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------------+------------------------------ Comment (by Phyx-): `generic` may work as well, as long as `llvm` doesn't generate the deprecated instructions then. Ideally, we should take the `-mcpu` option at configure time. And GHC should take it when calling llvm. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 18:13:07 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 18:13:07 -0000 Subject: [GHC] #14910: Bump required autoconf version Message-ID: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> #14910: Bump required autoconf version -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Autoconf should be set to a minimum of 2.69, to avoid this bug https://bugs.ruby-lang.org/issues/8179 specifically if using e.g. autoconf 2.64 things will fail with: {{{ configure:1510: error: possibly undefined macro: _m4_text_wrap_word If this token and others are legitimate, please use m4_pattern_allow. See the Autoconf documentation. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 18:13:40 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 18:13:40 -0000 Subject: [GHC] #14909: Change default armhf target to a newer architecture In-Reply-To: <044.27d87d6827047d9a351acb29d7974fea@haskell.org> References: <044.27d87d6827047d9a351acb29d7974fea@haskell.org> Message-ID: <059.37ee294e3cdc6aa6e06de1cac7805cb1@haskell.org> #14909: Change default armhf target to a newer architecture ---------------------------------------+------------------------------ Reporter: Phyx- | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (CodeGen) | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------------+------------------------------ Changes (by Phyx-): * version: 8.5 => 8.4.1 * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 20:57:23 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 20:57:23 -0000 Subject: [GHC] #14910: Bump required autoconf version In-Reply-To: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> References: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> Message-ID: <059.948ea756cca4d5c7cc46d92193249d31@haskell.org> #14910: Bump required autoconf version -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4495 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D4495 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 23:13:14 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 23:13:14 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.0f4077fb4be4df0db7ae0ccc1d5dc11c@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hvr): * status: closed => new * resolution: invalid => Comment: This unfortunately resurfaced in https://github.com/haskell/cabal/issues/5201 and is unfortunately quite easy to reproduce to the point of blocking `cabal` on GHC 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 23:15:28 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 23:15:28 -0000 Subject: [GHC] #14044: ghc-8.2.1 installation fails on OpenBSD 6.0 In-Reply-To: <053.45e29a06adb0c5bb94922ac641df7af0@haskell.org> References: <053.45e29a06adb0c5bb94922ac641df7af0@haskell.org> Message-ID: <068.14817bcbbd64932155d174e2beba2e58@haskell.org> #14044: ghc-8.2.1 installation fails on OpenBSD 6.0 -------------------------------------+------------------------------------- Reporter: romanzolotarev | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: None | Version: 8.2.1 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Installing GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: #14041 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * milestone: Research needed => Comment: This probably isn't a good topic for academic research. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 23:17:14 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 23:17:14 -0000 Subject: [GHC] #12043: internal error: evacuate: strange closure type In-Reply-To: <047.629114b05785e472aaf473c1aa71fdb1@haskell.org> References: <047.629114b05785e472aaf473c1aa71fdb1@haskell.org> Message-ID: <062.d93ad21fedd08958485b7ccf922ebfcc@haskell.org> #12043: internal error: evacuate: strange closure type ----------------------------------+------------------------------ Reporter: mattchan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: ia64 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+------------------------------ Changes (by sjakobi): * milestone: Research needed => Comment: This probably isn't a good topic for academic research. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 11 23:24:37 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 11 Mar 2018 23:24:37 -0000 Subject: [GHC] #13982: HEAD GHC+Cabal uses too much memory In-Reply-To: <044.c3b9c5d7c4e9062eebc02e4b69dbd535@haskell.org> References: <044.c3b9c5d7c4e9062eebc02e4b69dbd535@haskell.org> Message-ID: <059.8966776dc1189a16cfca810ad67c0eb9@haskell.org> #13982: HEAD GHC+Cabal uses too much memory -------------------------------------+------------------------------------- Reporter: mniip | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: libraries | Version: 8.3 (other) | Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hvr): * status: new => closed * resolution: => duplicate Comment: closing in favor of #13930 which contains more information and pointers to recently filed issues in the cabal issue tracker. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 03:01:17 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 03:01:17 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.159698b5930a4fbe8876b7ab6bf2f612@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by monoidal): * Attachment "Cogent.zip" added. smaller reproduction testcase -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 03:11:42 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 03:11:42 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.2d50f64464137513e39b19c693a4b19f@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): I have simplified a bit further, to 2 files; can be reproduced with {{{ ghc-8.2.1 --make Cogent/Desugar -fforce-recomp -O2 }}} This doesn't appear on ghc 8.4 - likely this was fixed. However, the panic depends on many conditions, even small changes to code can make it disappear, so it might be worth further investigation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 07:28:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 07:28:56 -0000 Subject: [GHC] #4459: Polymorphic Data.Dynamic In-Reply-To: <045.440a383f1785f051b223292e48377c3f@haskell.org> References: <045.440a383f1785f051b223292e48377c3f@haskell.org> Message-ID: <060.21bbfcb775950aeb3f55484e7ca19b2b@haskell.org> #4459: Polymorphic Data.Dynamic -------------------------------------+------------------------------------- Reporter: vivian | Owner: vivian Type: feature request | Status: new Priority: low | Milestone: Component: GHC API | Version: 7.1 Resolution: | Keywords: polymorphic, | dynamic, class, linking Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 4316 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by spl): * cc: leather@… (removed) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 07:35:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 07:35:28 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks Message-ID: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.6.1 Component: Core | Version: 8.4.1 Libraries | Keywords: CallStacks | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Sometimes, I may want to capture some information that can be reported when an error occurs. Suppose I have {{{#!hs f x y = g x (h y) g :: HasCallStack => ... g x y = ..... (error "whoopsy") .... }}} I may want `f` to record information about `y` that will be reported if `g` throws an exception. As far as I can tell, the only currently supported way to do this is horrible and limited: {{{#!hs f x y = unsafeDupablePerformIO $ catch (evaluate (g x (h y))) $ \e -> .... }}} I'd much rather have a function like {{{#!hs addMessage :: HasCallStack => String -> (HasCallStack => a) -> a }}} This would stick a string into the current call stack "frame" and call the argument. I imagine this can be implemented directly with the underlying implicit parameter, likely with a slight change to the `CallStack` representation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 07:45:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 07:45:36 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.908c7fa53b379ff969936558a6d425f4@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I took a peek at monoidal's reproduction, using a devel2 build of 8.2.2 with some extra `HasCallStack`s. Running with Core Lint and `-O2`, I get {{{ [2 of 2] Compiling Cogent.Desugar ( Cogent/Desugar.hs, Cogent/Desugar.o ) WARNING: file compiler/simplCore/OccurAnal.hs, line 69 Glomming in Cogent.Desugar: [s55P :-> OnceL!] ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): idInfo v_X5mQ Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Var.hs:526:34 in ghc:Var idInfo, called at compiler/basicTypes/Id.hs:736:37 in ghc:Id idInlinePragma, called at compiler/basicTypes/Id.hs:745:49 in ghc:Id idInlineActivation, called at compiler/simplCore/SimplUtils.hs:923:56 in ghc:SimplUtils getUnfoldingInRuleMatch, called at compiler/simplCore/Simplify.hs:1946:34 in ghc:Simplify tryRules, called at compiler/simplCore/Simplify.hs:1776:22 in ghc:Simplify }}} (I have no idea if the lint warning is relevant). About all I can see about what's gone wrong is that something seems to be treating a type variable as though it were a term variable. That is, if I understand the `Var` type properly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 07:47:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 07:47:24 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.2a195cbc9257e7e5826e91940dc49d1b@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 08:18:41 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 08:18:41 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.478954fc3efac6188c0cbaa55f03280c@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): Here's a very rough draft. This can be written without modifying the `CallStack` type, but I imagine it would be better to modify that. {{{#!hs extraCS :: HasCallStack => String -> (HasCallStack => a) -> a extraCS s a = let cs = ?callStack in let ?callStack = case cs of EmptyCallStack -> EmptyCallStack PushCallStack x y z -> PushCallStack (x ++ " (" ++ s ++ ")") y z q@(FreezeCallStack _) -> q in a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 08:46:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 08:46:19 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.860298d99f11dfa8fee491ea126e3821@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:16 dfeuer]: > About all I can see about what's gone wrong is that something seems to be treating a type variable as though it were a term variable. That is, if I understand the `Var` type properly. I've been suspecting some sort of type/term confusion myself - neither `error` nor `undefined` should, conceptually speaking, throw the type checker off guard, and they shouldn't produce different behavior as far as the types are concerned (both `error "Something"` and `undefined` are `forall a. a`, essentially), yet swapping one for the other seems to toggle the panic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 09:28:14 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 09:28:14 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.19d93df97841f77d828a77f0167cc028@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Managed to reproduce the panic on 8.2.1; GHC HEAD builds cleanly. Defining the following function in `Surface.hs`, and using that instead of any calls to `__impossible` in `Desugar.hs`, also allows me to build cleanly on 8.2.1: {{{ __impossibleDef :: a __impossibleDef = error "impossible" }}} The unmodified example also builds cleanly without optimizations. Which suggests that some optimization pass produces a situation that hits a bug somewhere, and that the difference between `__impossible` and `__impossibleDef` is enough to trigger or not trigger it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 09:33:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 09:33:36 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.d163bfb609fb6b5435c7e665a917f607@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Further, the following both get rid of the panic: - Moving `__impossible` into `Desugar.hs` - Declaring `{-#INLINE __impossible #-}` Both would lead to GHC inlining `__impossible`. This would explain how it is possible for seemingly benign changes to influence the appearance of the panic - changing small things would change the inlining heuristics, and bug may or may not be hit depending on the intermediate code (Core / STG) being generated. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 09:54:06 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 09:54:06 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.15c3421dddf00ab0457d961303a4e4f6@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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 like the idea. Worth a GHC proposal? Not because it'll be controversial, but because the debate often improves the design. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 11:24:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 11:24:24 -0000 Subject: [GHC] #14372: CMM contains a bunch of tail-merging opportunities In-Reply-To: <048.1c543d9c1482e4763ed7a0bf48a66309@haskell.org> References: <048.1c543d9c1482e4763ed7a0bf48a66309@haskell.org> Message-ID: <063.fc6e3b3b9c7d40003ac078fbe6e507a8@haskell.org> #14372: CMM contains a bunch of tail-merging opportunities -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: CodeGen Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14666 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by AndreasK): * cc: AndreasK (added) * related: => #14666 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 12:03:16 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 12:03:16 -0000 Subject: [GHC] #14372: CMM contains a bunch of tail-merging opportunities In-Reply-To: <048.1c543d9c1482e4763ed7a0bf48a66309@haskell.org> References: <048.1c543d9c1482e4763ed7a0bf48a66309@haskell.org> Message-ID: <063.ef59d768092668641a0d9c74a996ce3c@haskell.org> #14372: CMM contains a bunch of tail-merging opportunities -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: CodeGen Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14666 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 12:34:18 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 12:34:18 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.7e9c1b6cde02f6280825d69f60f66e09@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Ben asked me to provide the STG dumps of the module containing the `accum` function; original code as well the variant w/ the `ReadPackageIndexStrict` branch commented out respectively; I hadn't had time to look at those myself yet, so here they're unabridged: - https://gist.github.com/9fe0cc59b4414351ce0e03c21a068172 (original) - https://gist.github.com/759e338c8d841de9b3fb47d892fac398 (commented out `ReadPackageIndexStrict`) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 13:58:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 13:58:54 -0000 Subject: [GHC] #14912: UnsafeReenter test fails with threaded1 and threaded2 Message-ID: <048.0d06801876b264a33d0020ade629babb@haskell.org> #14912: UnsafeReenter test fails with threaded1 and threaded2 --------------------------------------+--------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.5 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: --------------------------------------+--------------------------------- {{{ /tmp/ghctest-n4fi8zlk/test spaces/./ffi/should_fail/UnsafeReenter.run UnsafeReenter [bad exit code] (threaded1) /tmp/ghctest-n4fi8zlk/test spaces/./ffi/should_fail/UnsafeReenter.run UnsafeReenter [bad exit code] (threaded2) }}} It's a quite simple program: {{{#!hs {-# LANGUAGE ForeignFunctionInterface #-} -- | Test that unsafe FFI calls crash the RTS if they attempt to re-enter -- Haskell-land module Main where import Foreign foreign import ccall "wrapper" wrap_f :: IO () -> IO (FunPtr (IO ())) foreign import ccall unsafe hello :: FunPtr (IO ()) -> IO () f :: IO () f = putStrLn "Back in Haskell" main :: IO () main = do putStrLn "In Haskell" wrap_f f >>= hello putStrLn "Finished" }}} This just seem to hang (until timeout) with the `threaded1` and `threaded2` ways, instead of erroring out with: {{{ UnsafeReenter: schedule: re-entered unsafely. Perhaps a 'foreign import unsafe' should be 'safe'? }}} which is the expected behaviour. I'll mark the test broken for those 2 ways in an upcoming patch, but this probably deserves a new ticket, so here it is. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 14:17:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 14:17:52 -0000 Subject: [GHC] #14913: testsuite driver does not honor `extra_run_opts` for the ghci way Message-ID: <048.b12dba8f90c9b100fd0346ef22bdd144@haskell.org> #14913: testsuite driver does not honor `extra_run_opts` for the ghci way -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.5 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 causes the `stack004` test to fail in the ghci way. Test declaration: {{{ test('stack004', [extra_run_opts('+RTS -K0 -RTS') ], compile_and_run, ['']) }}} Actual command executed by the testsuite driver: {{{ =====> stack004(ghci) 1 of 1 [0, 0, 0] cd "./rts/stack004.run" && "/home/alp/ghc/inplace/test spaces/ghc- stage2" stack004.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS < stack004.genscript Actual stdout output differs from expected: diff -uw "/dev/null" "./rts/stack004.run/stack004.run.stdout.normalised" --- /dev/null 2018-03-07 13:03:27.344000000 +0100 +++ ./rts/stack004.run/stack004.run.stdout.normalised 2018-03-08 11:53:55.339965000 +0100 @@ -0,0 +1 @@ +uh oh *** unexpected failure for stack004(ghci) }}} We can see that the extra `+RTS -K0 -RTS` options don't get passed to ghci. I'm marking `stack004` as broken for the ghci way for now, but we'll probably want to look into this at some point. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 14:24:38 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 14:24:38 -0000 Subject: [GHC] #11188: Confusing "parse error in pattern" for spurious indentation. In-Reply-To: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> References: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> Message-ID: <066.58531010ac609c5c5aeb889123ae7de5@haskell.org> #11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | 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): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * differential: => Phab:D4497 Comment: I think the problem here is not that it's suggesting adding more `do`s (it's saying "possibly", meaning the reason may be something else), but it's showing only a small part of the large expression that the parser considers as a pattern. I submitted Phab:D4497 to improve this. Previously the error message was: {{{ Main.hs:2:3: error: Parse error in pattern: putStrLn Possibly caused by a missing 'do'? | 2 | putStrLn "" $ do | ^^^^^^^^^^^ }}} this is not good enough because it doesn't show the whole part that's considered as a pattern. With Phab:D4497: {{{ Main.hs:2:3: error: Parse error in pattern: putStrLn "" $ do a <- return 3 c Possibly caused by a missing 'do'? putStrLn "" $ do a <- return 3 c | 2 | putStrLn "" $ do | ^^^^^^^^^^^^^^^^... }}} It's now clear that left hand side of second `<-` now covers the first `<-` because the whole part is shown. If the error message is still not good enough perhaps we can split the parsers for expressions and patterns (rather than using expression parser for patterns and then doing a check to see whether it's a valid pattern). In that case I think we'd still get a parse error in expression parser while parsing `return 3 c <- do ...` which would raise a better error message I think. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 14:27:31 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 14:27:31 -0000 Subject: [GHC] #11188: Confusing "parse error in pattern" for spurious indentation. In-Reply-To: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> References: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> Message-ID: <066.e01b0737fdf838669ede77bcd0711538@haskell.org> #11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * related: => #984 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 14:37:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 14:37:03 -0000 Subject: [GHC] #13844: Surprising behavior with CPP extension In-Reply-To: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> References: <044.323fec287ece7da9f882c4acbda76c83@haskell.org> Message-ID: <059.ba5faa7c6ce32dc0654acec2f50ae9bf@haskell.org> #13844: Surprising behavior with CPP extension -------------------------------------+------------------------------------- Reporter: deech | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Fwiw, this is old news. Here's an old proposal of mine that could lead us out of this misery: Proposal/NativeCpp Just needs somebody to implement it... :-) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 14:40:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 14:40:05 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.0c6e8c1189b25196206656409f703b54@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by monoidal): * Attachment "Cogent2.zip" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 14:41:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 14:41:12 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.2b783b395adee06ac98055512a1c1406@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): I've simplified the code further and the only dependencies now are Prelude, unsafePerformIO and GHC.Exts.lazy. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 15:07:15 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 15:07:15 -0000 Subject: [GHC] #12043: internal error: evacuate: strange closure type In-Reply-To: <047.629114b05785e472aaf473c1aa71fdb1@haskell.org> References: <047.629114b05785e472aaf473c1aa71fdb1@haskell.org> Message-ID: <062.b5033a6ba6e8a6d2af2cddf2a352003c@haskell.org> #12043: internal error: evacuate: strange closure type ----------------------------------+---------------------------------- Reporter: mattchan | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: MacOS X | Architecture: ia64 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+---------------------------------- Changes (by bgamari): * status: new => infoneeded Comment: Can someone confirm whether this is still reproducible? I'll close this if no one speaks up in the next month or so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 15:27:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 15:27:08 -0000 Subject: [GHC] #14711: Machine readable output of coverage In-Reply-To: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> References: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> Message-ID: <065.c23fef5f90ec82aee83facc096d575b8@haskell.org> #14711: Machine readable output of coverage -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Code Coverage | Version: 8.2.2 Resolution: | Keywords: newcomers 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 potomak): Can we consider this task as invalid or does it require to include also a JSON representation of the coverage output? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 15:32:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 15:32:09 -0000 Subject: [GHC] #12870: Allow completely disabling +RTS options parsing In-Reply-To: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> References: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> Message-ID: <057.f1a6a41051b0fa49919a721c2182cb13@haskell.org> #12870: Allow completely disabling +RTS options parsing -------------------------------------+------------------------------------- Reporter: nh2 | Owner: AndreasK Type: feature request | Status: closed Priority: normal | Milestone: 8.4.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): Phab:D3740 Wiki Page: | Phab:D4486 -------------------------------------+------------------------------------- Comment (by alpmestan): Thanks for the quick fix Andreas! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 15:59:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 15:59:54 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.3778a03c101c66cf6e8adc4b7e74fd7a@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Thanks, monoidal. Even if we don't understand what exactly is causing this error at the moment, we should probably check this in as a regression test, yes? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 16:35:17 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 16:35:17 -0000 Subject: [GHC] #13543: Improve demand analysis for join points In-Reply-To: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> References: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> Message-ID: <061.70f09d646a102a4668b40b1c4b477985@haskell.org> #13543: Improve demand analysis for join points -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): OK, I'll include this change in my WIP testsuite expectations changes patch and ask Simon about the "new" expected output (see below for the program & output). {{{#!hs {-# LANGUAGE RankNTypes, GADTs #-} module Foo where g :: (Int, Int) -> Int {-# NOINLINE g #-} g (p,q) = p+q f :: Int -> Int -> Int -> Int f x p q = g (let j y = (p,q) {-# NOINLINE j #-} in case x of 2 -> j 3 _ -> j 4) }}} {{{ ==================== Strictness signatures ==================== Foo.$trModule: m Foo.f: m Foo.g: m ==================== Strictness signatures ==================== Foo.$trModule: m Foo.f: m Foo.g: m }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 16:56:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 16:56:26 -0000 Subject: [GHC] #13543: Improve demand analysis for join points In-Reply-To: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> References: <046.3c4a77ff5e0e28a91ea42884fbdafb1b@haskell.org> Message-ID: <061.975e1ffcfcf0078d10e0a5829707fa1b@haskell.org> #13543: Improve demand analysis for join points -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 16:56:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 16:56:46 -0000 Subject: [GHC] #13366: addCStub doesn't allow control over compiler flags or source file file In-Reply-To: <046.e4d0ff069ca721205cf186e478fec23b@haskell.org> References: <046.e4d0ff069ca721205cf186e478fec23b@haskell.org> Message-ID: <061.32e8ac40befd23f0518b501cf6f96763@haskell.org> #13366: addCStub doesn't allow control over compiler flags or source file file -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: closed Priority: high | 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): Phab:D3280 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:02:40 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:02:40 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.1ad74a594ca95d96590f294edb87f63a@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D407 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) Comment: The T8089 test case fails for those 3 ways: {{{ /tmp/ghctest-n4fi8zlk/test spaces/../../libraries/base/tests/T8089.run T8089 [bad exit code] (ghci) /tmp/ghctest-n4fi8zlk/test spaces/../../libraries/base/tests/T8089.run T8089 [bad exit code] (threaded1) /tmp/ghctest-n4fi8zlk/test spaces/../../libraries/base/tests/T8089.run T8089 [bad exit code] (threaded2) }}} I'll mark those tests as expected broken for those 3 ways for now, is the above a manifestation of an actual, "serious" problem? Or simply a timeout program quirk? Depending on the answer, I might create a new ticket (as the problem doesn't seem immediately related to this ticket). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:12:49 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:12:49 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.20674a4ad172933f8e640999d1f7c9f9@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): I think the current test case is still too fragile to be checked in. For example, given the lines: {{{ desugarTlv Include = __impossible "desugarTlv" desugarTlv IncludeStd = __impossible "desugarTlv" desugarTlv FunDef = __impossible "desugarTlv" desugarTlv DocBlock = __impossible "desugarTlv" }}} the panic appears only if all four string literals are the same and nonempty. Removing any of the four lines makes the panic disappear. Removing of identifiers that are nowhere used such as `TypeDec`, `freshVars`, `_varCtx` also stops the panic from happening. The error can also be reproduced with `-O -fliberate-case -fspec-constr` instead of `-O2` but I didn't manage to break down `-O` to individual options and keep the panic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:18:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:18:03 -0000 Subject: [GHC] #10037: Several profiling tests give different results optimised vs. unoptimised In-Reply-To: <047.efcb9e013309246f2cfca887b5137899@haskell.org> References: <047.efcb9e013309246f2cfca887b5137899@haskell.org> Message-ID: <062.2cab590f4601d1c3b9e458912361d654@haskell.org> #10037: Several profiling tests give different results optimised vs. unoptimised -------------------------------------+------------------------------------- Reporter: simonmar | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4498 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D4498 Comment: Unfortunately we are still seeing non-determinism in the cost-centre order, leading to failures of `scc001` on CircleCI. I've opened Phab:D4498 as a possible fix for this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:20:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:20:57 -0000 Subject: [GHC] #14914: Only turn suitable targets into a fallthrough in CmmContFlowOpt. Message-ID: <047.e546ff075cab0520de14a4fd1c9b5069@haskell.org> #14914: Only turn suitable targets into a fallthrough in CmmContFlowOpt. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: (CodeGen) | 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: -------------------------------------+------------------------------------- We are inverting Branches in CmmContFlowOpt such that we get as many fall through paths as possible. However as it stands besides the conditionals themselves the only criterion used is the number of predecessors for a Block. This often (but not always) aligns with the actual possibility of turning branches into a fallthrough. We should at least look at the cost/benefit of tracking actual predecessors and see if that turns out as something worthwhile. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:21:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:21:47 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.a63038c2de5230489fa06edf39d4d93c@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): `-O2` is precisely `-O -fliberate-case -fspec-constr`. Sometimes the difference between `-O` and `-O2` can be that there there is an extra simplifier pass which runs after `-fliberate-case`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:23:39 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:23:39 -0000 Subject: [GHC] #14890: Make Linux slow validate green In-Reply-To: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> References: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> Message-ID: <061.c804c4abb636716c440103e609b90fe3@haskell.org> #14890: Make Linux slow validate green -------------------------------------+------------------------------------- Reporter: bgamari | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 alpmestan): I went ahead and took action for _all_ the unexpected passes and failures. See [https://github.com/alpmestan/ghc/commit/40d6393aca7742f6c26d93b3c3361cced08d55b3 this commit] in my GHC fork on github. I'm just going to ask for Simon PJ's input on 2-3 tests and will then proceed by pushing a diff on phabricator. I can then look into the stats failures if we so desire. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:27:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:27:22 -0000 Subject: [GHC] #4114: Add a flag to remove/delete intermediate files generated by GHC In-Reply-To: <044.5bde4abfdaa56d5ae586d71d6ff93b9d@haskell.org> References: <044.5bde4abfdaa56d5ae586d71d6ff93b9d@haskell.org> Message-ID: <059.e4ca9cc00d8b3bc1769d6c9b8c431831@haskell.org> #4114: Add a flag to remove/delete intermediate files generated by GHC -------------------------------------+------------------------------------- Reporter: guest | Owner: kaiha Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 6.10.4 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | driver/T4114a,b,c,d Blocked By: | Blocking: Related Tickets: #2258 | Differential Rev(s): Phab:D2021 Wiki Page: | Phab:D2050 -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:28:02 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:28:02 -0000 Subject: [GHC] #8542: Suggest NegativeLiterals In-Reply-To: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> References: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> Message-ID: <062.cbf330b3fce8a383db2328a28ae655a7@haskell.org> #8542: Suggest NegativeLiterals -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | numeric/should_fail/T8542 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:32:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:32:04 -0000 Subject: [GHC] #14915: T2783 fails with the threaded1 way Message-ID: <048.6a264df023f86951375f2289b1ed8d61@haskell.org> #14915: T2783 fails with the threaded1 way --------------------------------------+---------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.5 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: Runtime crash Test Case: T2783 | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+---------------------------------- When running `./validate --slow` the other day, I saw the XXX test failing with the `threaded1` way. Instead of detecting the loop and aborting with an informative message, we get an assertion failure in the `rts/ThreadPaused.c:threadPaused` function. The program: {{{#!hs main = print $ do x <- [ 0 .. 5 ] ; let { y = 5 - y } ; return y }}} The output: {{{ =====> T2783(threaded1) 1 of 1 [0, 0, 0] cd "./rts/T2783.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" -o T2783 T2783.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics- color=never -fno-diagnostics-show-caret -dno-debug-output -threaded -debug cd "./rts/T2783.run" && ./T2783 Wrong exit code for T2783(threaded1)(expected 1 , actual 134 ) Stderr ( T2783 ): T2783: internal error: ASSERTION FAILED: file rts/ThreadPaused.c, line 314 (GHC version 8.5.20180306 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) *** unexpected failure for T2783(threaded1) }}} The code for the corresponding assertion: {{{#!c // We should never have made it here in the event of blackholes that // we already own; they should have been marked when we blackholed // them and consequently we should have stopped our stack walk // above. ASSERT(!((bh_info == &stg_BLACKHOLE_info) && (((StgInd*)bh)->indirectee == (StgClosure*)tso))); }}} This seems to be an actual problem, hence this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 17:32:58 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 17:32:58 -0000 Subject: [GHC] #12870: Allow completely disabling +RTS options parsing In-Reply-To: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> References: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> Message-ID: <057.6b640b4c594bae8b655a827384ea16e9@haskell.org> #12870: Allow completely disabling +RTS options parsing -------------------------------------+------------------------------------- Reporter: nh2 | Owner: AndreasK Type: feature request | Status: closed Priority: normal | Milestone: 8.4.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): Phab:D3740 Wiki Page: | Phab:D4486 -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 18:30:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 18:30:10 -0000 Subject: [GHC] #13257: out-of-range warnings for negative literals, without -XNegativeLiterals In-Reply-To: <047.3e0304e938f8544e8155e6db1481b408@haskell.org> References: <047.3e0304e938f8544e8155e6db1481b408@haskell.org> Message-ID: <062.6d6d633a9db2852cd8e977adf0aa8c29@haskell.org> #13257: out-of-range warnings for negative literals, without -XNegativeLiterals -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: ruperthorlick Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deSugar/should_compile/T13257 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3281 Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): Is it correct not to warn about `-128 :: Int8` when `-XNegativeLiterals` is off? After all, without -XNegativeLiterals this means creating the overflowed integer `128 :: Int8` and only then negating it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 18:32:11 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 18:32:11 -0000 Subject: [GHC] #8542: Suggest NegativeLiterals In-Reply-To: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> References: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> Message-ID: <062.d8cd88818c72b4cfd8ca1c103886f471@haskell.org> #8542: Suggest NegativeLiterals -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | numeric/should_fail/T8542 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): Originally, we were giving this warning both to `128 :: Word8` and `-128 :: Word8`. In #13257 the code was modified to recognize the pattern `negate (fromIntegral x)`. I guess that HPC is modifying to code to be able to check for coverage of both the whole expression `negate (fromInteger x)` and the subexpression `fromInteger x`, and this causes the warning not to appear. Nothing to worry, I would just skip the test with this way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 19:06:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 19:06:03 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.03ff2c22ed70827cfcdb23ce80177f32@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I'll be happy to write a GHC proposal if you think that's appropriate. But do we need the full weight of that process for this change, or would a discussion on the libraries list be sufficient? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 12 21:17:14 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 12 Mar 2018 21:17:14 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.d196c4870d601a62b8f6c4c397c6e5b4@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I agree that this probably falls under the bar for a full proposal, given that this is simply a combinator that is defined in terms of the existing `base` API. A libraries mailing list discussion would suffice, in my view. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 08:05:45 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 08:05:45 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.f0744f22fb202b67dbf4ca541bb20f50@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): I'm a bit reluctant to brush this off as "the panic doesn't happen anymore on 8.4, so we must have fixed it somehow", because it could just be that we're now optimizing differently and the panic doesn't happen in this particular case anymore, but still might pop up in other situations. So I'm wondering whether we should: a) Just write up a suitable regression test, commit that, and see if it ever triggers again in the future. b) Actively go hunting for the source of this. Upside is that we would know whether the bug has been fixed or just masked; downside is that this is potentially very time consuming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 13:49:08 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 13:49:08 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.e82dddc92828fac6eb56c4e1841a2159@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I agree with Tobias in comment:25. Fortunately, thanks to all the helpful distillation done by others above, I was able to reproduce the bug, and I know precisely what is going on. Patch coming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 16:11:18 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 16:11:18 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.614f4b59af44b67fd88f47ffb50f4dc4@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => tdammers * priority: high => highest -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 16:15:49 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 16:15:49 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.09b7819c503f38ecee26ee9cdb705d96@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => simonpj * milestone: => 8.6.1 Comment: Simon PJ knows what is going on here and will take over this one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 16:29:25 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 16:29:25 -0000 Subject: [GHC] #14901: dsrun004 fails with most ways In-Reply-To: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> References: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> Message-ID: <063.8799c12d751e25509f1a06d63e9d40f9@haskell.org> #14901: dsrun004 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun004 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): This test was apparently added for #1031. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 18:11:39 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 18:11:39 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.9f0d8fb022ac92f7eaef33bdec22e9e8@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D407 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): What does the failed output look like? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 19:30:20 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 19:30:20 -0000 Subject: [GHC] #14916: Missing checks when deriving special classes Message-ID: <047.da5641b8bbed13bc8200a08817691187@haskell.org> #14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Poor/confusing Unknown/Multiple | error message Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- For the following program {{{ {-# LANGUAGE DeriveAnyClass #-} module T where import Data.Coerce import Data.Typeable data A = MkA deriving ((~) A) data B = MkB deriving (Coercible B) }}} the deriving clause for `A` is accepted without complaints, and the deriving clause for `B` fails with the following error: {{{ T.hs:8:24: error: Top-level bindings for unlifted types aren't allowed: | 8 | data B = MkB deriving (Coercible B) | ^^^^^^^^^^^ }}} Corresponding standalone deriving instances trigger errors saying "Manual instances of this class are not permitted". Probably similar error messages should be triggered here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 20:26:05 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 20:26:05 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position Message-ID: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple LevityPolymorphism | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The main problem with levity polymorphism in a binding position is that it's impossible to do codegen since the calling convention depending on the instantiation of the runtime representation variable. From the paper, we have the following rejected example code: {{{ bTwice :: ∀ (r :: RuntimeRep) (a :: TYPE r). Bool → a → (a → a) → a }}} However, if you are able to inline the function, this problem disappears. You would need a guarantee stronger than what the `INLINE` pragma provides though since the `INLINE` pragma still allows the function to be fed as an argument to a higher-order function. I'll refer to a hypothetical new pragma as `INLINE MANDATE`. This pragma causes a compile-time error to be admitted if the function is ever used in a way that would cause it to not be inlined. Now `bTwice` would be writeable: {{{ {-# INLINE MANDATE #-} bTwice :: ∀ (r :: RuntimeRep) (a :: TYPE r). Bool → a → (a → a) → a }}} The function definition would be provide in the `.hi` file just as it would be for a function marked as `INLINE`, but unlike the `INLINE` counterpart, there would be no generated code for this function, since generating the code would be impossible. I have several uses for this in mind. I often want a levity-polymorphic variant `ST`. With `INLINE MANDATE`, I still wouldn't get `do` notation, but I could write: {{{ -- This newtype is already allowed today newtype STL s (a :: TYPE r) = STL (State# s -> (# s, a #) #) intA, intB, intC :: STL s Int# wordA, wordB :: Int# -> STL s Word# {-# INLINE MANDATE #-} (>>=.) :: STL s a -> (a -> STL s b) -> STL s b STL a >>=. g = STL (\s0 -> case a s0 of (# s1, v #) -> case g v of STL f -> f s1 myFunc :: STL s Word# myFunc = intA >>=. \a -> intB >>=. \b -> intC >>=. \c -> wordA a >>=. \wa -> wordB b >>=. \wb -> ... -- do something with the data }}} I would appreciate any feedback on this. If there's something that makes this fundamentally impossible, that would be good to know. Or if other people feel like this would be useful, that would be good to know as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 20:48:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 20:48:33 -0000 Subject: [GHC] #8542: Suggest NegativeLiterals In-Reply-To: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> References: <047.bf5090fe22a22eb99898221a0c557cee@haskell.org> Message-ID: <062.f26491d3ecb93d6e2e5e4bdf5db5b74d@haskell.org> #8542: Suggest NegativeLiterals -------------------------------------+------------------------------------- Reporter: monoidal | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | numeric/should_fail/T8542 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Will do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 21:46:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 21:46:33 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.2279cd3c16ba64ad036556b333fa121a@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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 very cautious about this. Sometimes you can't inline. For example a recursive function. And {{{ f :: Int -> Int {-# INLINE f #-} f x = blah g xs = map f xs }}} I can't inline `f` here; or if I do I'll get a `\x`. In our paper we prove that, in our system, you never get a situation where you don't know the runtime reprsentation of a value you have to manipulate. I don't see how to produce a similar proof with weaker restrictions. Runtime code cloining, like .NET, is a good path. But it comes at a price! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 21:46:57 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 21:46:57 -0000 Subject: [GHC] #14916: Missing checks when deriving special classes In-Reply-To: <047.da5641b8bbed13bc8200a08817691187@haskell.org> References: <047.da5641b8bbed13bc8200a08817691187@haskell.org> Message-ID: <062.02f2366415fff9dc7a91a2e7ced91cfd@haskell.org> #14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Deriving -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 22:15:46 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 22:15:46 -0000 Subject: [GHC] #9724: reexport IsList class from a trustworthy module In-Reply-To: <044.b4b824d4864a7071bef003961687614b@haskell.org> References: <044.b4b824d4864a7071bef003961687614b@haskell.org> Message-ID: <059.fa6faaf014d4c0a1c6df969471fc7f34@haskell.org> #9724: reexport IsList class from a trustworthy module -------------------------------------+------------------------------------- Reporter: int-e | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.8.3 Resolution: | Keywords: SafeHaskell 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 kostmo): This issue also seems to block [https://github.com/Daniel-Diaz/sorted- list/pull/5 marking the `sorted-list` package as safe]. Does the `IsList` class (and its instances) depend on any unsafe functionality? If not, could a new marked-`Safe` module named `GHC.Exts.List` be created so that people can safely import this subset? `GHC.Exts.List` could then be re- exported from `GHC.Exts` for backwards-compatibility. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 22:40:20 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 22:40:20 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.6842bf1b016feab59a9bbbd2df001997@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): I agree that it isn’t always possible to inline. Higher order functions, like map, don’t allow it. Maybe the most accurate way to describe what I want is for there to be a way to make fully saturated calls to functions with levity polymorphic binders. It seems like it should be possible to perform a check for unsaturated calls. Recursive levity polymorphic functions would not be allowed, but there’s still a lot of useful stuff that could be done. Your point about the proof that the paper offers is good. My suggested addition would mess up that proof, which would be bad. What if (and this is total speculation since I don’t understand type theory) you had two universes that functions could live in. One universe is this one that we currently have. There are no levity polymorphic binders, and in this universe, you have the guarantee that you always know the runtime representation of values that need to be manipulated. In the second universe, levity polymorphism would be unrestricted. Technically, this universe would be a superset of the first one. But it may be helpful to think of them as separate universes since in GHC, codegen could only happen for functions in the first universe. Functions from 1 could be freely used in 2. Functions from 2 could be freely used in 2 as well. But, functions from 2 could not be freely used in 1. They would need to be specialized to satisfy the restrictions around levity polymorphism. In practice, this specialization would take the form of inlining. So, I guess that would mean that the function arrow would have a weird kind, since it could create types belonging to universe 1 or 2. And I have no idea how function application would typecheck. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 13 22:59:39 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 13 Mar 2018 22:59:39 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.7ebcfd1c928c81b2de931a7ac265940f@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D407 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Oops, forgot to include it in my previous comment. Here's what I get for say the 'ghci' way (same for threaded1 and threaded2 though): {{{ =====> T8089(ghci) 1 of 1 [0, 0, 0] cd "../../libraries/base/tests/T8089.run" && "/home/alp/ghc/inplace/test spaces/ghc-stage2" T8089.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output --interactive -v0 -ignore-dot-ghci -fno-ghci-history +RTS -I0.1 -RTS < T8089.genscript Wrong exit code for T8089(ghci) (expected 99 , actual 0 ) *** unexpected failure for T8089(ghci) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 00:15:03 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 00:15:03 -0000 Subject: [GHC] #14916: Missing checks when deriving special classes In-Reply-To: <047.da5641b8bbed13bc8200a08817691187@haskell.org> References: <047.da5641b8bbed13bc8200a08817691187@haskell.org> Message-ID: <062.e93e926da85f263f52ce5081b42d2b95@haskell.org> #14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4501 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4501 Comment: Luckily, fixing this is quite straightforward by using `checkValidInstHead`, which is what Phab:D4501 accomplishes. One thing that's interesting about `checkValidInstHead` is that is also does validity checks for `FlexibleInstances` and `MultiParamTypeClasses`. This means that using `checkValidInstHead`, unaltered, would result in this program, which is currently accepted by GHC: {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} module T where import Control.Monad.Reader newtype MyReader a = MyReader (Int -> a) deriving ( Functor, Applicative, Monad , MonadReader Int ) }}} Being rejected due to not enabling `FlexibleInstances` or `MultiParamTypeClasses`, since it generates `instance MonadReader Int MyReader`. I decided to err on the side of avoiding unnecessary breakage and tweaked `checkValidInstHead` so as to disable these checks for `deriving` clauses (just as we do for `SPECIALISE instance` pragmas today). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 00:56:28 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 00:56:28 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.8308db782544a8d93777d639b29f642c@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D407 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Can you try running this test manually? I strongly suspect that the testsuite driver elides the relevant part of the output. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 01:05:21 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 01:05:21 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.92426235be0c6bee5e49a1613880240f@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D407 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): For the record, the test in question is: {{{#!hs -- can be found in libraries/base/tests/T8089.hs import Control.Concurrent main :: IO () main = threadDelay maxBound }}} Building it (I copied the CLI arguments from the threaded1 run): {{{ $ inplace/bin/ghc-stage2 -o T8089 libraries/base/tests/T8089.hs -dcore- lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed- specialisations -fshow-warning-groups -fdiagnostics-color=never -fno- diagnostics-show-caret -dno-debug-output -threaded -debug [1 of 1] Compiling Main ( libraries/base/tests/T8089.hs, libraries/base/tests/T8089.o ) Linking T8089 ... }}} Running it: {{{ $ ./T8089 $ echo $? 0 }}} (the expected return code is 99, we get 0) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 01:32:53 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 01:32:53 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse Message-ID: <050.0ece8699aa4ecc920883092df1385787@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Keywords: deriving | 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: -------------------------------------+------------------------------------- (Originally noticed [here](https://github.com/ekmett/transformers- compat/issues/32).) Consider the following program: {{{#!hs {-# LANGUAGE MagicHash #-} module Bug where data T a = MkT { runT# :: a } deriving (Read, Show) t1, t2 :: T Int t1 = MkT 1 t2 = read $ show t1 main :: IO () main = print t2 }}} In GHC 8.2.1, this runs without issue: {{{ $ /opt/ghc/8.2.2/bin/runghc Bug.hs MkT {runT# = 1} }}} In GHC 8.4.1, however, this produces a runtime error: {{{ $ ~/Software/ghc-8.4.1/bin/runghc Bug.hs Bug.hs: Prelude.read: no parse }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 01:33:12 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 01:33:12 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.3900185b54f5eb173f8c34bc2eaaa8fb@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving 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: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description: > (Originally noticed [here](https://github.com/ekmett/transformers- > compat/issues/32).) > > Consider the following program: > > {{{#!hs > {-# LANGUAGE MagicHash #-} > module Bug where > > data T a = MkT { runT# :: a } > deriving (Read, Show) > > t1, t2 :: T Int > t1 = MkT 1 > t2 = read $ show t1 > > main :: IO () > main = print t2 > }}} > > In GHC 8.2.1, this runs without issue: > > {{{ > $ /opt/ghc/8.2.2/bin/runghc Bug.hs > MkT {runT# = 1} > }}} > > In GHC 8.4.1, however, this produces a runtime error: > > {{{ > $ ~/Software/ghc-8.4.1/bin/runghc Bug.hs > Bug.hs: Prelude.read: no parse > }}} New description: (Originally noticed [https://github.com/ekmett/transformers- compat/issues/32 here].) Consider the following program: {{{#!hs {-# LANGUAGE MagicHash #-} module Bug where data T a = MkT { runT# :: a } deriving (Read, Show) t1, t2 :: T Int t1 = MkT 1 t2 = read $ show t1 main :: IO () main = print t2 }}} In GHC 8.2.1, this runs without issue: {{{ $ /opt/ghc/8.2.2/bin/runghc Bug.hs MkT {runT# = 1} }}} In GHC 8.4.1, however, this produces a runtime error: {{{ $ ~/Software/ghc-8.4.1/bin/runghc Bug.hs Bug.hs: Prelude.read: no parse }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 01:41:23 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 01:41:23 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.12852a05176aa1a7fb02d78bc0b2b9cf@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14364 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: tdammers (added) * related: => #14364 Comment: Comparing the results of `-ddump-deriv` between GHC 8.2.1 and 8.4.1 is interesting. In GHC 8.2.1, we have: {{{ instance GHC.Read.Read a => GHC.Read.Read (Bug.T a) where GHC.Read.readPrec = GHC.Read.parens (Text.ParserCombinators.ReadPrec.prec 11 (do GHC.Read.expectP (Text.Read.Lex.Ident "MkT") GHC.Read.expectP (Text.Read.Lex.Punc "{") GHC.Read.expectP (Text.Read.Lex.Ident "runT") GHC.Read.expectP (Text.Read.Lex.Symbol "#") GHC.Read.expectP (Text.Read.Lex.Punc "=") a1_a2wO <- Text.ParserCombinators.ReadPrec.reset GHC.Read.readPrec GHC.Read.expectP (Text.Read.Lex.Punc "}") GHC.Base.return (Bug.MkT a1_a2wO))) GHC.Read.readList = GHC.Read.readListDefault GHC.Read.readListPrec = GHC.Read.readListPrecDefault }}} But in GHC 8.4.1, we have: {{{ instance GHC.Read.Read a => GHC.Read.Read (Bug.T a) where GHC.Read.readPrec = GHC.Read.parens (Text.ParserCombinators.ReadPrec.prec 11 (do GHC.Read.expectP (Text.Read.Lex.Ident "MkT") GHC.Read.expectP (Text.Read.Lex.Punc "{") a1_a2Tm <- GHC.Read.readField "runT#" (Text.ParserCombinators.ReadPrec.reset GHC.Read.readPrec) GHC.Read.expectP (Text.Read.Lex.Punc "}") GHC.Base.return (Bug.MkT a1_a2Tm))) GHC.Read.readList = GHC.Read.readListDefault GHC.Read.readListPrec = GHC.Read.readListPrecDefault }}} This likely has something to do with commit dbd81f7e86514498218572b9d978373b1699cc5b (Factor out readField (#14364)). tdammers, do you know what is going on here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 01:56:14 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 01:56:14 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.cbc8152818ca1256e869db07a17a903e@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: #14364 => #5041, #14364 Comment: Ah, I know what is happening here. #5041 is quite relevant, as is [http://git.haskell.org/ghc.git/blob/152055a19cf368439c8450040b68142f8e7d0346:/compiler/typecheck/TcGenDeriv.hs#l1057 this comment] from the GHC source: {{{#!hs -- For constructors and field labels ending in '#', we hackily -- let the lexer generate two tokens, and look for both in sequence -- Thus [Ident "I"; Symbol "#"]. See Trac #5041 }}} Now let's look at [http://git.haskell.org/ghc.git/blob/152055a19cf368439c8450040b68142f8e7d0346:/libraries/base/GHC/Read.hs#l370 what readField does]: {{{#!hs readField :: String -> ReadPrec a -> ReadPrec a readField fieldName readVal = do expectP (L.Ident fieldName) expectP (L.Punc "=") readVal }}} Alas, it attempts to treat the field name as a single `Ident`. But if that field name contains a `#` (e.g., `runT#`, as in the original example), then this will fail. It looks like we'll need a variant of `readField` that takes hashes into account. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 02:01:11 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 02:01:11 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.329e371801606c0582a8d806770ca6d0@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): Before putting stuff in `base`, maybe start start a library `ghc-stack- utils` or something with this (and possibly other combinators)? This would allow you to experiment more freely, users can use it with old versions of GHC and we see which combinators are actually useful. We can add a reference to this library in the documentation for `HasCallStack`, so that people can find it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 02:08:45 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 02:08:45 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.d27d6595291eb7598114db87c6987e4b@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): nomeata, the trouble is that I think doing this 'properly' requires modification of the `CallStack` type. We can't really do that elsewhere. I don't think the current interface has really been through the wringer either; it's brand new! Why should a minor extension have to face a high hurdle? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 03:28:32 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 03:28:32 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.0f0edc70d9167b7eec072ba0d31589d0@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): What’s wrong with your implementation of `extraCS`? I don’t see it as a hurdle, and don't oppose inclusion in `base`, but rather an opportunity; separate libraries are more agile. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 05:38:16 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 05:38:16 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.481701719fc667af0f2d75a788103925@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): My implementation of `extraCS` leads to pretty bad output, but I've finally managed to fix that. However, the only fix I managed to find involved doing some seriously shady things! Let me explain a little. If you look at `extraCS` above, you'll see a variable called `a`. That variable is very boring, and there's no point in having it show up in the stack trace. But because the passed function (bound to `a`) has a `HasCallStack` constraint, the name `a` is captured as a stack frame. Maybe there's some clever way to avoid that without shadiness, but I couldn't find one! I ended up having to do this: {{{#!hs {-# language RankNTypes #-} import GHC.Stack import GHC.Stack.Types import Unsafe.Coerce newtype Magic a = Magic (CallStack -> String -> (CallStack -> a) -> a) newtype Magic2 a = Magic2 (HasCallStack => String -> (HasCallStack => a) -> a) extraCS :: forall a. HasCallStack => String -> (HasCallStack => a) -> a extraCS = case unsafeCoerce (Magic boom) of Magic2 x -> x boom :: CallStack -> String -> (CallStack -> a) -> a boom cs s z = let cs' = case popCallStack cs of EmptyCallStack -> EmptyCallStack PushCallStack x y z -> PushCallStack (x ++ " (" ++ s ++ ")") y z r@(FreezeCallStack _) -> r in z cs' }}} What a mess! Unless someone comes up with a cleverer workaround (please do!), that leaves two options: 1. Add some sort of compiler magic to help. This would be beyond me, but potentially valuable to provide finer-grained control of call stacks in general. 2. Add logic to the call stack printer to make it skip those particular stack frames. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 06:17:37 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 06:17:37 -0000 Subject: [GHC] #11188: Confusing "parse error in pattern" for spurious indentation. In-Reply-To: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> References: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> Message-ID: <066.c05b3d0983de92d234834bb4c1749324@haskell.org> #11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ömer Sinan Ağacan ): In [changeset:"cb6d8589c83247ec96d5faa82df3e93f419bbfe0/ghc" cb6d858/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cb6d8589c83247ec96d5faa82df3e93f419bbfe0" Slighly improve infix con app pattern errors Given this program: main = do f $ do a <- return 3 c <- do return 5 GHC previously gave this error message: Main.hs:2:7: error: Parse error in pattern: do a <- return 3 c Possibly caused by a missing 'do'? | 2 | f $ do | ^^... What happened is GHC considered the whole `f $ do a <- return 3 c` as a pattern. When parsed as an expression it becomes an infix application of `($)`, and GHC checks left and right hand sides before checking if `($)` is a valid infix constructor name, and shows the first error it got. If instead we first check if the infix op is valid in pattern context, the error message becomes much clearer: Main.hs:2:3: error: Parse error in pattern: f $ do a <- return 3 c Possibly caused by a missing 'do'? | 2 | f $ do | ^^^^^^... This may not entirely fix #11188 but I think it's an improvement. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #11188 Differential Revision: https://phabricator.haskell.org/D4497 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 06:18:42 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 06:18:42 -0000 Subject: [GHC] #11188: Confusing "parse error in pattern" for spurious indentation. In-Reply-To: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> References: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> Message-ID: <066.b412f069523223c96b63c55932b12e0e@haskell.org> #11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => merge Comment: We discussed this and thought this improvement should be enough for now. Please let us know if the error is still not good enough. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 06:31:21 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 06:31:21 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.397fa9c302cfcb84de0275ce7cc38868@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): nomeata, I figured I'd get the package going anyway. See [http://hackage.haskell.org/package/ghc-call-stack-extras-0.1.0.0 ghc- call-stack-extras]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 06:41:54 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 06:41:54 -0000 Subject: [GHC] #11312: GHC inlining primitive string literals can affect program output In-Reply-To: <050.6392f4ea96644f5394022cd373a55178@haskell.org> References: <050.6392f4ea96644f5394022cd373a55178@haskell.org> Message-ID: <065.f9338207e80e00eacf2ff543dd3241a3@haskell.org> #11312: GHC inlining primitive string literals can affect program output -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: strings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #11292, #5218 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 08:18:40 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 08:18:40 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.ed350ae5caf7fd1408e525c1cf69c1bb@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): Another problem, arguably bigger: if an exception occurs when forcing a stack message, that could be handled gracefully by `renderStack` (in `base`), but not properly elsewhere. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 13:09:58 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 13:09:58 -0000 Subject: [GHC] #14089: Segmentation fault/access violation using Yesod and Postgresql In-Reply-To: <048.46aff377a8018fc7c501ce75cd3dd62b@haskell.org> References: <048.46aff377a8018fc7c501ce75cd3dd62b@haskell.org> Message-ID: <063.851df671712d658ca605c751f28c85e1@haskell.org> #14089: Segmentation fault/access violation using Yesod and Postgresql ---------------------------------+-------------------------------------- Reporter: Burtannia | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 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 RyanGlScott): * status: new => infoneeded Comment: Burtannia, do you still experience this isssue with [http://hackage.haskell.org/package/postgresql-libpq-0.9.4.1 postgresql- libpq-0.9.4.1]? That release contains a workaround for a [https://github.com/yesodweb/persistent/issues/794 very similar issue], so I'm curious to see if that fixes this as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 13:38:06 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 13:38:06 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.c1d848e8ef739c12cca77f3db603ea8b@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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 actually think this is a good idea. Simon's right in that figuring out exactly when you can inline can be tricky. But this logic is already in the compiler (in the inliner!) and so we can perhaps work it into the desugarer (which is where levity- polymorphism errors are issued). It's possible we'll have a hard time producing sensible error messages, but I think we'll be able to surmount that challenge. As to the proof: I'm not concerned. The proof is about Core. The proposed change wouldn't affect Core at all. Core still wouldn't have levity- polymorphic binders. (Unfoldings might, but not actual Core programs that will be compiled.) We can think of this proposal as suggesting "function templates", where these templates are stand-ins for a (perhaps infinite) family of levity-monomorphic functions. The implementation of this would be fiddly, but I don't see any true obstacles to it. And it does seem very silly that users can't reuse their typing for a function as simple as `twice`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 14:30:25 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 14:30:25 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.ed078288db444ab7106f3b5634a53f4c@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks 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): Ok ok, I get buy it now that the interface provided by `base` is not good enough yet :-) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 14:53:38 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 14:53:38 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.a33c12cba87b9d0475783abb8b78ea3a@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4502 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 15:08:00 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 15:08:00 -0000 Subject: [GHC] #14919: python3-based GHC scripts don't work on my RHEL machine Message-ID: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> #14919: python3-based GHC scripts don't work on my RHEL machine -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Building GHC Unknown/Multiple | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I recently switched over machines to work on GHC stuff, but to my dismay, several `python3`-based scripts which glue GHC together do not work with my new machine. One of these is `boot`. If I run this, I am greeted with: {{{ $ ./boot Traceback (most recent call last): File "./boot", line 193, in check_for_url_rewrites() File "./boot", line 29, in check_for_url_rewrites subprocess.check_output('git config remote.origin.url'.split()).find(b'github.com') != -1 and \ File "/l/python3/lib/python3.5/subprocess.py", line 626, in check_output **kwargs).stdout File "/l/python3/lib/python3.5/subprocess.py", line 693, in run with Popen(*popenargs, **kwargs) as process: File "/l/python3/lib/python3.5/subprocess.py", line 947, in __init__ restore_signals, start_new_session) File "/l/python3/lib/python3.5/subprocess.py", line 1551, in _execute_child raise child_exception_type(errno_num, err_msg) FileNotFoundError: [Errno 2] No such file or directory: 'git' }}} One thing that's relevant here is that my `python3` installation is in an unusual location, `/usr/local/bin`. Most of my other executables are installed in `/usr/bin`, such as `git`, `sed`, `autoconf`, `python2`, etc. The fact that `python3` is located elsewhere seems important, because if I hack `boot` to use `python2`: {{{#!diff diff --git a/boot b/boot index f913724..995293a 100755 --- a/boot +++ b/boot @@ -1,4 +1,4 @@ -#!/usr/bin/env python3 +#!/usr/bin/env python2 import glob import os @@ -18,7 +18,7 @@ parser.add_argument('--hadrian', action='store_true', help='Do not assume the ma args = parser.parse_args() def print_err(s): - print(dedent(s), file=sys.stderr) + print dedent(s) def die(mesg): print_err(mesg) }}} Then it works. It seems that `subprocess.check_output` is //only// looking up executable names in the same directory as `python(3)`, for reasons that I don't fully understand. Other scripts based around `python3`, such as the test suite driver, also fail. If I run those, I also experience errors, such as: {{{ $ make test TEST="T11311" /bin/sh: locale: command not found /bin/sh: grep: command not found /bin/sh: grep: command not found /bin/sh: locale: command not found /bin/sh: grep: command not found Timeout is 300 Found 400 .T files... Beginning test run at Wed Mar 14 11:03:46 2018 EDT =====> T11311(normal) 1 of 1 [0, 0, 0] cd "./dependent/should_compile/T11311.run" && "/nfs/nfs7/home/rgscott/Software/ghc/inplace/test spaces/ghc-stage2" -c T11311.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn- missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -dno-debug-output Compile failed (exit code 1) errors were: : error: Warning: Couldn't figure out C compiler information! Make sure you're using GNU gcc, or clang ghc-stage2: could not execute: gcc *** unexpected failure for T11311(normal) Unexpected results from: TEST="T11311" SUMMARY for test run started at Wed Mar 14 11:03:46 2018 EDT 0:00:02 spent to go through 1 total tests, which gave rise to 3 test cases, of which 2 were skipped 0 had missing libraries 0 expected passes 0 expected failures 0 caused framework failures 0 caused framework warnings 0 unexpected passes 1 unexpected failures 0 unexpected stat failures Unexpected failures: dependent/should_compile/T11311.run T11311 [exit code non-0] (normal) make[1]: *** [test] Error 1 make[1]: Leaving directory `/nfs/nfs7/home/rgscott/Software/ghc/testsuite/tests' make: *** [test] Error 2 }}} I don't know a way to hack around this problem, unfortunately. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 15:31:34 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 15:31:34 -0000 Subject: [GHC] #14919: python3-based GHC scripts don't work on my RHEL machine In-Reply-To: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> References: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> Message-ID: <065.5eac433729960428e32a7a7a8ab5ef46@haskell.org> #14919: python3-based GHC scripts don't work on my RHEL machine -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): What do you get as output of `import os; print(os.environ['PATH'])` in python 2 and 3? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 15:33:43 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 15:33:43 -0000 Subject: [GHC] #14919: python3-based GHC scripts don't work on my RHEL machine In-Reply-To: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> References: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> Message-ID: <065.c3b35e9a2f37f4a58f58ae0df475bf10@haskell.org> #14919: python3-based GHC scripts don't work on my RHEL machine -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): For `python2`: {{{ $ python2 Python 2.7.5 (default, May 3 2017, 07:55:04) [GCC 4.8.5 20150623 (Red Hat 4.8.5-14)] on linux2 Type "help", "copyright", "credits" or "license" for more information. >>> import os; print(os.environ['PATH']) /u/rgscott/Software/arcanist/bin:/u/rgscott/.cabal/bin:/u/rgscott/Software/haskell/ghc-8.2.2/bin:/usr/lib64/qt-3.3/bin:/usr/local/bin:/usr/bin:/usr/local/sbin:/usr/sbin:/u/rgscott/.cabal/bin:/opt/dell/srvadmin/bin:/u/rgscott/Software/hpx/bin:/u/rgscott/bin }}} For `python3`: {{{ $ python3 Python 3.5.2 (default, Aug 19 2016, 07:40:05) [GCC 4.8.5 20150623 (Red Hat 4.8.5-4)] on linux Type "help", "copyright", "credits" or "license" for more information. >>> import os; print(os.environ['PATH']) /l/python3/bin }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 16:31:43 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 16:31:43 -0000 Subject: [GHC] #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` Message-ID: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.4.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: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 16:31:55 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 16:31:55 -0000 Subject: [GHC] #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` In-Reply-To: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> References: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> Message-ID: <061.0c5eebf0c3d92a02550c644960614791@haskell.org> #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: sjakobi Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.4.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 sjakobi): * owner: (none) => sjakobi -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 17:13:05 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 17:13:05 -0000 Subject: [GHC] #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` In-Reply-To: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> References: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> Message-ID: <061.e01e0643308c9cca71fb759917808bf4@haskell.org> #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: sjakobi Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.4.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 sjakobi): Actually, `-haddock-opts` seems entirely unused. `DynFlags` has a field `haddockOptions`, but it doesn't seem to be used anywhere. Should it be removed? Or maybe we should keep it at least until the "Hi Haddock" proposal is implemented… Also, I'm not quite sure what `-haddock` actually does. It does make the parser include the haddocks in `HsModule` but what then? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 20:30:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 20:30:10 -0000 Subject: [GHC] #14921: Type inference breaks on constraint-kinded parameter used by a Rank-2 callback Message-ID: <051.12d35c7805454922cc0bcfb2ee8e00e1@haskell.org> #14921: Type inference breaks on constraint-kinded parameter used by a Rank-2 callback -------------------------------------+------------------------------------- Reporter: glittershark | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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: -------------------------------------+------------------------------------- Apologies in advance if the terminology in the summary is incorrect, I'm not really sure of the proper terms to use here The following code: {{{#!hs {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ScopedTypeVariables #-} module Scratch where import Prelude data Foo = FooA Int | FooB String useFoo :: forall cls a . (cls Int, cls String) => (forall k . cls k => k -> a) -> Foo -> a useFoo f (FooA a) = f a useFoo f (FooB b) = f b }}} seems like it should be able to infer the `cls` type parameter to `useFoo` based on the first argument, but instead calling with `kshow` gives the following error message: {{{#!hs >>> useFoo show (FooA 1) :52:1: error: • Could not deduce: (cls0 Int, cls0 String) arising from a use of ‘useFoo’ • In the expression: useFoo show (FooA 1) In an equation for ‘it’: it = useFoo show (FooA 1) :52:8: error: • Couldn't match type ‘a’ with ‘String’ ‘a’ is untouchable inside the constraints: cls0 k bound by a type expected by the context: forall k. cls0 k => k -> a at :52:1-20 ‘a’ is a rigid type variable bound by the inferred type of it :: a at :52:1-20 Possible fix: add a type signature for ‘it’ Expected type: k -> a Actual type: k -> String • In the first argument of ‘useFoo’, namely ‘show’ In the expression: useFoo show (FooA 1) In an equation for ‘it’: it = useFoo show (FooA 1) • Relevant bindings include it :: a (bound at :52:1) }}} Type-applying `useFoo` works as expected: {{{#!hs >>> :set -XTypeApplications >>> useFoo @Show show (FooA 1) "1" }}} This broke both with and without ScopedTypeVariables -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 20:33:11 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 20:33:11 -0000 Subject: [GHC] #5361: regSpill: out of spill slots! In-Reply-To: <049.cbc3b6a1173f092cb2619a218adec7c2@haskell.org> References: <049.cbc3b6a1173f092cb2619a218adec7c2@haskell.org> Message-ID: <064.fbb6ba631137fc61a08fdc198319feac@haskell.org> #5361: regSpill: out of spill slots! -------------------------------------+------------------------------------- Reporter: markwright | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 7.8.1 Component: Compiler | Version: 7.1 Resolution: fixed | Keywords: regSpill | panic impossible Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: crash | http://hackage.haskell.org/package/SHA Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simons): This issue still occurs with GHC 8.2.2. It's clearly not "fixed", unless one applies a very special interpretation of what that term is supposed to mean. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 20:46:15 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 20:46:15 -0000 Subject: [GHC] #14922: Add inductively-defined Nat to base Message-ID: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> #14922: Add inductively-defined Nat to base -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 8.2.2 libraries/base | Keywords: base | 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 proposed addition is simple, add the following to base: {{{#!hs data Nat = Zero | Succ Nat }}} I will list the pros/cons I see below. Pros: - Commonly defined throughout many packages, e.g. vinyl - The inductive definition of 'Nat' is useful for correctness (e.g. {{{#!hs safeHead :: Vec a (S n) -> a; safeHead (Cons a as) = a}}}) Cons: - '-XDependentHaskell' will most likely obviate any benefit brought about by type families involving Nat - Looking at base, I'm not sure where this would go. Having it in its own module seems a tad strange. I am open to criticism concerning the usefulness of the idea or if anyone sees a Pro(s)/Con(s) that I am missing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 20:47:34 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 20:47:34 -0000 Subject: [GHC] #14922: Add inductively-defined Nat to base In-Reply-To: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> References: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> Message-ID: <061.cfe22dcb7da444b4329a5e0bc89b10fb@haskell.org> #14922: Add inductively-defined Nat to base -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.2 Resolution: | Keywords: base 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 chessai: Old description: > The proposed addition is simple, add the following to base: > > {{{#!hs > data Nat = Zero | Succ Nat > }}} > > I will list the pros/cons I see below. > > Pros: > - Commonly defined throughout many packages, e.g. vinyl > - The inductive definition of 'Nat' is useful for correctness > (e.g. {{{#!hs safeHead :: Vec a (S n) -> a; safeHead (Cons a as) = > a}}}) > > Cons: > - '-XDependentHaskell' will most likely obviate any benefit brought about > by type families involving Nat > - Looking at base, I'm not sure where this would go. Having it in its own > module seems a tad strange. > > I am open to criticism concerning the usefulness of the idea or if anyone > sees a Pro(s)/Con(s) that I am missing. New description: The proposed addition is simple, add the following to base: {{{#!hs data Nat = Zero | Succ Nat }}} I will list the pros/cons I see below. Pros: - Commonly defined throughout many packages, e.g. vinyl - The inductive definition of 'Nat' is useful for correctness (e.g. {{{safeHead :: Vec a (S n) -> a; safeHead (Cons a as) = a}}}) Cons: - '-XDependentHaskell' will most likely obviate any benefit brought about by type families involving Nat - Looking at base, I'm not sure where this would go. Having it in its own module seems a tad strange. I am open to criticism concerning the usefulness of the idea or if anyone sees a Pro(s)/Con(s) that I am missing. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 20:53:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 20:53:10 -0000 Subject: [GHC] #14922: Add inductively-defined Nat to base In-Reply-To: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> References: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> Message-ID: <061.0ee60dfa6e1b4ab16f7df303ae2066b9@haskell.org> #14922: Add inductively-defined Nat to base -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.2 Resolution: | Keywords: base Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): I'm in favor of these. I've used several packages that define `Nat`, and I've written several that define `Nat`. The annoyance is minor, but it would be nice to have this in a standard place. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 22:33:26 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 22:33:26 -0000 Subject: [GHC] #14922: Add inductively-defined Nat to base In-Reply-To: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> References: <046.824a900ce6ed50badf546387ff7d4edf@haskell.org> Message-ID: <061.58f416d5db62db56a6f5c5577876767d@haskell.org> #14922: Add inductively-defined Nat to base -------------------------------------+------------------------------------- Reporter: chessai | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.2 Resolution: | Keywords: base Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This is a feature request to add something to a core library, and as such, you should run this by the [https://mail.haskell.org/mailman/listinfo/libraries libraries mailing list] first to ensure that there is community consensus to do this. It's worth noting that there have been previous proposals for this in the past, one of which is [https://mail.haskell.org/pipermail/libraries/2016-January/026537.html this one] (from January 2016). That one ended with the consensus that this should //not// be added to `base`. Still, if you feel strongly otherwise, it might be worth bringing this up again—it's possible that public opinion has shifted since then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 22:56:30 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 22:56:30 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.00ac17871f14dd5f05a3d675072a778c@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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): If something changes in the inliner could working levity-poly definitions fail? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 14 23:11:45 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 14 Mar 2018 23:11:45 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.d569c1eb4811812c0199a3f54f0851ed@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by andrewthad): @Iceland_jack I believe that the inlining phase (or phases) happens after type checking, so this couldn’t even be done during the usual inlining phase. You would need something similar to the inlining phase that happens prior to type checking. The only things allowed to inline during this phase would be fully saturated calls to functions with levity polymorphic binders ( maybe function template, as Richard suggests, is an appropriate name for it). This is why Richard says that it would be hard to produce sensible error messages. So, I don’t think that changes to the inliner could mess this up because this would be a separate and unusual inlining phase. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 04:36:09 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 04:36:09 -0000 Subject: [GHC] #14923: Recompilation avoidance fails after a LANGUAGE change Message-ID: <043.f58216ea69c9ec233e7328c6135b12f4@haskell.org> #14923: Recompilation avoidance fails after a LANGUAGE change -------------------------------------+------------------------------------- Reporter: akio | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Linux Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It looks like the recompilation checker can be confused when a LANGUAGE pragma is added or removed. The following shell script demonstrates the issue: {{{ #!/bin/sh cat >Foo.hs < GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 05:39:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 05:39:35 -0000 Subject: [GHC] #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` In-Reply-To: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> References: <046.8d907c50ea3f37a45ce08ed660fd315c@haskell.org> Message-ID: <061.244fb95dc34ab8236e63d361b9fbb989@haskell.org> #14920: Flag reference doesn't include `-haddock` and `-haddock-opts` -------------------------------------+------------------------------------- Reporter: sjakobi | Owner: sjakobi Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.4.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 alexbiehl): A comment on `-haddock`: yes, with this flag GHC will take a closer look on comments and keep them in its syntax tree for haddock to pick them up (see `collectDocs` in haddock-api package). For "Hi Haddock", as as a first approximation I am in favour of only putting documentation in hi files when `-haddock` flag is given. If it turns out to be performant enough we could still enable `-haddock` by default later. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 06:31:12 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 06:31:12 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.d6bd36a86c36794b2c0eb38f79137700@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 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): D4503 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ulysses4ever): * differential: => D4503 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 08:41:30 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 08:41:30 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.e971025ca8468bd12e22a7cab9ac98e8@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 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): D4503 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ulysses4ever): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 09:52:23 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 09:52:23 -0000 Subject: [GHC] #14924: GHC 8.4.1 has wrong __GLASGOW_HASKELL__ Message-ID: <044.895c1f7378a6508ca9b8f0c92e2902e5@haskell.org> #14924: GHC 8.4.1 has wrong __GLASGOW_HASKELL__ -------------------------------------+------------------------------------- Reporter: sergv | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 title pretty much says it all. As following shell interaction shows, the macro expands into 804, but I expected that it should expand into 840. Was my expectation wrong? {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.1 $ cat /tmp/Test.hs {-# LANGUAGE CPP #-} hello = __GLASGOW_HASKELL__ $ cat /tmp/Test.hspp | sed -r '/^$/d' # preprocessed file has too much whitespace {-# LINE 1 "/tmp/Test.hs" #-} # 1 "/tmp/Test.hs" # 1 "" # 1 "" # 1 "/usr/include/stdc-predef.h" 1 3 4 # 17 "/usr/include/stdc-predef.h" 3 4 # 7 "" 2 # 1 "/home/sergey/projects/haskell/ghc/local-8.4.1/lib/ghc-8.4.1/include/ghcversion.h" 1 # 7 "" 2 # 1 "/tmp/ghc20375_0/ghc_2.h" 1 # 7 "" 2 # 1 "/tmp/Test.hs" {-# LANGUAGE CPP #-} hello = 804 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 10:06:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 10:06:57 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.c82bf9959bbaf8c7f8aa7a5f92198722@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 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:D4503 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ulysses4ever): * differential: D4503 => Phab:D4503 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 10:34:26 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 10:34:26 -0000 Subject: [GHC] #11735: Optimize coercionKind In-Reply-To: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> References: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> Message-ID: <062.4be0fb43b94e55c67bf44f62f3a48be2@haskell.org> #11735: Optimize coercionKind -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | 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 tdammers): Effect of D4394 on compilation of `Grammar.hs`: Compiling with GHC HEAD (`02b3dad195`), built with the `quick` profile: {{{ tobias at zoidberg:~/well-typed/devel/ghc-T14683/ > time ../ghc/HEAD/inplace/bin/ghc-stage2 grammar-hs/Grammar.hs -fforce-recomp -O2 [1 of 1] Compiling Grammar ( grammar-hs/Grammar.hs, grammar- hs/Grammar.o ) ../ghc/HEAD/inplace/bin/ghc-stage2 grammar-hs/Grammar.hs -fforce-recomp -O2 465.26s user 0.52s system 100% cpu 7:45.42 total }}} Compiling with D4394 applied (`6493976fdb`), built with the `quick` profile: {{{ tobias at zoidberg:~/well-typed/devel/ghc-T14683/ > time ../ghc/D4394/inplace/bin/ghc-stage2 grammar-hs/Grammar.hs -fforce-recomp -O2 [1 of 1] Compiling Grammar ( grammar-hs/Grammar.hs, grammar- hs/Grammar.o ) ../ghc/D4394/inplace/bin/ghc-stage2 grammar-hs/Grammar.hs -fforce-recomp -O2 25.95s user 0.36s system 94% cpu 27.977 total }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 11:21:27 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 11:21:27 -0000 Subject: [GHC] #14895: STG CSE makes dead binders undead In-Reply-To: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> References: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> Message-ID: <060.59cc25fafad1606326bd4fc7c7e7045e@haskell.org> #14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Actually `isDeadBinder` check (the check that causes not printing case binders) is also used in code generation: {{{#!haskell cgCase (StgOpApp (StgPrimOp op) args _) bndr (AlgAlt tycon) alts | isEnumerationTyCon tycon -- Note [case on bool] = do { tag_expr <- do_enum_primop op args -- If the binder is not dead, convert the tag to a constructor -- and assign it. ; unless (isDeadBinder bndr) $ do { dflags <- getDynFlags ; tmp_reg <- bindArgToReg (NonVoid bndr) ; emitAssign (CmmLocal tmp_reg) (tagToClosure dflags tycon tag_expr) } ; (mb_deflt, branches) <- cgAlgAltRhss (NoGcInAlts,AssignedDirectly) (NonVoid bndr) alts -- See Note [GC for conditionals] ; emitSwitch tag_expr branches mb_deflt 0 (tyConFamilySize tycon - 1) ; return AssignedDirectly } }}} But this probably doesn't break anything because the scrutinee binder becomes undead only when (1) scrutinee is a data con application (2) the application repeats in an alternative. The code I showed above is for generating code when scrutinee is a primop application so it's safe. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 12:13:39 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 12:13:39 -0000 Subject: [GHC] #14924: GHC 8.4.1 has wrong __GLASGOW_HASKELL__ In-Reply-To: <044.895c1f7378a6508ca9b8f0c92e2902e5@haskell.org> References: <044.895c1f7378a6508ca9b8f0c92e2902e5@haskell.org> Message-ID: <059.20a7eca4c2b6945f36ad434ed017bca2@haskell.org> #14924: GHC 8.4.1 has wrong __GLASGOW_HASKELL__ -------------------------------------+------------------------------------- Reporter: sergv | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 sjakobi): That's not a bug. For example the value of `__GHC_VERSION__` for GHC-7.10 is `710`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 12:34:12 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 12:34:12 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.39187885546aa4b23649c03f997c169e@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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 am a bit less optimistic than Richard (in comment:3). You imply that all the inlining could be done in the desugarer; but that can only work if you could see all calls. GHC does already have the notion of a "compulsory unfolding" (see `CoreSyn.UnfoldingSource`). Bindings with a compulsory unfolding ''do not have a binding at all'', so they must be inlined at every call site. That fits with the proposal here because we can't implement the levity- polymorphic code, so we can't compile code for it. We'd still somehow need to check that, after the inlining, the levity- polymorphism had vanished, and give a decent error message if not. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 12:37:24 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 12:37:24 -0000 Subject: [GHC] #14925: Non-ASCII type names get garbled when their `TypeRep` is shown Message-ID: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> #14925: Non-ASCII type names get garbled when their `TypeRep` is shown -------------------------------------+------------------------------------- Reporter: | Owner: (none) leftaroundabout | Type: bug | Status: new Priority: low | Milestone: Component: | Version: 8.2.1 libraries/base | Keywords: Typeable | Operating System: Unknown/Multiple TypeRep Unicode ASCII UTF-8 | Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- [http://hackage.haskell.org/package/base-4.10.1.0/docs/Data-Typeable.html Typeable] allows easily showing the name of a type by, well, using `show` on it. However, this does not work right for types with Unicode symbols in their name: {{{ GHCi, version 8.2.1: http://www.haskell.org/ghc/ :? for help Prelude> :m +Data.Typeable Prelude Data.Typeable> data W = W Prelude Data.Typeable> typeOf W W Prelude Data.Typeable> data Ω = Ω Prelude Data.Typeable> typeOf Ω Î© }}} This did not yet happen in GHC-7: {{{ GHCi, version 7.10.2: http://www.haskell.org/ghc/ :? for help Prelude> :m +Data.Typeable Prelude Data.Typeable> data W = W Prelude Data.Typeable> typeOf W W Prelude Data.Typeable> data Ω = Ω Prelude Data.Typeable> typeOf Ω Ω }}} N.b.: {{{ Prelude> import Data.ByteString.Char8 as BC8 Prelude BC8> BC8.putStrLn $ pack "Ω" Ω }}} So, this appears to be a UTF-8 problem – something interprets bytestring- stored type-representation names as a different character encoding. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 12:43:39 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 12:43:39 -0000 Subject: [GHC] #14924: GHC 8.4.1 has wrong __GLASGOW_HASKELL__ In-Reply-To: <044.895c1f7378a6508ca9b8f0c92e2902e5@haskell.org> References: <044.895c1f7378a6508ca9b8f0c92e2902e5@haskell.org> Message-ID: <059.7a174625ff547319631013fbc6e34965@haskell.org> #14924: GHC 8.4.1 has wrong __GLASGOW_HASKELL__ -------------------------------------+------------------------------------- Reporter: sergv | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => invalid Comment: Indeed. See https://downloads.haskell.org/~ghc/8.4.1/docs/html/users_guide/phases.html#c -pre-processor for the users' guide documentation for how `__GLASGOW_HASKELL__` is generated. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 12:48:45 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 12:48:45 -0000 Subject: [GHC] #14921: Type inference breaks on constraint-kinded parameter used by a Rank-2 callback In-Reply-To: <051.12d35c7805454922cc0bcfb2ee8e00e1@haskell.org> References: <051.12d35c7805454922cc0bcfb2ee8e00e1@haskell.org> Message-ID: <066.a20e778f87fbdb26a635dda20ac530bc@haskell.org> #14921: Type inference breaks on constraint-kinded parameter used by a Rank-2 callback -------------------------------------+------------------------------------- Reporter: glittershark | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10651 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #10651 Comment: This is more or less expected behavior. See #10651 for a similar scenario. In general, GHC doesn't unify underneath equalities or something that might turn into an equality, such as `cls k` (this is why `a` is untouchable in your error message, as you'd have to unify it underneath `cls k`). As SPJ notes in https://ghc.haskell.org/trac/ghc/ticket/10651#comment:2, this limitation is explained in Section 5 of the [http://research.microsoft.com/~simonpj/papers/constraints/jfp- outsidein.pdf OutsideIn paper], and it's unknown how to improve this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 15:08:29 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 15:08:29 -0000 Subject: [GHC] #14919: python3-based GHC scripts don't work on my RHEL machine In-Reply-To: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> References: <050.836f17d1cc4b6e2b8077082eaa2d7d30@haskell.org> Message-ID: <065.55a24f8bfb64b56383ff7314328ab41b@haskell.org> #14919: python3-based GHC scripts don't work on my RHEL machine -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => invalid Comment: Never mind. It turns out that this is entirely an issue with how `python3` is installed on my machine: {{{ $ more /usr/local/bin/python3 export PATH=/l/python3/bin export LD_LIBRARY_PATH=/l/python3/lib export LD_RUN_PATH=/l/python3/lib export PKG_CONFIG_PATH=/l/python3/lib/pkgconfig exec /l/python3/bin/python3 ${1+"$@"} }}} Ugh. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 16:46:15 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 16:46:15 -0000 Subject: [GHC] #14926: failed to build cross-compiler Message-ID: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> #14926: failed to build cross-compiler -------------------------------------+------------------------------------- Reporter: rueshyna | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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: -------------------------------------+------------------------------------- I'm trying to build cross-compiler(ghc-8.4.1) but got an error. Target platform is 32-bit windows. Here is what I do: 1. pull docker image[1]: `docker pull gregweber/ghc-haskell-dev` 2. install gcc-mingw-w64-i686: `apt-get install gcc-mingw-w64-i686` 3. download ghc source and switch to tag ghc-8.4.1-release 4. run `./boot` 5. `CC=/usr/bin/i686-w64-mingw32-gcc ./configure --target=i686-w64-mingw32 --enable-unregisterised` 6. `cp mk/build.mk.sample mk/build.mk` 7. uncomment the line: `BuildFlavour = quick-cross-ncg` 8. run `make` Error message: {{{ Configuring ghc-pkg-6.9... "inplace/bin/mkdirhier" utils/ghc-pkg/dist/build/tmp//. "/opt/ghc/8.2.1/bin/ghc" -o utils/ghc-pkg/dist/build/tmp/ghc-pkg -hisuf hi -osuf o -hcsuf hc -static -O0 -H64m -Wall -package-db libraries/bootstrapping.conf -hide-all-packages -i -iutils/ghc-pkg/. -iutils/ghc-pkg/dist/build -Iutils/ghc-pkg/dist/build -iutils/ghc- pkg/dist/build/ghc-pkg/autogen -Iutils/ghc-pkg/dist/build/ghc-pkg/autogen -optP-include -optPutils/ghc-pkg/dist/build/ghc-pkg/autogen/cabal_macros.h -no-user-package-db -rtsopts -odir utils/ghc-pkg/dist/build -hidir utils/ghc-pkg/dist/build -stubdir utils/ghc-pkg/dist/build -static -O0 -H64m -Wall -package-db libraries/bootstrapping.conf -hide-all- packages -i -iutils/ghc-pkg/. -iutils/ghc-pkg/dist/build -Iutils/ghc- pkg/dist/build -iutils/ghc-pkg/dist/build/ghc-pkg/autogen -Iutils/ghc- pkg/dist/build/ghc-pkg/autogen -optP-include -optPutils/ghc- pkg/dist/build/ghc-pkg/autogen/cabal_macros.h -no-user-package-db -rtsopts -no-auto-link-packages -no-hs-main ghc: no input files Usage: For basic information, try the `--help' option. utils/ghc-pkg/ghc.mk:70: recipe for target 'utils/ghc-pkg/dist/build/tmp /ghc-pkg' failed make[1]: *** [utils/ghc-pkg/dist/build/tmp/ghc-pkg] Error 1 Makefile:122: recipe for target 'all' failed make: *** [all] Error 2 }}} If using `BuildFlavour = quick`, it works well. [1]https://ghc.haskell.org/trac/ghc/wiki/Building/Preparation/Linux#Docker -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 17:43:50 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 17:43:50 -0000 Subject: [GHC] #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. Message-ID: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. -------------------------------------+------------------------------------- Reporter: | Owner: (none) leftaroundabout | Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.2.1 libraries/base | 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: -------------------------------------+------------------------------------- `asinh` is supposed to be the inverse of `sinh`, and this works pretty reliable for positive arguments. However, for negative arguments, the [http://hackage.haskell.org/package/base-4.10.1.0/docs/src/GHC.Float.html#line-473 currently used formula] {{{ asinh x = log (x + sqrt (1.0+x*x)) }}} gets unstable much earlier than necessary, namely when the summands in the logarithm cancel almost to zero, dominated by the numerical error of the square root. This is particularly troubling because mathematically **a)** `asinh` is a very “inert” function (i.e. you can carelessly put in huge numbers and – as long as they're not outright `Infinity` – always get a somewhat sane result), pseudo-sigmoidal as it were **b)** it is an ''odd function'', fulfilling `asinh (-x) = -asinh x`. Both is reflected in other implementations, e.g. Python, but not in GHC Haskell: {{{ GHCi, version 8.2.1 Python 3.5.2 (default, Nov 23 2017, 16:37:01) In [1]: from math import * Prelude> asinh 1e6 In [2]: asinh(1e6) 14.50865773852447 Out[2]: 14.50865773852447 Prelude> asinh (-1e6) In [3]: asinh(-1e6) -14.50865012405984 Out[3]: -14.50865773852447 Prelude> asinh 1e9 In [4]: asinh(1e9) 21.416413017506358 Out[4]: 21.416413017506354 Prelude> asinh (-1e9) In [5]: asinh(-1e9) -Infinity Out[5]: -21.416413017506354 Prelude> asinh 1e76 In [6]: asinh(1e76) 175.6896142481074 Out[6]: 175.68961424810743 Prelude> asinh (-1e76) In [7]: asinh(-1e76) -Infinity Out[7]: -175.68961424810743 }}} Demo of non-inverse property: {{{ Prelude> [(x, asinh $ sinh x) | x <- [-25..25]] [(-25.0,-Infinity) ,(-24.0,-Infinity) ,(-23.0,-Infinity) ,(-22.0,-Infinity) ,(-21.0,-Infinity) ,(-20.0,-Infinity) ,(-19.0,-18.021826694558577) ,(-18.0,-18.021826694558577) ,(-17.0,-17.0102257828801) ,(-16.0,-15.998624871201619) ,(-15.0,-14.999878578873695) ,(-14.0,-13.999968823323222) ,(-13.0,-12.999991335176079) ,(-12.0,-12.000000137072186) ,(-11.0,-10.999999903206444) ,(-10.0,-10.000000013503529) ,(-9.0,-9.000000000551713) ,(-8.0,-8.00000000017109) ,(-7.0,-7.000000000036329) ,(-6.0,-5.999999999998066) ,(-5.0,-5.000000000000641) ,(-4.0,-4.000000000000046) ,(-3.0,-2.999999999999989) ,(-2.0,-1.9999999999999991) ,(-1.0,-1.0) ,(0.0,0.0) ,(1.0,1.0) ,(2.0,2.0) ,(3.0,3.0) ,(4.0,4.0) ,(5.0,5.0) ,(6.0,6.0) ,(7.0,7.0) ,(8.0,8.0) ,(9.0,9.0) ,(10.0,10.0) ,(11.0,11.0) ,(12.0,12.0) ,(13.0,13.0) ,(14.0,14.0) ,(15.0,15.0) ,(16.0,16.0) ,(17.0,17.0) ,(18.0,18.0) ,(19.0,19.0) ,(20.0,20.0) ,(21.0,21.0) ,(22.0,22.0) ,(23.0,23.0) ,(24.0,24.0) ,(25.0,25.0)] }}} Those results are less than satisfying, even for inputs that aren't astronomically big at all. A simple fix would be to “copy” the sane positive-number behaviour to the negative side: {{{ asinh x | x < 0 = -asinh (-x) | otherwise = log (x + sqrt (1.0+x*x)) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 19:25:14 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 19:25:14 -0000 Subject: [GHC] #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. In-Reply-To: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> References: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> Message-ID: <069.92866a1d773e4acb27e8566694692562@haskell.org> #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by leftaroundabout): Alternatives to the fix suggestion above: - {{{asinh x = signum x * log (abs x + sqrt (1 + x*x))}}} More concise form of the same thing; quite possibly faster performance because a branch can be avoided. - Actually, the Python version has also a higher ''upper'' limit: {{{ Prelude> asinh 1e200 In [3]: asinh(1e200) Infinity Out[3]: 461.2101657793691 }}} The reason is that `x*x` overflows even though the function as a whole could still be well-defined. I consider this not nearly as problematic as the much earlier problems I showed for the negative side, but it's still not great. This issue can be fixed by noting that for `x > 1/ε²`, we have anyways `1 + x*x == x*x` and thus `asinh x` gives the same result as `log (2*x) = log 2 + log x`. So, a ''really'' stable area hyperbolic sine would be {{{ asinh x | x > huge = log 2 + log x | x < 0 = -asinh (-x) | otherwise = log (1 + sqrt (1 + x*x)) }}} with {{{ huge = 1 / last (takeWhile ((>1).(+1)) $ recip . (2^) <$> [0..]) {- == 1 / Numeric.IEEE.epsilon -} }}} Mind, the exact value is completely uncritical, we could as well hard- code `huge = 1e20`. That implementation accurately left-inverts `sinh` (for `Double`) for all the range from `-710` to `710` (in other words, it right-inverts `sinh` for all the range from `-1.17e308` to `1.17e308`), which is basically the same as in Python. The current implementation only reaches up to `sinh 355`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 19:26:51 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 19:26:51 -0000 Subject: [GHC] #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. In-Reply-To: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> References: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> Message-ID: <069.86bcad343f6044be7d4c6202c1d4b50c@haskell.org> #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Floating | IEEE754 trigonometric 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 leftaroundabout): * keywords: => Floating IEEE754 trigonometric -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 20:04:18 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 20:04:18 -0000 Subject: [GHC] #14928: TH eats 50 GB memory when creating ADT with multiple constructors Message-ID: <047.b13a12d7e6e4b7703250170f5b54bd52@haskell.org> #14928: TH eats 50 GB memory when creating ADT with multiple constructors -------------------------------------+------------------------------------- Reporter: YitzGale | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.2.2 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When TH creates a data type with multiple constructors, GHC consumes huge amounts of memory in what appears to be a highly superlinear manner. A common use case: in the Yesod web framework, localized strings are represented by constructors of a Messages data type, created by a TH splice. There is one constructor for each localized string on the site, possibly hundreds. The splice also creates a class instance for the data type whose method matches against all the constructors for each language for which localizations are provided; this may or may not play a role in the memory leak. This Trac ticket corresponds to this Yesod issue: https://github.com/yesodweb/yesod/issues/1487 Here are two reproductions, and one NON-reproduction: 1. A blank "hello world" Yesod web site, with 500 messages defined for about 30 languages. The single page displays the messages in the user's language. Compiling this program in GHC 8.2.2 (stackage lts-10.5) on Ubuntu 16.04 eats over 50 GB of memory. https://gitub.com/ygale/yesod-bug1487 2. @snoyberg has cut down this reproduction to avoid using any libraries not included with GHC. It is in the same repo, on the {{{snoyberg- master}}} branch. NON-reproduction: The code in this gist, which is similar to what is generated by the TH in the above reproductions, is compiled by GHC without the bat of an eyelash. This demonstrates that the bug requires TH to reproduce. https://gist.github.com/92347aa93d226e31f977a0b62b443aa7 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 21:45:40 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 21:45:40 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.67eee64c85fc702d9f0e7f7c6a69a191@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 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:D4503 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ulysses4ever): Let's turn to `thNameToGhcName` now. We want to remove `initTcForLookup` from it, and for this we need to replace `lookupThName_maybe` with Tc-less version. The `lookupThName_maybe`, in turn, depends on `lookupGlobalOccRn_maybe` which seems to be very `Rn`-heavy inside. So I'm not sure how to proceed: should I try to rewrite `lookupGlobalOccRn_maybe` or leave it. In the latter case we need to find a way to run `RnM` in `thNameToGhcName`, which, I guess, not far from the dreaded `initTcForLookup`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 22:35:04 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 22:35:04 -0000 Subject: [GHC] #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks In-Reply-To: <049.64e07177e9110058c04a019d46370d44@haskell.org> References: <049.64e07177e9110058c04a019d46370d44@haskell.org> Message-ID: <064.03105dc01551a8f99b4c670ec48b623f@haskell.org> #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: NoFib benchmark | Version: 8.0.1 suite | 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 mpickering): * keywords: => newcomer Comment: There are still some benchmarks specifically to do with effect handlers which could be added but they require a bit more work to extract from the libraries. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 15 23:46:30 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 15 Mar 2018 23:46:30 -0000 Subject: [GHC] #14929: Program compiled with -O2 exhibits much worse performance Message-ID: <049.ba205f50f7e92bd0b7f0e4b08e0f1c92@haskell.org> #14929: Program compiled with -O2 exhibits much worse performance -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A user on reddit reports that compiling the program with `-O2` makes his program use a lot more memory. https://www.reddit.com/r/haskell/comments/84qovv/an_example_of_code_where_ghcs_o2_makes_things/ It runs in constant memory without `-O2` and leaks memory with `-O2. It seems worth investigating as the example is quite small (< 1000 lines) and self-contained. https://github.com/luispedro/TestingNGLESS -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 02:50:11 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 02:50:11 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.9d0dcf4f0fd3ca61cb9da25c8134f9c1@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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): Yes, I was thinking of compulsory unfoldings without realizing it. I think the existing check for levity-polymorphic arguments in the desugarer (which wouldn't change under this proposal) would catch cases where a levity-polymorphic function wasn't sufficiently specialized. All that would be left to check for is that the compulsory unfolding would actually work (and that the function was sufficiently saturated). If it doesn't, I think we would be able to report a sensible error, because we at least have the name of the thing that didn't unfold. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 02:51:35 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 02:51:35 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.62cb6e9f1cb29a5cc6053652da6b89c9@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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): You know, this is all very much like unboxed tuples. Unboxed tuples are themselves levity polymorphic, must be levity monomorphic at use sites, and have a compulsory unfolding. So perhaps much of the plumbing is installed already. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 09:30:33 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 09:30:33 -0000 Subject: [GHC] #14930: GHC.Stats Since annotations are wrong Message-ID: <051.88392e05880baa9ae42f028321b6669c@haskell.org> #14930: GHC.Stats Since annotations are wrong -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.4.1 libraries/base | 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: -------------------------------------+------------------------------------- GHC.Stats claims all the RTS Stats stuff is available since base 4.9.0.0. In truth it was only added in base 4.10.0.0. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 12:26:38 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 12:26:38 -0000 Subject: [GHC] #14930: GHC.Stats Since annotations are wrong In-Reply-To: <051.88392e05880baa9ae42f028321b6669c@haskell.org> References: <051.88392e05880baa9ae42f028321b6669c@haskell.org> Message-ID: <066.cd4b0265bce6b59999095c6473acf4b8@haskell.org> #14930: GHC.Stats Since annotations are wrong -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.4.1 Resolution: | Keywords: newcomer 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 RyanGlScott): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 12:29:15 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 12:29:15 -0000 Subject: [GHC] #14928: TH eats 50 GB memory when creating ADT with multiple constructors In-Reply-To: <047.b13a12d7e6e4b7703250170f5b54bd52@haskell.org> References: <047.b13a12d7e6e4b7703250170f5b54bd52@haskell.org> Message-ID: <062.605217b5d79e3197a2d223eea5725d16@haskell.org> #14928: TH eats 50 GB memory when creating ADT with multiple constructors -------------------------------------+------------------------------------- Reporter: YitzGale | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: Old description: > When TH creates a data type with multiple constructors, GHC consumes huge > amounts of memory in what appears to be a highly superlinear manner. > > A common use case: in the Yesod web framework, localized strings are > represented by constructors of a Messages data type, created by a TH > splice. There is one constructor for each localized string on the site, > possibly hundreds. The splice also creates a class instance for the data > type whose method matches against all the constructors for each language > for which localizations are provided; this may or may not play a role in > the memory leak. This Trac ticket corresponds to this Yesod issue: > > https://github.com/yesodweb/yesod/issues/1487 > > Here are two reproductions, and one NON-reproduction: > > 1. A blank "hello world" Yesod web site, with 500 messages defined for > about 30 languages. The single page displays the messages in the user's > language. Compiling this program in GHC 8.2.2 (stackage lts-10.5) on > Ubuntu 16.04 eats over 50 GB of memory. > > https://gitub.com/ygale/yesod-bug1487 > > 2. @snoyberg has cut down this reproduction to avoid using any libraries > not included with GHC. It is in the same repo, on the {{{snoyberg- > master}}} branch. > > NON-reproduction: The code in this gist, which is similar to what is > generated by the TH in the above reproductions, is compiled by GHC > without the bat of an eyelash. This demonstrates that the bug requires TH > to reproduce. https://gist.github.com/92347aa93d226e31f977a0b62b443aa7 New description: When TH creates a data type with multiple constructors, GHC consumes huge amounts of memory in what appears to be a highly superlinear manner. A common use case: in the Yesod web framework, localized strings are represented by constructors of a Messages data type, created by a TH splice. There is one constructor for each localized string on the site, possibly hundreds. The splice also creates a class instance for the data type whose method matches against all the constructors for each language for which localizations are provided; this may or may not play a role in the memory leak. This Trac ticket corresponds to this Yesod issue: https://github.com/yesodweb/yesod/issues/1487 Here are two reproductions, and one NON-reproduction: 1. A blank "hello world" Yesod web site, with 500 messages defined for about 30 languages. The single page displays the messages in the user's language. Compiling this program in GHC 8.2.2 (stackage lts-10.5) on Ubuntu 16.04 eats over 50 GB of memory. https://github.com/ygale/yesod-bug1487 2. @snoyberg has cut down this reproduction to avoid using any libraries not included with GHC. It is in the same repo, on the {{{snoyberg- master}}} branch. NON-reproduction: The code in this gist, which is similar to what is generated by the TH in the above reproductions, is compiled by GHC without the bat of an eyelash. This demonstrates that the bug requires TH to reproduce. https://gist.github.com/92347aa93d226e31f977a0b62b443aa7 -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:22:01 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:22:01 -0000 Subject: [GHC] #14931: Segfault compiling files with -fprof-all Message-ID: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> #14931: Segfault compiling files with -fprof-all -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Originally noticed [https://github.com/llvm-hs/llvm- hs/issues/86#issuecomment-373710312 here]. Take the following two files: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE UndecidableInstances #-} module State (MonadState(..), Lazy.evalState) where import qualified Control.Monad.Trans.State.Lazy as Lazy (StateT, get, put, evalState) class Monad m => MonadState s m | m -> s where get :: m s put :: s -> m () instance Monad m => MonadState s (Lazy.StateT s m) where get = Lazy.get put = Lazy.put }}} {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Prelude (Int, IO, Bool(..), Num(..), Monad(..), not, print) import qualified Language.Haskell.TH.Syntax as TH import State wat :: IO () wat = print $(let playGame [] = do (_, score) <- get return score playGame (x:xs) = do (on, score) <- get case x of 'a' | on -> put (on, score + 1) 'b' | on -> put (on, score - 1) 'c' -> put (not on, score) _ -> put (on, score) playGame xs startState :: (Bool, Int) startState = (False, 0) in TH.lift (evalState (playGame "abcaaacbbcabbab") startState) ) }}} Compiling them like so leads to a segfault: {{{ $ ~/Software/ghc-8.4.1/bin/ghc -c -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi State.hs $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi State.hs -fprof-auto $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi Bug.hs Segmentation fault (core dumped) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:23:15 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:23:15 -0000 Subject: [GHC] #14931: Segfault compiling files with -fprof-all In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.bdc19dcd8828764cc45bd6cf6ab97247@haskell.org> #14931: Segfault compiling files with -fprof-all -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This bug has an interesting history. On GHC 8.0.2, doing the same thing yielded [https://github.com/llvm-hs/llvm- hs/issues/86#issuecomment-301194192 this error]: {{{ $ /opt/ghc/8.0.2/bin/ghc -c -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi State.hs $ /opt/ghc/8.0.2/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi State.hs -fprof-auto $ /opt/ghc/8.0.2/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi Bug.hs ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: State_zdfMonadStatesStateTzuzdcget_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs at haskell.org }}} However, on GHC 8.2.1 and 8.2.2, it appeared to work without issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:24:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:24:48 -0000 Subject: [GHC] #14931: Segfault compiling files with -fprof-auto (was: Segfault compiling files with -fprof-all) In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.0e8ec6f63ee7fb1228c91f1eb77c8956@haskell.org> #14931: Segfault compiling files with -fprof-auto -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:27:16 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:27:16 -0000 Subject: [GHC] #14931: Segfault compiling files with -prof (was: Segfault compiling files with -fprof-auto) In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.de895669bf344f90c7d624192187002f@haskell.org> #14931: Segfault compiling files with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Actually, `-fprof-auto` has nothing to do with this—you can reproduce the issue with simply `-prof`: {{{ $ ~/Software/ghc-8.4.1/bin/ghc -c -O -static -dynamic-too -dynosuf dyn_o -dynhisuf dyn_hi State.hs $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi State.hs $ ~/Software/ghc-8.4.1/bin/ghc -c -O -prof -osuf p_o -hisuf p_hi Bug.hs Segmentation fault (core dumped) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:34:46 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:34:46 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof (was: Segfault compiling files with -prof) In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.ffe63354d492fe0fb434060fd5a2e6e6@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I forgot that `mtl` is bundled with GHC now, so you can reproduce this with a single file: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TemplateHaskell #-} module Bug where import Prelude (Int, IO, Bool(..), Num(..), Monad(..), not, print) import qualified Language.Haskell.TH.Syntax as TH import Control.Monad.State wat :: IO () wat = print $(let playGame [] = do (_, score) <- get return score playGame (x:xs) = do (on, score) <- get case x of 'a' | on -> put (on, score + 1) 'b' | on -> put (on, score - 1) 'c' -> put (not on, score) _ -> put (on, score) playGame xs startState :: (Bool, Int) startState = (False, 0) in TH.lift (evalState (playGame "abcaaacbbcabbab") startState) ) }}} {{{ $ ~/Software/ghc-8.4.1/bin/ghc -O -prof -osuf p_o -hisuf p_hi Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.p_o ) Segmentation fault (core dumped) }}} Also, Template Haskell appears to be a key ingredient here, since removing it makes the issue go away. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:43:35 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:43:35 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.24a99b7e759fd82bbac2e7369aa2ba52@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nmattia): Ok, this is really strange. I've tried to reproduce the example given in https://ghc.haskell.org/trac/ghc/ticket/8025. In this case, GHC 8.0.2 and 8.2.2 fail with {{{ ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: ... }}} while 8.4.1 (actually, [8.4.0 https://github.com/NixOS/nixpkgs/issues/37026]) ) compiles successfully: {{{ nicolas at nicolas-XPS-13-9370:/tmp/no-code$ cat A.hs {-# LANGUAGE TemplateHaskell #-} module A where a = [|3|] nicolas at nicolas-XPS-13-9370:/tmp/no-code$ cat B.hs {-# LANGUAGE TemplateHaskell #-} module B where import A x = $(a) nicolas at nicolas-XPS-13-9370:/tmp/no-code$ nix-shell -p 'haskell.compiler.ghc802' --run 'ghc -fno-code B' [1 of 2] Compiling A ( A.hs, nothing ) [2 of 2] Compiling B ( B.hs, nothing ) ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: A_a_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs at haskell.org nicolas at nicolas-XPS-13-9370:/tmp/no-code$ nix-shell -p 'haskell.compiler.ghc822' --run 'ghc -fno-code B' [1 of 2] Compiling A ( A.hs, nothing ) [2 of 2] Compiling B ( B.hs, nothing ) ghc: ^^ Could not load 'A_a_closure', dependency unresolved. See top entry above. ByteCodeLink.lookupCE During interactive linking, GHCi couldn't find the following symbol: A_a_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please send a bug report to: glasgow-haskell-bugs at haskell.org nicolas at nicolas-XPS-13-9370:/tmp/no-code$ nix-shell -p 'haskell.compiler.ghc841' --run 'ghc -fno-code B' [1 of 2] Compiling A ( A.hs, /run/user/1001/ghc17566_0/ghc_2.o ) [2 of 2] Compiling B ( B.hs, /run/user/1001/ghc17566_0/ghc_4.o ) nicolas at nicolas-XPS-13-9370:/tmp/no-code$ echo $? 0 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 13:48:50 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 13:48:50 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.f558f0a8cfa29eebe5add645ed2e4300@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here's a version which doesn't depend on `mtl`: {{{#!hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Data.Functor.Identity (runIdentity) import Language.Haskell.TH.Syntax (lift) wat :: IO () wat = print $(lift $ runIdentity $ do (_, x) <- return (True, False) return x) }}} {{{ $ ~/Software/ghc-8.4.1/bin/ghc -O -prof -osuf p_o -hisuf p_hi Bug.hs [1 of 1] Compiling Bug ( Bug.hs, Bug.p_o ) Segmentation fault (core dumped) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 14:02:57 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 14:02:57 -0000 Subject: [GHC] #9671: Allow expressions in patterns In-Reply-To: <051.5c0ed72ec50bbc2111e7cfd2e5c841ff@haskell.org> References: <051.5c0ed72ec50bbc2111e7cfd2e5c841ff@haskell.org> Message-ID: <066.738f251cfe7d1c0d4a7547098feae94b@haskell.org> #9671: Allow expressions in patterns -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) 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: | -------------------------------------+------------------------------------- Changes (by ekmett): * cc: ekmett (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 15:06:52 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 15:06:52 -0000 Subject: [GHC] #9671: Allow expressions in patterns In-Reply-To: <051.5c0ed72ec50bbc2111e7cfd2e5c841ff@haskell.org> References: <051.5c0ed72ec50bbc2111e7cfd2e5c841ff@haskell.org> Message-ID: <066.4840deba235e50aaa5d31ee91d6e59b0@haskell.org> #9671: Allow expressions in patterns -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) 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 ekmett): {{{Lookup $"Alice" =}}} is syntactically ambiguous in the context where you are doing a destructuring assignment. It could be defining `$` or providing the marker. This seems to indicate that the marker should be a divider or indicator of purpose that is already reserved syntax and isn't a valid operator. `->` is taken by view patterns, but you could use (with varying degrees of absurdity) already reserved operators like `<-`, `\`, `;`, `..`, `=>` as either a separator between parameters and fields or as an indicator in a manner that would simply be filling a hole in the grammar, if you really want a visual indicator of which arguments to the pattern are inputs if we really do want a visual marker here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 15:16:15 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 15:16:15 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.260e75edc458479f6657abdf8a1c254e@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => highest * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 15:35:03 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 15:35:03 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.391c09ef74f3dd45af840372ab1939e3@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Given that annotations and template haskell are handled in a similar way, I'm thinking there is a possibility that this could be related to #14675 (see comment 22 & 23 for a summary) and similar tickets. However, 8.4.1 shipped with a workaround... which might break things here? Or some other commits since 8.2.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 20:03:59 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 20:03:59 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.6e71b87906da8ebd7ee8fd1a9cbcad75@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See also Kavon's patch offered at https://phabricator.haskell.org/D4505 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 20:38:42 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 20:38:42 -0000 Subject: [GHC] #5611: Asynchronous exception discarded after safe FFI call In-Reply-To: <048.a1f4840a208dec01f4783b6a8911d995@haskell.org> References: <048.a1f4840a208dec01f4783b6a8911d995@haskell.org> Message-ID: <063.5db642317d63398f6a368b7b0c4373e7@haskell.org> #5611: Asynchronous exception discarded after safe FFI call -------------------------------------+------------------------------------- Reporter: joeyadams | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 7.0.3 Resolution: fixed | Keywords: FFI, | exception, Exceptions 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 bgamari): * status: new => closed * resolution: => fixed Comment: I've not seen this fail on CI in the years I've been looking at results. I'm going to call this resolved. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 20:51:32 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 20:51:32 -0000 Subject: [GHC] #9671: Allow expressions in patterns In-Reply-To: <051.5c0ed72ec50bbc2111e7cfd2e5c841ff@haskell.org> References: <051.5c0ed72ec50bbc2111e7cfd2e5c841ff@haskell.org> Message-ID: <066.9bac8a78dee5af0015936c9752cec70f@haskell.org> #9671: Allow expressions in patterns -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) 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 Iceland_jack): People seem to like `\` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 16 21:17:10 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 16 Mar 2018 21:17:10 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.6786968a57f523a345ffd369c6e736b7@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * cc: kavon (added) Comment: While working on my own version of this patch (without knowing about this work yet) I noticed that we may not want to perform the loopification transformation too early, as specialization and other optimizations end up turning a binder marked as `RecursiveTailCalled` into a a full join point, and we end up with better code. Thus, my plan was to implement it as a separate Core pass to figure out at what point(s) during optimization to perform loopification. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 00:33:41 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 00:33:41 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.632a1f5039c1b29c160b56d6910fe9df@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:36 osa1]: > Sorry for the confusion -- it turns out GHC 8.2.2 already optimizes this. Perhaps this can be closed or we may need a new reproducer. I have a very similar program where, with 8.4.1, the forM_ version allocates 50% more than the version with recursive go but both versions run in about the same time . Is it worth giving that code here in this bug or should I enter a new bug referencing this one? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 11:09:34 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 11:09:34 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.8446e4e4615c06ab13e6ce8da48ea894@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): > I have a very similar program where, with 8.4.1, the forM_ version allocates 50% more than the version with recursive go but both versions run in about the same time . Is it worth giving that code here in this bug or should I enter a new bug referencing this one? What is the first argument of `forM_` in you program? This ticket (and #7206) is specifically about `forM_`/`mapM_` when the foldable argument is of form `[n .. m]`. If your program is different than perhaps a new ticket would be better. In any case, it's not a big deal if you paste your program here, we can move it to a new ticket if it turns out to be something different than what we try to improve here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 19:15:36 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 19:15:36 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.ad4391f791f4da3372d3314908d8ca11@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ckoparkar): I'd like to work on this, if that's OK with @mrkgnao. I have a patch on my local machine that does the right thing for the examples posted in the description (and some tests: `th/T3319`, `th/T5700`, `th/TH_foreignInterruptible`). While I work on submitting that on Phabricator, I wanted to post a summary here and get some early feedback. (1) It seems that `showName` doesn't play a role in pretty-printing the splices with `-ddump-splices`. Instead, the `Outputable` instances in GHC do most of the work. Specifically, `Outputable RdrName` is responsible for printing out the fully qualified names in question. (2) When the Renamer typechecks & runs a splice (`RnSplice.runRnSplice`), it converts the splice to `HsSyn RdrName` (hence the `Outputable RdrName`). `TcSplice.lookupThName` is involved in the process, which converts a `TH.Name` to `Name` via `Convert.thRdrNameGuesses`. (3) For primitives like `[]`, `(:)` etc. `TH.dataToQa` generates a fully qualified global name, i.e `NameG NameSpace PkgName ModName`. And the corresponding `RdrName` generated by `thRdrNameGuesses` is also fully qualified (`Orig Module OccName`). But this is not what we want for built- in syntax. (4) So the "patch" is a simple change to modify this behavior. If `thOrigRdrName` is dealing with built-in syntax, it returns an `Exact Name` instead. {{{#!haskell thOrigRdrName :: String -> TH.NameSpace -> PkgName -> ModName -> RdrName thOrigRdrName occ th_ns pkg mod = let occ' = mk_occ (mk_ghc_ns th_ns) occ in case isBuiltInOcc_maybe occ' of Just name -> nameRdrName name Nothing -> (mkOrig $! (mkModule (mk_pkg pkg) (mk_mod mod))) $! occ' }}} I ran the testsuite, and apart from some `perf` tests, almost everything else worked. These tests fail: {{{ ghci/linking/ghcilink003.run ghcilink003 [bad exit code] (normal) ghci/linking/ghcilink006.run ghcilink006 [bad exit code] (normal) th/T13366.run -- (gcc: error trying to exec 'cc1plus': execvp: -- No such file or directory) }}} but there's a good chance that this is unrelated to the patch. Does the overall approach seem reasonable ? I'll submit a patch soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 19:22:59 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 19:22:59 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.159dec27686dd4e493860d2866801954@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That approach looks promising to me! All of the test failures seem to be C++-related—do you have `g++` installed? In any case, I'd go ahead and just submit your patch to Phabricator. If the CI fails on those tests //there//, then we can puzzle it over :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 20:34:47 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 20:34:47 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.ad7c849ccbf2a28fd1829f54059a75ee@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4506 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ckoparkar): * status: new => patch * differential: => Phab:D4506 Comment: Great! Submitted a patch to Phabricator :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 20:39:47 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 20:39:47 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables Message-ID: <050.9f4e9be95913004697959a884a0f5742@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 (Type checker) | Keywords: deriving | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: #13272 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code (courtesy of kosmikus) should typecheck, but does not: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module Zero where import GHC.Exts class Zero a where zero :: a default zero :: (Code a ~ '[xs], All Zero xs) => a zero = undefined type family All c xs :: Constraint where All c '[] = () All c (x : xs) = (c x, All c xs) type family Code (a :: *) :: [[*]] type instance Code B1 = '[ '[ ] ] data B1 = B1 deriving Zero }}} This produces the following error: {{{ GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /nfs/nfs7/home/rgscott/.ghci [1 of 1] Compiling Zero ( Bug.hs, interpreted ) Bug.hs:23:11: error: • Couldn't match type ‘xs0’ with ‘'[]’ arising from the 'deriving' clause of a data type declaration ‘xs0’ is untouchable inside the constraints: All Zero xs0 bound by the deriving clause for ‘Zero B1’ at Bug.hs:23:11-14 • When deriving the instance for (Zero B1) | 23 | deriving Zero | ^^^^ }}} This error is baffling, however, because `xs0` should be a unification variable that readily unifies with `'[]`! As evidence, this typechecks: {{{ instance Zero B1 }}} But the equivalent `deriving` clause does not. I know what is going on here after some sleuthing: `DeriveAnyClass` (specifically, `inferConstraintsDAC`) is producing unification variables whose TcLevel is always bumped to three. However, in the program above, we will not form an implication constraints around those unification variables, since `zero` has no locally quantified type variables or given constraints. Thus, `simplifyDeriv` will try to simplify unification variables with TcLevel 3 at the top level, which results in them being untouchable. Blegh. This was partially noticed in #13272, when we were failing to bump unification variables that //did// appear inside implication constraints. However, we overlooked this one corner case, which kosmikus happened to stumble upon in a `generics-sop` [https://stackoverflow.com/a/49335338/1482749 example]. Patch incoming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 20:48:57 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 20:48:57 -0000 Subject: [GHC] #14731: Document alignment & underlying size invariants for array types in GHC.Prim (was: Document alignment invariants for array types in GHC.Prim) In-Reply-To: <048.57574daf7b44935566d768b0adc24ecb@haskell.org> References: <048.57574daf7b44935566d768b0adc24ecb@haskell.org> Message-ID: <063.1374a9577b2562d50b19b429bdd70759@haskell.org> #14731: Document alignment & underlying size invariants for array types in GHC.Prim -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2917 #9806 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by jberryman: Old description: > Through a combination of reading some of the wiki entries on the RTS, > some trac tickets, and experimentation I've inferred that the payloads > for bytearray types will always be aligned to the machine word size, even > after GC. I guess this is obvious in retrospect since otherwise non- > pinned arrays would be pretty useless. > > I'm not sure what the promises are for all the `Foreign` stuff. New description: Through a combination of reading some of the wiki entries on the RTS, some trac tickets, and experimentation I've inferred that the payloads for bytearray types will always be aligned to the machine word size, even after GC. I guess this is obvious in retrospect since otherwise non-pinned arrays would be pretty useless. Another thing I've picked up is that the memory backing a ByteArray is always evenly divisible by the machine word size: http://haskell.1045720.n5.nabble.com/Is-it-safe-to-index-a-little-bit-out- of-bounds-td5872779.html It would be great if these were documented, but more importantly (to me), I'd like to be able to rely on them as invariants in my own libraries. The first is obviously important (any code doing reads larger than single byte relies on it), but the second one is also really useful: e.g. I'm working on a hashing library that works on `text` and reads machine words for efficiency, doing endian adjustments as needed; it's a little easier and more efficient to do word-aligned word-sized "dirty" reads that cover all the data and then to clean up either end. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 21:03:58 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 21:03:58 -0000 Subject: [GHC] #14731: Document alignment & underlying size invariants for array types in GHC.Prim In-Reply-To: <048.57574daf7b44935566d768b0adc24ecb@haskell.org> References: <048.57574daf7b44935566d768b0adc24ecb@haskell.org> Message-ID: <063.362a244696dbfbfc1e50bcf0567b9a34@haskell.org> #14731: Document alignment & underlying size invariants for array types in GHC.Prim -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2917 #9806 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jberryman): I updated the ticket to also mention the property that ByteArray have underlying size evenly divisible by word-size. It's not clear if that's something GHC wants to commit to as an invariant, e.g. I was just reading #11312 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 21:57:00 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 21:57:00 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.ed576903439b938044ad2d5eec8b555c@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Hi Kavon, nice to see someone else working on this. With the ICFP deadline out of the way, I want to pick this up again. > as specialization and other optimizations end up turning a binder marked as RecursiveTailCalled into a a full join point, and we end up with better code. Can you elaborate? I noticed that the most regressions due to loopification are due to ConstSpec only targetting recursive things. Do you observe that as well? So the plan would be to experiment with a specializer that works also for non-recursive functions. Do you want to try that out? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 22:22:47 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 22:22:47 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic Message-ID: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: deriving | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This program panics: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module Bug where import Control.Concurrent (ThreadId) import Control.Monad.Reader class Wrapped s where type Unwrapped s :: * _Wrapped' :: Iso' s (Unwrapped s) type Iso' s a = forall f. Functor f => (a -> f a) -> s -> f s class Fork m where fork :: x -> m () -> m ThreadId default fork :: ( Wrapped (m ()) , Unwrapped (m ()) ~ t () , Fork t , Wrapped (m ThreadId) , Unwrapped (m ThreadId) ~ t ThreadId ) => x -> m () -> m ThreadId fork = undefined -- view _Unwrapped' . fork . view _Wrapped' instance Fork m => Fork (ReaderT e m) where fork x action = ReaderT $ \env -> fork x (runReaderT action env) data Env newtype MyThing m a = MyThing { unMyThing :: ReaderT Env m a } deriving newtype (Functor, Applicative, Monad) deriving anyclass (Fork) instance Wrapped (MyThing m a) where type Unwrapped (MyThing m a) = ReaderT Env m a _Wrapped' = undefined -- iso unMyThing MyThing }}} {{{ [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:39:24: error:ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): No skolem info: m_a1Hs[sk:2] Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcErrors.hs:2653:5 in ghc:TcErrors }}} (Program adapted from [https://github.com/ekmett/lens/issues/793#issuecomment-369597846 here].) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 22:24:01 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 22:24:01 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.be6f5fcc68c182ade8f7a76c84be56ea@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13272 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well, I do have a patch. But I also recently noticed the existence of #14933, which shares many similar characteristics with this issue, and now I'm wondering if perhaps I should clean up GHC's approach to `DeriveAnyClass` further to nail both bugs at once. Let me see how far I get... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 17 22:59:21 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 17 Mar 2018 22:59:21 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic In-Reply-To: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> References: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> Message-ID: <065.4beefbea5a14d668e69b8712449fc27b@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): Smaller version: {{{ {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE TypeFamilies #-} module Bug where class Wrapped s where type Unwrapped s :: * class Fork m where fork :: (x, m) default fork :: ( Wrapped m , Unwrapped m ~ t , Fork t ) => (x, m) fork = undefined newtype MyThing m = MyThing m deriving (Fork) instance Wrapped (MyThing m) where type Unwrapped (MyThing m) = m }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 01:14:15 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 01:14:15 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.ee8fba514221860026a4b28cff5c76fb@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4507 * related: #13272 => #13272, #14933 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 01:15:38 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 01:15:38 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic In-Reply-To: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> References: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> Message-ID: <065.d7366c013603abb98aed3fb0655fa3cf@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4507 * related: => #14932 Comment: Ack, it turns out that we are re-using the same unification variables across multiple iterations of `simplifyDeriv`, which results in utter disaster. (Honestly, I'm not sure how anything was working before.) Phab:D4507 fixes this issue (and #14932) by generating new unification variables across //each// iteration of `simplifyDeriv`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 03:46:02 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 03:46:02 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. Message-ID: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I am getting the following error repeatedly: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-unknown-linux): go_axiom_rule Sub0R Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1371:15 in ghc:TcIface }}} I got it on 8.2.1, and tried upgrading to 8.4.1 to see if it went away, but it did not. It occurs frequently when I do a `--make` and recompile a subset of modules. I can avoid it by force-recompiling all modules, although of course this is inefficient. Since I'm working with a codebase of thousands of lines and don't understand ghc's innards, I'm not sure where to start looking for the cause, to produce a minimal failing example. But it did start happening around the time I expanded my use of this module: https://github.com/agrafix/superrecord Since there are unsafe operations in there, it is possible it is doing something illicit, but it is hard to see how it would cause this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 11:35:23 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 11:35:23 -0000 Subject: [GHC] #14930: GHC.Stats Since annotations are wrong In-Reply-To: <051.88392e05880baa9ae42f028321b6669c@haskell.org> References: <051.88392e05880baa9ae42f028321b6669c@haskell.org> Message-ID: <066.a263e6bb3bb84d3012d60ac358bc2742@haskell.org> #14930: GHC.Stats Since annotations are wrong -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.4.1 Resolution: | Keywords: newcomer 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: | -------------------------------------+------------------------------------- Comment (by ckoparkar): It seems like this is fixed in HEAD by this [https://github.com/ghc/ghc/commit/8ff11c4e5ae475cf9bb7de4ce5271b4e62cbdeab commit]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 13:15:18 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 13:15:18 -0000 Subject: [GHC] #14930: GHC.Stats Since annotations are wrong In-Reply-To: <051.88392e05880baa9ae42f028321b6669c@haskell.org> References: <051.88392e05880baa9ae42f028321b6669c@haskell.org> Message-ID: <066.49cce5de46095f9f7af788bdc9c396b7@haskell.org> #14930: GHC.Stats Since annotations are wrong -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 8.4.1 Resolution: duplicate | Keywords: newcomer 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 RyanGlScott): * status: new => closed * resolution: => duplicate Comment: Indeed it was. Thanks for noticing! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 13:29:00 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 13:29:00 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.480bc995cea5df4f59ef80ca4188f6f8@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => infoneeded Comment: We'll likely need some more information before we can debug this. As a start, you mentioned that you experienced this bug when recompiling modules after a change, which isn't [https://ghc.haskell.org/trac/ghc/ticket/13695 unheard of]. Can you point us to a project of yours where: 1. Building it, 2. Making some change, and 3. Rebuilding Produces the panic? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 13:49:30 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 13:49:30 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.76e588890fc49468a569e44abb68b551@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): That being said, I have a wild hunch what could be causing this. [http://git.haskell.org/ghc.git/blob/0693b0b0500236a3dec933350a13f1b0e8c1cb54:/compiler/iface/TcIface.hs#l1336 Here] is where `go_axiom_co` is defined: {{{#!hs tcIfaceCo :: IfaceCoercion -> IfL Coercion tcIfaceCo = go where -- ... go (IfaceAxiomRuleCo ax cos) = AxiomRuleCo <$> go_axiom_rule ax <*> mapM go cos -- ... go_axiom_rule :: FastString -> IfL CoAxiomRule go_axiom_rule n = case Map.lookup n typeNatCoAxiomRules of Just ax -> return ax _ -> pprPanic "go_axiom_rule" (ppr n) }}} It seems that the `Sub0R` axiom isn't in [http://git.haskell.org/ghc.git/blob/0693b0b0500236a3dec933350a13f1b0e8c1cb54:/compiler/typecheck/TcTypeNats.hs#l378 typeNatCoAxiomRules]: {{{#!hs typeNatCoAxiomRules :: Map.Map FastString CoAxiomRule typeNatCoAxiomRules = Map.fromList $ map (\x -> (coaxrName x, x)) [ axAddDef , axMulDef , axExpDef , axLeqDef , axCmpNatDef , axCmpSymbolDef , axAppendSymbolDef , axAdd0L , axAdd0R , axMul0L , axMul0R , axMul1L , axMul1R , axExp1L , axExp0R , axExp1R , axLeqRefl , axCmpNatRefl , axCmpSymbolRefl , axLeq0L , axSubDef -- axSub0R isn't here!!! , axAppendSymbol0R , axAppendSymbol0L , axDivDef , axDiv1 , axModDef , axMod1 , axLogDef ] }}} So perhaps we should just add it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 14:21:02 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 14:21:02 -0000 Subject: [GHC] #14407: rts: Threads/caps affinity In-Reply-To: <044.bf4507a98f68743970936df39c9089d2@haskell.org> References: <044.bf4507a98f68743970936df39c9089d2@haskell.org> Message-ID: <059.2e044fcab263d003c9b9abef09e77ac7@haskell.org> #14407: rts: Threads/caps affinity -------------------------------------+------------------------------------- Reporter: pacak | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.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): Phab:D4143 Wiki Page: | -------------------------------------+------------------------------------- Comment (by YitzGale): How does this relate to the {{{setThreadAfinity}}} mentioned in #10229, that was implemented 3 years ago in GHC 7.10? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 14:36:49 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 14:36:49 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.d2df2396031f806cb1f83b1941b1ec45@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: infoneeded => new Comment: I can reproduce the issue now. Take these two files: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeOperators #-} module Foo where import GHC.TypeLits data Foo :: Nat -> * where MkFoo0 :: Foo 0 MkFoo1 :: Foo 1 f :: Foo (1 - 0) -> Foo 1 f x = x }}} {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} module Bar where import Foo import GHC.TypeLits g :: Foo (1 - 0) g = f MkFoo1 {- h :: Foo (1 - 0) h = MkFoo1 -} }}} And perform the following steps: 1. Run `/opt/ghc/8.2.2/bin/ghc Bar.hs -O2`. 2. Uncomment out the definition of `h` in `Bar.hs`. 3. Re-run `/opt/ghc/8.2.2/bin/ghc Bar.hs -O2`: {{{ $ /opt/ghc/8.2.2/bin/ghc Bar.hs -O2 [1 of 2] Compiling Foo ( Foo.hs, Foo.o ) [2 of 2] Compiling Bar ( Bar.hs, Bar.o ) $ vim Bar.hs $ /opt/ghc/8.2.2/bin/ghc Bar.hs -O2 [2 of 2] Compiling Bar ( Bar.hs, Bar.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): go_axiom_rule Sub0R Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1349:15 in ghc:TcIface }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 14:54:42 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 14:54:42 -0000 Subject: [GHC] #14935: Vary default RTS settings so that performance does not degrade with increasing number of capabilities Message-ID: <047.c1e3c537cd577233605e2a8fc8124d44@haskell.org> #14935: Vary default RTS settings so that performance does not degrade with increasing number of capabilities -------------------------------------+------------------------------------- Reporter: YitzGale | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When the number of capabilities increases to 32 or more, which is common nowadays, performance of GHC-compiled applications, hence also of GHC itself, begins to degrade considerably with default RTS settings. It should not be required to optimize RTS settings manually to get applications to be usable. By default, GHC should use at least sane RTS settings appropriate for the number of capabilities, even if not optimized. See: https://www.reddit.com/r/haskell/comments/83e6dq/need_advice_on_compile_and_runtime_options_for/ for some of the RTS settings you need to change to get things working. Here is a sample use case - we needed to increase memory by a lot to work around #14928. We don't care about extra cores, but we get them automatically when we enlarge our EC2 instance to have enough memory. The compile is run by deployment engineers - non-Haskell-programmers - via build tools that normally do not give easy access to RTS options on the individual {{{ghc}}} commands that run during the build ({{{yesod keter}}} in this case). We just want the build to run no worse than if there were 4 cores, or even 1 core. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 16:45:49 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 16:45:49 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.470895a693c89248aa6475d242270218@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by galen): Nice! The commenting/uncommenting of `h` is not even necessary. If I compile with it uncommented, do a `touch Bar.hs`, and recompile, I still get the error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 17:06:05 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 17:06:05 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.a83b1863f316b1cb18b54a729b67072f@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D4508 Comment: Or, for maximum terseness: {{{ $ ghc Foo.hs -c -O $ ghc Bar.hs -c -O ghc: panic! (the 'impossible' happened) (GHC version 8.2.2 for x86_64-unknown-linux): go_axiom_rule Sub0R Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/iface/TcIface.hs:1349:15 in ghc:TcIface }}} I'll use this as the regression test in Phab:D4508. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 17:42:01 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 17:42:01 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes Message-ID: <046.51c083465a95f77099b97377aa2723e3@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.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: -------------------------------------+------------------------------------- Here is some serious performance regression in the following code: {{{ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} module Main where import Prelude import qualified Foreign.Storable as Storable import qualified Control.Monad.State.Strict as S import Control.Monad.IO.Class import Foreign.Marshal.Alloc (mallocBytes) import Criterion.Main newtype Foo a = Foo a intSize :: Int intSize = Storable.sizeOf (undefined :: Int) slow :: Int -> IO () slow i = do ptr <- mallocBytes $ 2 * intSize Storable.pokeByteOff ptr intSize (0 :: Int) let go 0 = pure () go j = do Foo (!_, !off) <- S.get !(x :: Int) <- liftIO $ Storable.peekByteOff ptr off liftIO $ Storable.pokeByteOff ptr off $! (x + 1) go (j - 1) S.evalStateT (go i) (Foo ((0::Int),(intSize::Int))) fast :: Int -> IO () fast i = do ptr <- mallocBytes $ 2 * intSize Storable.pokeByteOff ptr intSize (0 :: Int) let go 0 = pure () go j = do (!_, !off) <- S.get !(x :: Int) <- liftIO $ Storable.peekByteOff ptr off liftIO $ Storable.pokeByteOff ptr off $! (x + 1) go (j - 1) S.evalStateT (go i) ((0::Int),(intSize::Int)) main :: IO () main = defaultMain [ bgroup "slow" $ (\(i :: Int) -> bench ("10e" <> show i) $ perRunEnv (return ()) $ \v -> slow (10 ^ i)) <$> [7..8] , bgroup "fast" $ (\(i :: Int) -> bench ("10e" <> show i) $ perRunEnv (return ()) $ \v -> fast (10 ^ i)) <$> [7..8] ] }}} Compiled with flags: `-threaded -funbox-strict-fields -O2 -fconstraint-solver-iterations=100 -fexcess-precision -fexpose-all-unfoldings -flate-dmd-anal -fspec-constr- keen -fspecialise-aggressively -fstatic-argument-transformation -fmax- worker-args=200` The `slow` function executes 2 times slower than the `fast` one. The only difference is that the state is wrapped in a newtype. It was working properly in GHC 8.2 (both functions were equally fast - as fast as the current `fast` function). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 18:46:58 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 18:46:58 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.8b1dcb46b0764d45ea9e4fd90d006fb0@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.4.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 danilo2): * priority: high => highest -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 18:49:25 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 18:49:25 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.fa7b57ad88a217dcc852633e59c6436f@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Here is a slighter smaller example to demonstrate the issue: {{{#!hs {-# LANGUAGE BangPatterns #-} module Bug2 where import Control.Monad.Trans.State.Strict newtype Foo a = Foo a slowGo :: Int -> StateT (Foo (Int, Int)) IO () slowGo 0 = pure () slowGo j = do Foo (!_, !off) <- get slowGo (j - 1) fastGo :: Int -> StateT (Int, Int) IO () fastGo 0 = pure () fastGo j = do (!_, !off) <- get fastGo (j - 1) }}} In GHC 8.2.2, if you compare the Core between these two functions (in the `_$s_$w` functions that perform most of the work): {{{ $ /opt/ghc/8.2.2/bin/ghc Bug2.hs -O2 -fforce-recomp -ddump-simpl -dsuppress-idinfo -dsuppress-uniques -dsuppress-module-prefixes -dsuppress-coercions [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) ==================== Tidy Core ==================== Result size of Tidy Core = {terms: 190, types: 298, coercions: 60, joins: 0/0} ... Rec { -- RHS size: {terms: 24, types: 23, coercions: 0, joins: 0/0} fastGo_$s$wfastGo :: State# RealWorld -> Int# -> Int# -> Int# -> (# State# RealWorld, ((), (Int, Int)) #) fastGo_$s$wfastGo = \ (sc :: State# RealWorld) (sc1 :: Int#) (sc2 :: Int#) (sc3 :: Int#) -> case sc3 of ds { __DEFAULT -> fastGo_$s$wfastGo sc sc1 sc2 (-# ds 1#); 0# -> (# sc, ((), (I# sc1, I# sc2)) #) } end Rec } ... Rec { -- RHS size: {terms: 25, types: 37, coercions: 6, joins: 0/0} slowGo_$s$wslowGo :: State# RealWorld -> Int# -> Int# -> ((Int, Int) :: *) ~R# (Foo (Int, Int) :: *) => Int# -> (# State# RealWorld, ((), Foo (Int, Int)) #) slowGo_$s$wslowGo = \ (sc :: State# RealWorld) (sc1 :: Int#) (sc2 :: Int#) (sg :: ((Int, Int) :: *) ~R# (Foo (Int, Int) :: *)) (sc3 :: Int#) -> case sc3 of ds { __DEFAULT -> slowGo_$s$wslowGo sc sc1 sc2 @~ (-# ds 1#); 0# -> (# sc, ((), (I# sc1, I# sc2) `cast` ) #) } end Rec } }}} Then they are essentially identical (the `slowGo` one has an extra argument of type `((Int, Int) :: *) ~R# (Foo (Int, Int) :: *)`, but that is zero-width, so it shouldn't have any effect at runtime). On the other hand, in GHC 8.4.1: {{{ $ ~/Software/ghc-8.4.1/bin/ghc Bug2.hs -O2 -fforce-recomp -ddump-simpl -dsuppress-idinfo -dsuppress-uniques -dsuppress-module-prefixes -dsuppress-coercions [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) ==================== Tidy Core ==================== Result size of Tidy Core = {terms: 163, types: 231, coercions: 54, joins: 0/0} ... Rec { -- RHS size: {terms: 24, types: 23, coercions: 0, joins: 0/0} fastGo_$s$wfastGo :: State# RealWorld -> Int# -> Int# -> Int# -> (# State# RealWorld, ((), (Int, Int)) #) fastGo_$s$wfastGo = \ (sc :: State# RealWorld) (sc1 :: Int#) (sc2 :: Int#) (sc3 :: Int#) -> case sc3 of ds { __DEFAULT -> fastGo_$s$wfastGo sc sc1 sc2 (-# ds 1#); 0# -> (# sc, ((), (I# sc1, I# sc2)) #) } end Rec } ... Rec { -- RHS size: {terms: 27, types: 34, coercions: 9, joins: 0/0} $wslowGo :: Int# -> Foo (Int, Int) -> State# RealWorld -> (# State# RealWorld, ((), Foo (Int, Int)) #) $wslowGo = \ (ww :: Int#) (w :: Foo (Int, Int)) (w1 :: State# RealWorld) -> case ww of ds { __DEFAULT -> case w `cast` of wild { (ds1, off) -> case ds1 of { I# ipv -> case off of { I# ipv1 -> $wslowGo (-# ds 1#) (wild `cast` ) w1 } } }; 0# -> (# w1, ((), w) #) } end Rec } }}} This time, `slowGo` doesn't have something akin to `slowGo_$s$wslowGo`. Instead, it performs the body of the loop in `$wslowGo`, which uses `Foo (Int, Int)` instead of two unboxed `Int#` arguments. I could imagine that this alone contributes to the slowdown. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 19:09:46 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 19:09:46 -0000 Subject: [GHC] #14937: QuantifiedConstraints: Reify implication constraints from terms lacking them Message-ID: <044.d2a38f2a080b1fef4440349e47b3df3b@haskell.org> #14937: QuantifiedConstraints: Reify implication constraints from terms lacking them -------------------------------------+------------------------------------- Reporter: Bj0rn | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #14822 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is possibly the same question as #14822, asked in more general terms. Would it be viable/sound to have a way of extracting implication constraints out of terms which effectively encode such constraints, such as `(:-)` from `Data.Constraint`? Here's how I think about it. `a :- b` is equivalent to `forall r. a => (b => r) -> r`. This is a type that, as I read it, expresses "if you can show `a`, then I can show `b`". This is very similar to `forall r. ((a => b) => r) -> r`, which expresses "(without obligations) I can show that `a` implies `b`". It seems to me (and I know this is hand-wavy) like expressions of both of these types actually must have the same "knowledge", i.e. that `a` imples `b`. Is this actually correct? I am wondering whether we could have a built-in function like: {{{#!hs reifyImplication :: forall a b. (forall r. a => (b => r) -> r) -> (forall r. ((a => b) => r) -> r) }}} We can already write the function that goes the other direction. There are plenty of ways to represent this conversion. Some more straight- forward, using `a :- b` or `Dict a -> Dict b`. I just went with one that doesn't require any types beyond arrows. I'm curious about the soundness of this. I have tried really hard to implement this function, but I don't think it can be done. I don't know if this proves anything, but replacing `(=>)` with `(->)` and all constraints `c` with `Dict c`, this function can be written: {{{#!hs dictReifyImplication :: forall a b. (forall r. Dict a -> (Dict b -> r) -> r) -> (forall r. ((Dict a -> Dict b) -> r) -> r) dictReifyImplication f g = g (\a -> f a id) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 19:21:29 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 19:21:29 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.b43cc260127124d5a6900bf10159cfff@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.4.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 sjakobi): * cc: sjakobi (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 19:23:26 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 19:23:26 -0000 Subject: [GHC] #14859: Allow explicit impredicativity In-Reply-To: <046.bce52cd0cbee25c5f867b88fe7e6b527@haskell.org> References: <046.bce52cd0cbee25c5f867b88fe7e6b527@haskell.org> Message-ID: <061.d49e8d38ef9ada0cbad6de958a74917a@haskell.org> #14859: Allow explicit impredicativity -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | ImpredicativeTypes 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 Sun Mar 18 20:51:26 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 20:51:26 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.f521b2289a85b05042d1b9e9f1df0fd4@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * Attachment "fuse.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 20:52:09 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 20:52:09 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.d7ce388e25156ef34c7dfcaad6bb5cf4@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * cc: george (removed) * cc: George (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 21:01:44 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 21:01:44 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.09d134d761475ba021ce201d585281a2@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): Attached file fuse.hs , similar to the first file but with nested forM_, both versions run in the same time but the forM_ version allocates about 50% more {{{ ghc -O2 fuse.hs +RTS [1 of 1] Compiling Main ( fuse.hs, fuse.o ) Linking fuse ... bash-3.2$ ./fuse 1 +RTS -s 486341683267690 320,057,352 bytes allocated in the heap 8,232 bytes copied during GC 44,576 bytes maximum residency (1 sample(s)) 29,152 bytes maximum slop 308 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 1 colls, 0 par 0.000s 0.000s 0.0000s 0.0000s Gen 1 1 colls, 0 par 0.000s 0.025s 0.0254s 0.0254s INIT time 0.000s ( 0.003s elapsed) MUT time 5.432s ( 5.634s elapsed) GC time 0.000s ( 0.025s elapsed) EXIT time 0.000s ( 0.005s elapsed) Total time 5.433s ( 5.667s elapsed) %GC time 0.0% (0.4% elapsed) Alloc rate 58,918,474 bytes per MUT second Productivity 100.0% of total user, 99.5% of total elapsed bash-3.2$ ./fuse 2 +RTS -s 486341683267690 560,057,328 bytes allocated in the heap 15,992 bytes copied during GC 320,028,576 bytes maximum residency (2 sample(s)) 868,448 bytes maximum slop 308 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 228 colls, 0 par 0.001s 0.002s 0.0000s 0.0001s Gen 1 2 colls, 0 par 0.000s 0.026s 0.0128s 0.0254s INIT time 0.000s ( 0.003s elapsed) MUT time 5.453s ( 5.630s elapsed) GC time 0.002s ( 0.027s elapsed) EXIT time 0.000s ( 0.008s elapsed) Total time 5.455s ( 5.667s elapsed) %GC time 0.0% (0.5% elapsed) Alloc rate 102,698,216 bytes per MUT second Productivity 100.0% of total user, 99.5% of total elapsed }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 18 22:45:56 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 18 Mar 2018 22:45:56 -0000 Subject: [GHC] #14407: rts: Threads/caps affinity In-Reply-To: <044.bf4507a98f68743970936df39c9089d2@haskell.org> References: <044.bf4507a98f68743970936df39c9089d2@haskell.org> Message-ID: <059.afabd0c443801cf7d0cabab2a00578fd@haskell.org> #14407: rts: Threads/caps affinity -------------------------------------+------------------------------------- Reporter: pacak | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.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): Phab:D4143 Wiki Page: | -------------------------------------+------------------------------------- Comment (by pacak): > How does this relate to the `setThreadAfinity` mentioned in #10229, that was implemented 3 years ago in GHC 7.10? They serve slightly different purpose. #10229 deals with distributing Haskell OS thread between underlying CPU cores in order to avoid when possible running code on different logical CPUs that gets mapped to the same physical CPU, while this `setAffinity` deals with distributing Haskell light threads between different capabilities - to allow giving some threads priority over some other threads but without having to manually pin them to specific capabilities. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 00:20:50 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 00:20:50 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.9f1e631c0f87ff42bf53176c29aff11a@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): @sgraf, are you actively working on !SpecConstr, and if so, is your patch going to help with this (specconstring non-recursive functions)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 00:44:41 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 00:44:41 -0000 Subject: [GHC] #14937: QuantifiedConstraints: Reify implication constraints from terms lacking them In-Reply-To: <044.d2a38f2a080b1fef4440349e47b3df3b@haskell.org> References: <044.d2a38f2a080b1fef4440349e47b3df3b@haskell.org> Message-ID: <059.f8d3dff627d35357666a8f48a5cea151@haskell.org> #14937: QuantifiedConstraints: Reify implication constraints from terms lacking them -------------------------------------+------------------------------------- Reporter: Bj0rn | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14822 | 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 Mon Mar 19 00:46:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 00:46:55 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.24707cbc3cecf80bba467ae19ef3747b@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I have been staring at the !SpecConstr code quite a bit now (which is pretty dense, I must say), and am no longer able to say with certainty that !SpecConstr only works on recursive functions. In fact, it seems that `Note [Local let bindings]` implies local non-recursive lets are being specialized! (despite `Note [Good arguments]` claiming it only works for self-recursive functions… It seems that specialization for non-recursive functions was added in changeset:99f41975ae61fc919638aa389199b32742332eff by Simon PJ (maybe not all notes were updated to reflect this change)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 05:33:58 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 05:33:58 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters Message-ID: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: GADTs, | Operating System: Unknown/Multiple TypeFamilies | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compiling the following code {{{#!hs type family R (x :: k) (y :: k) (prf :: x :~: y) :: x :~: y where R x y Refl = Refl }}} fails with the error {{{#!txt Temp.hs:49:9: error: • Expected kind ‘x :~: y’, but ‘Refl’ has kind ‘x :~: x’ • In the third argument of ‘R’, namely ‘Refl’ In the type family declaration for ‘R’ | 49 | R x y Refl = Refl | ^^^^ }}} where `Refl` is defined as {{{#!hs data a :~: b where Refl :: a :~: a }}} I would expect pattern-matching on `Refl` to bring the equality `x ~ y` into scope. It seems like it not only doesn't do that, but the pattern match itself is rejected. (both 8.2.2 and HEAD) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 05:34:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 05:34:54 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.6035db2bc04b75c56471bbaaf7a7f1e8@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by kcsongor): * Attachment "Temp.hs" added. Complete program -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 06:02:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 06:02:52 -0000 Subject: [GHC] #10832: Generalize injective type families In-Reply-To: <048.1487f224b00112fe37d31a1812a748a4@haskell.org> References: <048.1487f224b00112fe37d31a1812a748a4@haskell.org> Message-ID: <063.5c9757581f71344433f0710f3922e02a@haskell.org> #10832: Generalize injective type families -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: jstolarek Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: TypeFamilies, Resolution: | InjectiveFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #6018 | Differential Rev(s): Phab:D1287 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I haven't found so many uses for this, but I wanted to try this lately {{{#!hs -- Free :: (Type -> Constraint) -> (Type -> Type) -- Forget :: (Type -> Constraint) -> (Type -> Type) newtype Free cls a = Free (forall xx. cls xx => (a -> xx) -> xx) type family Forget cls free = res | res cls -> free where Forget cls (Free cls a) = a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 06:17:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 06:17:03 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.f6b8881e94b372c2a8f1aa07614cd26a@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: FunDeps 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 AntC): Replying to [ticket:10675 simonpj]: > Should these two instance declarations be accepted? * I'm going to '''argue they should''' * In addition to the bogusness documented on this ticket, there's a '''design weakness''' in the FunDep consistency check. * Exploiting that with malice aforethought, there's some '''disturbing behaviour''' '''Argument to accept:''' Yes GHC's consistency check is bogus/contrary to all the literature. But it's been in place since at least 2004. Lot's of code relies on it. So we can provide no grounds to reject the instances, unless we can look also at other class params not involved in the FunDep. But then according to the Type Families work, a FunDep should be equivalent to a superclass equi constraint with a Type Family call. I.e. {{{ class C x a b | a -> b where -- O.P. class (F a ~ b) => C x a b where -- Type Family F }}} The Type Family can look only at the class's second parameter. The (weird) unification behaviour described in the O.P. is in effect trying to reverse engineer `F`'s equations from the class instances. So ghc must unify. OTOH there's no definition for `F` you could write that would be consistent with where ghc ends up in the type for function `f`. '''Design weakness:''' in ghc checking instances for FunDep consistency is that it only checks (and unifies) pairwise. It doesn't check all instances globally. Then arguably '''Definition 6 (Consistency Condition)''' in the ''FunDeps via CHRs'' paper is too weak. (Note that the definition of Functional Dependency in database theory quantifies across all rows in a table.) '''Disturbing behaviour:''' consider this exploit {{{ {-# LANGUAGE as per O.P. #-} class C x a b | a -> b where -- as O.P. op :: x -> a -> b instance C Bool [x] (x, Bool) instance C Char x y => C Char [x] (Int, y) instance C Char x y => C Char [x] (y, y) f x = op True [x] -- as O.P. }}} Quick: what type inferred for `f`? What odds would you lay it's `f :: Int -> (Int, Int)`? Luckily we can't actually call `f`: `Couldn't match type 'Bool' with 'Int'`. So the `True` parameter to `op` in `f`'s rhs is trying to pick the 'right' instance for `C`. More disturbingly, if you switch round the order of instances, you'll get a different inferred type for `f`: it's the unifier of whichever are the last two instances. (Full disclosure: this is at ghc 8.0.1. Sensitivity to ordering of instances sounds like #9210, but that seems to have gone away at 8.0.) The fix in all these examples is to make the FunDep full (which it really should be) {{{ class C x a b | x a -> b where }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 06:54:44 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 06:54:44 -0000 Subject: [GHC] #14939: StaticPointers + -dcore-lint: cause Core Lint error?? Message-ID: <051.8bc9e96ca4b89b1613c7c0914d47c2a8@haskell.org> #14939: StaticPointers + -dcore-lint: cause Core Lint error?? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple StaticPointers | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is an odd bug {{{#!hs {-# Language StaticPointers #-} import Data.Kind type Cat ob = ob -> ob -> Type type Alg cls ob = ob newtype Frí (cls::Type -> Constraint) :: (Type -> Alg cls Type) where Frí :: { with :: forall x. cls x => (a -> x) -> x } -> Frí cls a data AlgCat (cls::Type -> Constraint) :: Cat (Alg cls Type) where AlgCat :: (cls a, cls b) => (a -> b) -> AlgCat cls a b leftAdj :: AlgCat cls (Frí cls a) b -> (a -> b) leftAdj (AlgCat f) a = undefined }}} causes a {{{ $ ./ghc-stage2 --interactive -ignore-dot-ghci -dcore-lint 222-bug.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( 222-bug.hs, interpreted ) *** Core Lint errors : in result of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) *** : warning: In the type ‘forall (cls :: * -> Constraint) (b :: Alg cls *). b’ Variable escape in forall: forall (cls :: * -> Constraint) (b :: Alg cls *). b *** Offending Program *** with :: forall (cls :: * -> Constraint) a. Frí cls a -> forall x. cls x => (a -> x) -> x [LclIdX[[RecSel]], Arity=2] with .. . --->8------->8------->8--- .. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 08:57:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 08:57:03 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.786b4acda3182f6e16b4c960b3d0eb5d@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate 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:D615 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Started looking into this, With -O1 evaluate (and `seq#`, and the `throwIfNegative` call) vanishes, and the whole program is transformed into an assertFailure: {{{ Main.main1 = \ (eta2_a3iv :: GHC.Prim.State# GHC.Prim.RealWorld) -> GHC.Prim.catch# @ () @ SomeException Main.main3 Main.main2 eta2_a3iv Main.main3 = \ _ [Occ=Dead, OS=OneShot] -> case Main.main4 of wild_00 { } Main.main4 = assertFailure_rCn @ (IO ()) lvl1_r4kE Main.main2 = \ (e1_a3iI [OS=OneShot] :: SomeException) (eta_B1 [OS=OneShot] :: GHC.Prim.State# GHC.Prim.RealWorld) -> case e1_a3iI of wild_a3jJ }}} With some debug prints I was able to find the simplifier call that eliminates seq#: {{{ rebuildCase is_plain_seq expr ok for side effects: seq# @ String @ RealWorld (throwIfNegative (I# -1#)) s_a3jI alts: [((#,#), [ipv_a3jL, ipv1_a3jM], case assertFailure @ (IO ()) (build @ Char (\ (@ b_a3eo) -> unpackFoldrCString# @ b_a3eo "must throw when given a negative number"#)) of { })] cont: Stop[BoringCtxt] (# State# RealWorld, () #) ret: (SimplFloats {lets: FltLifted [] joins: [] in_scope: InScope {...}}, case assertFailure @ (IO ()) (build @ Char (\ (@ b_a3eo) -> unpackFoldrCString# @ b_a3eo "must throw when given a negative number"#)) of wild_00 { }) }}} This basically says `rebuildCase` sees the `seq#` call in the scrutinee position, thinks that it's side-effect-free (because the primop is not marked as effectful), also thinks that it's a "plain seq", and eliminates the case expression. "Plain seq" in this context is defined like this: {{{ is_plain_seq = all_dead_bndrs && isDeadBinder case_bndr -- Evaluation *only* for effect }}} So the code looks correct to me; primops is not marked as effectful, and this case expression is only for the (non-existent) effects, so it can be eliminated. Looking at the discussion above, I think not marking `seq#` as effectful was deliberate (otherwise `seq#` becomes `spark#`). I guess the idea was to force sequencing via a dependency of `State# RealWorld` return value of `seq#` and the next IO action, but I'm not sure how is that supposed to work in pure code. Can anyone say a few words about how do we expect to keep `seq#` when it's not effectful, and its return value is not used? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 08:58:53 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 08:58:53 -0000 Subject: [GHC] #14791: Move stack checks out of code paths that don't use the stack. In-Reply-To: <047.2ea20512b2a37aa4c0736d7573c92c30@haskell.org> References: <047.2ea20512b2a37aa4c0736d7573c92c30@haskell.org> Message-ID: <062.687bc9f3368fbaed2764f79f47cc3e95@haskell.org> #14791: Move stack checks out of code paths that don't use the stack. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by AndreasK): There are a number of similar issues already on Trac, although mostly about Heap instead of Stack usage: * #8326 Place heap checks common in case alternatives before the case * #12231 Eliminate redundant heap allocations/deallocations * #1498 Optimisation: eliminate unnecessary heap check in recursive function #8326 is about moving heap checks out of case alternatives by checking for the maximum needed for all branches. While it does the opposite of this issue it contains a lot of good discussion already. #12231 Is a **very** similar issue but for heap checks. #1498 Also sounds like it involves the same moving parts. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 09:00:45 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 09:00:45 -0000 Subject: [GHC] #14939: StaticPointers + -dcore-lint: cause Core Lint error?? In-Reply-To: <051.8bc9e96ca4b89b1613c7c0914d47c2a8@haskell.org> References: <051.8bc9e96ca4b89b1613c7c0914d47c2a8@haskell.org> Message-ID: <066.0db14daf62edbd0210f05e5578020843@haskell.org> #14939: StaticPointers + -dcore-lint: cause Core Lint error?? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | StaticPointers 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 monoidal): Smaller version: {{{#!haskell {-# Language StaticPointers, TypeInType, GADTs #-} import Data.Kind type Alg cls = Type data AlgCat (cls::Type) :: Alg cls -> Type where leftAdj :: AlgCat cls a -> a leftAdj f = undefined }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 09:08:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 09:08:10 -0000 Subject: [GHC] #14672: Make likelyhood of branches/conditions available throughout the compiler. In-Reply-To: <047.de2c13e36902d9be8400d9448aa09671@haskell.org> References: <047.de2c13e36902d9be8400d9448aa09671@haskell.org> Message-ID: <062.f22c2f9ff383477fee1b2ce184d0f184@haskell.org> #14672: Make likelyhood of branches/conditions available throughout the compiler. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4316 Wiki Page: | Phab:D4324 Phab:D4327 -------------------------------------+------------------------------------- Comment (by AndreasK): Just document it for a future time: Coming across the Ticky-ticky profiling page this would seem like a good way collect branch weights for the generated STG code. The plan would then be to * Compile the executable with ticky-ticky enabled. * Collect information from a representative set of use cases. * Compile the executable without tick-ticky, using the collected information to inform GHC about relative branch weights. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 09:41:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 09:41:22 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.5b2ec3d4a507ea476e514bc3d02b32a0@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alexbiehl): * related: => #13930 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 09:47:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 09:47:36 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.29daa94329f554aa130c92268d4bb092@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): One way to fix this if we want to keep `seq#` as effect-free is avoiding inlining `evaluate` with `{-# NOINLINE evaluate #-}`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 10:02:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 10:02:00 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.c5d897072ba1f77f3840e1266af98a44@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982, #5129 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hvr): * related: #13982 => #13982, #5129 Comment: Alex Biehl just pointed out this may be related to the rather old #5129 ticket -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 10:18:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 10:18:09 -0000 Subject: [GHC] #14791: Move stack checks out of code paths that don't use the stack. In-Reply-To: <047.2ea20512b2a37aa4c0736d7573c92c30@haskell.org> References: <047.2ea20512b2a37aa4c0736d7573c92c30@haskell.org> Message-ID: <062.5bddc06c69effb1de00adc1800797d75@haskell.org> #14791: Move stack checks out of code paths that don't use the stack. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 (CodeGen) | Resolution: | Keywords: CodeGen Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => CodeGen Comment: There's a list of code-gen-related tickets, and other useful pointers, on [wiki:Commentary/Compiler/CodeGen] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 10:22:49 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 10:22:49 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.3869406d5f37c743f215b8e4bb9748ef@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982, #5129 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): This is indeed #5129. Adding `{-# NOINLINE evaluate #-}` fixes both this and #5129. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 10:23:16 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 10:23:16 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.ad91e15f79d2a6585fb0d0c8f482152b@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Confirmed that adding `{-# NOINLINE evaluate #-}` also fixes #13930. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 11:32:39 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 11:32:39 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic In-Reply-To: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> References: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> Message-ID: <065.c1e9b010a52c384bac3dd6c3d544bb15@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"2a3702d8950ebdec27357e08caae3b1cd4f8b00d/ghc" 2a3702d8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2a3702d8950ebdec27357e08caae3b1cd4f8b00d" Comments and tiny refactor Related to Ryan's upcoming patch for Trac #14933 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 11:45:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 11:45:57 -0000 Subject: [GHC] #14868: -O -g breaks string literals In-Reply-To: <043.b85ddd9da71a7b040ce01bef4d2ffb0c@haskell.org> References: <043.b85ddd9da71a7b040ce01bef4d2ffb0c@haskell.org> Message-ID: <058.59440e58a71afb786f7dc68ff122060a@haskell.org> #14868: -O -g breaks string literals -------------------------------------+------------------------------------- Reporter: akio | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14779, #14123 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): bgamari, is this supposed to be fixed in GHC 8.4.1? I can reproduce this error: {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.1 $ cat Main.hs {-# OPTIONS -O -g #-} main = print (4, "foo") $ ghc Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Linking Main ... $ ./Main (4,"\248m@") }}} I tried with both DWARF and non-DWARF build. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 11:52:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 11:52:24 -0000 Subject: [GHC] #14895: STG CSE makes dead binders undead In-Reply-To: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> References: <045.443cdfa1dbd8aaefea07acaabba112a5@haskell.org> Message-ID: <060.c4028a490047f3f4abad48af355bad97@haskell.org> #14895: STG CSE makes dead binders undead -------------------------------------+------------------------------------- Reporter: hsyl20 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Delicate! Can you add a Note in `StgCSE` to explain? Actually it'd be more correct to do this in `StgCSE` * Zap the dead-binder flag on most case-binders (explaining why) * But not the ones for primop applications (because they aren't CSE'd, I think you are saying). That way they never lie. We'd still need a note to say that dead-ness is now a bit pessimistic; but the code gen doesn't use it (except in a narrow case) so the pessimism doesn't matter. Not hard to do. Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 12:47:06 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 12:47:06 -0000 Subject: [GHC] #10774: Use `Natural` rather than `Integer` in `GHC.TypeLits` In-Reply-To: <042.7c7cb988b2d1af2ee71900558e4a13e4@haskell.org> References: <042.7c7cb988b2d1af2ee71900558e4a13e4@haskell.org> Message-ID: <057.21da6446699a51e0ddac491c43a81f2c@haskell.org> #10774: Use `Natural` rather than `Integer` in `GHC.TypeLits` -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2 Resolution: duplicate | Keywords: TypeLits | Natural Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13181 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #13181 Comment: I believe this was fixed in #13181, so I'll close this as a duplicate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 12:49:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 12:49:03 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.d8731577d3addc2be0a5d0e01d8641ce@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ömer Sinan Ağacan ): In [changeset:"5a1ad231fc871f27f2811ae46285a79573d8dfae/ghc" 5a1ad231/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5a1ad231fc871f27f2811ae46285a79573d8dfae" Update test for #5129: Make sure it runs with --fast validate with correct optimisation settings (-O1 or above) so that it actually tests the bug. Because the bug is in the simplifier running it with -O0 doesn't test it. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 13:17:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 13:17:54 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.3d06123fda4489a3e4d03eb85e7b132b@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982, #5129 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Sounds plausible. I managed to reproduce on GHC HEAD, and running on a machine with a HDD clearly shows excessive disk I/O. So my hypothesis so far has been that overly enthusiastic inlining might be the culprit, and if `{-# NOINLINE evaluate #-}` fixes it, then that would be consistent with that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 13:22:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 13:22:26 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.a4c1d98ec61841a809fab49e3d09571d@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, 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): But if you have a type-level `Refl` here, then `x` and `y` really will be the same. The equation you want is `R x x Refl = Refl`, like in those other dependently typed languages. If you write a larger example, I can show you how the equation I suggest will work. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 13:31:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 13:31:28 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.f635b51b131204d4dd250142b4a946d8@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > You know, this is all very much like unboxed tuples. But do we allow `(#,,#) x y` or stuff like that with a possibly- unsaturated use of the data constructor? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 13:56:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 13:56:56 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.bcceeaa2fcce0db8249aa2966cc90b85@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982, #5129 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): I suggest parking this for now, let's first see where we end up with #5129. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 13:59:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 13:59:52 -0000 Subject: [GHC] #7741: Add SIMD support to x86/x86_64 NCG In-Reply-To: <047.ec0118457b1e4a3b6ea3c008b0b9e4f2@haskell.org> References: <047.ec0118457b1e4a3b6ea3c008b0b9e4f2@haskell.org> Message-ID: <062.73235aae4cc6d48c2ba53b08c62e8f29@haskell.org> #7741: Add SIMD support to x86/x86_64 NCG -------------------------------------+------------------------------------- Reporter: shelarcy | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (NCG) | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #3557 | Differential Rev(s): Wiki Page: wiki:SIMD | -------------------------------------+------------------------------------- Comment (by carter): Ben: what are your current thoughts about how to handle supporting different microarchitectures? 1) Allow generating the instructions but require the application to do cpu detection to avoid bad instructions ? (I’d be fine with that ) Or 2) add micro architecture logic to ghc compilation and have a fall back path? Or 3) some mix of both supported? I’d think near term 1 would be simpler to get working and 3 is what we want to love to -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 14:40:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 14:40:19 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.02a04dbd2a6b75c0674f7cca466523fc@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, 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 RyanGlScott): I'd be OK with requiring the user write `R x x Refl`. But in that case, the error message is pretty darn misleading. It's complaining about `Refl`, but the real error is due to the fact that `x` and `y` are distinct, right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 15:39:33 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 15:39:33 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.31c097bb6eadc422710893073794bb98@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: GADTs, TypeFamilies => GADTs, TypeFamilies, TypeInType Comment: I agree that talking about `x` and `y` would be an improvement, though I wouldn't call the current message wrong... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 15:53:07 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 15:53:07 -0000 Subject: [GHC] #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. In-Reply-To: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> References: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> Message-ID: <069.d13d4191d82952f4dc7e776add16878f@haskell.org> #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Floating | IEEE754 trigonometric Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Either of these options sound reasonable to me. Would you be willing to offer a patch? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:22:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:22:27 -0000 Subject: [GHC] #14868: -O -g breaks string literals In-Reply-To: <043.b85ddd9da71a7b040ce01bef4d2ffb0c@haskell.org> References: <043.b85ddd9da71a7b040ce01bef4d2ffb0c@haskell.org> Message-ID: <058.89d096af873d2b426068c312491745a1@haskell.org> #14868: -O -g breaks string literals -------------------------------------+------------------------------------- Reporter: akio | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.5 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #14779, #14123 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.4.2 Comment: Unfortunately due to a mistake in the bindist preparation this patch didn't quite make it for 8.4.1. It will be present in 8.4.2 (which will likely happen soon). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:23:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:23:04 -0000 Subject: [GHC] #14779: Compiling with -g fails -lint-core checks In-Reply-To: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> References: <046.6e6bd1042efbe2eb4e6d4f927eb5bdcd@haskell.org> Message-ID: <061.2bc518d4c5622f9cc9dd78035aa94242@haskell.org> #14779: Compiling with -g fails -lint-core checks -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.3 (Debugging) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14122, #14123, | Differential Rev(s): phab:D4470 #8472, #14406 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.4.1 => 8.4.2 Comment: Unfortunately due to a mistake in the bindist preparation this patch didn't quite make it for 8.4.1. It will be present in 8.4.2 (which will likely happen soon). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:27:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:27:09 -0000 Subject: [GHC] #14929: Program compiled with -O2 exhibits much worse performance In-Reply-To: <049.ba205f50f7e92bd0b7f0e4b08e0f1c92@haskell.org> References: <049.ba205f50f7e92bd0b7f0e4b08e0f1c92@haskell.org> Message-ID: <064.41923d6f10b0b2ff0ac049c2d860c96a@haskell.org> #14929: Program compiled with -O2 exhibits much worse performance -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * failure: None/Unknown => Runtime performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:28:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:28:19 -0000 Subject: [GHC] #14926: failed to build cross-compiler In-Reply-To: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> References: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> Message-ID: <062.b15f2319b8819d83cbb972b38c065ce5@haskell.org> #14926: failed to build cross-compiler -------------------------------------+------------------------------------- Reporter: rueshyna | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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): * cc: angerman (added) Comment: Hmm, interesting. CCing angerman who is working on cross-compilation currently. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:34:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:34:10 -0000 Subject: [GHC] #14925: Non-ASCII type names get garbled when their `TypeRep` is shown In-Reply-To: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> References: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> Message-ID: <069.4fde995e737680c9202c45c4fa882e51@haskell.org> #14925: Non-ASCII type names get garbled when their `TypeRep` is shown -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Typeable | TypeRep Unicode ASCII UTF-8 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | typecheck/T14925 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/T14925 Comment: Very interesting. Test added in Phab:D4512. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:37:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:37:28 -0000 Subject: [GHC] #3553: parallel gc suffers badly if one thread is descheduled In-Reply-To: <047.48e7cf5ad32bf05ce8bca6e11b9273f8@haskell.org> References: <047.48e7cf5ad32bf05ce8bca6e11b9273f8@haskell.org> Message-ID: <062.32107cc0da785e65a85781e44532f3d2@haskell.org> #3553: parallel gc suffers badly if one thread is descheduled -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 6.12.2 Component: Runtime System | Version: 6.10.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2918abf75594001deed51ee252a05b146f844489/ghc" 2918abf7/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2918abf75594001deed51ee252a05b146f844489" rts: Add --internal-counters RTS flag and several counters The existing internal counters: * gc_alloc_block_sync * whitehole_spin * gen[g].sync * gen[1].sync are now not shown in the -s report unless --internal-counters is also passed. If --internal-counters is passed we now show the counters above, reformatted, as well as several other counters. In particular, we now count the yieldThread() calls that SpinLocks do as well as their spins. The added counters are: * gc_spin (spin and yield) * mut_spin (spin and yield) * whitehole_threadPaused (spin only) * whitehole_executeMessage (spin only) * whitehole_lockClosure (spin only) * waitForGcThreadsd (spin and yield) As well as the following, which are not SpinLock-like things: * any_work * do_work * scav_find_work See the Note for descriptions of what these counters are. We add busy_wait_nops in these loops along with the counter increment where it was absent. Old internal counters output: ``` gc_alloc_block_sync: 0 whitehole_gc_spin: 0 gen[0].sync: 0 gen[1].sync: 0 ``` New internal counters output: ``` Internal Counters: Spins Yields gc_alloc_block_sync 323 0 gc_spin 9016713 752 mut_spin 57360944 47716 whitehole_gc 0 n/a whitehole_threadPaused 0 n/a whitehole_executeMessage 0 n/a whitehole_lockClosure 0 0 waitForGcThreads 2 415 gen[0].sync 6 0 gen[1].sync 1 0 any_work 2017 no_work 2014 scav_find_work 1004 ``` Test Plan: ./validate Check it builds with #define PROF_SPIN removed from includes/rts/Config.h Reviewers: bgamari, erikd, simonmar, hvr Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #3553, #9221 Differential Revision: https://phabricator.haskell.org/D4302 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:37:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:37:28 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.7a9949cc56ce36323b73303b1c1810cc@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910, #8224 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2918abf75594001deed51ee252a05b146f844489/ghc" 2918abf7/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2918abf75594001deed51ee252a05b146f844489" rts: Add --internal-counters RTS flag and several counters The existing internal counters: * gc_alloc_block_sync * whitehole_spin * gen[g].sync * gen[1].sync are now not shown in the -s report unless --internal-counters is also passed. If --internal-counters is passed we now show the counters above, reformatted, as well as several other counters. In particular, we now count the yieldThread() calls that SpinLocks do as well as their spins. The added counters are: * gc_spin (spin and yield) * mut_spin (spin and yield) * whitehole_threadPaused (spin only) * whitehole_executeMessage (spin only) * whitehole_lockClosure (spin only) * waitForGcThreadsd (spin and yield) As well as the following, which are not SpinLock-like things: * any_work * do_work * scav_find_work See the Note for descriptions of what these counters are. We add busy_wait_nops in these loops along with the counter increment where it was absent. Old internal counters output: ``` gc_alloc_block_sync: 0 whitehole_gc_spin: 0 gen[0].sync: 0 gen[1].sync: 0 ``` New internal counters output: ``` Internal Counters: Spins Yields gc_alloc_block_sync 323 0 gc_spin 9016713 752 mut_spin 57360944 47716 whitehole_gc 0 n/a whitehole_threadPaused 0 n/a whitehole_executeMessage 0 n/a whitehole_lockClosure 0 0 waitForGcThreads 2 415 gen[0].sync 6 0 gen[1].sync 1 0 any_work 2017 no_work 2014 scav_find_work 1004 ``` Test Plan: ./validate Check it builds with #define PROF_SPIN removed from includes/rts/Config.h Reviewers: bgamari, erikd, simonmar, hvr Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #3553, #9221 Differential Revision: https://phabricator.haskell.org/D4302 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:38:09 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:38:09 -0000 Subject: [GHC] #14881: Consistent labeling of redundant, qualified imports In-Reply-To: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> References: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> Message-ID: <062.f70490ee835bbc99069d4455ba320d6b@haskell.org> #14881: Consistent labeling of redundant, qualified imports -------------------------------------+------------------------------------- Reporter: crockeea | Owner: sighingnow Type: bug | Status: patch Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4461 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"fad822e2a5aa4373c3aa64e913e51fd5509c3f67/ghc" fad822e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fad822e2a5aa4373c3aa64e913e51fd5509c3f67" Improve the warning message of qualified unused imports. Pretty-print unused imported names unqualified unconditionally to make the warning message consistent for ambiguous/unambiguous identifiers. Signed-off-by: HE, Tao Test Plan: make test TEST="T14881" Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14881 Differential Revision: https://phabricator.haskell.org/D4461 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:38:11 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:38:11 -0000 Subject: [GHC] #14923: Recompilation avoidance fails after a LANGUAGE change In-Reply-To: <043.f58216ea69c9ec233e7328c6135b12f4@haskell.org> References: <043.f58216ea69c9ec233e7328c6135b12f4@haskell.org> Message-ID: <058.d9d3bf152d0bfe6ff49ac885c80d57d0@haskell.org> #14923: Recompilation avoidance fails after a LANGUAGE change -------------------------------------+------------------------------------- Reporter: akio | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, very interesting. It looks to me like `fingerprintDynFlags` includes the language flags in its hash. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:38:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:38:52 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.d7a8ee41dc408c7534172a99bd160e7b@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: andrewthad Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a00b88b9a27736c9c41f1921fcb6b7759ad8425e/ghc" a00b88b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a00b88b9a27736c9c41f1921fcb6b7759ad8425e" Implement -dword-hex-literals Provide flag for showing showing Word# and Word64# as hexadecimal when dumping GHC core. The only affects Word, not Int, and it prefixes the hexadecimal with enough zeroes to make the total character count a power of two. For example: - 0x0C0C instead of 0xC0C - 0x00BA00BA instead of 0xBA00BA This also affects the presentation of Word# and Word64# in GHC's error messages. It is not expected that the flag will be used for this, but it is a side-effect worth noting. Test Plan: none Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, mpickering, rwbarton, thomie, carter, andrewthad GHC Trac Issues: #14872 Differential Revision: https://phabricator.haskell.org/D4465 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:39:59 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:39:59 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.4927248fac6df7e789c1c12c8271d33e@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kcsongor): Replying to [comment:1 goldfire]: > But if you have a type-level `Refl` here, then `x` and `y` really will be the same. The equation you want is `R x x Refl = Refl`, like in those other dependently typed languages. In the end I did end up using that equation, but my original idea was to try and avoid non-linear patterns, and passing in an explicit proof seemed like a sensible idea. For example, Idris lets me write {{{#!idris r : x -> y -> x = y -> x = y r x y Refl = Refl }}} (But of course non-linear patterns are not supported) Is there something obvious I missed that would explain why this form of matching should not accepted? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:40:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:40:35 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.0da87dd228414b5e7430630ba7de87d8@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4506 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9868f91fd9f04fdee241df69ae826feeae89a0b6/ghc" 9868f91f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9868f91fd9f04fdee241df69ae826feeae89a0b6" Turn a TH Name for built-in syntax into an unqualified RdrName Previously, the Renamer would turn any fully qualified Template Haskell name into a corresponding fully qualified `RdrName`. But this is not what we want for built-in syntax, as it produces unnecessarily qualified names (eg. GHC.Types.[], GHC.Tuple.(,) etc.). Test Plan: ./validate Reviewers: RyanGlScott, bgamari, goldfire Reviewed By: RyanGlScott, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #13776 Differential Revision: https://phabricator.haskell.org/D4506 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:40:39 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:40:39 -0000 Subject: [GHC] #14881: Consistent labeling of redundant, qualified imports In-Reply-To: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> References: <047.1e5b968dc24b0581b32ca81ea3058b37@haskell.org> Message-ID: <062.551c185d0400bd2d8d8eb1d581bd6321@haskell.org> #14881: Consistent labeling of redundant, qualified imports -------------------------------------+------------------------------------- Reporter: crockeea | Owner: sighingnow Type: bug | Status: closed Priority: lowest | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4461 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:40:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:40:51 -0000 Subject: [GHC] #14872: Hex Literals in GHC Core In-Reply-To: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> References: <049.c7f8536ce8cd12b30d252cb5fd399def@haskell.org> Message-ID: <064.d92dc829c2fae73b9f411f8b5405076a@haskell.org> #14872: Hex Literals in GHC Core -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: andrewthad Type: feature request | Status: closed Priority: lowest | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:41:02 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:41:02 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.7dd98a1409846dac455c0248a77dca92@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"c3aea39678398fdf88166f30f0d01225a1874a32/ghc" c3aea39/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c3aea39678398fdf88166f30f0d01225a1874a32" Fix #14934 by including axSub0R in typeNatCoAxiomRules For some reason, `axSub0R` was left out of `typeNatCoAxiomRules` in `TcTypeNats`, which led to disaster when trying to look up `Sub0R` from an interface file, as demonstrated in #14934. The fix is simple—just add `axSub0R` to that list. To help prevent an issue like this happening in the future, I added a `Note [Adding built-in type families]` to `TcTypeNats`, which contains a walkthrough of all the definitions in `TcTypeNats` you need to update when adding a new built-in type family. Test Plan: make test TEST=T14934 Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #14934 Differential Revision: https://phabricator.haskell.org/D4508 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:41:21 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:41:21 -0000 Subject: [GHC] #14048: Data instances of kind Constraint In-Reply-To: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> References: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> Message-ID: <066.155e606fa09cacd817c72bb73f5164ea@haskell.org> #14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f748c52997f61a9f58eccbf4b8df0a0c8c6887e5/ghc" f748c529/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f748c52997f61a9f58eccbf4b8df0a0c8c6887e5" Don't permit data types with return kind Constraint Previously, GHC allowed all of the following: ```lang=haskell data Foo1 :: Constraint data family Foo2 :: Constraint data family Foo3 :: k data instance Foo3 :: Constraint ``` Yikes! This is because GHC was confusing `Type` with `Constraint` due to careless use of the `isLiftedTypeKind` function. To respect this distinction, I swapped `isLiftedTypeKind` out for `tcIsStarKind`—which does respect this distinction—in the right places. Test Plan: make test TEST="T14048a T14048b T14048c" Reviewers: bgamari Reviewed By: bgamari Subscribers: goldfire, rwbarton, thomie, carter GHC Trac Issues: #14048 Differential Revision: https://phabricator.haskell.org/D4479 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:41:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:41:35 -0000 Subject: [GHC] #12870: Allow completely disabling +RTS options parsing In-Reply-To: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> References: <042.8ee30dc911ab648c85fb1ba15e356468@haskell.org> Message-ID: <057.9cb0e71569bf88161979803fab13101e@haskell.org> #12870: Allow completely disabling +RTS options parsing -------------------------------------+------------------------------------- Reporter: nh2 | Owner: AndreasK Type: feature request | Status: closed Priority: normal | Milestone: 8.4.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): Phab:D3740 Wiki Page: | Phab:D4486 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"fdec06a201f81467badb9e2a5d43b4a85564dff9/ghc" fdec06a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fdec06a201f81467badb9e2a5d43b4a85564dff9" Update tests for #12870 to pass with a slow run of the testsuite. Test Plan: make slow Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #12870 Differential Revision: https://phabricator.haskell.org/D4486 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:41:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:41:57 -0000 Subject: [GHC] #14048: Data instances of kind Constraint In-Reply-To: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> References: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> Message-ID: <066.e61faf241af0e14069de8f41aa9775b8@haskell.org> #14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.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: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:42:16 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:42:16 -0000 Subject: [GHC] #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types In-Reply-To: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> References: <050.87f5b641e82d5f06fa4748e90b74c406@haskell.org> Message-ID: <065.8bd873519289e09b8c663411d32e5502@haskell.org> #13776: -ddump-splices produces unnecessarily qualified names for tuple and list types -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: mrkgnao Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4506 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Thanks for the patch! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:42:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:42:12 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.ee546495baa444a0a54965379e29f7be@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:44:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:44:01 -0000 Subject: [GHC] #7741: Add SIMD support to x86/x86_64 NCG In-Reply-To: <047.ec0118457b1e4a3b6ea3c008b0b9e4f2@haskell.org> References: <047.ec0118457b1e4a3b6ea3c008b0b9e4f2@haskell.org> Message-ID: <062.7ec3b3dae6cf40d0d333554c8c2e1883@haskell.org> #7741: Add SIMD support to x86/x86_64 NCG -------------------------------------+------------------------------------- Reporter: shelarcy | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (NCG) | Version: 7.7 Resolution: | Keywords: SIMD Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #3557 | Differential Rev(s): Wiki Page: wiki:SIMD | -------------------------------------+------------------------------------- Comment (by bgamari): I think (1) is the best option given the amount of effort we have available to expend on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 16:54:40 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 16:54:40 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.6da4c09a3d82c75a3ec2bd71be6f703d@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Hm. Maybe it's only Agda that requires you to write a non-linear pattern here. Except that the pattern isn't ''really'' non-linear, because the non-linearity (at least in Agda) isn't checked. (Agda has a notation for an argument that has to be a certain way but that isn't checked for when matching.) In any case, you're right, though. `Refl` doesn't bring into scope any coercion. Instead, the appearance of `Refl` ''requires'' a coercion in order for the equation to match. But because type family equations are at the top level and that there is no phase separation between kind-checking and type-checking, this is all OK. After all, the same type checker that allowed `Refl` to be type checked at the type family application site is checking whether the equation matches; if one can prove the types equal, the other can, too. This design decision does have a few consequences, though. For example, you can't quantify a type family equation over an equality between type family applications: `type family F a (pf :: G a :~: H a)`. That just won't work (for several reasons). Of course, it's my hope that we won't have type families in a few years and can use normal GADT pattern matching instead! :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 17:15:37 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 17:15:37 -0000 Subject: [GHC] #14886: Add max GC pause to GHC.Stats/-t --machine-readable In-Reply-To: <047.0641890e447a41b5694f0694e508f86b@haskell.org> References: <047.0641890e447a41b5694f0694e508f86b@haskell.org> Message-ID: <062.4eda222175f62f7bf17b51a418da57dc@haskell.org> #14886: Add max GC pause to GHC.Stats/-t --machine-readable -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomer * component: Compiler => Runtime System Comment: Indeed having this information in a machine-readable form would be quite useful. Frankly, I wonder whether it might be helpful to just export everything from `-s` in JSON or some similarly ubiquitous format. This would greatly simplify parsing. Patches welcome! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 18:01:59 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 18:01:59 -0000 Subject: [GHC] #14940: GHC doesn't accept url specifying output file that is in a directory that is created by the -outputdir flag Message-ID: <042.924464ba57d18245043305ea777116b4@haskell.org> #14940: GHC doesn't accept url specifying output file that is in a directory that is created by the -outputdir flag --------------------------------------+--------------------------- Reporter: ntj | Owner: (none) Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: Other Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------- Command: {{{ ghc p.hs -outputdir simple -o simple/po }}} Output: {{{ : error: directory portion of "simple/po" does not exist (used with "-o" option.) }}} Directory "simple" does not exist before the time of compilation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 18:09:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 18:09:24 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.6e0be93ae3970374b799cbdcc1761585@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by kcsongor): Thanks for the explanation! I have encountered that limitation on several occasions, but it never quite clicked; now it makes total sense. So the only way to match `pf` against `Refl` is by first providing an `a` for which `G a` and `H a` can actually reduce to the same thing {{{#!hs type family G a where G Int = Nat type family H a where H Int = Nat type family F a (pf :: G a :~: H a) where F Int Refl = True }}} So it seems like I got the "direction" of the matching wrong. Could you by any chance point me to any resources where this decision is explained in more detail? I skimmed the System FC with Explicit Kind Equality paper, but it wasn't obvious where this would be described. In any case, I'm happy to close this ticket, as I'm now convinced it's not a bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 18:21:31 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 18:21:31 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.0530088575e065dca07a77bba3b29f5c@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Changes (by osa1): * differential: Phab:D615 => Phab:D615, Phab:D4514 Comment: Submitted a patch for this. Assuming we want to keep `seq#` pure (e.g. `has_side_effects = False` in the primop definition) I think hiding evaluate from the simplifier makes sense. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 18:29:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 18:29:01 -0000 Subject: [GHC] #13386: Poor compiler performance with type families In-Reply-To: <049.c62ef75e26f3d606baae71cbfbd84e45@haskell.org> References: <049.c62ef75e26f3d606baae71cbfbd84e45@haskell.org> Message-ID: <064.b10e2fd9dd9838df25fb9e0947d20677@haskell.org> #13386: Poor compiler performance with type families -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8095 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * cc: alanz (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 19:09:14 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 19:09:14 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.17129f8a945b5036642d64c38b6f0c55@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 19:24:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 19:24:36 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.c6ed66dac5897460bed0973707cb74fc@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I stared some more at the code, and learned: * Currently, !SpecConstr does specialize local non-recursive functions, but not top-level non-recursive functions. Comment in the source code about that: “Oddly, we don't seem to specialise top-level non-rec functions”. This can be fixed in `scTopBind`. * Together with loopification, SpecConstr only specialized everything as before if it is run twice, with a simplification in between. Otherwise, it refuses to specialize the outer non-recursive function because it does not see that its parameters are being scrutinized. I hope this can somehow be fixed in `SpecConstr`, so that it anticipates the state after simplifications. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 19:37:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 19:37:51 -0000 Subject: [GHC] #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) Message-ID: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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 selectVectorDestructive2 :: (PrimMonad m, VG.Vector v e, Ord e, Show e, VG.Mutable v ~ vm) => Int -> v e -> vm (PrimState m) e -> Int -> Int -> m () -- slow selectVectorDestructive2 :: (PrimMonad m, VG.Vector v e, Ord e, Show e) => Int -> v e -> VG.Mutable v (PrimState m) e -> Int -> Int -> m () -- fast }}} These two functions are identical except one has `VG.Mutable v ~ vm` as a constraint, the other one has it in the type signature right of the `=>`. The second function is 10x faster. I would expect them to be equally fast. The code of the functions is identical, I change only the type declaration. The slowness happens because with the first function, inlining of primitives like `unsafeRead` does not happen, and thus also it boxes the `Int#`s back to `Int`s when calling `unsafeRead`. In particular, in `-ddump-simpl`, the slow version has {{{#!hs $wpartitionLoop2_rgEy :: forall (m :: * -> *) (vm :: * -> * -> *) e. (PrimMonad m, MVector vm e, Ord e) => vm (PrimState m) e -> GHC.Prim.Int# -> e -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> m Int $wpartitionLoop2_rgEy = \... -> let { endIndex_a7Ay :: Int ... endIndex_a7Ay = GHC.Types.I# ww2_sfZn } in ... (VGM.basicUnsafeRead ... endIndex_a7Ay) ... }}} while the fast version has {{{#!hs $w$spartitionLoop2_rgUN :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.MutableByteArray# GHC.Prim.RealWorld -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #) ... $spartitionLoop2_rgUP :: VG.Mutable VU.Vector (PrimState IO) Int -> Int -> Int -> Int -> Int -> Int -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #) }}} So with `VG.Mutable v (PrimState m) e` in the type signature, GHC managed to inline + specialise it all the way down to concrete types (`VUM.MVector`, `IO`, and `Int` as the element type), and consequently inline `basicUnsafeRead` on unboxed `Int#`. But with `VG.Mutable v ~ vm`, ghc keeps `vm (PrimState m) e` all the way, passes around dictionaries, thus eventually cannot inline `basicUnsafeRead` and re-packs already unboxed values, like `endIndex_a7Ay = GHC.Types.I# ww2_sfZn`, before passing them into the non-inlined call of `basicUnsafeRead`, thus making a tight loop allocate that normally wouldn't allocate. Why might rewriting the type signature in such a trivial way make this happen? ---- I have tested this on GHC 8.0.2, GHC 8.2.2, and GHC 8.5 HEAD commit cc4677c36ee. Reproducer: * https://github.com/nh2/haskell-quickselect-median-of- medians/blob/0efd6293e779fda2d864ec3d75329fb16b8af6d9/Main.hs#L506 * Running instructions are [https://github.com/nh2/haskell-quickselect- median-of-medians/commit/7a49d673990dfaebdb0ba837c3fbbaae0455dba0 in this commit message]; for short: `stack exec -- ghc -O --make Main.hs -rtsopts -ddump-simpl -dsuppress-coercions -fforce-recomp -ddump-to-file -fno-full- laziness && ./Main +RTS -sstderr` * For that file, I have pregenerated `-dverbose-core2core` output here: https://github.com/nh2/haskell-quickselect-median-of- medians/tree/0efd6293e779fda2d864ec3d75329fb16b8af6d9/slowness-analysis * I originally just wanted to write a fast median-of-medians implementation on ZuriHac 2017, but got totally derailed by this performance problem. The version of it that I link here is a total mess because of me mauling it to track down this performance issue. Trying to increase `-funfolding-use-threshold` or `-funfolding-keeness- factor` did not change the situation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 19:45:20 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 19:45:20 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.929fff8dad773a2c5cd164524f2cb752@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): And here some details on the second point. After the first run of SpecConstr, we have somthing like this {{{ $w$lf_s6DU [InlPrag=NOUSERINLINE[0]] :: Double -> Double -> GHC.Prim.Int# -> (# Double, Double #) [LclId, Arity=3, Str=m] $w$lf_s6DU = \ (ww_s6AD :: Double) (ww_s6AE :: Double) (ww_s6AI :: GHC.Prim.Int#) -> joinrec { $s$l$w$lf_s6Hv :: GHC.Prim.Int# -> GHC.Prim.Double# -> GHC.Prim.Double# -> (# Double, Double #) [LclId[JoinId(3)], Arity=3, Str=] $s$l$w$lf_s6Hv (sc_s6Hu :: GHC.Prim.Int#) (sc_s6Ht :: GHC.Prim.Double#) (sc_s6Hs :: GHC.Prim.Double#) … $l$w$lf_X6Ep [Occ=LoopBreaker] :: Double -> Double -> GHC.Prim.Int# -> (# Double, Double #) [LclId[JoinId(3)], Arity=3, RULES: "SC:$l$w$lf0" forall (sc_s6Hu :: GHC.Prim.Int#) (sc_s6Ht :: GHC.Prim.Double#) (sc_s6Hs :: GHC.Prim.Double#). $l$w$lf_X6Ep (GHC.Types.D# sc_s6Hs) (GHC.Types.D# sc_s6Ht) sc_s6Hu = jump $s$l$w$lf_s6Hv sc_s6Hu sc_s6Ht sc_s6Hs] $l$w$lf_X6Ep (ww_X6B9 [Dmd=] :: Double) (ww_X6Bb [Dmd=] :: Double) (ww_X6Bg [Dmd=] :: GHC.Prim.Int#) … }; } in jump $l$w$lf_X6Ep ww_s6AD ww_s6AE ww_s6AI … … … case $w$lf_s6DU (GHC.Types.D# (GHC.Prim.cosDouble# wild2_a5jY)) (GHC.Types.D# (GHC.Prim.sinDouble# wild2_a5jY)) wild_XM of }}} We can clearly see that `$w$lf_s6DU` has been loopified, with a local joinrec `$l$w$lf_X6Ep`, and that this local join rec `$l$w$lf_X6Ep` has been !SpecConstr’ed to `$s$l$w$lf_s6Hv`. But why does `$w$lf_s6DU` not get `SpecConstr’ed? Because of {{{ specialise entry { $w$lf_s6DU [$w$lf_s6DU (D# (cosDouble# wild2_a5jY)) (D# (sinDouble# wild2_a5jY)) wild_XM] callToPats [D# (cosDouble# wild2_a5jY), D# (sinDouble# wild2_a5jY), wild_XM] [unk-occ, unk-occ, unk-occ] }}} which means that it sees the calls passing constructors, but it does not know that the arguments (e.g. `ww_s6AD`) get scrutinizes, so it does not act on this. After simplification, however, we have {{{ $w$lf_s6DU [InlPrag=NOUSERINLINE[0]] :: Double -> Double -> GHC.Prim.Int# -> (# Double, Double #) [LclId, Arity=3, Str=m, RULES: "SC:$w$lf0" [0] forall (sc_s6KF :: GHC.Prim.Int#) (sc_s6KE :: GHC.Prim.Double#) (sc_s6KD :: GHC.Prim.Double#). $w$lf_s6DU (GHC.Types.D# sc_s6KD) (GHC.Types.D# sc_s6KE) sc_s6KF = $s$w$lf_s6KG sc_s6KF sc_s6KE sc_s6KD] $w$lf_s6DU = \ (ww_s6AD :: Double) (ww_s6AE :: Double) (ww_s6AI :: GHC.Prim.Int#) -> joinrec { $s$l$w$lf_s6Hv [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Double# -> GHC.Prim.Double# -> (# Double, Double #) … }; } in case ww_s6AD of ww3_s6DY { GHC.Types.D# ww4_s6DZ -> case ww_s6AE of ww5_s6E1 { GHC.Types.D# ww6_s6E2 -> case GHC.Prim.remInt# ww_s6AI 2# of { __DEFAULT -> case ww_s6AI of wild_X11 { … }}} i.e. `$l$w$lf_X6Ep` has been inlined and thus exposed a case analysis of ww_s6AD, and now `$w$lf_s6DU` gets specialized as expected. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:37:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:37:56 -0000 Subject: [GHC] #14155: GHC mentions unlifted types out of the blue (to me anyway) In-Reply-To: <051.e9a8763157e763f2ef920c4bfc2f101b@haskell.org> References: <051.e9a8763157e763f2ef920c4bfc2f101b@haskell.org> Message-ID: <066.fcd4a2a9fa8d61200543197e0932fa5e@haskell.org> #14155: GHC mentions unlifted types out of the blue (to me anyway) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.2.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 bgamari): * owner: (none) => goldfire -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:39:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:39:51 -0000 Subject: [GHC] #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) In-Reply-To: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> References: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> Message-ID: <057.33ea6f4b4fce1424108749de2eb26ad2@haskell.org> #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I can reproduce this but I had to delete the criterion dependency in the cabal file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:41:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:41:46 -0000 Subject: [GHC] #7398: RULES don't apply to a newtype constructor In-Reply-To: <046.1bb2e495c45c32508f69b7364d934e7b@haskell.org> References: <046.1bb2e495c45c32508f69b7364d934e7b@haskell.org> Message-ID: <061.913ad6a59c1b956c890f025512beab5d@haskell.org> #7398: RULES don't apply to a newtype constructor -------------------------------------+------------------------------------- Reporter: shachaf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #6082, #10418, | Differential Rev(s): #13290 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => 8.8.1 Comment: It doesn't look like this will happen for 8.6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:45:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:45:24 -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.7e1754b868370ee61240766ffc140ff8@haskell.org> #12389: Limit duplicate export warnings for datatypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: parsonsmatt Type: feature request | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 7.10.3 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: #11959 | Differential Rev(s): Phab:D4134 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => 8.8.1 Comment: Thanks for taking this on, parsonsmatt! However, given that the Proposal is going to be revised I doubt this will happen for 8.6. Bumping. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:46:32 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:46:32 -0000 Subject: [GHC] #14660: Improve +RTS -t --machine-readable In-Reply-To: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> References: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> Message-ID: <058.44eae3596c19b0a1a980cc6d848aa4fb@haskell.org> #14660: Improve +RTS -t --machine-readable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4303 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2d4bda2e4ac68816baba0afab00da6f769ea75a7/ghc" 2d4bda2e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2d4bda2e4ac68816baba0afab00da6f769ea75a7" rts, base: Refactor stats.c to improve --machine-readable report There should be no change in the output of the '+RTS -s' (summary) report, or the 'RTS -t' (one-line) report. All data shown in the summary report is now shown in the machine readable report. All data in RTSStats is now shown in the machine readable report. init times are added to RTSStats and added to GHC.Stats. Example of the new output: ``` [("bytes allocated", "375016384") ,("num_GCs", "113") ,("average_bytes_used", "148348") ,("max_bytes_used", "206552") ,("num_byte_usage_samples", "2") ,("peak_megabytes_allocated", "6") ,("init_cpu_seconds", "0.001642") ,("init_wall_seconds", "0.001027") ,("mut_cpu_seconds", "3.020166") ,("mut_wall_seconds", "0.757244") ,("GC_cpu_seconds", "0.037750") ,("GC_wall_seconds", "0.009569") ,("exit_cpu_seconds", "0.000890") ,("exit_wall_seconds", "0.002551") ,("total_cpu_seconds", "3.060452") ,("total_wall_seconds", "0.770395") ,("major_gcs", "2") ,("allocated_bytes", "375016384") ,("max_live_bytes", "206552") ,("max_large_objects_bytes", "159344") ,("max_compact_bytes", "0") ,("max_slop_bytes", "59688") ,("max_mem_in_use_bytes", "6291456") ,("cumulative_live_bytes", "296696") ,("copied_bytes", "541024") ,("par_copied_bytes", "493976") ,("cumulative_par_max_copied_bytes", "104104") ,("cumulative_par_balanced_copied_bytes", "274456") ,("fragmentation_bytes", "2112") ,("alloc_rate", "124170795") ,("productivity_cpu_percent", "0.986838") ,("productivity_wall_percent", "0.982935") ,("bound_task_count", "1") ,("sparks_count", "5836258") ,("sparks_converted", "237") ,("sparks_overflowed", "1990408") ,("sparks_dud ", "0") ,("sparks_gcd", "3455553") ,("sparks_fizzled", "390060") ,("work_balance", "0.555606") ,("n_capabilities", "4") ,("task_count", "10") ,("peak_worker_count", "9") ,("worker_count", "9") ,("gc_alloc_block_sync_spin", "162") ,("gc_alloc_block_sync_yield", "0") ,("gc_alloc_block_sync_spin", "162") ,("gc_spin_spin", "18840855") ,("gc_spin_yield", "10355") ,("mut_spin_spin", "70331392") ,("mut_spin_yield", "61700") ,("waitForGcThreads_spin", "241") ,("waitForGcThreads_yield", "2797") ,("whitehole_gc_spin", "0") ,("whitehole_lockClosure_spin", "0") ,("whitehole_lockClosure_yield", "0") ,("whitehole_executeMessage_spin", "0") ,("whitehole_threadPaused_spin", "0") ,("any_work", "1667") ,("no_work", "1662") ,("scav_find_work", "1026") ,("gen_0_collections", "111") ,("gen_0_par_collections", "111") ,("gen_0_cpu_seconds", "0.036126") ,("gen_0_wall_seconds", "0.036126") ,("gen_0_max_pause_seconds", "0.036126") ,("gen_0_avg_pause_seconds", "0.000081") ,("gen_0_sync_spin", "21") ,("gen_0_sync_yield", "0") ,("gen_1_collections", "2") ,("gen_1_par_collections", "1") ,("gen_1_cpu_seconds", "0.001624") ,("gen_1_wall_seconds", "0.001624") ,("gen_1_max_pause_seconds", "0.001624") ,("gen_1_avg_pause_seconds", "0.000272") ,("gen_1_sync_spin", "3") ,("gen_1_sync_yield", "0") ] ``` Test Plan: Ensure that one-line and summary reports are unchanged. Reviewers: bgamari, erikd, simonmar, hvr Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14660 Differential Revision: https://phabricator.haskell.org/D4303 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:46:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:46:56 -0000 Subject: [GHC] #14910: Bump required autoconf version In-Reply-To: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> References: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> Message-ID: <059.db92da77c524aea5fe1aa8063ea87611@haskell.org> #14910: Bump required autoconf version -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.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:D4495 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:47:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:47:00 -0000 Subject: [GHC] #14910: Bump required autoconf version In-Reply-To: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> References: <044.9d7c26e62d984b0cdc4899d7e0507020@haskell.org> Message-ID: <059.f470f6def56572e407f805ef88252dbc@haskell.org> #14910: Bump required autoconf version -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.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:D4495 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6a71ef79cffbfbf09f1567d0136711d80452eb41/ghc" 6a71ef79/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6a71ef79cffbfbf09f1567d0136711d80452eb41" Bump autoconf version bound to >= 2.69 Reviewers: hvr Subscribers: rwbarton, thomie, erikd, carter GHC Trac Issues: #14910 Differential Revision: https://phabricator.haskell.org/D4495 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:47:17 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:47:17 -0000 Subject: [GHC] #14660: Improve +RTS -t --machine-readable In-Reply-To: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> References: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> Message-ID: <058.64013ae7442039a20421cd1e6685d25e@haskell.org> #14660: Improve +RTS -t --machine-readable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 8.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:D4303 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:47:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:47:57 -0000 Subject: [GHC] #14660: Improve +RTS -t --machine-readable In-Reply-To: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> References: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> Message-ID: <058.8b7a844d6a644b6a3dc2767e489bef45@haskell.org> #14660: Improve +RTS -t --machine-readable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.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:D4303 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:48:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:48:04 -0000 Subject: [GHC] #14886: Add max GC pause to GHC.Stats/-t --machine-readable In-Reply-To: <047.0641890e447a41b5694f0694e508f86b@haskell.org> References: <047.0641890e447a41b5694f0694e508f86b@haskell.org> Message-ID: <062.35c137593eef78f118d1febc22aff4e4@haskell.org> #14886: Add max GC pause to GHC.Stats/-t --machine-readable -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.2.2 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14660 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * related: => #14660 * milestone: => 8.6.1 Comment: For the record, pause times were added to `-t` in #14660. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:52:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:52:52 -0000 Subject: [GHC] #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) In-Reply-To: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> References: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> Message-ID: <057.bf01a8a101b2b4188213b71158f5dffa@haskell.org> #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by nh2: Old description: > {{{#!hs > selectVectorDestructive2 :: (PrimMonad m, VG.Vector v e, Ord e, Show e, > VG.Mutable v ~ vm) > => Int -> v e -> vm (PrimState m) e -> Int -> Int -> m () > -- slow > > selectVectorDestructive2 :: (PrimMonad m, VG.Vector v e, Ord e, Show e) > => Int -> v e -> VG.Mutable v (PrimState m) e -> Int -> Int -> m () > -- fast > }}} > > These two functions are identical except one has `VG.Mutable v ~ vm` as a > constraint, the other one has it in the type signature right of the `=>`. > > The second function is 10x faster. > > I would expect them to be equally fast. > > The code of the functions is identical, I change only the type > declaration. > > The slowness happens because with the first function, inlining of > primitives like `unsafeRead` does not happen, and thus also it boxes the > `Int#`s back to `Int`s when calling `unsafeRead`. > > In particular, in `-ddump-simpl`, the slow version has > > {{{#!hs > $wpartitionLoop2_rgEy > :: forall (m :: * -> *) (vm :: * -> * -> *) e. > (PrimMonad m, MVector vm e, Ord e) => > vm (PrimState m) e > -> GHC.Prim.Int# > -> e > -> GHC.Prim.Int# > -> GHC.Prim.Int# > -> GHC.Prim.Int# > -> m Int > $wpartitionLoop2_rgEy > = \... -> > let { > endIndex_a7Ay :: Int > ... > endIndex_a7Ay = GHC.Types.I# ww2_sfZn } in > ... > (VGM.basicUnsafeRead > ... > endIndex_a7Ay) > ... > }}} > > while the fast version has > > {{{#!hs > $w$spartitionLoop2_rgUN > :: GHC.Prim.Int# > -> GHC.Prim.Int# > -> GHC.Prim.MutableByteArray# GHC.Prim.RealWorld > -> GHC.Prim.Int# > -> GHC.Prim.Int# > -> GHC.Prim.Int# > -> GHC.Prim.Int# > -> GHC.Prim.Int# > -> GHC.Prim.State# GHC.Prim.RealWorld > -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #) > > ... > > $spartitionLoop2_rgUP > :: VG.Mutable VU.Vector (PrimState IO) Int > -> Int > -> Int > -> Int > -> Int > -> Int > -> GHC.Prim.State# GHC.Prim.RealWorld > -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #) > }}} > > So with `VG.Mutable v (PrimState m) e` in the type signature, GHC managed > to inline + specialise it all the way down to concrete types > (`VUM.MVector`, `IO`, and `Int` as the element type), and consequently > inline `basicUnsafeRead` on unboxed `Int#`. > > But with `VG.Mutable v ~ vm`, ghc keeps `vm (PrimState m) e` all the way, > passes around dictionaries, thus eventually cannot inline > `basicUnsafeRead` and re-packs already unboxed values, like > `endIndex_a7Ay = GHC.Types.I# ww2_sfZn`, before passing them into the > non-inlined call of `basicUnsafeRead`, thus making a tight loop allocate > that normally wouldn't allocate. > > Why might rewriting the type signature in such a trivial way make this > happen? > > ---- > > I have tested this on GHC 8.0.2, GHC 8.2.2, and GHC 8.5 HEAD commit > cc4677c36ee. > > Reproducer: > > * https://github.com/nh2/haskell-quickselect-median-of- > medians/blob/0efd6293e779fda2d864ec3d75329fb16b8af6d9/Main.hs#L506 > * Running instructions are [https://github.com/nh2/haskell-quickselect- > median-of-medians/commit/7a49d673990dfaebdb0ba837c3fbbaae0455dba0 in this > commit message]; for short: `stack exec -- ghc -O --make Main.hs -rtsopts > -ddump-simpl -dsuppress-coercions -fforce-recomp -ddump-to-file -fno- > full-laziness && ./Main +RTS -sstderr` > * For that file, I have pregenerated `-dverbose-core2core` output here: > https://github.com/nh2/haskell-quickselect-median-of- > medians/tree/0efd6293e779fda2d864ec3d75329fb16b8af6d9/slowness-analysis > * I originally just wanted to write a fast median-of-medians > implementation on ZuriHac 2017, but got totally derailed by this > performance problem. The version of it that I link here is a total mess > because of me mauling it to track down this performance issue. > > Trying to increase `-funfolding-use-threshold` or `-funfolding-keeness- > factor` did not change the situation. New description: {{{#!hs selectVectorDestructive2 :: (PrimMonad m, VG.Vector v e, Ord e, Show e, VG.Mutable v ~ vm) => Int -> v e -> vm (PrimState m) e -> Int -> Int -> m () -- slow selectVectorDestructive2 :: (PrimMonad m, VG.Vector v e, Ord e, Show e) => Int -> v e -> VG.Mutable v (PrimState m) e -> Int -> Int -> m () -- fast }}} These two functions are identical except one has `VG.Mutable v ~ vm` as a constraint, the other one has it in the type signature right of the `=>`. The second function is 10x faster. I would expect them to be equally fast. The code of the functions is identical, I change only the type declaration. The slowness happens because with the first function, inlining of primitives like `unsafeRead` does not happen, and thus also it boxes the `Int#`s back to `Int`s when calling `unsafeRead`. In particular, in `-ddump-simpl`, the slow version has {{{#!hs $wpartitionLoop2_rgEy :: forall (m :: * -> *) (vm :: * -> * -> *) e. (PrimMonad m, MVector vm e, Ord e) => vm (PrimState m) e -> GHC.Prim.Int# -> e -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> m Int $wpartitionLoop2_rgEy = \... -> let { endIndex_a7Ay :: Int ... endIndex_a7Ay = GHC.Types.I# ww2_sfZn } in ... (VGM.basicUnsafeRead ... endIndex_a7Ay) ... }}} while the fast version has {{{#!hs $w$spartitionLoop2_rgUN :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.MutableByteArray# GHC.Prim.RealWorld -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #) ... $spartitionLoop2_rgUP :: VG.Mutable VU.Vector (PrimState IO) Int -> Int -> Int -> Int -> Int -> Int -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, Int #) }}} So with `VG.Mutable v (PrimState m) e` in the type signature, GHC managed to inline + specialise it all the way down to concrete types (`VUM.MVector`, `IO`, and `Int` as the element type), and consequently inline `basicUnsafeRead` on unboxed `Int#`. But with `VG.Mutable v ~ vm`, ghc keeps `vm (PrimState m) e` all the way, passes around dictionaries, thus eventually cannot inline `basicUnsafeRead` and re-packs already unboxed values, like `endIndex_a7Ay = GHC.Types.I# ww2_sfZn`, before passing them into the non-inlined call of `basicUnsafeRead`, thus making a tight loop allocate that normally wouldn't allocate. Why might rewriting the type signature in such a trivial way make this happen? ---- I have tested this on GHC 8.0.2, GHC 8.2.2, and GHC 8.5 HEAD commit cc4677c36ee (edit: in which case I commented out the quickcheck and criterion related stuff because their deps don't build there yet). Reproducer: * https://github.com/nh2/haskell-quickselect-median-of- medians/blob/0efd6293e779fda2d864ec3d75329fb16b8af6d9/Main.hs#L506 * Running instructions are [https://github.com/nh2/haskell-quickselect- median-of-medians/commit/7a49d673990dfaebdb0ba837c3fbbaae0455dba0 in this commit message]; for short: `stack exec -- ghc -O --make Main.hs -rtsopts -ddump-simpl -dsuppress-coercions -fforce-recomp -ddump-to-file -fno-full- laziness && ./Main +RTS -sstderr` * For that file, I have pregenerated `-dverbose-core2core` output here: https://github.com/nh2/haskell-quickselect-median-of- medians/tree/0efd6293e779fda2d864ec3d75329fb16b8af6d9/slowness-analysis * I originally just wanted to write a fast median-of-medians implementation on ZuriHac 2017, but got totally derailed by this performance problem. The version of it that I link here is a total mess because of me mauling it to track down this performance issue. Trying to increase `-funfolding-use-threshold` or `-funfolding-keeness- factor` did not change the situation. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 20:57:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 20:57:00 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.fc3f2ca7a19f1e08e562c32c1597a47e@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I distilled this example to show the effect {{{ module T14844Example (bar1, bar2) where large x = x {-# NOINLINE large #-} foo :: Int -> (a -> b -> Bool) -> (a,b) -> Bool foo 0 _ _ = False foo s f t = l s' t where l 0 t = False l 1 t = case t of (x,y) -> f x y l n (x,y) = l (n-1) (x,y) s' = -- To prevent inlining large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ large $ s bar1 :: Int -> (a -> b -> Bool) -> a -> b -> Bool bar1 s f x y = foo s f (x,y) bar2 :: Int -> (a -> b -> Bool) -> a -> b -> Bool bar2 s f x y = foo (s + 1) f (x,y) }}} This needs to rounds of !SpecConstr to specialize `foo` for the `(x,y)` call pattern; in the first round, `l` is specialized, then the (then non- recursive `l`) gets inlined into `foo`, then `foo` gets specialized. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:14:07 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:14:07 -0000 Subject: [GHC] #12619: Allow users guide to be built independently from GHC In-Reply-To: <046.2df188325e9671498d5d7f855d704a92@haskell.org> References: <046.2df188325e9671498d5d7f855d704a92@haskell.org> Message-ID: <061.b514c37c75c0c8abc0f9412c783eb996@haskell.org> #12619: Allow users guide to be built independently from GHC -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomer * milestone: 8.6.1 => 8.8.1 Comment: For the record, I believe this should now be much easier as `mkUserGuideParts` has been removed. It would likely be best (and easiest!) to start with Hadrian, however. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:20:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:20:52 -0000 Subject: [GHC] #14270: GHC HEAD's ghc-stage1 panics on Data.Typeable.Internal In-Reply-To: <042.d21b92eb840644cd16549869583bccd0@haskell.org> References: <042.d21b92eb840644cd16549869583bccd0@haskell.org> Message-ID: <057.d06efc23ac095b942abe6f3ffc8c6611@haskell.org> #14270: GHC HEAD's ghc-stage1 panics on Data.Typeable.Internal -------------------------------------+------------------------------------- Reporter: hvr | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.8.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: 14119 | Blocking: Related Tickets: #14236 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * blockedby: => 14119 * milestone: 8.6.1 => 8.8.1 Comment: Given that there's no sign of motion on #14119, I think it's unlikely that this will happen for 8.8. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:23:29 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:23:29 -0000 Subject: [GHC] #12737: T12227 is failing on ghc-8.0 In-Reply-To: <045.0ea1cfebd1260afa6de135f4f7b4ff86@haskell.org> References: <045.0ea1cfebd1260afa6de135f4f7b4ff86@haskell.org> Message-ID: <060.9613bda71727a06bc5f294d57aa105af@haskell.org> #12737: T12227 is failing on ghc-8.0 -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Visual Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Sadly there has been no motion on this; demilestoning. Do ping if this sounds interesting to you, however. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:24:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:24:04 -0000 Subject: [GHC] #12737: T12227 is failing on ghc-8.0 In-Reply-To: <045.0ea1cfebd1260afa6de135f4f7b4ff86@haskell.org> References: <045.0ea1cfebd1260afa6de135f4f7b4ff86@haskell.org> Message-ID: <060.920d4f2947b218e5f87b636a4a39be44@haskell.org> #12737: T12227 is failing on ghc-8.0 -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Visual Haskell | 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 bgamari): * status: closed => new * resolution: fixed => * milestone: 8.6.1 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:24:07 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:24:07 -0000 Subject: [GHC] #12715: T3994 is intermittently broken on Windows In-Reply-To: <046.c5c17c3ffa0f5995b9ee92c16bf2d478@haskell.org> References: <046.c5c17c3ffa0f5995b9ee92c16bf2d478@haskell.org> Message-ID: <061.a74de96723b2ef7139861d498aebbbe9@haskell.org> #12715: T3994 is intermittently broken on Windows ---------------------------------+-------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Test Suite | Version: 8.1 Resolution: fixed | 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 bgamari): * status: new => closed * resolution: => fixed Comment: I haven't seen this in quite some time. Closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:24:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:24:26 -0000 Subject: [GHC] #14155: GHC mentions unlifted types out of the blue (to me anyway) In-Reply-To: <051.e9a8763157e763f2ef920c4bfc2f101b@haskell.org> References: <051.e9a8763157e763f2ef920c4bfc2f101b@haskell.org> Message-ID: <066.a52602885ffd7c5ab0cdc0a65c3efffe@haskell.org> #14155: GHC mentions unlifted types out of the blue (to me anyway) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.2.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 bgamari): * priority: high => normal * milestone: 8.6.1 => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:25:27 -0000 Subject: [GHC] #14501: hp2ps and unlit are compiled by the stage0 compiler In-Reply-To: <046.d2c7325ab6aa360259cb4180f4cc3fba@haskell.org> References: <046.d2c7325ab6aa360259cb4180f4cc3fba@haskell.org> Message-ID: <061.81f7a14e170459be1e5d8c2729346c04@haskell.org> #14501: hp2ps and unlit are compiled by the stage0 compiler -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.2.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: alpmestan (added) * status: new => infoneeded Comment: Angerman, Alp, is this now fixed in Hadrian? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:26:43 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:26:43 -0000 Subject: [GHC] #12038: Shutdown interacts badly with requestSync() In-Reply-To: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> References: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> Message-ID: <062.8d9a7f9a3c5a8ef8549c6e041c451ac0@haskell.org> #12038: Shutdown interacts badly with requestSync() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | 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: #5553 | Differential Rev(s): Phab:D2926 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Demilestoning due to lack of progress. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:27:40 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:27:40 -0000 Subject: [GHC] #14501: hp2ps and unlit are compiled by the stage0 compiler In-Reply-To: <046.d2c7325ab6aa360259cb4180f4cc3fba@haskell.org> References: <046.d2c7325ab6aa360259cb4180f4cc3fba@haskell.org> Message-ID: <061.0b256026c8c644da980656e78cb490ba@haskell.org> #14501: hp2ps and unlit are compiled by the stage0 compiler -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12193 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: infoneeded => closed * resolution: => duplicate * related: => #12193 Comment: It looks like this is a duplicate of #12193. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:29:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:29:55 -0000 Subject: [GHC] #14282: tagToEnum# . dataToTag# not optimized away In-Reply-To: <045.5438ce0b3dc299cc3f08e924d6abe37c@haskell.org> References: <045.5438ce0b3dc299cc3f08e924d6abe37c@haskell.org> Message-ID: <060.e4eb33c5665ae01081fc5b80c083e0b2@haskell.org> #14282: tagToEnum# . dataToTag# not optimized away -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: dfeuer Type: bug | Status: patch Priority: low | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: datacon-tags Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4375 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => low * milestone: 8.6.1 => Comment: Demilestoning since moving this along further will be nontrivial. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:30:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:30:22 -0000 Subject: [GHC] #12193: Include target versions of unlit and hsc2hs when cross-compiling In-Reply-To: <047.70c7f34a854dd4d3e899f2d863451090@haskell.org> References: <047.70c7f34a854dd4d3e899f2d863451090@haskell.org> Message-ID: <062.79cca3af78600136c4bbd368279c8fcf@haskell.org> #12193: Include target versions of unlit and hsc2hs when cross-compiling -------------------------------------+------------------------------------- Reporter: glaubitz | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.0.1 Resolution: | Keywords: cross-compile Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14501 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #14501 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:31:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:31:08 -0000 Subject: [GHC] #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks In-Reply-To: <049.64e07177e9110058c04a019d46370d44@haskell.org> References: <049.64e07177e9110058c04a019d46370d44@haskell.org> Message-ID: <064.7c5bce783d0d75dab2ecfda264224497@haskell.org> #13892: Add some benchmarks to nofib from Andras Kovac's Eff benchmarks -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 8.0.1 suite | 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 bgamari): * milestone: 8.6.1 => Comment: Removing the milestone since it's unlikely to happen for 8.6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:36:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:36:03 -0000 Subject: [GHC] #14023: Split up glasgow_exts.rst In-Reply-To: <046.00c07fe5ce6492eaedacdeae3c6ea07a@haskell.org> References: <046.00c07fe5ce6492eaedacdeae3c6ea07a@haskell.org> Message-ID: <061.3c59998bc3b9d88cc9891356e6469fb6@haskell.org> #14023: Split up glasgow_exts.rst -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Documentation | Version: 8.0.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomers -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:36:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:36:26 -0000 Subject: [GHC] #14078: -ddump-json doesn't work well with GHCi In-Reply-To: <050.a3c1661fff8336ca3c521994e1a88d18@haskell.org> References: <050.a3c1661fff8336ca3c521994e1a88d18@haskell.org> Message-ID: <065.bcb9f45f13eb54f5523f760ecb8ed072@haskell.org> #14078: -ddump-json doesn't work well with GHCi -------------------------------------+------------------------------------- Reporter: dramforever | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: GHCi | Version: 8.2.1 Resolution: | Keywords: JSON 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): mpickering, do you think we will be able to fix this by 8.6? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:38:15 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:38:15 -0000 Subject: [GHC] #13654: Optimize casMutVar# for single-threaded runtime In-Reply-To: <045.de130c37edb1393ac27afa1cebe7df28@haskell.org> References: <045.de130c37edb1393ac27afa1cebe7df28@haskell.org> Message-ID: <060.57f70e2a52b1cb6e21171cc6a6503c5e@haskell.org> #13654: Optimize casMutVar# for single-threaded runtime -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.4.1 Component: Runtime System | Version: 8.2.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: 8.6.1 => 8.4.1 Comment: This was carried out in ff7a3c4f9034af0aca1119c1c1e8f7187460bbad. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:44:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:44:01 -0000 Subject: [GHC] #13378: LLVM backend doesn't support MacOS dead code stripping In-Reply-To: <047.6398a672bf9fd46b39701222a0eefc74@haskell.org> References: <047.6398a672bf9fd46b39701222a0eefc74@haskell.org> Message-ID: <062.0adf4dc987bb4fd232d1f50d3ffc6c9e@haskell.org> #13378: LLVM backend doesn't support MacOS dead code stripping -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 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.6.1 => Comment: angerman, what ever happened to this? It looks like the LLVM patch never made it upstream. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:45:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:45:22 -0000 Subject: [GHC] #13639: Skylighting package compilation is glacial In-Reply-To: <046.64388e0a2e512a976d78587b5b6b3aaa@haskell.org> References: <046.64388e0a2e512a976d78587b5b6b3aaa@haskell.org> Message-ID: <061.079f9d5107b72f9a7058ae3a6870204b@haskell.org> #13639: Skylighting package compilation is glacial -------------------------------------+------------------------------------- Reporter: bgamari | Owner: dfeuer Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: I believe this is resolved. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:53:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:53:57 -0000 Subject: [GHC] #13443: Typeclass resolution errors quite puzzling In-Reply-To: <051.f75b47e89b46a32f178b489cb149873e@haskell.org> References: <051.f75b47e89b46a32f178b489cb149873e@haskell.org> Message-ID: <066.a28a4df2e9c3ee70507263500fe1f547@haskell.org> #13443: Typeclass resolution errors quite puzzling -------------------------------------+------------------------------------- Reporter: tomjaguarpaw | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Old description: > This ticket is based on a post I made to haskell-cafe: > https://mail.haskell.org/pipermail/haskell-cafe/2016-August/124622.html > > Here's a program with an odd error message (GHC 8.0.1): > > {{{ > data A a = A a deriving Eq > data B = B > > main :: IO () > main = print (A B == A B) > > test/main.hs:5:15: error: > • No instance for (Eq B) arising from a use of ‘==’ > • In the first argument of ‘print’, namely ‘(A B == A B)’ > In the expression: print (A B == A B) > In an equation for ‘main’: main = print (A B == A B) > }}} > > I get an error about `Eq B` even though it's `Eq A` that is manifestly > required at the call site. This error is odder when `A` and `B` are > defined far away from the use of `==`. > > This is even odder: > > {{{ > data A a = A a > data B = B > > instance Ord a => Eq (A a) where > > main :: IO () > main = print (A B == A B) > > test/main.hs:7:15: error: > • No instance for (Ord B) arising from a use of ‘==’ > • In the first argument of ‘print’, namely ‘(A B == A B)’ > In the expression: print (A B == A B) > In an equation for ‘main’: main = print (A B == A B) > }}} > > Now not only is the type puzzling (`B` instead of `A`) but the *class* is > puzzling (`Ord` instead of `Eq`). This occurred to me in practice > because `Data.Graph.Inductive.PatriciaTree.Gr` has `(Eq a, Ord b) => Eq > (Gr a b)`. > > It would have been a lot more helpful to see > > {{{ > * No instance for (Ord B) > * arising from (Eq A) > * arising from the use of '==' > }}} > > Does anyone agree with me that GHC should produce the full trace when it > fails to resolve instances rather than just the proximal failure? New description: This ticket is based on a post I made to haskell-cafe: https://mail.haskell.org/pipermail/haskell-cafe/2016-August/124622.html Here's a program with an odd error message (GHC 8.0.1): {{{#!hs data A a = A a deriving Eq data B = B main :: IO () main = print (A B == A B) test/main.hs:5:15: error: • No instance for (Eq B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}} I get an error about `Eq B` even though it's `Eq A` that is manifestly required at the call site. This error is odder when `A` and `B` are defined far away from the use of `==`. This is even odder: {{{#!hs data A a = A a data B = B instance Ord a => Eq (A a) where main :: IO () main = print (A B == A B) test/main.hs:7:15: error: • No instance for (Ord B) arising from a use of ‘==’ • In the first argument of ‘print’, namely ‘(A B == A B)’ In the expression: print (A B == A B) In an equation for ‘main’: main = print (A B == A B) }}} Now not only is the type puzzling (`B` instead of `A`) but the *class* is puzzling (`Ord` instead of `Eq`). This occurred to me in practice because `Data.Graph.Inductive.PatriciaTree.Gr` has `(Eq a, Ord b) => Eq (Gr a b)`. It would have been a lot more helpful to see {{{ * No instance for (Ord B) * arising from (Eq A) * arising from the use of '==' }}} Does anyone agree with me that GHC should produce the full trace when it fails to resolve instances rather than just the proximal failure? -- Comment: Demilestoning as no one has stepped up to carry this out yet. Do ping if this sounds like the sort of project you would like to try. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:55:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:55:05 -0000 Subject: [GHC] #14942: QuantifiedConstraints: GHC can't infer Message-ID: <051.958f742763b6ceef29a453a2ee8d4b69@haskell.org> #14942: QuantifiedConstraints: GHC can't infer -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This works {{{#!hs {-# Language QuantifiedConstraints, GADTs, KindSignatures, RankNTypes, ConstraintKinds #-} import Data.Kind newtype Free :: (Type -> Constraint) -> (Type -> Type) where Free :: (forall x. cls x => (a -> x) -> x) -> Free cls a var :: a -> Free cls a var a = Free $ \var -> var a oneTwo :: (forall x. semi x => Semigroup x) => Free semi Int oneTwo = Free $ \var -> var 1 <> var 2 nil :: (forall x. mon x => Monoid x) => Free mon Int nil = Free $ \var -> mempty together :: (forall x. mon x => Monoid x) => [Free mon Int] together = [var 0, nil, oneTwo] }}} If we comment out `together`'s type signature GHC cannot infer it back, shouldn't it be able to though? {{{ $ ./ghc-stage2 --interactive -ignore-dot-ghci Proposal.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Proposal.hs, interpreted ) Proposal.hs:21:20: error: • Could not deduce (Monoid x) arising from a use of ‘nil’ from the context: cls x bound by a quantified context at Proposal.hs:21:1-31 Possible fix: add (Monoid x) to the context of a quantified context • In the expression: nil In the expression: [var 0, nil, oneTwo] In an equation for ‘together’: together = [var 0, nil, oneTwo] | 21 | together = [var 0, nil, oneTwo] | ^^^ Proposal.hs:21:25: error: • Could not deduce (Semigroup x) arising from a use of ‘oneTwo’ from the context: cls x bound by a quantified context at Proposal.hs:21:1-31 Possible fix: add (Semigroup x) to the context of a quantified context • In the expression: oneTwo In the expression: [var 0, nil, oneTwo] In an equation for ‘together’: together = [var 0, nil, oneTwo] | 21 | together = [var 0, nil, oneTwo] | ^^^^^^ Failed, no modules loaded. Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:56:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:56:03 -0000 Subject: [GHC] #12712: break011 is broken on Windows In-Reply-To: <046.625cebc98263ea38795f8428b7bfe04f@haskell.org> References: <046.625cebc98263ea38795f8428b7bfe04f@haskell.org> Message-ID: <061.26cbf8649689737e4e778ade31023703@haskell.org> #12712: break011 is broken on Windows ---------------------------------+-------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Test Suite | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: break011 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: 8.6.1 => 8.4.1 Comment: It looks like this was fixed in 7af0b906116e13fbd90f43f2f6c6b826df2dca77. Yay! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:57:18 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:57:18 -0000 Subject: [GHC] #13452: Lock .tix file In-Reply-To: <045.e111ce23004cdc0b4740a146d49d8624@haskell.org> References: <045.e111ce23004cdc0b4740a146d49d8624@haskell.org> Message-ID: <060.bf6b0e574fa630315d8729e4b97ff328@haskell.org> #13452: Lock .tix file -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Code Coverage | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomer * milestone: 8.6.1 => Comment: Removing milestone as no one has stepped up to carry this out. Do ping if this sounds like the sort of project you would be interested in trying. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 21:58:18 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 21:58:18 -0000 Subject: [GHC] #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown In-Reply-To: <049.12eb233680e8d62e08f397274c91a741@haskell.org> References: <049.12eb233680e8d62e08f397274c91a741@haskell.org> Message-ID: <064.c51d5e0316fceb93194a2a22301ea917@haskell.org> #13851: Change in specialisation(?) behaviour since 8.0.2 causes 6x slowdown -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: inlining Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one has stepped up to carry this on. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:00:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:00:00 -0000 Subject: [GHC] #13690: Running profiling tests in the GHCi way is extremely slow In-Reply-To: <045.fb69f1a6160438a1692ed4b6bf5047fa@haskell.org> References: <045.fb69f1a6160438a1692ed4b6bf5047fa@haskell.org> Message-ID: <060.e875f8f5ac3b83a8c29635f7fa8cba29@haskell.org> #13690: Running profiling tests in the GHCi way is extremely slow -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => worksforme Comment: Hmm, I can't reproduce this. `time make test TEST=profinline001 WAY=prof` shows a real time of 300 milliseconds on my machine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:02:14 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:02:14 -0000 Subject: [GHC] #13276: Unboxed sums are not Typeable In-Reply-To: <046.4162392a9dfa8c9df65b438ac9c9523d@haskell.org> References: <046.4162392a9dfa8c9df65b438ac9c9523d@haskell.org> Message-ID: <061.56f63333e8b5e72d85e7e77d584dce75@haskell.org> #13276: Unboxed sums are not Typeable -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: typeable, | UnboxedSums Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13261 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there are currently no plans to fix this. Making the change isn't hard (i.e. simply revert 42ff5d97), however we'll need to sort out the compile-time implications before moving ahead. Do holler if this is blocking you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:03:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:03:24 -0000 Subject: [GHC] #13165: Speed up the RTS hash table In-Reply-To: <047.5597063b110123c6100b4b707918365d@haskell.org> References: <047.5597063b110123c6100b4b707918365d@haskell.org> Message-ID: <062.bbe8d26a14ac7285c4e842d163e06de9@haskell.org> #13165: Speed up the RTS hash table -------------------------------------+------------------------------------- Reporter: dobenour | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomer * milestone: 8.6.1 => Comment: Removing milestone as no one is currently working on this. Do holler if this is something that you would be interested in trying. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:04:16 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:04:16 -0000 Subject: [GHC] #11765: Allow documentary type signatures In-Reply-To: <045.51543a8e2596876e20358182acc17b6e@haskell.org> References: <045.51543a8e2596876e20358182acc17b6e@haskell.org> Message-ID: <060.b67aa5a34ffb284f819907211598eb56@haskell.org> #11765: Allow documentary type signatures -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: It seems like this is something that would be best handled through the [[https://github.com/ghc-proposals/ghc-proposals|proposal process]]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:04:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:04:54 -0000 Subject: [GHC] #11773: linux/powepc : ghc-stage1 segfaults when building unregisterised In-Reply-To: <044.a4a61ba55383f88cbd05cc1baa6706bc@haskell.org> References: <044.a4a61ba55383f88cbd05cc1baa6706bc@haskell.org> Message-ID: <059.497eb2a7a1196bf8e37568172d7da403@haskell.org> #11773: linux/powepc : ghc-stage1 segfaults when building unregisterised ----------------------------------------+------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: #11784 | Differential Rev(s): Wiki Page: | ----------------------------------------+------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: erikd, any word on this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:05:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:05:52 -0000 Subject: [GHC] #11827: InteractiveEval error handling gets a boot ModSummary instead of normal ModSummary In-Reply-To: <046.24c2998367c5a8124c7521e8ac11ef2c@haskell.org> References: <046.24c2998367c5a8124c7521e8ac11ef2c@haskell.org> Message-ID: <061.2d3f23f9ebe35a1126f37315d3b286dc@haskell.org> #11827: InteractiveEval error handling gets a boot ModSummary instead of normal ModSummary -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: ghci/T11827 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => ghci/T11827 * milestone: 8.6.1 => Comment: Removing milestone as no one is actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:07:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:07:35 -0000 Subject: [GHC] #11495: TH_spliceE5_prof is failing with release candidate 8.0.1 In-Reply-To: <045.e71529dd8c6b021f985c7b75a2a26fb0@haskell.org> References: <045.e71529dd8c6b021f985c7b75a2a26fb0@haskell.org> Message-ID: <060.9924c6e495bc4f2fbf75a9fd9183abd6@haskell.org> #11495: TH_spliceE5_prof is failing with release candidate 8.0.1 -------------------------------------+------------------------------------- Reporter: thomie | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is no one actively working on this and we very much lack direction here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:07:59 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:07:59 -0000 Subject: [GHC] #11260: Re-compilation driver/recomp11 test fails In-Reply-To: <047.28b99765e1530b4875c5afc418e3bf27@haskell.org> References: <047.28b99765e1530b4875c5afc418e3bf27@haskell.org> Message-ID: <062.9d83d16203147600b148904c0737933b@haskell.org> #11260: Re-compilation driver/recomp11 test fails -------------------------------------+------------------------------------- Reporter: trommler | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | driver/recomp011 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is no one actively working on this and we very much lack direction here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:09:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:09:08 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.a9a10d354a7f50cabd2fa443e1d3532c@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.4.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: simonpj (added) * milestone: => 8.4.2 Comment: This regression was introduced in commit fb050a330ad202c1eb43038dc18cca2a5be26f4a (`Do not bind coercion variables in SpecConstr rules`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:19:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:19:24 -0000 Subject: [GHC] #11382: Optimize Data.Char In-Reply-To: <046.07b85d059cbd81601867717299b83062@haskell.org> References: <046.07b85d059cbd81601867717299b83062@haskell.org> Message-ID: <061.48e013d40dbc89b15aa592d4bf58195f@haskell.org> #11382: Optimize Data.Char -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.3 Resolution: wontfix | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9638, #1473 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix * milestone: 8.6.1 => Comment: Given the findings in ticket:9638#comment:4, I'm going to close this for now. I, for one, don't have time to look into this at the moment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:20:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:20:00 -0000 Subject: [GHC] #11259: Use system runtime linker in GHCi on PowerPC 64 bit In-Reply-To: <047.f1dbe111d1a2b1b825a51a6a842cbde6@haskell.org> References: <047.f1dbe111d1a2b1b825a51a6a842cbde6@haskell.org> Message-ID: <062.4a04159c16b5737d26a5f95f20856ce2@haskell.org> #11259: Use system runtime linker in GHCi on PowerPC 64 bit -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc64 Type of failure: GHCi crash | Test Case: ghcilink004, | prog001, and 11 more Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is no one actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:20:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:20:56 -0000 Subject: [GHC] #10141: CUSK mysteries In-Reply-To: <047.0645604fc6dcb528cffc10034076546d@haskell.org> References: <047.0645604fc6dcb528cffc10034076546d@haskell.org> Message-ID: <062.7997fe203ed689879c0a00413dee45db@haskell.org> #10141: CUSK mysteries -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1-rc2 Resolution: | Keywords: TypeFamilies, | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: indexed- | types/should_fail/T10141 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Old description: > Take the following definition: > > {{{ > type family G (a :: k) where > G Int = Bool > G Bool = Int > G a = a > }}} > > It compiles in 7.8.3, but not in 7.10.1 RC2. This makes me sad. I will > fix. > > (Found by Jan Stolarek.) New description: Take the following definition: {{{#!hs type family G (a :: k) where G Int = Bool G Bool = Int G a = a }}} It compiles in 7.8.3, but not in 7.10.1 RC2. This makes me sad. I will fix. (Found by Jan Stolarek.) -- Comment: Removing milestone as no one is actively looking at this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:21:45 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:21:45 -0000 Subject: [GHC] #13896: Use response file to invoke hsc2hs In-Reply-To: <046.8d005e1593e32147d596c190fbabb716@haskell.org> References: <046.8d005e1593e32147d596c190fbabb716@haskell.org> Message-ID: <061.292e983fb2bb0047a9d613a4d85fccbd@haskell.org> #13896: Use response file to invoke hsc2hs ---------------------------------+---------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: hsc2hs | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * priority: high => normal Comment: Demoting in priority although retaining the milestone as we really ought to just fix this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:22:17 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:22:17 -0000 Subject: [GHC] #13650: Implement KPush in types In-Reply-To: <047.e26721ad30e2e3d90c01c9e924788439@haskell.org> References: <047.e26721ad30e2e3d90c01c9e924788439@haskell.org> Message-ID: <062.4ca52178dd4dc45aaea6f8d6ef77c91c@haskell.org> #13650: Implement KPush in types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: new Priority: high | 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 bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is no one actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:23:25 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:23:25 -0000 Subject: [GHC] #14468: Why does alanz's branch blow up GHC's heap? In-Reply-To: <046.be390aa8ac1f4abd294d2b3b0f58b57c@haskell.org> References: <046.be390aa8ac1f4abd294d2b3b0f58b57c@haskell.org> Message-ID: <061.eff30ba5f82d582c66f34669f1364864@haskell.org> #14468: Why does alanz's branch blow up GHC's heap? -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: closed Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8095, #13386 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => invalid * related: => #8095, #13386 Comment: I'm going to close this as it has served it's purpose. Alanz suspects that #8095 and #13386 may be relevant. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:24:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:24:57 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.42471526cf645941f2514230e5cdaaad@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => normal * milestone: 8.6.1 => Comment: Bumping down in priority and removing milestone as this has been open for several years with no progress. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:29:49 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:29:49 -0000 Subject: [GHC] #10068: Make the runtime reflection API for names, modules, locations more systematic In-Reply-To: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> References: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> Message-ID: <061.f36397824bad358f0781e4df23d73e95@haskell.org> #10068: Make the runtime reflection API for names, modules, locations more systematic -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Generics, | 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 bgamari): * priority: high => normal * milestone: 8.6.1 => Comment: Removing milestone as no one is working on this. For the record, I suspect this change should probably go through the [[https://github.com/ghc-proposals/ghc-proposals|proposal process]]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:31:29 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:31:29 -0000 Subject: [GHC] #10506: SourceNotes are not applied to all identifiers In-Reply-To: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> References: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> Message-ID: <064.d23835996c025b4948df989f7e5827df@haskell.org> #10506: SourceNotes are not applied to all identifiers -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | 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): Phab:D1565 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded * milestone: 8.6.1 => Comment: gridaphobe, what ended up happening with this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:32:48 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:32:48 -0000 Subject: [GHC] #10346: Cross-module SpecConstr In-Reply-To: <046.b576f13f2450fed85380ce289fdfae5b@haskell.org> References: <046.b576f13f2450fed85380ce289fdfae5b@haskell.org> Message-ID: <061.26a9fe994347a35ddef1167a8618eebc@haskell.org> #10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is no one actively working on this at the moment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:33:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:33:55 -0000 Subject: [GHC] #10189: explicit promotions of prefix data constructors can't be parsed naturally In-Reply-To: <048.7a1fa374089d49b55ac4c378c43baf5b@haskell.org> References: <048.7a1fa374089d49b55ac4c378c43baf5b@haskell.org> Message-ID: <063.9249e4ff16e20782101612d63455e856@haskell.org> #10189: explicit promotions of prefix data constructors can't be parsed naturally -------------------------------------+------------------------------------- Reporter: Kinokkory | Owner: Kinokkory Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10188 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is currently no one actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:34:39 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:34:39 -0000 Subject: [GHC] #7273: Binary size increase in nofib/grep between 7.6.1 and HEAD In-Reply-To: <047.56a3d4f639e4f19c232c77ec82adbeca@haskell.org> References: <047.56a3d4f639e4f19c232c77ec82adbeca@haskell.org> Message-ID: <062.3a3c2a9f51c474c35006cf6f10de3754@haskell.org> #7273: Binary size increase in nofib/grep between 7.6.1 and HEAD -------------------------------------+------------------------------------- Reporter: simonmar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is currently no one actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:34:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:34:52 -0000 Subject: [GHC] #3427: control what sort of entity a deprecated pragma applies to In-Reply-To: <044.6e5c26a8435c2fcde3f9de3ab4769428@haskell.org> References: <044.6e5c26a8435c2fcde3f9de3ab4769428@haskell.org> Message-ID: <059.d98ca8eae755d4b9a777ebde97d29bbd@haskell.org> #3427: control what sort of entity a deprecated pragma applies to -------------------------------------+------------------------------------- Reporter: igloo | Owner: thoughtpolice Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 6.10.4 Resolution: | Keywords: deprecate | warning, 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 bgamari): * keywords: deprecate warning => deprecate warning, newcomer * milestone: 8.6.1 => Comment: Removing milestone as there is currently no one actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:35:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:35:13 -0000 Subject: [GHC] #4879: Deprecate exports In-Reply-To: <049.ea1fa273b308c2a35269907288b50645@haskell.org> References: <049.ea1fa273b308c2a35269907288b50645@haskell.org> Message-ID: <064.65fb61b73a77783f16897e164c2f5484@haskell.org> #4879: Deprecate exports -------------------------------------+------------------------------------- Reporter: basvandijk | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.1 Resolution: | Keywords: deprecate | warning Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10071 #2119 | Differential Rev(s): Phab:D638 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is currently no one actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:37:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:37:08 -0000 Subject: [GHC] #10640: Document prim-ops In-Reply-To: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> References: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> Message-ID: <061.72c7f489aaf9410b97b24d7601e7d8ab@haskell.org> #10640: Document prim-ops -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 7.10.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): Phab:D1082 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Things are gradually getting better here but I'm going to remove the milestone as it is an on-going project. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:38:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:38:05 -0000 Subject: [GHC] #12982: Missed constant folding oportunities In-Reply-To: <044.d9771cbd0fd576f4750f411f0acf4ba6@haskell.org> References: <044.d9771cbd0fd576f4750f411f0acf4ba6@haskell.org> Message-ID: <059.21a13b491496e37aa6399badaa7a897c@haskell.org> #12982: Missed constant folding oportunities -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/hoopl | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomer * milestone: 8.6.1 => Comment: sio, sorry I missed your comment; were you able to make any progress on this? Do ping if you need help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:38:42 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:38:42 -0000 Subject: [GHC] #11092: ApiAnnotations : make annotation for shebang In-Reply-To: <044.0bd4290eed8d430160dff757f59d13b8@haskell.org> References: <044.0bd4290eed8d430160dff757f59d13b8@haskell.org> Message-ID: <059.1004f5b7dc1702da9cbaa15f1e3d7066@haskell.org> #11092: ApiAnnotations : make annotation for shebang -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.10.2 Resolution: | Keywords: | ApiAnnotations 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): alanz, has there been any progress on this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:39:44 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:39:44 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.e3f80e759dc127112ee7177c48e458a9@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Build 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): Phab:D1021 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => alpmestan Comment: Assigning to Alp to ensure this happens in Hadrian. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:41:11 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:41:11 -0000 Subject: [GHC] #7860: Add more bit fiddling functions to 'integer-gmp' In-Reply-To: <046.cf50459cade182946253e5602ab21f1f@haskell.org> References: <046.cf50459cade182946253e5602ab21f1f@haskell.org> Message-ID: <061.420eec900231801671976253dfe7ef17@haskell.org> #7860: Add more bit fiddling functions to 'integer-gmp' -------------------------------------+------------------------------------- Reporter: lebedev | Owner: hvr Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: | Keywords: integer-gmp Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3489, #9835 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: It sounds like there is still a bit more work to be done here. Removing milestone as no one is currently working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:42:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:42:47 -0000 Subject: [GHC] #10933: REMOVED pragma In-Reply-To: <047.034826e24c434b8ddb0afbdd6905b9d3@haskell.org> References: <047.034826e24c434b8ddb0afbdd6905b9d3@haskell.org> Message-ID: <062.8aef369da427abed1dec1aa7c7ae4b3b@haskell.org> #10933: REMOVED pragma -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: feature request | Status: new Priority: normal | 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 bgamari): * milestone: 8.6.1 => Comment: This probably ought to go through the [[https://github.com/ghc-proposals /ghc-proposals|GHC proposals process]]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:43:32 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:43:32 -0000 Subject: [GHC] #12437: 20% regression in max_bytes_used for T1969 In-Reply-To: <047.090b2624111211cac9a272929b897b02@haskell.org> References: <047.090b2624111211cac9a272929b897b02@haskell.org> Message-ID: <062.61416a6da656311794f51a92fe1b27a0@haskell.org> #12437: 20% regression in max_bytes_used for T1969 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:44:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:44:28 -0000 Subject: [GHC] #3094: Some GHC.* module should export word size and heap object header size In-Reply-To: <045.907bdf02870cf9d7a457cb5fba873bca@haskell.org> References: <045.907bdf02870cf9d7a457cb5fba873bca@haskell.org> Message-ID: <060.523383e14deb035ac8e65ada0e3ce0bb@haskell.org> #3094: Some GHC.* module should export word size and heap object header size -------------------------------------+------------------------------------- Reporter: duncan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 6.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:45:21 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:45:21 -0000 Subject: [GHC] #12218: Implement -fexternal-interpreter via static linking In-Reply-To: <047.d2ead1284e240e7bcc878975afeb5ae1@haskell.org> References: <047.d2ead1284e240e7bcc878975afeb5ae1@haskell.org> Message-ID: <062.a99fac6ec47918f504898f2ad495a015@haskell.org> #12218: Implement -fexternal-interpreter via static linking -------------------------------------+------------------------------------- Reporter: simonmar | Owner: (none) 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 bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:45:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:45:46 -0000 Subject: [GHC] #12498: Support unconventionally named import libraries In-Reply-To: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> References: <044.5e703c77c226248ade6b1c9ac24961ab@haskell.org> Message-ID: <059.c559ff72fbad4283ad3454a3fd938880@haskell.org> #12498: Support unconventionally named import libraries -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: feature request | 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: #11072 | Differential Rev(s): Phab:D3513 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:45:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:45:57 -0000 Subject: [GHC] #12517: Simplify runghc command line options In-Reply-To: <047.25090793b7ae3d8bda213d279284c8da@haskell.org> References: <047.25090793b7ae3d8bda213d279284c8da@haskell.org> Message-ID: <062.82e55628eece94fce9fb38b21267f255@haskell.org> #12517: Simplify runghc command line options -------------------------------------+------------------------------------- Reporter: harendra | Owner: harendra Type: bug | Status: new Priority: normal | Milestone: Component: None | Version: 8.0.1 Resolution: | Keywords: runghc Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2940 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:46:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:46:19 -0000 Subject: [GHC] #12669: Add some weird Kmettian tests to the test suite In-Reply-To: <045.51265cdb375454bf32c5460f73599b17@haskell.org> References: <045.51265cdb375454bf32c5460f73599b17@haskell.org> Message-ID: <060.572a0727367d132df228bdb224ab6e42@haskell.org> #12669: Add some weird Kmettian tests to the test suite -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Test Suite | 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): * type: feature request => task * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:47:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:47:47 -0000 Subject: [GHC] #14943: Make (=>) polykinded (:: k -> k -> Constraint) Message-ID: <051.6fe39954d13f1f127aabba85c357373f@haskell.org> #14943: Make (=>) polykinded (:: k -> k -> Constraint) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Would it be a good idea to treat `=>` in `-XQuantifiedConstraints` as {{{#!hs type family (=>) :: k -> k -> Constraint where (=>) = Implies0 (=>) = Implies1 (=>) = Implies2 .. }}} {{{#!hs class (a => b) => Implies a b instance (a => b) => Implies a b class (forall x. f x => g x) => Implies1 f g instance (forall x. f x => g x) => Implies1 f g class (forall x y. f x y => g x y) => Implies2 f g instance (forall x y. f x y => g x y) => Implies2 f g .. }}} or will this get too confusing? This means type signatures like the ones from #14942 {{{#!hs oneTwo :: (forall x. semi x => Semigroup x) => Free semi Int nil :: (forall x. mon x => Monoid x) => Free mon Int together :: (forall x. mon x => Monoid x) => [Free mon Int] }}} could equivalently be written {{{#!hs oneTwo :: (semi => Semigroup) => Free semi Int nil :: (mon => Monoid) => Free mon Int together :: (mon => Monoid) => [Free mon Int] }}} I'm not sold on this idea myself. It's quite possible this would screw with the parser. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:48:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:48:01 -0000 Subject: [GHC] #12964: Runtime regression to RTS change In-Reply-To: <046.bcf824695cea07d48dc888c9a5c7fa61@haskell.org> References: <046.bcf824695cea07d48dc888c9a5c7fa61@haskell.org> Message-ID: <061.f7dd7b867ffb69adc6fd172e1421ed2e@haskell.org> #12964: Runtime regression to RTS change -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 8.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 bgamari): * status: new => closed * resolution: => invalid * milestone: 8.6.1 => Comment: This doesn't really seem to be a bug but rather an unfortunate property of a particular test. Closing since there is nothing clearly actionable here, although do feel free to reopen if you disagree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:48:56 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:48:56 -0000 Subject: [GHC] #12714: T9405 fails on Windows In-Reply-To: <046.8d33f0cca216ec45205082af03358f60@haskell.org> References: <046.8d33f0cca216ec45205082af03358f60@haskell.org> Message-ID: <061.d6676d0735c602a189aae1fd97e7b42e@haskell.org> #12714: T9405 fails on Windows -----------------------------------+-------------------------------------- Reporter: bgamari | Owner: (none) 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: | -----------------------------------+-------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Phyx, any idea what might be going on here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:50:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:50:03 -0000 Subject: [GHC] #13104: runRW# ruins join points In-Reply-To: <049.de62ded7b05ef8af28dbfe5dd7c43ff2@haskell.org> References: <049.de62ded7b05ef8af28dbfe5dd7c43ff2@haskell.org> Message-ID: <064.50337713cd06dc714cd47b51d90163d7@haskell.org> #13104: runRW# ruins join points -------------------------------------+------------------------------------- Reporter: lukemaurer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:50:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:50:22 -0000 Subject: [GHC] #11238: Redesign the dynamic linking on ELF systems In-Reply-To: <047.b64204058d590ba33e44f36f6140b2e6@haskell.org> References: <047.b64204058d590ba33e44f36f6140b2e6@haskell.org> Message-ID: <062.ed4b78ab40c7491c8f212cccb4820dcf@haskell.org> #11238: Redesign the dynamic linking on ELF systems -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: task | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 (Linker) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: 9237, 9498, | 11042, 11499, 12684 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is currently actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:52:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:52:22 -0000 Subject: [GHC] #11472: Remove CallStack CPP guards in GHC 8.4 In-Reply-To: <046.fe08b3b66c71764affdf5dd1237373e0@haskell.org> References: <046.fe08b3b66c71764affdf5dd1237373e0@haskell.org> Message-ID: <061.603d45dac6eb6b99ba064cf09aba90df@haskell.org> #11472: Remove CallStack CPP guards in GHC 8.4 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: 8.6.1 => 8.4.1 Comment: This was carried out in c13720c8c6047844f659ad4ce684946b80c99bee. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:53:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:53:00 -0000 Subject: [GHC] #10542: Incorrect Unicode input on Windows Console In-Reply-To: <045.3387c3cc5f6c1e19d58646a0ead1675d@haskell.org> References: <045.3387c3cc5f6c1e19d58646a0ead1675d@haskell.org> Message-ID: <060.3f47c1df0d638254b0c9d3b88ee924f1@haskell.org> #10542: Incorrect Unicode input on Windows Console -------------------------------------+------------------------------------- Reporter: ptroev | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: windows stdin | utf-8 cmd chcp 65001 getLine Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #11394, #4471 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Phyx says the new I/O manager may well be ready for 8.6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:55:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:55:05 -0000 Subject: [GHC] #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) In-Reply-To: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> References: <042.0e3de7917bdd684aac8357b129fd4898@haskell.org> Message-ID: <057.74c1c949b433c870b5cdc15d6638aaad@haskell.org> #14941: Switching direct type family application to EqPred (~) prevents inlining in code using vector (10x slowdown) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I copied the core of `selectVectorDestructive2` from the good and bad examples and diffed them. They looked basically the same apart from lots and lots of code like the following: In bad: {{{ 1# -> case $wlvl_rnHf @ VUM.MVector @ Int @ IO Data.Vector.Unboxed.Base.$fMVectorMVectorInt ((Data.Vector.Primitive.Mutable.MVector @ ghc- prim-0.5.2.0:GHC.Prim.RealWorld @ Int ww1_smP2 ww2_smP3 ww3_smP4) `cast` (Sym (Data.Vector.Unboxed.Base.N:R:MVectorsInt[0] _N) ; Sym (Data.Vector.Unboxed.Base.DR:MVectorsInt0[0] (Control.Monad.Primitive.D:R:PrimStateIO[0])) :: (Data.Vector.Primitive.Mutable.MVector ghc- prim-0.5.2.0:GHC.Prim.RealWorld Int :: *) ~R# (VUM.MVector (PrimState IO) Int :: *))) ww4_smP8 of wild_00 { } }}} In good: {{{ 1# -> case $wlvl_rnRh ww2_smWB ww3_smWC ww4_smWG of wild_00 { } }}} So it looks like on every call the `MVector` is being constructed rather than created one and shared? Anyone know immediately why this is such a problem? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:56:58 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:56:58 -0000 Subject: [GHC] #11126: Entered absent arg in a Repa program In-Reply-To: <049.08d17e678ab01e39cf7b040134e05fa3@haskell.org> References: <049.08d17e678ab01e39cf7b040134e05fa3@haskell.org> Message-ID: <064.0971799a5b7fe8fb076c070d14dd09be@haskell.org> #11126: Entered absent arg in a Repa program -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: Component: Compiler | Version: 7.10.2 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:D3221 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: bgamari => (none) * milestone: 8.6.1 => Comment: I've not looked at this in some time. Unassigning. The patch is still there and still breaks one-shot analysis. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:57:58 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:57:58 -0000 Subject: [GHC] #14411: `make fasttest` exits successfully even in presence of failures In-Reply-To: <047.a89ff3751f3bb0ca676c5fa509a7a698@haskell.org> References: <047.a89ff3751f3bb0ca676c5fa509a7a698@haskell.org> Message-ID: <062.39a9044a9f6f67a2beadbcdb48d50622@haskell.org> #14411: `make fasttest` exits successfully even in presence of failures -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.2.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:D4268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Fixed in 030243953d522f2f8185ae417869a94d5f86210f. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:58:24 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:58:24 -0000 Subject: [GHC] #10915: Statistical profiling support in the RTS In-Reply-To: <046.7220ccda33e87c4faaaf43cf13abd1b6@haskell.org> References: <046.7220ccda33e87c4faaaf43cf13abd1b6@haskell.org> Message-ID: <061.9025494c66fad1bd9bacfbe1912157ca@haskell.org> #10915: Statistical profiling support in the RTS -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: feature request | Status: patch Priority: normal | 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): Phab:D1215, Wiki Page: | Phab:D1214 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: This won't happen for 8.6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:59:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:59:00 -0000 Subject: [GHC] #14324: Consider deprecating STM invariant mechanism In-Reply-To: <046.7d9457872c0d5f0243f1b38705442b7b@haskell.org> References: <046.7d9457872c0d5f0243f1b38705442b7b@haskell.org> Message-ID: <061.176cf45cdc841a0f09081c937d10414e@haskell.org> #14324: Consider deprecating STM invariant mechanism -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.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:D4372 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged in e5d0101121cf4ce4dffe59025360096ee57c5372. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 22:59:31 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 22:59:31 -0000 Subject: [GHC] #14492: Tiered memory allocation restricts available memory In-Reply-To: <044.e21e37476590d999c81ca942af908658@haskell.org> References: <044.e21e37476590d999c81ca942af908658@haskell.org> Message-ID: <059.ee6e14b7f531db7f840beaad5dcbd39e@haskell.org> #14492: Tiered memory allocation restricts available memory -------------------------------------+------------------------------------- Reporter: unode | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: memory ulimit Operating System: Linux | Architecture: x86_64 Type of failure: Poor/confusing | (amd64) error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4215 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari Comment: I'll try to take care of this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 23:00:10 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 23:00:10 -0000 Subject: [GHC] #11715: Constraint vs * In-Reply-To: <046.907e6fb89981c8664a4e7309489f51fd@haskell.org> References: <046.907e6fb89981c8664a4e7309489f51fd@haskell.org> Message-ID: <061.90e0b1afa9e6da98ace041b4f0cea96a@haskell.org> #11715: Constraint vs * -------------------------------------+------------------------------------- Reporter: bgamari | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Keywords: Typeable, Resolution: | LevityPolymorphism, Roles Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3316 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: highest => high * milestone: 8.6.1 => Comment: Unmilestoning as no one is actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 23:03:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 23:03:35 -0000 Subject: [GHC] #14938: Pattern matching on GADT does not refine type family parameters In-Reply-To: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> References: <047.978f70ab5d3550499b5776f22c5bd354@haskell.org> Message-ID: <062.5ff6b1c40b110830108396c96136e71d@haskell.org> #14938: Pattern matching on GADT does not refine type family parameters -------------------------------------+------------------------------------- Reporter: kcsongor | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: GADTs, Resolution: | TypeFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): No, I can't point you to more discussion -- this was a decision of convenience during implementing. At the time, I hadn't fully noticed all the ramifications of it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 23:07:29 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 23:07:29 -0000 Subject: [GHC] #14309: Expand comment in hPutStrLn In-Reply-To: <045.d57739ec737fed854d627d9f1df20af7@haskell.org> References: <045.d57739ec737fed854d627d9f1df20af7@haskell.org> Message-ID: <060.68001d9b0dd7c83df58bbd883a24f356@haskell.org> #14309: Expand comment in hPutStrLn -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.2.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 bgamari): * milestone: 8.6.1 => Comment: Removing milestone as no one is actively working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 19 23:21:40 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 19 Mar 2018 23:21:40 -0000 Subject: [GHC] #14935: Vary default RTS settings so that performance does not degrade with increasing number of capabilities In-Reply-To: <047.c1e3c537cd577233605e2a8fc8124d44@haskell.org> References: <047.c1e3c537cd577233605e2a8fc8124d44@haskell.org> Message-ID: <062.5f400caa9fc446e5d75062297d3eb95d@haskell.org> #14935: Vary default RTS settings so that performance does not degrade with increasing number of capabilities -------------------------------------+------------------------------------- Reporter: YitzGale | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I can't quite tell whether this is a general request for the runtime (which would apply to all GHC-compiled executables by default) or GHC in particular. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:06:45 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:06:45 -0000 Subject: [GHC] #14944: Compile speed regression Message-ID: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: -------------------------------------+------------------------------------- Compile time went from 5 seconds in 7.6.1 to 12 seconds in 8.2.2 and then down to 10 seconds in 8.4.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:07:04 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:07:04 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.f22824d9243c6e5223059ff2eb70edae@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 br1): * Attachment "Main.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:07:18 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:07:18 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.f8a2e02259e7c47cf0b5bdd47ca61936@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 br1): * Attachment "Paper.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:07:53 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:07:53 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.ab242ec1696d663b741f662cbfaf5e34@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Description changed by br1: Old description: > Compile time went from 5 seconds in 7.6.1 to 12 seconds in 8.2.2 and then > down to 10 seconds in 8.4.1. New description: Compile time with -O went from 5 seconds in 7.6.1 to 12 seconds in 8.2.2 and then down to 10 seconds in 8.4.1. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:29:14 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:29:14 -0000 Subject: [GHC] #13378: LLVM backend doesn't support MacOS dead code stripping In-Reply-To: <047.6398a672bf9fd46b39701222a0eefc74@haskell.org> References: <047.6398a672bf9fd46b39701222a0eefc74@haskell.org> Message-ID: <062.77d49e53b4de12159e49c5e04b3450a6@haskell.org> #13378: LLVM backend doesn't support MacOS dead code stripping -------------------------------------+------------------------------------- Reporter: angerman | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: Resolution: invalid | 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 angerman): * status: new => closed * resolution: => invalid Comment: This actually made it upstream... https://github.com/llvm- mirror/llvm/commit/c7a57cdda643e397720daa35ea3b1c4b7ce42371 However, the use of aliases in the llvm backend prevents llvm to properly insert the altEntry at the right place For macOS, the NCG does allow dead-stripping. For LLVM the llvm-ng backend allows deadstripping of mach-o files (macOS, iOS, ...) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:31:00 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:31:00 -0000 Subject: [GHC] #14882: memchr# In-Reply-To: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> References: <049.d311c4dc46a1ba64360104935c7463ac@haskell.org> Message-ID: <064.8ecf8c4eb4643d11d6ed92ffe10009ab@haskell.org> #14882: memchr# -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4472 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Is there a benefit to baking it in as a primop rather than making it an FFI function in `base` or even `ghc-prim`? If not, I don't see the point. Personally, I suspect that there is not ''yet'' a benefit, but that there might be one in the future. In particular, if we ever have sufficient support for vector registers, we might get a small speed boost by implementing `memchr#` ourselves and inlining it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 02:40:34 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 02:40:34 -0000 Subject: [GHC] #14926: failed to build cross-compiler In-Reply-To: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> References: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> Message-ID: <062.86c121e4ae615d6bedcb427b1b1d0c62@haskell.org> #14926: failed to build cross-compiler -------------------------------------+------------------------------------- Reporter: rueshyna | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Comment (by angerman): I've not see this error before. It seems strange that we invoke ghc without and source files. Does that same happen when `configuring` without `--enable-unregistered`? The only difference to what I build is that I built for 64bit windows. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 03:06:31 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 03:06:31 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.131465aaf1aead524168ded7ea1e2e9a@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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): Sure we do. I have not explored ''how'' we do, but sure we do. This program compiles and runs: {{{#!hs data List (b :: TYPE (TupleRep [IntRep, DoubleRep, LiftedRep])) = Nil | Cons b (List b) mapUbx :: forall (a :: Type) (b :: TYPE (TupleRep [IntRep, DoubleRep, LiftedRep])). (a -> b) -> [a] -> List b mapUbx _ [] = Nil mapUbx f (x : xs) = Cons (f x) (mapUbx f xs) blargh :: forall a. Int# -> Double# -> a -> (# Int#, Double#, a #) blargh x y = (#,,#) x y strange = mapUbx (blargh 3# 2.78##) [True, False] printList :: Show b => List (# Int#, Double#, b #) -> IO () printList Nil = return () printList (Cons (# n, d, b #) xs) = do print (I# n) print (D# d) print b printList xs main = do printList strange }}} We probably just eta-expand `blargh`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 03:29:09 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 03:29:09 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.0cf842cb43df14cda854618dcf7b9d83@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Comment (by dfeuer): This `NOINLINE` strikes me as something fragile that doesn't really get at the point. I don't have this properly paged in right now, but see Exceptions/PreciseExceptions for some of my previous thoughts on the matter. I don't understand the sense in pretending it's "pure". I ''think'' we want to consider it side-effecting. I imagine it's already marked as lazy, but just in case it's not, it should be. There are situations where it's okay to remove `seq#`, but I'm less sure how to be sure that it ''remains'' safe after further transformations. The most obvious situation: {{{#!hs case seq# a s of (# s', a' #) -> seq# a' s' -- ==> seq# a s }}} A similar situation: {{{#!hs case x of !x' -> seq# x' s }}} Surely we don't want to force `x` twice, but we don't want to drop the `seq#`; we want to transform this to `seq# x s`. Suppose we have {{{#!hs case x of !x' -> case f x of !y -> case seq# x' s of (# s', _ #) -> (# s', y #) }}} That's a bit trickier. It's certainly safe to transform it to {{{#!hs case seq# x s of (# s', x' #) -> case f x' of !y -> (# s', y #) }}} That might be too conservative, but I don't know if it will really hurt. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 05:43:06 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 05:43:06 -0000 Subject: [GHC] #14876: Reading source files in text mode so that we get CRLF conversion under Windows? In-Reply-To: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> References: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> Message-ID: <065.8f1acf25ec9c3e22ffbc55194cdbc422@haskell.org> #14876: Reading source files in text mode so that we get CRLF conversion under Windows? -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by SimonHengel): Should we consider to fix this for QuasiQuote only at first? I think passing CRLF to quasi quoters hardly makes sense and can be the source of windows specific bugs. But of course it's still a breaking change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 05:59:29 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 05:59:29 -0000 Subject: [GHC] #14876: Reading source files in text mode so that we get CRLF conversion under Windows? In-Reply-To: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> References: <050.ffa46e7f4b0bcbbb7b48f945e594901c@haskell.org> Message-ID: <065.96b3138978b3a35a40bc035590eddf53@haskell.org> #14876: Reading source files in text mode so that we get CRLF conversion under Windows? -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by SimonHengel): I haven't tried, but just from looking at the code for {{{quoteFile}}} I think that the current behavior is also inconsistent. {{{quoteFile}}} uses {{{readFile}}} and hence when we use a QuasiQuoter with {{{quoteFile}}} we will get newline conversions, while when we use the QuasiQuoter without {{{quoteFile}}} we do not get newline conversions. https://hackage.haskell.org/package/template- haskell-2.13.0.0/docs/src/Language.Haskell.TH.Quote.html#quoteFile -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 07:43:18 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 07:43:18 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.1e7e16ffa2bee5330a1d0dd81c2077ee@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Comment (by osa1): In comment:24 I say that the `case seq# ... of` is eliminated because the result is not used and `seq#` is effect-free. The reason why the result is not used is because `assertFailure` is a pure function with type `String -> a`. Just wanted to post this update because I was confused about this for a long time (I thought `assertFailure` was an IO function). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 08:08:57 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 08:08:57 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.716a0f135713eeeaf718f6eebf076ebf@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): This works with GHC HEAD. > However, 8.4.1 shipped with a workaround GHC 8.4.1 is shipped without some of the commits that were supposed to be included, e.g. #14868 is also broken in 8.4.1 even though the fix was merged to the branch. This may be another such case where the commit was merged to the branch but not included in the release somehow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 09:17:42 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 09:17:42 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c Message-ID: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Building GHC (amd64) | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm receiving the following error message when compiling ghcHEAD: {{{ "inplace/bin/ghc-stage1" -optc-fno-stack-protector -optc-Wall -optc-Wall -optc-Wextra -optc-Wstrict-prototypes -optc-Wmissing-prototypes -optc- Wmissing-declarations -optc-Winline -optc-Waggregate-return -optc- Wpointer-arith -optc-Wmissing-noreturn -optc-Wnested-externs -optc- Wredundant-decls -optc-Wundef -optc-Iincludes -optc-Iincludes/dist -optc- Iincludes/dist-derivedconstants/header -optc-Iincludes/dist- ghcconstants/header -optc-Irts -optc-Irts/dist/build -optc-DCOMPILING_RTS -optc-fno-strict-aliasing -optc-fno-common -optc-Irts/dist/build/./autogen -optc-Werror=unused-but-set-variable -optc-Wno-error=inline -optc-O2 -optc-fomit-frame-pointer -optc-g -optc-DRtsWay=\"rts_p\" -optc-ffunction- sections -optc-fdata-sections -static -prof -eventlog -H32m -O -Wall -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-unit-id rts -dcmm-lint -i -irts -irts/dist/build -Irts/dist/build -irts/dist/build/./autogen -Irts/dist/build/./autogen -O2 -Wcpp-undef -Wnoncanonical-monad-instances -c rts/Stats.c -o rts/dist/build/Stats.p_o rts/Stats.c: In function 'report_summary': rts/Stats.c:741:39: error: error: 'RTSSummaryStats {aka const struct RTSSummaryStats_}' has no member named 'rc_cpu_ns'; did you mean 'rp_cpu_ns'? TimeToSecondsDbl(sum->rc_cpu_ns), ^ | 741 | TimeToSecondsDbl(sum->rc_cpu_ns), | ^ rts/Stats.c:29:39: error: note: in definition of macro 'TimeToSecondsDbl' #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) ^ | 29 | #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) | ^ rts/Stats.c:742:39: error: error: 'RTSSummaryStats {aka const struct RTSSummaryStats_}' has no member named 'rc_elapsed_ns'; did you mean 'rp_elapsed_ns'? TimeToSecondsDbl(sum->rc_elapsed_ns)); ^ | 742 | TimeToSecondsDbl(sum->rc_elapsed_ns)); | ^ rts/Stats.c:29:39: error: note: in definition of macro 'TimeToSecondsDbl' #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) ^ | 29 | #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) | ^ rts/Stats.c: In function 'report_machine_readable': rts/Stats.c:904:58: error: error: 'RTSSummaryStats {aka const struct RTSSummaryStats_}' has no member named 'hp_cpu_ns'; did you mean 'rp_cpu_ns'? MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); ^ | 904 | MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); | ^ rts/Stats.c:867:62: error: note: in definition of macro 'MR_STAT' statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) ^~~~~ | 867 | statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) | ^ rts/Stats.c:904:36: error: note: in expansion of macro 'TimeToSecondsDbl' MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); ^~~~~~~~~~~~~~~~ | 904 | MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); | ^ rts/Stats.c:905:59: error: error: 'RTSSummaryStats {aka const struct RTSSummaryStats_}' has no member named 'hp_elapsed_ns'; did you mean 'rp_elapsed_ns'? MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); ^ | 905 | MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); | ^ rts/Stats.c:867:62: error: note: in definition of macro 'MR_STAT' statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) ^~~~~ | 867 | statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) | ^ rts/Stats.c:905:37: error: note: in expansion of macro 'TimeToSecondsDbl' MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); ^~~~~~~~~~~~~~~~ | 905 | MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); | ^ `cc' failed in phase `C Compiler'. (Exit code: 1) make[1]: *** [rts/ghc.mk:295: rts/dist/build/Stats.p_o] Error 1 make[1]: *** Waiting for unfinished jobs.... make: *** [Makefile:127: all] Error 2 builder for '/nix/store/qvidsmhk6a1a1h96q85dx1dalgqgph4l- ghc-8.5.20180319.drv' failed with exit code 2 error: build of '/nix/store/qvidsmhk6a1a1h96q85dx1dalgqgph4l- ghc-8.5.20180319.drv' failed }}} I suspect it's related to the recent commit 2d4bda2e4ac68816baba0afab00da6f769ea75a7. Currently compiling the previous revision to confirm. Has anyone confirmed similar error in another environment? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 09:22:49 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 09:22:49 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.ad26009431bf977ddbd3c00d75794c32@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Also reported in the differential: https://phabricator.haskell.org/D4302 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 11:16:39 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 11:16:39 -0000 Subject: [GHC] #14926: failed to build cross-compiler In-Reply-To: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> References: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> Message-ID: <062.f808d26e3283853d2a8c4112a22e1bba@haskell.org> #14926: failed to build cross-compiler -------------------------------------+------------------------------------- Reporter: rueshyna | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Comment (by rueshyna): Nope, it doesn't work without `--enable-unregistered`. I also tried to build for 64bit windows, it turns out the same error here. Here is a command for building 64bit windows, the other commands/settings are the same for 32bit one: `CC=/usr/bin/x86_64-w64-mingw32-gcc ./configure --target=x86_64-w64-mingw32` Just to be sure, so you used this docker image `egweber/ghc-haskell-dev` and our build env are the same? I also found out that if I ran `make` second times, it shows different error messages: {{{ Configuring ghc-pkg-6.9... [312/1603] "/opt/ghc/8.2.1/bin/ghc" -hisuf hi -osuf o -hcsuf hc -static -O0 -H64m -Wall -package-db libraries/bootstrapping.conf -hide-all-packages -i -iutil s/ghc-pkg/. -iutils/ghc-pkg/dist/build -Iutils/ghc-pkg/dist/build -iutils /ghc-pkg/dist/build/ghc-pkg/autogen -Iutils/ghc-pkg/dist/build/ghc- pkg/autogen -optP-DWITH_TERMINFO -optP-include -optPutils/ghc-pkg/dist/build/ghc- pkg/autogen/cabal_macros.h -package-id base-4.10.0.0 -package-id directory-1.3 .0.2 -package-id process-1.6.1.0 -package-id containers-0.5.10.2 -package- id filepath-1.4.1.2 -package-id Cabal-2.2.0.0 -package-id binary-0.8.5.1 -pac kage-id ghc-boot-8.4.1 -package-id bytestring-0.10.8.2 -package-id terminfo-0.4.1.1-package-id unix-2.7.2.2 -XHaskell2010 -no-user-package- db -rtsopts -odir utils/ghc-pkg/dist/build -hidir utils/ghc-pkg/dist/build -stubdir utils/ghc-pkg/dist/build -c utils/ghc-pkg/./Main.hs -o utils /ghc-pkg /dist/build/Main.o utils/ghc-pkg/Main.hs:30:1: error: Could not find module ‘Version’ Use -v to see a list of the files searched for. | 30 | import Version ( version, targetOS, targetARCH ) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:31:1: error: Could not find module ‘GHC.PackageDb’ There are files missing in the ‘ghc-boot-8.4.1’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 31 | import qualified GHC.PackageDb as GhcPkg | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:32:1: error: Could not find module ‘GHC.PackageDb’ There are files missing in the ‘ghc-boot-8.4.1’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 32 | import GHC.PackageDb (BinaryStringRep(..)) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:33:1: error: Could not find module ‘Distribution.Simple.PackageIndex’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 33 | import qualified Distribution.Simple.PackageIndex as PackageIndex [272/1603] | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:35:1: error: Could not find module ‘Distribution.ModuleName’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 35 | import qualified Distribution.ModuleName as ModuleName | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:36:1: error: Could not find module ‘Distribution.ModuleName’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 36 | import Distribution.ModuleName (ModuleName) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:37:1: error: Could not find module ‘Distribution.InstalledPackageInfo’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 37 | import Distribution.InstalledPackageInfo as Cabal | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:38:1: error: Could not find module ‘Distribution.Compat.ReadP’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 38 | import Distribution.Compat.ReadP hiding (get) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:39:1: error: Could not find module ‘Distribution.ParseUtils’ [232/1603] There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 39 | import Distribution.ParseUtils | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:40:1: error: Could not find module ‘Distribution.Package’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 40 | import Distribution.Package hiding (installedUnitId) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:41:1: error: Could not find module ‘Distribution.Text’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 41 | import Distribution.Text | ^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:42:1: error: Could not find module ‘Distribution.Version’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 42 | import Distribution.Version | ^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:43:1: error: Could not find module ‘Distribution.Backpack’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | [192/1603] 43 | import Distribution.Backpack | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:44:1: error: Could not find module ‘Distribution.Types.UnqualComponentName’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 44 | import Distribution.Types.UnqualComponentName | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:45:1: error: Could not find module ‘Distribution.Types.MungedPackageName’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 45 | import Distribution.Types.MungedPackageName | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:46:1: error: Could not find module ‘Distribution.Types.MungedPackageId’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 46 | import Distribution.Types.MungedPackageId | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/Main.hs:47:1: error: Could not find module ‘Distribution.Simple.Utils’ There are files missing in the ‘Cabal-2.2.0.0’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 47 | import Distribution.Simple.Utils (fromUTF8BS, toUTF8BS, writeUTF8File, readUTF8File) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ [153/1603] utils/ghc-pkg/Main.hs:96:1: error: Could not find module ‘System.Console.Terminfo’ There are files missing in the ‘terminfo-0.4.1.1’ package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. | 96 | import System.Console.Terminfo as Terminfo | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ utils/ghc-pkg/ghc.mk:70: recipe for target 'utils/ghc- pkg/dist/build/Main.o' failed make[1]: *** [utils/ghc-pkg/dist/build/Main.o] Error 1 Makefile:122: recipe for target 'all' failed make: *** [all] Error 2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 11:22:26 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 11:22:26 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.18097e2c6d36c8e49a4616edafe414e8@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by terrorjack): The build succeeded with the previous revision. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 11:24:47 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 11:24:47 -0000 Subject: [GHC] #14946: GHC Calls CPP for HS with -undef Message-ID: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> #14946: GHC Calls CPP for HS with -undef -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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: -------------------------------------+------------------------------------- GHC Is calling the C preprocessor when processing HS files with `-undef` which unsets and compiler pre-defines. Essentially it means you cannot use any normal compiler defines to check for platform or intrinsics support. Is this really the intended behavior? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 11:25:17 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 11:25:17 -0000 Subject: [GHC] #14946: GHC Calls CPP for HS with -undef In-Reply-To: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> References: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> Message-ID: <059.b22966810fff5e3f82b6139cdebb59c2@haskell.org> #14946: GHC Calls CPP for HS with -undef -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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: | -------------------------------------+------------------------------------- Description changed by Phyx-: Old description: > GHC Is calling the C preprocessor when processing HS files with `-undef` > which unsets and compiler pre-defines. > > Essentially it means you cannot use any normal compiler defines to check > for platform or intrinsics support. > > Is this really the intended behavior? New description: GHC Is calling the C preprocessor[1] when processing HS files with `-undef` which unsets and compiler pre-defines. Essentially it means you cannot use any normal compiler defines to check for platform or intrinsics support. Is this really the intended behavior? [1] https://github.com/ghc/ghc/blob/60aa53d97da1bbfbb88e9f2791c3f686ba34e764/aclocal.m4#L2241 -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 11:35:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 11:35:12 -0000 Subject: [GHC] #14609: Per-instance UndecidableInstances In-Reply-To: <048.249a939a6e76cafabb0ae79267f4d3cf@haskell.org> References: <048.249a939a6e76cafabb0ae79267f4d3cf@haskell.org> Message-ID: <063.1d6cdc8f2e668ec62f7728a3b35582f0@haskell.org> #14609: Per-instance UndecidableInstances -------------------------------------+------------------------------------- Reporter: ryanreich | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.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 AntC): Replying to [comment:1 AntC]: > Replying to [ticket:14609 ryanreich]: > > Can (or why can't) this also be done for UndecidableInstances? > > It can and should; and there's almost certainly a proposal somewhere; or a comment on a ticket on (say) overlaps or FunDeps. Aha! ticket:10675#comment:17 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 11:37:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 11:37:33 -0000 Subject: [GHC] #13650: Implement KPush in types In-Reply-To: <047.e26721ad30e2e3d90c01c9e924788439@haskell.org> References: <047.e26721ad30e2e3d90c01c9e924788439@haskell.org> Message-ID: <062.0bdaaeb043d61982ccaa705f48ffa5a5@haskell.org> #13650: Implement KPush in types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: task | Status: new Priority: high | Milestone: Component: Compiler | Version: 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 simonpj): * keywords: => TypeInType -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 12:00:16 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 12:00:16 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() Message-ID: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: Runtime crash (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Steps to reproduce on Windows 10 x64: {{{ stack --version Version 1.6.5, Git revision 24ab0d6ff07f28276e082c3ce74dfdeb1a2ca9e9 (5514 commits) x86_64 hpack-0.20.0 git clone https://github.com/varosi/cgraytrace.git cd cgraytrace git checkout 8c9499e4f3b1ba18b71e499667e865bb6db61856 stack build --profile stack exec --rts-options="-hr" -- cgraytrace-exe Rendering to sample.png... cgraytrace-exe.EXE: internal error: Invalid object *c in push() (GHC version 8.4.1 for x86_64_unknown_mingw32) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug This application has requested the Runtime to terminate it in an unusual way. Please contact the application's support team for more information. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 12:00:31 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 12:00:31 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.58aad9388607914a8c58dd6d44ba5964@haskell.org> #14947: internal error: Invalid object *c in push() ----------------------------------+-------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Changes (by varosi): * os: Unknown/Multiple => Windows -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 12:03:00 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 12:03:00 -0000 Subject: [GHC] #14946: GHC Calls CPP for HS with -undef In-Reply-To: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> References: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> Message-ID: <059.a46638700a8c7df31876ffd4b9ad8df9@haskell.org> #14946: GHC Calls CPP for HS with -undef -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 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: | -------------------------------------+------------------------------------- Description changed by Phyx-: Old description: > GHC Is calling the C preprocessor[1] when processing HS files with > `-undef` which unsets and compiler pre-defines. > > Essentially it means you cannot use any normal compiler defines to check > for platform or intrinsics support. > > Is this really the intended behavior? > > [1] > https://github.com/ghc/ghc/blob/60aa53d97da1bbfbb88e9f2791c3f686ba34e764/aclocal.m4#L2241 New description: GHC Is calling the C preprocessor[1] when processing HS files with `-undef` which unsets the C compiler pre-defines. Essentially it means you cannot use any normal compiler defines to check for platform or intrinsics support. Is this really the intended behavior? I get the fact that we're processing a Haskell source file, but why restrict the pre-processor to only GHC defines. You lose information like if unaligned accesses are supported or not etc. [1] https://github.com/ghc/ghc/blob/60aa53d97da1bbfbb88e9f2791c3f686ba34e764/aclocal.m4#L2241 -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 12:34:07 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 12:34:07 -0000 Subject: [GHC] #14926: failed to build cross-compiler In-Reply-To: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> References: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> Message-ID: <062.73e48ca4373ad9ff23ae76c264625fcf@haskell.org> #14926: failed to build cross-compiler -------------------------------------+------------------------------------- Reporter: rueshyna | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Comment (by angerman): That sounds very suspect. I did not build with the docker image, I might get a chance to do so tomorrow. I usually built on macOS. Could you post the final output of the `./configure` call in the meantime? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 12:48:46 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 12:48:46 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.1fa70589dcda6578c2e3a5e7e662b7e5@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I've been looking into this, here's what I found out so far: - Because we start evaluating `foo` before hitting the breakpoint, by the time the we return to the GHCi prompt `foo` points to a blackhole. - Once we stop at the breakpoint we do `:print foo`, `pprintClosureCommand` calls `bindSuspensions` with the id `foo`. - `bindSuspensions` invents a new name `_t1` and binds it to the thunk that is `foo`, via `RtClosureInspect.cvObtainTerm`. - `cvObtainTerm` looks at the heap object pointed to by `foo`, which is a blackhole, and follows the indirectee pointer. It turns out the indirectee is a TSO object. At this point `_t1` becomes bound to a TSO object, and evaluating it (e.g. with `print _t1`) causes this crash because TSO objects can't be entered. I tried modifying `cvObtainTerm` so that it doesn't follow the indirectee pointer when it sees a blackhole. That way we bind `_t1` to the blackhole object instead of the TSO object pointed by the indirectee field, but that caused a deadlock in the scheduler. I don't understand why yet. simonmar, could you advise? Does the story make sense so far? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 14:01:22 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 14:01:22 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.8f60d176d1e215f0d89979dd0d8ec1a5@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): So here is an idea that might help here, and that I want to run past people who know !SpecConstr well (is that anyone else but SPJ at this point?). Status quo: `l` gets specialized, because of the two call patterns `s' t0` and `(s-1) (x,y)`, the second one is interesting *and* its second argument gets scrutinized (the `scu_occs` field reports `ScrutOcc` for `t`). But `foo` does not get specialized: It does have an interesting call pattern, but `scu_occs` reports `UnkOcc`, because `foo`’s parameters are just passed to `t`. But: When we decide to !SpecConstr `l`, we know that one of the calls to to `l` is of the shape `s' t0`. This is a boring call, and we do not create a specialization for it. But we create a specialization for `l` using the the other call pattern. This means we know that it would be beneficial if `t0` were a constructor. So can we, at this point, decide to include `t0 ↦ ScrutOcc` in `scu_occs`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 15:26:09 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 15:26:09 -0000 Subject: [GHC] #14508: Bring up Appveyor for Windows CI In-Reply-To: <046.b1e7fd0356de10b29814d8db318f756c@haskell.org> References: <046.b1e7fd0356de10b29814d8db318f756c@haskell.org> Message-ID: <061.67641bcc4dc1868267e6aeac54415aa6@haskell.org> #14508: Bring up Appveyor for Windows CI -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: task | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.1 Integration | 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 mrkkrp): Status update: I succeeded in running full builds with tests on AppVeyor using a private build cloud. Here is the PR I opened yesterday: https://github.com/ghc/ghc/pull/112 I've got admin access to GHC AppVeyor now, but it needs to have premium plan and "private build cloud" feature enabled. For this we should disable premium plan for our (Tweag) fork and enable it for GHC AppVeyor account. This needs actions from Mathieu who is on vacation right now, so there may be a little delay with it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 15:37:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 15:37:33 -0000 Subject: [GHC] #14948: A program which benefits from a late specialisation pass Message-ID: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> #14948: A program which benefits from a late specialisation pass -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In this repo there is a small program which performs much better with a late specialisation pass. There is a plugin which implements this pass. Instructions about how to build the repo are in the README. https://github.com/mpickering/legendary-train Without plugin {{{ time benchmarks () real 0m0.112s }}} With plugin (comparable to hand-written code) {{{ time benchmarks () real 0m0.049s }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 15:37:59 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 15:37:59 -0000 Subject: [GHC] #14949: Perform builds on non-Debian-based systems on Circle CI Message-ID: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> #14949: Perform builds on non-Debian-based systems on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I could not find already existing ticket and so I'm creating this one. Ben mentioned (in his latest status update on GHC devops mailing list) that we need to do building on non-Debian-based systems on CI. To quote: > e. Support for building on non-Debian-based systems (e.g. Fedora), which is necessary if we want to produce our binary distributions via CI. So this ticket is to track progress on that. I'm planning to start working on this tomorrow perhaps. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 15:38:21 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 15:38:21 -0000 Subject: [GHC] #14949: Perform builds on non-Debian-based systems on Circle CI In-Reply-To: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> References: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> Message-ID: <060.84722ace6e526458149c538bae7e8356@haskell.org> #14949: Perform builds on non-Debian-based systems on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.2 Integration | 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 mrkkrp): * owner: (none) => bgamari * component: Compiler => Continuous Integration -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 15:38:45 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 15:38:45 -0000 Subject: [GHC] #14949: Perform builds on non-Debian-based systems on Circle CI In-Reply-To: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> References: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> Message-ID: <060.72c4374a245421eb99b01ea4bab2a546@haskell.org> #14949: Perform builds on non-Debian-based systems on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: mrkkrp Type: bug | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.2 Integration | 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 mrkkrp): * owner: bgamari => mrkkrp -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 15:51:49 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 15:51:49 -0000 Subject: [GHC] #14950: GHC 8.2.2: GHCi duplicates breakpoint range prompt Message-ID: <048.640f97ab7b833fac48d6aee56fed1321@haskell.org> #14950: GHC 8.2.2: GHCi duplicates breakpoint range prompt -------------------------------------+------------------------------------- Reporter: lierdakil | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I think breakpoint range is being printed twice, once as part of prompt, and the second time by itself. To reproduce, create `test.hs` file like this: {{{#!hs module Test where test :: IO () test = putStrLn "Hello, World!" }}} Then run the following GHCi session: {{{ $ ghci test.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Test ( test.hs, interpreted ) Ok, one module loaded. *Test> :break test Breakpoint 0 activated at test.hs:4:8-31 *Test> :trace test Stopped in Test.test, test.hs:4:8-31 _result :: IO () = _ [test.hs:4:8-31] [test.hs:4:8-31] *Test> :set prompt "" [test.hs:4:8-31] }}} Notice `[test.hs:4:8-31]` is printed twice, and is even printed when prompt is set to `""`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 16:08:55 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 16:08:55 -0000 Subject: [GHC] #14950: GHC 8.2.2: GHCi duplicates breakpoint range prompt In-Reply-To: <048.640f97ab7b833fac48d6aee56fed1321@haskell.org> References: <048.640f97ab7b833fac48d6aee56fed1321@haskell.org> Message-ID: <063.7bf9c8c9021597d5ad8fee7bbe0cebd7@haskell.org> #14950: GHC 8.2.2: GHCi duplicates breakpoint range prompt -------------------------------------+------------------------------------- Reporter: lierdakil | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.2.2 Resolution: | Keywords: debugger 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 RyanGlScott): * keywords: => debugger -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 16:34:45 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 16:34:45 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.99f1c9b25c6b5bd282f3b64b3fdf7633@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * os: Windows => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple Comment: I can also reproduce this on Linux. One thing that would help enormously in debugging this is producing a more minimal example that has minimal dependencies. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 16:34:51 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 16:34:51 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.cb19c11bdfb07ead1be4f7ad14ecc2c9@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 16:36:21 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 16:36:21 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.c3ca583a870c50231a5a684791b1af48@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Comment (by simonpj): > One way to fix this if we want to keep seq# as effect-free is avoiding inlining evaluate with {-# NOINLINE evaluate #-}. I'm very unhappy with this. It just sweeps the problem under the rug. What if the ''user'' wrote {{{ ..(case (seq# (throwIfNegative (I# -1#)) s) of )... }}} We don't want to discard the case. Moreover we shouldn't. The "plain-seq" transformation in `Simplify.hs` looks like {{{ | is_plain_seq , exprOkForSideEffects scrut = ... }}} Well, should `exprOkForSideEffects` return False (as it does) for `seq# (throwIfNegative (I# -1#)) s`? The comments in `CoreUtils` say {{{ -- Precisely, exprOkForSpeculation returns @True@ iff: -- a) The expression guarantees to terminate, -- b) soon, -- c) without causing a write side effect (e.g. writing a mutable variable) -- d) without throwing a Haskell exception -- e) without risking an unchecked runtime exception (array out of bounds, -- divide by zero) -- -- For @exprOkForSideEffects@ the list is the same, but omitting (e). }}} So clearly `exprOkForSideEffects` should return False! That's the real bug! Why does it return True? Because in `arg_ok` in `CoreUtils.app_ok` we see {{{ arg_ok (Anon ty) arg -- A term argument | isUnliftedType ty = expr_ok primop_ok arg | otherwise = True -- See Note [Primops with lifted arguments] }}} Uh oh! It never even looks at the argument `throwIfNegative minus_one`! I think that `seq#` is exception to the reasoning in `Note [Primops with lifted arguments]`, which says that a primop doesn't evaluate a lifted argument. In effect `seq#` does. So in the `PrimOpId` case of `app_ok` I think we want to add {{{ | SeqOp <- op -> all (expr_ok primop_ok) args }}} And sure enough that fixes it. I'll make a patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 16:43:16 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 16:43:16 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.85601e0c4635725644a6ebb0d19005b0@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Comment (by tdammers): Just to be sure; will this also solve #13930? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:00:47 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:00:47 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.879f03e39c4e52ce5d1058560719853c@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Changes (by simonmar): * cc: simonmar (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:01:41 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:01:41 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.fb34903da0e0e8b2575f7ea68d1c6d4c@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982, #5129 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Check if spj's patch on #5129 does indeed fix this one too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:11:37 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:11:37 -0000 Subject: [GHC] #8281: The impossible happened: primRepToFFIType In-Reply-To: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> References: <044.47e20917996e473150de04c1ce1afc0b@haskell.org> Message-ID: <059.8eefc347025661877f3fdd0e2bda6af2@haskell.org> #8281: The impossible happened: primRepToFFIType -------------------------------------+------------------------------------- Reporter: tibbe | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3619 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The plan: * Work out if and how the issue can now be reproduced * Document `UnliftedFFITypes` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:11:57 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:11:57 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.1f82654721355973c5f3aecd520fb473@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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): * owner: (none) => dfeuer Comment: David will characterise this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:13:20 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:13:20 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.e4c4e62ef2274326c7722752e77eaeef@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Something about an accidental coincidence of uniques, and the rule-matcher not cloning the forall'd binders of the rule properly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:13:46 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:13:46 -0000 Subject: [GHC] #11126: Entered absent arg in a Repa program In-Reply-To: <049.08d17e678ab01e39cf7b040134e05fa3@haskell.org> References: <049.08d17e678ab01e39cf7b040134e05fa3@haskell.org> Message-ID: <064.5ed132fca16b3dbc2c353aa34da81955@haskell.org> #11126: Entered absent arg in a Repa program -------------------------------------+------------------------------------- Reporter: tuplanolla | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: Component: Compiler | Version: 7.10.2 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:D3221 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): This is an error that came up repeatedly when I worked on my own usage analysis (which includes absence analysis). It was caused by RULEs (orphans and associated ones) and/or unfoldings in module `Lib` referencing otherwise absent/dead bindings, so that some binding (e.g. specialisations of an exported binding) that appeared to be dead could suddenly become alive when a specialisation fired in some client module `Main`. That lead to such an absent error, spread over multiple modules. FWIW, this won't frequently occur with the current demand analyser, because it assumes that *all* top-level bindings are alive instead of trying hard to find the minimal set, like the occurence analyser does. But this may pop up again e.g. for Call Arity, where the assumption is that only exported ids are such 'usage roots'. The disregard for RULEs and Unfoldings could lead, in theory, to a situation where we eta-expand a binding from arity 2 to arity 3 because every considered live call allows that, but some call in a RULE or Unfolding might still only have arity 2. Like in #10176, this could make bindings too lazy for their own good. The (naive) fix of treating Unfoldings/RULEs as an additional RHS of a binding (`if ? then orig_rhs else unfolding`) had detrimental effect on the precision of my usage analysis. I suspect this is the case here, too? In the end, I decided not to include the fix in order to be comparable to Call Arity and demand analysis, which is quite a shame. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:17:01 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:17:01 -0000 Subject: [GHC] #14926: failed to build cross-compiler In-Reply-To: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> References: <047.7e41252e6edebe6a23db1a7997fb158e@haskell.org> Message-ID: <062.c823ec2f12355c87b1475bdf23ca05e5@haskell.org> #14926: failed to build cross-compiler -------------------------------------+------------------------------------- Reporter: rueshyna | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Comment (by rueshyna): Thanks for help! Here you are. The output of `./configure` https://gist.github.com/rueshyna/99cb26289e8a631c1cccb6a1e2b79cea Please let me know if you need any other information. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:20:40 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:20:40 -0000 Subject: [GHC] #14823: Test profiling/should_run/scc001 fails on Circle CI In-Reply-To: <045.0b0f4063ccfb05bae50903cdc06ece01@haskell.org> References: <045.0b0f4063ccfb05bae50903cdc06ece01@haskell.org> Message-ID: <060.a2c704e56bd791e1a8ae60c9d64aef16@haskell.org> #14823: Test profiling/should_run/scc001 fails on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14705 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => new * resolution: duplicate => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:23:05 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:23:05 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.6f9cbc001b3a21568d19e8c3a9b217d6@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 bgamari): * owner: (none) => osa1 Comment: Omer will look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:27:47 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:27:47 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.ce2f7f538e52237b18a251d798fe9620@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): We now think this is fixed by the same patch as #14705 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:28:02 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:28:02 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.ceb35d1e61e90e8c4963682440882387@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14705 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #14705 Comment: This looks to be #14705. Sadly the fix for this didn't quite make it in to 8.4.1 due to administrative error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:28:40 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:28:40 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.dec08fe13f922ac070a01b51f25c2669@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * related: #14705 => Comment: Add regression test from comment:6 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:30:59 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:30:59 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.a757c5fb307386138d0e72ae8e76dc76@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): I'm currently on vacation, so I'm afraid I won't be able to write much code. I'm not doing anything targeting non-recursive functions, that in itself should be pretty much independent. But given that you seem to have stumbled over the same "phase dependency" problems, here are some notes: Re: "anticipates the state after simplifications": That's what I figured out, too, and becomes much more crucial once you add lambdas, which does beta-reduction and makes seeing which arguments are scrutinized a little harder. Currently, SpecConstr only gets its `ArgOcc`s (which is a criterion for how deep it's worth to specialise in absence of forced `SPEC`) only considers the original RHS. Specialised RHS' Occs are never considered, although /calls/ from their RHSs are considered. My plan forward is to revise the fix-pointing scheme in a way that we can translate occurences in specialised RHSs back to occurences on the original RHS' arguments. In the case of lambdas, this also involves unification of call patterns with bound variables, which is rather nasty and what I've been fiddling with the last weeks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:38:51 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:38:51 -0000 Subject: [GHC] #14823: Test profiling/should_run/scc001 fails on Circle CI In-Reply-To: <045.0b0f4063ccfb05bae50903cdc06ece01@haskell.org> References: <045.0b0f4063ccfb05bae50903cdc06ece01@haskell.org> Message-ID: <060.beb16681daba0ad778b49a5cf69d9ec0@haskell.org> #14823: Test profiling/should_run/scc001 fails on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14705 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 17:42:18 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 17:42:18 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.baafb33cb221e729998edfdda76966c7@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"abaf43d9d88d6fdf7345b936a571d17cfe1fa140/ghc" abaf43d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="abaf43d9d88d6fdf7345b936a571d17cfe1fa140" Fix seq# case of exprOkForSpeculation This subtle patch fixes Trac #5129 (again; comment:20 and following). I took the opportunity to document seq# properly; see Note [seq# magic] in PrelRules, and Note [seq# and expr_ok] in CoreUtils. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 19:06:05 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 19:06:05 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice Message-ID: <046.2335cd5876de5516a20812036c470d04@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: SpecConstr | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #14844 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is a spin-off of #14844, which is a spin-off of #14068, but applies on its own. Consider this code: {{{ module T14844Example (topLvl) where topLvl large = (bar1, bar2, foo) where foo :: Integer -> (a -> b -> Bool) -> (a,b) -> Bool foo 0 _ _ = False foo s f t = l s' t where l 0 t = False l 1 t = case t of (x,y) -> f x y l n (x,y) = l (n-1) (x,y) s' = large s bar1 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool bar1 s f x y = foo s f (x,y) bar2 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool bar2 s f x y = foo (s + 1) f (x,y) }}} Status quo: `l` gets specialized, because of the two call patterns `s' t0` and `(s-1) (x,y)`, the second one is interesting *and* its second argument gets scrutinized (the `scu_occs` field reports `ScrutOcc` for `t`). But `foo` does not get specialized: It does have an interesting call pattern, but `scu_occs` reports `UnkOcc`, because `foo`’s parameters are just passed to `t`. But: When we decide to !SpecConstr `l`, we know that one of the calls to `l` is of the shape `s' t0`. This is a boring call, and we do not create a specialization for it. But we create a specialization for `l` using the the other call pattern. This means we know that it would be beneficial if `t0` were a constructor. So can we, at this point, decide to include `t0 ↦ ScrutOcc` in `scu_occs`? First experiments look good, so I am working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 20:17:53 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 20:17:53 -0000 Subject: [GHC] #14949: Perform builds on non-Debian-based systems on Circle CI In-Reply-To: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> References: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> Message-ID: <060.e8ce178aced47af7ead8feb155f7a6ba@haskell.org> #14949: Perform builds on non-Debian-based systems on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: mrkkrp Type: bug | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.2 Integration | 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): Thank you for opening this! You may find the table on wiki:Platforms/Linux useful. It tabulates the toolchain, gmp, and libc versions shipped with a variety of Linux distributions. In principle we only need to produce one bindist per combination (and can potentially ignore the libc version, so long as we build on the oldest `glibc` in our support set). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 20:44:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 20:44:12 -0000 Subject: [GHC] #14952: Warning messages use white text which is unreadable on white background terminals Message-ID: <050.f97f7da246eb9d0653ba2b994de97ceb@haskell.org> #14952: Warning messages use white text which is unreadable on white background terminals -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When using a terminal with white background, the error messages such as "addDependentFile path (Template Haskell) listed in [...] does not exist" are partially unreadable, see screenshot. No text should be output as explicitly white, at least not without checking the terminal colors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 20:44:41 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 20:44:41 -0000 Subject: [GHC] #14952: Warning messages use white text which is unreadable on white background terminals In-Reply-To: <050.f97f7da246eb9d0653ba2b994de97ceb@haskell.org> References: <050.f97f7da246eb9d0653ba2b994de97ceb@haskell.org> Message-ID: <065.b6814c1e463fc13c9b8f71d3eb5cf4a7@haskell.org> #14952: Warning messages use white text which is unreadable on white background terminals -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 Koterpillar): * Attachment "Screen Shot 2018-03-21 at 07.41.47.png" added. Output on white background terminal -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 21:37:02 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 21:37:02 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.041f2931693f1632d862dfaad8a41bd8@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): That sounds like you want to associate 'argument occurence signatures' with functions, analogous to demand signatures, that transport `ArgOcc` information to arguments of a call. I think that would be a great idea, especially if it would work reliably for recursive functions. Although that will probably run into the same limitations as Let Up (usage from body decides over what to specialise for) vs. Let Down (signature needed where the function is in scope). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 21:37:34 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 21:37:34 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.0348ba39ca5113fb12626301cceb97b8@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * cc: sgraf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 21:37:51 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 21:37:51 -0000 Subject: [GHC] #14844: SpecConstr also non-recursive function In-Reply-To: <046.efe4b52b55047d5007c336d909140c96@haskell.org> References: <046.efe4b52b55047d5007c336d909140c96@haskell.org> Message-ID: <061.a9f3dec27c8394b1ba50d1704e029d45@haskell.org> #14844: SpecConstr also non-recursive function -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * cc: sgraf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 21:47:32 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 21:47:32 -0000 Subject: [GHC] #14946: GHC Calls CPP for HS with -undef In-Reply-To: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> References: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> Message-ID: <059.ac05adcb4e53f58d9c4f6df237457a2a@haskell.org> #14946: GHC Calls CPP for HS with -undef -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): erikd says, > Phyx-, bgamari-, angerman : the preprocessor should *not* be getting called with `-undef` , but it should be getting called with `-Wcpp-undef` which warns on undefined macros. see 3cb32d8b0b51c5 > > so adding `-Wcpp-undef` to ghc command line adds `-Wundef` to the CPP command line That being said, I don't see why this is responsible for the issue that Phyx- is seeing as it adds `-Wundef`, not `-undef` (and indeed the commit looks right). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 21:54:00 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 21:54:00 -0000 Subject: [GHC] #14948: A program which benefits from a late specialisation pass In-Reply-To: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> References: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> Message-ID: <064.db3ee3a6a041e2f4e76f5707f3a80c88@haskell.org> #14948: A program which benefits from a late specialisation pass -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Interesting! Do you have any insight about ''why'' it benefits from late specialisaion? In general that's unusual. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 21:54:16 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 21:54:16 -0000 Subject: [GHC] #14946: GHC Calls CPP for HS with -undef In-Reply-To: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> References: <044.024b26d493ac99eaf4d21968cfe71235@haskell.org> Message-ID: <059.6985ec6bc1b066cf6f9499813ad08923@haskell.org> #14946: GHC Calls CPP for HS with -undef -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): I think erikd was referring to something a bit unrelated to this issue. Warning flags are not the issue. As far as I can see going as far back as ghc 7.8 (I stopped trying to track it after that as the option keeps getting refactored to somewhere else making the blame annoying) it seems that GHC has always passed `-undef` to the C preprocessor. Which I think is a mistake. It makes the CPP mode a lot less useful. For instance https://phabricator.haskell.org/D26 was one such refactoring that moved the option from somewhere else. So we've been doing this for years and years. I should probably finish the archeology to see if I can't figure out why we did this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:02:30 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:02:30 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.66bdef56795b5c97f35b940d07db6e8e@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): You are thinking one step ahead. But it does not need something analogous to demand signatures: The !SpecConstr code already gathers all calls to `f` and remembers them when it specializes `f`, so we can add the `ArgOcc` information there, without having the LetUp vs. LetDown dilemma. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:05:27 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:05:27 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.0534eb947d7014750d4854c1d301a858@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): Pushed varosi/ghc84_bug with lot less dependencies (mainly without Yesod). Is it enough? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:10:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:10:12 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.3df039f15451a36a97b6824b24d43537@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Well, somewhat :) But it still has several bulky dependencies, such as `vector`, `linear`, `dimensional`, and `JuicyPixels`. I suspect there's a small kernel of code that's causing this panic, but I don't know how to sort through all of the scaffolding in place to find it at present. Since you know this codebase far better than I do, any useless code you can remove ("useless" meaning "I can still trigger the panic without it") would be of invaluable help here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:10:14 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:10:14 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.0f395bc7c56f6d9911d4fe35f5f9df6d@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description: > This is a spin-off of #14844, which is a spin-off of #14068, but applies > on its own. > > Consider this code: > {{{ > module T14844Example (topLvl) where > > topLvl large = (bar1, bar2, foo) > where > foo :: Integer -> (a -> b -> Bool) -> (a,b) -> Bool > foo 0 _ _ = False > foo s f t = l s' t > where > l 0 t = False > l 1 t = case t of (x,y) -> f x y > l n (x,y) = l (n-1) (x,y) > s' = large s > > bar1 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool > bar1 s f x y = foo s f (x,y) > > bar2 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool > bar2 s f x y = foo (s + 1) f (x,y) > }}} > > Status quo: `l` gets specialized, because of the two call patterns `s' > t0` and `(s-1) (x,y)`, the second one is interesting *and* its second > argument gets scrutinized (the `scu_occs` field reports `ScrutOcc` for > `t`). But `foo` does not get specialized: It does have an interesting > call pattern, but `scu_occs` reports `UnkOcc`, because `foo`’s parameters > are just passed to `t`. > > But: When we decide to !SpecConstr `l`, we know that one of the calls to > `l` is of the shape `s' t0`. This is a boring call, and we do not create > a specialization for it. But we create a specialization for `l` using the > the other call pattern. This means we know that it would be beneficial if > `t0` were a constructor. So can we, at this point, decide to include `t0 > ↦ ScrutOcc` in `scu_occs`? > > First experiments look good, so I am working on this. New description: This is a spin-off of #14844, which is a spin-off of #14068, but applies on its own. Consider this code: {{{ module T14844Example (topLvl) where topLvl large = (bar1, bar2, foo) where foo :: Integer -> (a -> b -> Bool) -> (a,b) -> Bool foo 0 _ _ = False foo s f t = l s' t where l 0 t = False l 1 t = case t of (x,y) -> f x y l n (x,y) = l (n-1) (x,y) s' = large s bar1 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool bar1 s f x y = foo s f (x,y) bar2 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool bar2 s f x y = foo (s + 1) f (x,y) }}} Status quo: `l` gets specialized, because of the two call patterns * `l s' t` and * `l (n-1) (x,y)` The second one is interesting *and* its second argument gets scrutinized (the `scu_occs` field reports `ScrutOcc` for `t`). But `foo` does not get specialized: It does have an interesting call pattern, but `scu_occs` reports `UnkOcc`, because `foo`’s parameters are just passed to `t`. When we decide to !SpecConstr `l`, we know that one of the calls to `l` is of the shape `s' t0`. This is a boring call, and we do not create a specialization for it. But we create a specialization for `l` using the the other call pattern. This means we know that it would be beneficial if `t0` were a constructor. So can we, at this point, decide to include `t0 ↦ ScrutOcc` in `scu_occs`? First experiments look good, so I am working on this. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:12:59 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:12:59 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.7ec494b150d758db1ccb96d943d2528a@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): The reason for the big version gap seems likely to be the fact that the code didn't compile at all under 7.8.4 or 7.10.3 without extra help. Here are the times I get: === 7.8.4 This version needed `-fcontext-stack=197` to compile. <> === 7.10.3 This version needed `-fcontext-stack=197` to compile. <> === 8.0.2 <> === 8.2.2 <> === 8.4.1 <> So there was a major regression from 7.8.4 to 7.10.3, another large one from 7.10.3 to 8.0.2, a large improvement from 8.0.2 to 8.2.2, and a smaller improvement from 8.2.2 to 8.4.1. I can verify that we're still running considerably slower, and allocating considerably more, than 7.8.4. FYI, while we no longer need `-fcontext-stack`, that's because the default limit has been raised or removed. It seems versions 8.0.2 through 8.4.1 need a reduction depth of 199. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:18:41 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:18:41 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.645fbd3c4fce882e9b9c561b2bde2f18@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > So can we, at this point, decide to include t0 ↦ ScrutOcc in scu_occs? I'm not at all sure. There might be many specialisations of `l`, with many RULES. Which of them would you like to use when gathering occurrence info `foo`'s argument. Sebastian's thought is interesting though. Perhaps we want the fact that `l`'s argument is scrutinesed to flow from `l` to `l`'s call sites, via some kind of !SpecConstr signature. It might be as if we'd inlined one "layer" of `l` at the call site. I wonder about fixpointing such signatures. Consider {{{ f True x y = case x of (p,q) -> ... f False x y = f True y x }}} We'd get a specialisation for `x`, but (I think) not for `y`. But one for `y` would be good! !SpecConstr is jolly compilicated. Splitting it into an analysis followed by exploitation woudl be a good thing. Just like demand analysis. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:20:03 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:20:03 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.79a376b65a01080ff0f2941d4999863b@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): BTW, what is the connection to the title of the ticket? Why does two runs help? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:23:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:23:12 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.be7f0e513fbdc571ba3994f004e79929@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): See `wip/T14951` for what I have in mind. If fixes the problem with the example code in the ticket. > BTW, what is the connection to the title of the ticket? Why does two runs help? Ah, right: If you simplify, then `l` gets inlined, and suddenly the body of `foo` _does_ scrutinize `t` and a second run of !SpecConstr would specialize `l`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:23:55 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:23:55 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.17186bd621ee3bdc639f468696f502f7@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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): Does the size of the program change at all between 7.6 and 8.4? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:25:02 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:25:02 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.29785dfffa76de84ea930423d9734462@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): I'm looking into that new. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:27:23 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:27:23 -0000 Subject: [GHC] #14948: A program which benefits from a late specialisation pass In-Reply-To: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> References: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> Message-ID: <064.2c34e18acf7a8cbf8f2c7e90a817363b@haskell.org> #14948: A program which benefits from a late specialisation pass -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): The code in question first uses a type class to generate an overloaded function. The overloaded function is not immediately apparent, it is defined in terms of combinators which must be inlined and then later we get calls of `fmap` next to a dictionary which can be specialised upon. Diffing the core output immediately shows where the difference is. In the bad version we have lots of calls to `fmap` which are not eliminated because the function they are contained in is not specialised. {{{ 1486,1497c1514,1560 < -- RHS size: {terms: 13, types: 12, coercions: 13, joins: 0/0} < $s$fGHasTypeskaK1_$cgtypes_$s$dHastypes' < $s$fGHasTypeskaK1_$cgtypes_$s$dHastypes' < = \ eta_B2 eta1_B1 -> < case eta1_B1 of { < [] -> [] `cast` ; < : g1_ab8Q g2_ab8R -> < (: ((eta_B2 g1_ab8Q) `cast` ) < (($s$fGHasTypeskaK1_$cgtypes_$s$dHastypes' eta_B2 g2_ab8R) < `cast` )) < `cast` < } --- > -- RHS size: {terms: 63, types: 791, coercions: 308, joins: 0/0} > $s$fGHasTypeskaK1_$cgtypes1 > $s$fGHasTypeskaK1_$cgtypes1 > = \ @ f_a5xv $dApplicative_a5xx eta_B2 eta1_B1 -> > fmap > ($p1Applicative $dApplicative_a5xx) > $fGeneric[]_$cto > ((fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes8 `cast` ) > (case eta1_B1 of { > [] -> > fmap > ($p1Applicative $dApplicative_a5xx) > L1 > (fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes7 `cast` ) > (pure $dApplicative_a5xx U1)); > : g1_abai g2_abaj -> > fmap > ($p1Applicative $dApplicative_a5xx) > R1 > (fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes6 `cast` ) > (<*> > $dApplicative_a5xx > (fmap > ($p1Applicative $dApplicative_a5xx) > :*: > (fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes5 `cast` ) > (fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes4 `cast` ) > (eta_B2 g1_abai)))) > (fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes3 `cast` ) > (fmap > ($p1Applicative $dApplicative_a5xx) > ($s$fGHasTypeskaK1_$cgtypes2 `cast` ) > ($s$fGHasTypeskaK1_$cgtypes1 $dApplicative_a5xx eta_B2 g2_abaj))))) > })) > `cast` ) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:39:38 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:39:38 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.aecd7a33fc43773c60042f3adbdfca34@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > So the plan would be to experiment with a specializer that works also for non-recursive functions. That idea is pursued in #14844. But I'd still like to be be sure that this is truly the reason for the regression. We have comment:27 which shows a regession for `x2n1` (is it the only regression?). Then comment:28 says "maybe it's this". But we have no concrete evidence for what the `x2n1` regression really is. It'd be good to know. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:48:25 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:48:25 -0000 Subject: [GHC] #14948: A program which benefits from a late specialisation pass In-Reply-To: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> References: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> Message-ID: <064.3533a3def7060f3a2847a4a9ec86f82e@haskell.org> #14948: A program which benefits from a late specialisation pass -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The odd thing is that this function still exists {{{ > $s$fGHasTypeskaK1_$cgtypes1 > = \ @ f_a5xv $dApplicative_a5xx eta_B2 eta1_B1 -> }}} It has a dictionary argument so it'd ususally have been specialised earlier. Looking at it, it could originally have been a function of type {{{ foo :: forall a. C a => foralll b. D b => blah }}} Now, I think the specialiser might specialise only one "layer" of a function like that at a time. And ''that'' might be fixable, if that's the problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 22:51:00 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 22:51:00 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.0a712791462ab6d7799659cf5944dd25@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I am now confident that this is it, together with #14844 and #14951, because only if I fix both these issues, I get the same low allocation number for `x2n1`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 20 23:19:45 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 20 Mar 2018 23:19:45 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.c4509b1ce24a9802e05057dfa9ada4ae@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by varosi): I'll try to remove some dependencies, but vector, linear and dimensional are core parts of the project and cannot be removed easily without rewriting everything. btw, on GHC 8.2.2 (master branch) there is no problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 00:38:14 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 00:38:14 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.e98369302e8d67356a3287984a8250f3@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): Yes, the size of the program changes quite a lot. The most notable thing about this program is the sheer number of types, which is enormous in every case, but varies quite a lot. In each case I give the result of `CorePrep` from `Paper` (which always compiles reasonably quickly) along with pertinent-looking information about `Main` (which takes a while). === 7.8.4 Paper: {{{ {terms: 1,719, types: 4,049, coercions: 768} }}} Main: {{{ Result size of Desugar (after optimization) = {terms: 3,973, types: 630,023, coercions: 196} ... Result size of Simplifier = {terms: 3,384, types: 628,456, coercions: 5} Result size of Specialise = {terms: 4,785, types: 865,456, coercions: 5} Result size of Float out(FOS {Lam = Just 0, Consts = True, PAPs = False}) = {terms: 6,373, types: 1,100,676, coercions: 5} Result size of Simplifier iteration=1 = {terms: 8,674, types: 1,377,245, coercions: 211,797} Result size of Simplifier iteration=2 = {terms: 4,051, types: 730,227, coercions: 84,460} -- things go up and down a few times Result size of Tidy Core = {terms: 5,157, types: 1,104,496, coercions: 84,451} }}} === 7.10.3 Paper: {{{ Result size of CorePrep = {terms: 1,736, types: 3,973, coercions: 778} }}} Main: {{{ Result size of Desugar (after optimization) = {terms: 3,973, types: 630,023, coercions: 196} Result size of Specialise = {terms: 12,088, types: 2,092,764, coercions: 392} *** Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}): Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) = {terms: 13,674, types: 2,327,982, coercions: 392} Result size of Simplifier iteration=1 = {terms: 14,824, types: 2,416,989, coercions: 371,022} Result size of Simplifier iteration=2 = {terms: 10,101, types: 2,096,313, coercions: 321,082} Result size of Simplifier iteration=1 = {terms: 12,295, types: 2,650,706, coercions: 321,081} ... nothing much changes for a long time -- Sudden size drop in core tidy Result size of Tidy Core = {terms: 5,146, types: 1,104,452, coercions: 84,448} }}} This comment is getting long; I'll continue in the next one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 03:17:04 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 03:17:04 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules Message-ID: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `A.hs` {{{ {-# LANGUAGE DuplicateRecordFields #-} module A where data R = R {unR :: Int} }}} --- `B.hs` {{{ {-# LANGUAGE DuplicateRecordFields #-} module B where data R = R {unR :: Int} }}} --- `C.hs` {{{ {-# LANGUAGE DuplicateRecordFields #-} module C (module A, module B) where import A import B }}} --- Output: {{{ C.hs:3:21: error:ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180224 for x86_64-unknown-linux): exportClashErr $sel:unR:R Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcRnExports.hs:740:22 in ghc:TcRnExports }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 03:17:30 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 03:17:30 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules In-Reply-To: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> References: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> Message-ID: <059.9b44a379f244d806ef5e62741d31af80@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by lyxia: Old description: > `A.hs` > > {{{ > {-# LANGUAGE DuplicateRecordFields #-} > module A where > data R = R {unR :: Int} > }}} > > --- > > `B.hs` > > {{{ > {-# LANGUAGE DuplicateRecordFields #-} > module B where > data R = R {unR :: Int} > }}} > > --- > > `C.hs` > > {{{ > {-# LANGUAGE DuplicateRecordFields #-} > > module C (module A, module B) where > > import A > import B > }}} > > --- > > Output: > > {{{ > C.hs:3:21: error:ghc-stage2: panic! (the 'impossible' happened) > (GHC version 8.5.20180224 for x86_64-unknown-linux): > exportClashErr > $sel:unR:R > Call stack: > CallStack (from HasCallStack): > callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in > ghc:Outputable > pprPanic, called at compiler/typecheck/TcRnExports.hs:740:22 in > ghc:TcRnExports > > }}} New description: `A.hs` {{{ {-# LANGUAGE DuplicateRecordFields #-} module A where data R = R {unR :: Int} }}} --- `B.hs` {{{ {-# LANGUAGE DuplicateRecordFields #-} module B where data R = R {unR :: Int} }}} --- `C.hs` {{{ {-# LANGUAGE DuplicateRecordFields #-} module C (module A, module B) where import A import B }}} --- Output of `ghc C.hs`: {{{ C.hs:3:21: error:ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180224 for x86_64-unknown-linux): exportClashErr $sel:unR:R Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcRnExports.hs:740:22 in ghc:TcRnExports }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 04:16:04 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 04:16:04 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.3c76e49110bb1b5f63ff210347cd8a28@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): === 8.0.2 Paper: {{{ Result size of CorePrep = {terms: 2,704, types: 5,400, coercions: 996} }}} Main: {{{ Result size of Desugar (after optimization) = {terms: 4,574, types: 632,608, coercions: 196} Result size of Specialise = {terms: 13,274, types: 2,100,628, coercions: 392} Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) = {terms: 14,860, types: 2,335,846, coercions: 392} Result size of Simplifier iteration=1 = {terms: 15,614, types: 2,423,788, coercions: 366,704} Result size of Simplifier iteration=2 = {terms: 10,121, types: 2,098,814, coercions: 322,579} .... Result size of Simplifier = {terms: 12,570, types: 2,807,500, coercions: 320,217} Result size of Tidy Core = {terms: 5,208, types: 1,104,414, coercions: 84,359} }}} === 8.2.2 Paper: {{{ Result size of CorePrep = {terms: 3,280, types: 5,538, coercions: 1,000, joins: 2/50} }}} Main: {{{ Result size of Desugar (after optimization) = {terms: 4,564, types: 632,574, coercions: 196, joins: 0/982} Result size of Simplifier iteration=1 = {terms: 6,858, types: 1,023,896, coercions: 86,509, joins: 0/786} Result size of Simplifier iteration=2 = {terms: 4,014, types: 726,796, coercions: 85,137, joins: 1/2} ... Result size of Specialise = {terms: 9,329, types: 1,646,724, coercions: 168,346, joins: 2/2} *** Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) [Main]: Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) = {terms: 10,823, types: 1,939,926, coercions: 168,346, joins: 1/2} Result size of Simplifier iteration=1 = {terms: 9,648, types: 1,706,501, coercions: 227,811, joins: 2/2} Result size of Simplifier iteration=2 = {terms: 9,349, types: 1,647,213, coercions: 168,353, joins: 2/2} ... Result size of Tidy Core = {terms: 5,212, types: 1,104,424, coercions: 84,359, joins: 2/2} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 04:26:53 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 04:26:53 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.2e99c889b497216383fffb70f6b71111@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): === 8.4.1 Paper: {{{ Result size of CorePrep = {terms: 3,228, types: 5,423, coercions: 1,008, joins: 3/50} }}} Main: {{{ Result size of Desugar (after optimization) = {terms: 4,564, types: 632,574, coercions: 196, joins: 0/982} Result size of Simplifier iteration=1 = {terms: 6,858, types: 1,023,896, coercions: 86,509, joins: 0/786} Result size of Simplifier iteration=2 = {terms: 4,014, types: 726,796, coercions: 85,137, joins: 1/2} Result size of Specialise = {terms: 9,329, types: 1,646,724, coercions: 168,346, joins: 2/2} Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = False}) = {terms: 10,431, types: 1,862,310, coercions: 168,346, joins: 1/2} Result size of Simplifier iteration=1 = {terms: 9,648, types: 1,706,501, coercions: 227,811, joins: 2/2} Result size of Simplifier iteration=2 = {terms: 9,349, types: 1,647,213, coercions: 168,353, joins: 2/2} ... Result size of Simplifier = {terms: 9,334, types: 1,647,199, coercions: 168,352, joins: 2/2} -- What happened here?????? Result size of Simplifier iteration=1 = {terms: 110,206, types: 1,818,532, coercions: 379,933, joins: 593/20,293} Result size of Simplifier = {terms: 8,914, types: 1,272,932, coercions: 85,550, joins: 5/203} .... Result size of Demand analysis = {terms: 8,323, types: 1,272,755, coercions: 85,550, joins: 5/6} !!! Demand analysis [Main]: finished in 200.01 milliseconds, allocated 115.130 megabytes *** CoreTidy [Main]: Result size of Tidy Core = {terms: 1,867, types: 166,695, coercions: 1,988, joins: 5/6} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 06:47:28 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 06:47:28 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.9babb1e3bd0d26b0084b126846f90241@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Indeed we can only add `t ↦ ScrutOcc` if we know that a matching specialisation will apply. Consider what would happen if we regarded `(n-1)` as a constructor form (it isn't , of course, but imagine inductive nats), too: Then we would have `[ScrutOcc [UnkOcc], ScrutOcc [UnkOcc, UnkOcc]` for `l`s RHS and would have a more specific specialisation for `l (n-1) (x,y)`. If we bubble out a usage of `t ↦ ScrutOcc` within `foo` from the `l s' t` call, this will attempt to do a specialisation of `foo` when it hits a call site like in `bar1`. But now there's no matching specialisation of `l` anymore: The one which was a candidate before also assumes `n-1` as an argument. This can potentially make things much worse. So the whole signature thing seems like not such a good idea after all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 07:51:44 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 07:51:44 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.5ccf5457c01e493aab4c604662a2a107@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Changes (by osa1): * status: new => merge Comment: Thanks Simon, the notes are really helpful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 08:41:38 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 08:41:38 -0000 Subject: [GHC] #14954: Passing -fno-code disables reporting of some warnings Message-ID: <045.0b1aea2fec0c02d18d010967483b9949@haskell.org> #14954: Passing -fno-code disables reporting of some warnings -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here is how to reproduce the issue with GHC 8.2.2: {{{ $ cat Main.hs module Main (main) where main = case (1+1) :: Int of 1 -> return () $ ghc -Wall -Werror -fno-code Main.hs [1 of 1] Compiling Main ( Main.hs, nothing ) Main.hs:3:1: warning: [-Wmissing-signatures] Top-level binding with no type signature: main :: IO () | 3 | main = | ^^^^ : error: Failing due to -Werror. $ ghc -Wall -Werror Main.hs [1 of 1] Compiling Main ( Main.hs, Main.o ) Main.hs:3:1: warning: [-Wmissing-signatures] Top-level binding with no type signature: main :: IO () | 3 | main = | ^^^^ Main.hs:4:3: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: p where p is not one of {1} | 4 | case (1+1) :: Int of | ^^^^^^^^^^^^^^^^^^^^... : error: Failing due to -Werror. }}} Note that `missing-signature` is reported both times, but the `incomplete- patterns` is not reported with `-fno-code`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 09:37:53 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 09:37:53 -0000 Subject: [GHC] #14954: Passing -fno-code disables reporting of some warnings In-Reply-To: <045.0b1aea2fec0c02d18d010967483b9949@haskell.org> References: <045.0b1aea2fec0c02d18d010967483b9949@haskell.org> Message-ID: <060.0a03189aebacb21e1ac3e2101d5215c9@haskell.org> #14954: Passing -fno-code disables reporting of some warnings -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): See #10600 . I still don't know why the pattern match checking happens in the desugarer but perhaps this is fixed? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 10:21:42 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 10:21:42 -0000 Subject: [GHC] #14935: Vary default RTS settings so that performance does not degrade with increasing number of capabilities In-Reply-To: <047.c1e3c537cd577233605e2a8fc8124d44@haskell.org> References: <047.c1e3c537cd577233605e2a8fc8124d44@haskell.org> Message-ID: <062.fdf2f961d381009efb9c2115187d3bce@haskell.org> #14935: Vary default RTS settings so that performance does not degrade with increasing number of capabilities -------------------------------------+------------------------------------- Reporter: YitzGale | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 YitzGale): Replying to [comment:1 bgamari]: > I can't quite tell whether this is a general request for the runtime (which would apply to all GHC-compiled executables by default) or GHC in particular. You're right, I conflated the two. They're both important. And GHC is after all an instance of an application compiled by GHC. Should this be two separate tickets? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 10:36:15 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 10:36:15 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.1cc829e3d92f0e44e6c62556ce88f659@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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): Thanks for this data. Several interesting things here. * There's a big jump in compilation cost between 7.8 and 7.10. (Like a factor of 2 in compiler allocation, according to comment:3. According to comment:6, the result of Specialise is much bigger in 7.10 than in 7.8. This extra code appears to be discarded at the end, but it persists through the compilation pipeline. '''Questions''': what are the extra specialisations? Do we need them? Why are they eventually discarded? Could we discard them earlier? * As you say in comment:8 it seems that GHC 8.4 has a new, and huge (temporary) blow-up in porgram size. It'd be really good to work out what this is. (You'll presumably need to cut down the program size to make this tractable.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 10:49:03 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 10:49:03 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.e437c84836939fa72276815a8f922c37@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => SpecConstr -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 11:18:31 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 11:18:31 -0000 Subject: [GHC] #14955: Musings on manual type class desugaring Message-ID: <049.12855af11ea5950a6983dee948966231@haskell.org> #14955: Musings on manual type class desugaring -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: SpecConstr | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I recently wrote a short post explaining why manual type class desugaring was different to actually writing a type class because of how they are optimised. http://mpickering.github.io/posts/2018-03-20-recordsvstypeclasses.html I implement 4 different equivalent programs which are all optimised differently. I paste the whole file below as it is not very big. Implementation 1 is in terms of a type class. Implementation 2 is in terms of explicit dictionary passing. Implementation 3 wraps a dictionary in a type class Implementation 4 wraps a dictionary in a type class with an additional dummy argument. Naively, a user would expect all 4 implementations to be as fast as each other. {{{ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE AllowAmbiguousTypes #-} module Prop where import Prelude (Bool(..), (||), (&&)) -- Implementation 1 class Prop r where or :: r -> r -> r and :: r -> r -> r true :: r false :: r instance Prop Bool where or = (||) and = (&&) true = True false = False -- Implementation 2 data PropDict r = PropDict { dor :: r -> r -> r , dand :: r -> r -> r , dtrue :: r , dfalse :: r } boolDict = PropDict { dor = (||) , dand = (&&) , dtrue = True , dfalse = False } -- Implementation 3 class PropProxy r where propDict :: PropDict r instance PropProxy Bool where propDict = boolDict -- Implementation 4 class PropProxy2 r where propDict2 :: PropDict r dummy :: () instance PropProxy2 Bool where propDict2 = boolDict dummy = () ors :: Prop r => [r] -> r ors [] = true ors (o:os) = o `or` ors os {-# INLINABLE ors #-} dors :: PropDict r -> [r] -> r dors pd [] = dtrue pd dors pd (o:os) = dor pd o (dors pd os) pors :: PropProxy r => [r] -> r pors [] = dtrue propDict pors (o:os) = dor propDict o (pors os) {-# INLINABLE pors #-} porsProxy :: PropProxy2 r => [r] -> r porsProxy [] = dtrue propDict2 porsProxy (o:os) = dor propDict2 o (porsProxy os) {-# INLINABLE porsProxy #-} }}} Then using the 4 different implementations of `ors` in another module implementations 1 and 4 are fast whilst 2 and 3 are slow. https://github.com/mpickering/rtcwrao-benchmarks/blob/master/Prop2.hs {{{ benchmarking tc/Implementation 1 time 3.510 ms (3.509 ms .. 3.512 ms) 1.000 R² (1.000 R² .. 1.000 R²) mean 2.976 ms (2.886 ms .. 3.060 ms) std dev 241.1 μs (195.4 μs .. 293.1 μs) variance introduced by outliers: 51% (severely inflated) benchmarking tc/Implementation 2 time 25.05 ms (21.16 ms .. 30.43 ms) 0.912 R² (0.849 R² .. 0.984 R²) mean 19.18 ms (16.20 ms .. 21.45 ms) std dev 5.627 ms (4.710 ms .. 6.618 ms) variance introduced by outliers: 89% (severely inflated) benchmarking tc/Implementation 3 time 20.06 ms (15.33 ms .. 23.57 ms) 0.856 R² (0.755 R² .. 0.934 R²) mean 18.43 ms (16.92 ms .. 19.85 ms) std dev 3.490 ms (3.003 ms .. 4.076 ms) variance introduced by outliers: 74% (severely inflated) benchmarking tc/Implementation 4 time 3.498 ms (3.484 ms .. 3.513 ms) 1.000 R² (1.000 R² .. 1.000 R²) mean 3.016 ms (2.935 ms .. 3.083 ms) std dev 205.7 μs (162.6 μs .. 261.8 μs) variance introduced by outliers: 42% (moderately inflated) }}} I compiled the module with `-O2`. If I turn off `-fno-worker-wrapper` and `-fno-spec-constr` then implementation 3 is also fast. Implementation 2 is always slow. This ticket is querying what could be done to improve the robustness of these different refactorings. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 11:50:21 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 11:50:21 -0000 Subject: [GHC] #14598: 32-bit Linux environment In-Reply-To: <046.d2f4ecc843f7c7bed1054ebabaec5cff@haskell.org> References: <046.d2f4ecc843f7c7bed1054ebabaec5cff@haskell.org> Message-ID: <061.8035f2e2d665f71f30dffae24f6fd0b2@haskell.org> #14598: 32-bit Linux environment -------------------------------------+------------------------------------- Reporter: bgamari | Owner: mrkkrp Type: bug | Status: closed Priority: normal | Milestone: Component: Continuous | Version: 8.2.1 Integration | 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 mrkkrp): * status: new => closed * resolution: => fixed Comment: Looks like this has been merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 13:16:39 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 13:16:39 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.0451b3b6819d95e0698985ffd62fbb91@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: bgamari (added) Comment: While I'm no closer to minimizing the program, I believe I've found the commit that caused this: 4bfff7a507b5807736e9c6ce9814a9cfa60faeff (`rts: Don't default to single capability when profiled`). Ben, do you have any idea what might be happening here? I don't know how to interpret this error message. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 13:18:16 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 13:18:16 -0000 Subject: [GHC] #14869: Documentation for isLiftedTypeKind is incorrect In-Reply-To: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> References: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> Message-ID: <065.949bc53e8fabdcf6c641ef36d9a7cd1e@haskell.org> #14869: Documentation for isLiftedTypeKind is incorrect -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4474 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"49ac3f0f2a13f66fea31a258fa98b0de39bfbf10/ghc" 49ac3f0f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="49ac3f0f2a13f66fea31a258fa98b0de39bfbf10" Fix #14869 by being more mindful of Type vs. Constraint Summary: Before, we were using `isLiftedTypeKind` in `reifyType` before checking if a type was `Constraint`. But as it turns out, `isLiftedTypeKind` treats `Constraint` the same as `Type`, so every occurrence of `Constraint` would be reified as `Type`! To make things worse, the documentation for `isLiftedTypeKind` stated that it treats `Constraint` //differently// from `Type`, which simply isn't true. This revises the documentation for `isLiftedTypeKind` to reflect reality, and defers the `isLiftedTypeKind` check in `reifyType` so that it does not accidentally swallow `Constraint`. Test Plan: make test TEST=T14869 Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14869 Differential Revision: https://phabricator.haskell.org/D4474 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 13:20:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 13:20:10 -0000 Subject: [GHC] #14869: Documentation for isLiftedTypeKind is incorrect In-Reply-To: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> References: <050.35651f1fbd8cecc022a69aff4010777f@haskell.org> Message-ID: <065.d2b03333eecb755865ef98e322b1409d@haskell.org> #14869: Documentation for isLiftedTypeKind is incorrect -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: th/T14869 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4474 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => th/T14869 * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 14:03:42 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 14:03:42 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.1951c59431d667e9e51bf43874e18adf@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Simon, I implemented changes in `cvObtainTerm` as discussed yesterday, but I'm still getting "TSO object entered" errors. Previously `cvObtainTerm` follwed indirectee's of BLACKHOLEs no matter what. With my changes I only follow the indirectees when they're not TSO or BLOCKING_QUEUE. Somehow with this I still get "TSO object entered". If I don't follow BLACKHOLE indirectees at all (and bind a BLACKHOLE to `_t1` in this reproducer) then I get a deadlock as expected. Do you have any ideas on why this may be happening? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 15:39:46 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 15:39:46 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.87de78956b9717cb90c720b7466126d3@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): And, to add numbers to this: Running !SpecConstr on top-level non- recursive functions and running it twice (with simplification in between) improves `x2n1` allocations by 45%, compared to just loopification, and fixes some of the other regressions: https://perf.haskell.org/ghc/#compare/9245c4bbc2156b3b84f253c97cc2ee8bd8b7dd98/0f1fee6be3df20837543ede7223a827abb6a4759. [https://perf.haskell.org/ghc/#compare/abaf43d9d88d6fdf7345b936a571d17cfe1fa140/0f1fee6be3df20837543ede7223a827abb6a4759 Overall], the whole branch has a few promising improvements of ~7%, but also still some egregious regressions that need to be tracked down (`queens` +240%). And it is of course not immediately clear which of the improvements are due to loopification, and which are independent of loopification and due to the changes to !SpecConstr. But in any ways we need to conclude the !SpecConstr story first and see what, if anything at all, we want to change there. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 15:43:01 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 15:43:01 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.7843e3b71a324407373e04b8be6d419c@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > This can potentially make things much worse. What do you mean with worse? We can construct cases where we would create specializations of the outer functions that are not beneficial, but it wound’t make things worse, right? In the end it's all heuristic. But I’d like to be able to make small steps forwards to unblock loopification rather than wait for a complete rewrite of !SpecConstr (as much as I appreciate such a thing, the module is a beast :-)) And in general we try hard to make our transformations as idempotent as possible, so we should do that here as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 16:13:59 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 16:13:59 -0000 Subject: [GHC] #14956: NUMA not detected on Aarch64 NUMA machine Message-ID: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> #14956: NUMA not detected on Aarch64 NUMA machine --------------------------------------+--------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.1 Keywords: | Operating System: Linux Architecture: aarch64 | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- {{{ # lscpu Architecture: aarch64 Byte Order: Little Endian CPU(s): 96 On-line CPU(s) list: 0-95 Thread(s) per core: 1 Core(s) per socket: 48 Socket(s): 2 NUMA node(s): 2 L1d cache: 32K L1i cache: 78K L2 cache: 16384K NUMA node0 CPU(s): 0-47 NUMA node1 CPU(s): 48-95 # ./cgraytrace_prof_thread +RTS -s -A40m -qn24 --numa cgraytrace_prof_thread: --numa: OS reports NUMA is not available cgraytrace_prof_thread: cgraytrace_prof_thread: Usage: [+RTS | -RTS ] ... --RTS ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 16:19:33 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 16:19:33 -0000 Subject: [GHC] #14957: Build failure in brew Message-ID: <047.586421682b524ccdbc2ab9ccd893291d@haskell.org> #14957: Build failure in brew -------------------------------------+------------------------------------- Reporter: cafeface | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: None/Unknown (amd64) | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ <> <> <> ghc: internal error: evacuate(static): strange closure type 0 (GHC version 8.4.1 for x86_64_apple_darwin) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug make[1]: *** [libraries/Cabal/Cabal/dist- boot/build/Distribution/Simple/Setup.o] Abort trap: 6 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 16:19:55 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 16:19:55 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.527601f108b19420dc1b6a99e6cfcb26@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): > What do you mean with worse? Well, assuming we would specialise `foo` for `foo s f (x,y)` without calling a specialised `l`, then we would just defer constructing the pair. So, you're right: not actually worse at all, but unnecessary code bloat, still. Come to think of it, have you tried to weave in [https://hackage.haskell.org/package/ghc-prim-0.5.1.1/docs/GHC- Types.html#t:SPEC GHC.Types.SPEC] into `foo`s signature instead? That essentially makes !SpecConstr forget to find matching `ArgOcc`s and blindly specialises for call sites and is probably what would help here, too. Probably at the expense of even worse code bloat when there are many different call patterns, but there is only one in your specific case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 16:23:00 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 16:23:00 -0000 Subject: [GHC] #14957: Build failure in brew In-Reply-To: <047.586421682b524ccdbc2ab9ccd893291d@haskell.org> References: <047.586421682b524ccdbc2ab9ccd893291d@haskell.org> Message-ID: <062.1bd9c3a0ef7c2592dedd727de954bff7@haskell.org> #14957: Build failure in brew ---------------------------------+-------------------------------------- Reporter: cafeface | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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 cafeface): * version: 8.2.2 => 8.4.1 * os: Unknown/Multiple => MacOS X -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 16:45:18 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 16:45:18 -0000 Subject: [GHC] #14956: NUMA not detected on Aarch64 NUMA machine In-Reply-To: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> References: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> Message-ID: <060.5bc538c9d0cd8c90eb13401c57973973@haskell.org> #14956: NUMA not detected on Aarch64 NUMA machine -----------------------------------+------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: aarch64 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+------------------------------- Description changed by varosi: Old description: > {{{ > # lscpu > Architecture: aarch64 > Byte Order: Little Endian > CPU(s): 96 > On-line CPU(s) list: 0-95 > Thread(s) per core: 1 > Core(s) per socket: 48 > Socket(s): 2 > NUMA node(s): 2 > L1d cache: 32K > L1i cache: 78K > L2 cache: 16384K > NUMA node0 CPU(s): 0-47 > NUMA node1 CPU(s): 48-95 > > # ./cgraytrace_prof_thread +RTS -s -A40m -qn24 --numa > cgraytrace_prof_thread: --numa: OS reports NUMA is not available > cgraytrace_prof_thread: > cgraytrace_prof_thread: Usage: [+RTS | -RTS > ] ... --RTS > ... > }}} New description: Ubuntu 16 LTS {{{ # lscpu Architecture: aarch64 Byte Order: Little Endian CPU(s): 96 On-line CPU(s) list: 0-95 Thread(s) per core: 1 Core(s) per socket: 48 Socket(s): 2 NUMA node(s): 2 L1d cache: 32K L1i cache: 78K L2 cache: 16384K NUMA node0 CPU(s): 0-47 NUMA node1 CPU(s): 48-95 # ./cgraytrace_prof_thread +RTS -s -A40m -qn24 --numa cgraytrace_prof_thread: --numa: OS reports NUMA is not available cgraytrace_prof_thread: cgraytrace_prof_thread: Usage: [+RTS | -RTS ] ... --RTS ... }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 16:49:57 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 16:49:57 -0000 Subject: [GHC] #14958: QuantifiedConstraints: Doesn't apply implication for existential? Message-ID: <051.4c7a20f12068d6c91dfb6a24439e15b7@haskell.org> #14958: QuantifiedConstraints: Doesn't apply implication for existential? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints, wipT2893 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This fails {{{#!hs {-# Language GADTs, RankNTypes, ConstraintKinds, QuantifiedConstraints, AllowAmbiguousTypes #-} data Foo where Foo :: (forall x. ((forall y. cls y => Num y), cls x) => x) -> Foo a :: Foo a = Foo 10 }}} {{{ $ ... -ignore-dot-ghci /tmp/Optic.hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/Optic.hs, interpreted ) /tmp/Optic.hs:7:9: error: • Could not deduce (Num x) arising from the literal ‘10’ from the context: (forall y. cls0 y => Num y, cls0 x) bound by a type expected by the context: forall x. (forall y. cls0 y => Num y, cls0 x) => x at /tmp/Optic.hs:7:5-10 Possible fix: add (Num x) to the context of a type expected by the context: forall x. (forall y. cls0 y => Num y, cls0 x) => x • In the first argument of ‘Foo’, namely ‘10’ In the expression: Foo 10 In an equation for ‘a’: a = Foo 10 | 7 | a = Foo 10 | ^^ Failed, no modules loaded. Prelude> }}} GHC knows that `cls ~=> Num` but still GHC cannot deduce `Num x` from `cls x`. ---- The reason for trying this is creating a `newtype` for optics where we still get subsumption {{{#!hs {-# Language GADTs, RankNTypes, ConstraintKinds, QuantifiedConstraints, AllowAmbiguousTypes, ApplicativeDo, TypeOperators, MultiParamTypeClasses, FlexibleInstances, UndecidableInstances, PolyKinds, FlexibleContexts #-} data Optic cls s a where Optic :: (forall f. cls f => (a -> f a) -> (s -> f s)) -> Optic cls s a class (forall x. f x => g x) => (f ~=> g) instance (forall x. f x => g x) => (f ~=> g) _1 :: cls ~=> Functor => Optic cls (a, b) a _1 = Optic $ \f (a, b) -> do a' <- f a pure (a', b) lens_1 :: Optic Functor (a, b) a lens_1 = _1 trav_1 :: Optic Applicative (a, b) a trav_1 = _1 }}} and I wanted to move `cls ~=> Functor` into the `Optic` type itself. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:07:14 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:07:14 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.22ffac5c06e1fc0abb3a73b7b7e7693b@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): That sounds like it requires user intervention; that’s certainly not an option here, where I am trying to fix regressions due to loopification. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:15:54 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:15:54 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.b982890c13998401c5ab075e8673989d@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): You could thread the `SPEC` value through your RHS. This will require an additional `INLINE` binding, unless you want to fix up call sites, too. Assuming you loopified `foo`: {{{ foo :: Integer -> (a -> b -> Bool) -> (a,b) -> Bool foo = $wfoo SPEC where $wfoo !_ 0 _ _ = False $wfoo !_ f t = l s' t where l 0 t = False l 1 t = case t of (x,y) -> f x y l n (x,y) = l (n-1) (x,y) s' = large s {-# INLINE foo #-} bar1 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool bar1 s f x y = foo s f (x,y) bar2 :: Integer -> (a -> b -> Bool) -> a -> b -> Bool bar2 s f x y = foo (s + 1) f (x,y) }}} Provided the simplifier inlines `foo` before !SpecConstr runs, this should make sure that `$wfoo` will be specialised for its call pattern. This would not need !SpecConstr to change at all, I think. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:19:11 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:19:11 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.970ba6b06846d55bbae21cc5887c8cba@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Build 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): Phab:D1021 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): This is very easy to achieve with Hadrian and I just submitted [https://github.com/snowleopard/hadrian/pull/535/files a pull request] against hadrian `master` that documents how it can be done. Will post another comment when it gets merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:22:14 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:22:14 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.50e511a81500951aed33109901d6f0fd@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): If I understand this correctly, then you are proposing that loopification should tell !SpecConstr to very aggressively specialize a loopified binding, independent of whether its arguments are actually scrutinzed anywhere? But isn’t that strictly less precise than my proposal, which only specializes `foo` if there is some indication that it will be beneficial? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:27:06 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:27:06 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.4e3c07e45481321557fabb0f33620094@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): That's what I was referring to by 'at the expense of even worse code bloat'. The difference is that you might have a better time being less precise for loopified bindings (have more bloat there) than to have potentially little more bloat for //every// non-recursive binding. Also depending on how far you are with your changes to !SpecConstr, this could be simpler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:32:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:32:10 -0000 Subject: [GHC] #14951: SpecContsr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.1dfad2d04c3430f40bf74aba8506f8a2@haskell.org> #14951: SpecContsr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > potentially little more bloat for every non-recursive binding. It’s not just non-recursive bindings. It’s gonna bloat * every binding * that has interesting calls * that itself calls a local function * which itself is being specialized * and where the specialization of the inner function match the calls to the outer * but matches them only partially (the case where they match completely is the one we are interested in). which seems pretty narrow to me. > Also depending on how far you are with your changes to SpecConstr, this could be simpler. They were pretty simple it needs just a bit more cleanup, see [https://github.com/ghc/ghc/compare/wip/T14951 wip/T14951]. I am basically waiting for perf.haskell.org to report the results. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:32:33 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:32:33 -0000 Subject: [GHC] #14959: Heep overflow in optimizer Message-ID: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> #14959: Heep overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compiling the following with optimisations: {{{ module Test where import Data.Bits (setBit) f = foldl setBit 0 [x | (x,_) <- zip [0..] [1]] :: Integer }}} fails with: {{{ $ ghc -O0 -fforce-recomp Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) $ ghc -O -fforce-recomp Test.hs [1 of 1] Compiling Test ( Test.hs, Test.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-unknown-linux): heap overflow }}} Fails on 8.0.2, 8.2.2, and 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:44:44 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:44:44 -0000 Subject: [GHC] #14959: Heap overflow in optimizer (was: Heep overflow in optimizer) In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.580a3878bf430817635015a5b6687592@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Stunning. This bug goes all the way back to GHC 8.0.1, even (note that before 8.4.1, you would simply get the error message `ghc: Out of memory` instead of a panic). GHC 7.10.3 does not suffer from this issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:55:18 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:55:18 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.835aed1da2dd83d34b5edfe19ecc2564@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 darchon): Some notes which I forgot to mention: * Result need to be `Integer`, no heap overflow on `Int` or `Word` * The folded computation needs to be `setBit`, no heap overflow on `+` or `div` * The `[0..]` needs to be the first argument of `zip`, no heap overflow on `zip [1] [0..]` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 17:55:19 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 17:55:19 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.e84481ecdb0fbed55c569471a2145f61@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): The `-ddump-rule-rewrites` output for this program is rather interesting: {{{ $ ghc -O -fforce-recomp -ddump-rule-rewrites Bug.hs [1 of 1] Compiling Test ( Bug.hs, Bug.o ) Rule fired Rule: ==# Module: (BUILTIN) Before: GHC.Prim.==# ValArg x_a2Lu ValArg 9223372036854775807# After: case x_a2Lu of wild_00 { __DEFAULT -> 0#; 9223372036854775807# -> 1# } Cont: StrictArg GHC.Prim.tagToEnum# Select nodup wild1_a2Lw Stop[RhsCtxt] [GHC.Integer.Type.Integer] -> GHC.Integer.Type.Integer -> GHC.Integer.Type.Integer Rule fired Rule: tagToEnum# Module: (BUILTIN) Before: GHC.Prim.tagToEnum# TyArg GHC.Types.Bool ValArg 0# After: GHC.Types.False Cont: Select ok wild1_a2Lw Stop[BoringCtxt] [GHC.Integer.Type.Integer] -> GHC.Integer.Type.Integer -> GHC.Integer.Type.Integer Rule fired Rule: tagToEnum# Module: (BUILTIN) Before: GHC.Prim.tagToEnum# TyArg GHC.Types.Bool ValArg 1# After: GHC.Types.True Cont: Select ok wild1_a2Lw Stop[BoringCtxt] [GHC.Integer.Type.Integer] -> GHC.Integer.Type.Integer -> GHC.Integer.Type.Integer Rule fired Rule: bitInteger Module: (BUILTIN) Before:ghc: Out of memory }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 19:29:21 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 19:29:21 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.cf7a985e6def6986b3b746cc8fb89fac@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 darchon): Incidentally, the `bitInteger` rule was updated/changed/added in 8.0.1 according to: * https://github.com/ghc/ghc/blob/abaf43d9d88d6fdf7345b936a571d17cfe1fa140/compiler/prelude/PrelRules.hs#L1324-L1338 * https://ghc.haskell.org/trac/ghc/ticket/8832 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 22:36:54 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 22:36:54 -0000 Subject: [GHC] #14951: SpecConstr needs two runs when one should suffice (was: SpecContsr needs two runs when one should suffice) In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.a7df6ec4f8551e6faaff009a3415726d@haskell.org> #14951: SpecConstr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 22:53:07 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 22:53:07 -0000 Subject: [GHC] #14954: Passing -fno-code disables reporting of some warnings In-Reply-To: <045.0b1aea2fec0c02d18d010967483b9949@haskell.org> References: <045.0b1aea2fec0c02d18d010967483b9949@haskell.org> Message-ID: <060.cff165f5cd0b66f452ab27446e32ed49@haskell.org> #14954: Passing -fno-code disables reporting of some warnings -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10600 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #10600 Comment: Indeed, this is a duplicate of #10600, as this emits the warning with GHC 8.4.1: {{{ $ /opt/ghc/8.4.1/bin/ghci -Wall -fno-code Bug.hsGHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, nothing ) Bug.hs:3:1: warning: [-Wmissing-signatures] Top-level binding with no type signature: main :: IO () | 3 | main = | ^^^^ Bug.hs:4:3: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In a case alternative: Patterns not matched: p where p is not one of {1} | 4 | case (1+1) :: Int of | ^^^^^^^^^^^^^^^^^^^^... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 22:54:13 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 22:54:13 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules In-Reply-To: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> References: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> Message-ID: <059.288b2be3ca4ce4af184b65da2458c6ee@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => ORF -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 23:09:55 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 23:09:55 -0000 Subject: [GHC] #14960: Invalid law for MonadPlus: v >> mzero = mzero Message-ID: <044.449c68dc8d30881b40ff3fbea7bc7774@haskell.org> #14960: Invalid law for MonadPlus: v >> mzero = mzero -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.2.2 libraries/base | Keywords: laws, mzero | 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 documentation of `MonadPlus` states: `v >> mzero = mzero`. This law is broken by `IO`, `MaybeT`, and a few other monads with some notion of "irreversible effects". I propose to just remove that law. https://hackage.haskell.org/package/base-4.11.0.0/docs/Control- Monad.html#t:MonadPlus Another alternative is to keep it but remove unlawful instances, so `MonadPlus` instances can signal that those laws hold, on top of the `Alternative` instances. But that breaks backwards compatibility, because `MonadPlus` for `IO` and `MaybeT` is already used in many places. This thread previously brought up the issue but hasn't been followed up: https://mail.haskell.org/pipermail/libraries/2014-January/021993.html, continued on https://mail.haskell.org/pipermail/libraries/2014-February/022004.html with some interesting discussion about what those laws should be. This even older thread also discusses `MonadPlus` laws, hence it also seems relevant to improve the documentation: https://mail.haskell.org/pipermail/haskell-cafe/2005-January/008751.html. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 21 23:45:58 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 21 Mar 2018 23:45:58 -0000 Subject: [GHC] #14731: Document alignment & underlying size invariants for array types in GHC.Prim In-Reply-To: <048.57574daf7b44935566d768b0adc24ecb@haskell.org> References: <048.57574daf7b44935566d768b0adc24ecb@haskell.org> Message-ID: <063.e7f3d6a2ccd0b24cfbb00e8a567333bb@haskell.org> #14731: Document alignment & underlying size invariants for array types in GHC.Prim -------------------------------------+------------------------------------- Reporter: jberryman | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2917 #9806 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jberryman): Documenting `newAlignedPinnedByteArray#` is also relevant. It seems that the alignment argument is only important for data that needs to be aligned to greater than word size (i.e. all byte arrays, pinned or not are word aligned). It's awkward to future-proof code for the case where GHC starts storing pinned arrays more tightly aligned. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 00:57:40 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 00:57:40 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.0b46f216cc69228478646d9b33e93714@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: 8.6.1 Component: Build 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): Phab:D1021 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): The PR has been merged, this is now covered explicitly in hadrian's documentation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 03:05:32 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 03:05:32 -0000 Subject: [GHC] #14961: QuantifiedConstraints: class name introduced via an equality constraint does not reduce Message-ID: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> #14961: QuantifiedConstraints: class name introduced via an equality constraint does not reduce -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints wipT2893 | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: #14860 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following doesn't typecheck with the `wip/T2893` branch: {{{#!hs {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE TypeFamilies #-} module Subst where class (forall x. c x => d x) => c ~=> d instance (forall x. c x => d x) => c ~=> d foo :: forall c a. c ~=> Monoid => (c a => a) -- ok foo = mempty bar :: forall c a m. (m ~ Monoid, c ~=> m) => (c a => a) -- ok bar = mempty baz :: forall c a. (forall m. m ~ Monoid => c ~=> m) => (c a => a) -- fails baz = mempty }}} {{{ Prelude> :reload [1 of 1] Compiling Subst ( src/Subst.hs, interpreted ) src/Subst.hs:21:7: error: • Could not deduce (Monoid a) arising from a use of ‘mempty’ from the context: (forall (m :: * -> Constraint). (m ~ Monoid) => c ~=> m, c a) bound by the type signature for: baz :: forall (c :: * -> Constraint) a. (forall (m :: * -> Constraint). (m ~ Monoid) => c ~=> m, c a) => a at src/Subst.hs:20:1-66 Possible fix: add (Monoid a) to the context of the type signature for: baz :: forall (c :: * -> Constraint) a. (forall (m :: * -> Constraint). (m ~ Monoid) => c ~=> m, c a) => a • In the expression: mempty In an equation for ‘baz’: baz = mempty | 21 | baz = mempty | ^^^^^^ Failed, no modules loaded. }}} Shouldn't the equality constraint be "substituted in"? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 03:06:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 03:06:57 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails (was: QuantifiedConstraints: class name introduced via an equality constraint does not reduce) In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.7288f005e3cc1876976f07218628b43c@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 04:09:31 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 04:09:31 -0000 Subject: [GHC] #14944: Compile speed regression In-Reply-To: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> References: <042.a1a810a22d187d8f36f05e0ae090a13a@haskell.org> Message-ID: <057.03e838628358911d8aa40247b223bb80@haskell.org> #14944: Compile speed regression -------------------------------------+------------------------------------- Reporter: br1 | Owner: dfeuer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): In case this helps any, the simplifier runs iteration 1,2,1,2,3,1,2,3, and then the next iteration (1) is the one that blows up the term count in 8.4.1. It appears that the blow-up is non-linear. When I increase the number of lines in the `Main.hs` source, the ratio of terms in that iteration to terms in the previous one increases. Similarly, the ratio of time and allocation in that simplifier run compared to the previous one increases. I've tried looking at a very cut-down version with `-ddump- simpl-iterations`, but there are still an awful lot of terms to look at. I'll keep at it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:02:02 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:02:02 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit Message-ID: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: | Owner: (none) martijnbastiaan | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code snippet: {{{#!hs module Test where import Data.Bits (setBit) import Data.List f :: Integer f = foldl setBit 0 toSet where toSet = [n | (n, _) <- zip [0..] [1]] }}} Fails to compile, yielding: {{{ martijn at qbltop:~/code/scratch$ ghc Test.hs -O1 [1 of 1] Compiling Test ( Test.hs, Test.o ) ghc: Out of memory }}} A few observations: - Compiling with no optimizations (-O0) works fine - I have not found a function other than setBit which triggers this behavior - Changing foldl to its strict brother foldl' does not help - Changing the type signature of "f" from "Integer" to "Int" causes the code to compile just fine I have been unable to reduce this example any further. I am using GHC 8.2.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:06:20 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:06:20 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.e149472b658680c123134491dd85b193@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by martijnbastiaan: Old description: > The following code snippet: > > {{{#!hs > module Test where > > import Data.Bits (setBit) > import Data.List > > f :: Integer > f = foldl setBit 0 toSet > where > toSet = [n | (n, _) <- zip [0..] [1]] > }}} > > Fails to compile, yielding: > > {{{ > martijn at qbltop:~/code/scratch$ ghc Test.hs -O1 > [1 of 1] Compiling Test ( Test.hs, Test.o ) > ghc: Out of memory > }}} > > A few observations: > > - Compiling with no optimizations (-O0) works fine > - I have not found a function other than setBit which triggers this > behavior > - Changing foldl to its strict brother foldl' does not help > - Changing the type signature of "f" from "Integer" to "Int" causes the > code to compile just fine > > I have been unable to reduce this example any further. I am using GHC > 8.2.1. New description: The following code snippet: {{{#!hs module Test where import Data.Bits (setBit) f :: Integer f = foldl setBit 0 toSet where toSet = [n | (n, _) <- zip [0..] [1]] }}} Fails to compile, yielding: {{{ martijn at qbltop:~/code/scratch$ ghc Test.hs -O1 [1 of 1] Compiling Test ( Test.hs, Test.o ) ghc: Out of memory }}} A few observations: - Compiling with no optimizations (-O0) works fine - I have not found a function other than setBit which triggers this behavior - Changing foldl to its strict brother foldl' does not help - Changing the type signature of "f" from "Integer" to "Int" causes the code to compile just fine - Changing [0..] to something silly like [0..2^1024] does not trigger the bug I have been unable to reduce this example any further. I am using GHC 8.2.1. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:07:51 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:07:51 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.a3c2a4ef18d2ccde92bde3d04f36a99d@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate Comment: See #14959 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:11:56 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:11:56 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.5952fc917106737d1882c48704cfd73b@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by martijnbastiaan): Ah alright, thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:25:13 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:25:13 -0000 Subject: [GHC] #94: Bad space behaviour with huge input file In-Reply-To: <042.80f11eb0988c096464f0c72de76154b1@haskell.org> References: <042.80f11eb0988c096464f0c72de76154b1@haskell.org> Message-ID: <057.5687aadfb3f8e2f652c698c45ff82331@haskell.org> #94: Bad space behaviour with huge input file --------------------------------+--------------------- Reporter: ajk | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 5.04 Resolution: Rejected | Keywords: Type of failure: None/Unknown | --------------------------------+--------------------- Changes (by Simon Peyton Jones ): * failure: => None/Unknown Comment: In [changeset:"411a97e2c0083529b4259d0cad8f453bae110dee/ghc" 411a97e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="411a97e2c0083529b4259d0cad8f453bae110dee" Allow as-patterns in unidirectional patttern synonyms This patch implements GHC Proposal #94, described here https://github.com/ghc-proposals/ghc-proposals/pull/94 The effect is simply to lift a totally-undocumented restriction to unidirecional pattern synonyms, namely that they can't have as-patterns or n+k patterns. The fix is easy: just remove the checks. I also took the opportunity to improve the manual entry for the semantics of pattern matching for pattern synonyms. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:25:13 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:25:13 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.1b9888f7f591814d132935623bb25d41@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"3446cee05e08d78033e141fa46d4de6929542cbb/ghc" 3446cee0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3446cee05e08d78033e141fa46d4de6929542cbb" Fix two obscure bugs in rule matching This patch fixes Trac #14777, a compiler crash. There were actually two bugs. 1. In Rules.matchN, I was (consciously) not rename the template binders of the rule. Sadly, in rare cases an accidental coincidence of uniques could mean that a term variable was mapped to a type variable, utterly bogusly. See "Historical note" in Note [Cloning the template binders] in Rules. This was hard to find, but easy to fix. 2. The fix to (1) showed up a bug in Unify.hs. The test in Unify.tvBindFlag was previously using the domain of the RnEnv2 to detect locally-bound variables (e.g. when unifying under a forall). That's fine when teh RnEnv2 starts empty, as it does in most entry points. But the tcMatchTyKisX entry point, used from the rule matcher, passes in a non-empty RnEnv2 (by design). Now the domain of the RnEnv doesn't idenfity those locally-bound variables any more :-(. Solution: extend UmEnv with a new field um_skols, to capture the skolems directly. Simple, easy, works. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:57:08 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:57:08 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.cf8e923ff43d27583a3c7015c9e0033e@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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): See also dup report #14962 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:59:03 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:59:03 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.812f5d0c9e0bb3c907ff99e0f5ad10bc@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: simonpj Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: Done. Merge to 8.4. Thank you to everyone who distilled the test case; that made it FAR easier for me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 08:59:23 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 08:59:23 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.50ee0bfebf61288302a0bdc5faecfbcd@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: simonpj Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): PS: No regression test because it's bizarrely difficult to reproduce. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 09:23:03 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 09:23:03 -0000 Subject: [GHC] #14777: panic when using a function defined in terms of `error` In-Reply-To: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> References: <045.edfc759cf3fa890282fee96e32a2a8f2@haskell.org> Message-ID: <060.27d74734784b709210a18663285f615c@haskell.org> #14777: panic when using a function defined in terms of `error` -------------------------------------+------------------------------------- Reporter: zilinc | Owner: simonpj Type: bug | Status: merge Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by zilinc): Many thanks to everyone who helped with this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 10:00:00 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 10:00:00 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.f4a4afcab635aa2530ceff5955364b73@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 this code in Core {{{ go_a2Rl = \ (x_a2Rm :: GHC.Prim.Int#) (eta_B1 :: [Integer]) (eta_X2 :: Integer) -> case eta_B1 of { [] -> eta_X2; : y_a2SA ys_a2SB -> let { eta_Xn :: Integer eta_Xn = GHC.Integer.Type.orInteger eta_X2 (GHC.Integer.Type.bitInteger x_a2Rm) } in case x_a2Rm of wild_XL { __DEFAULT -> go_a2Rl (GHC.Prim.+# wild_XL 1#) ys_a2SB eta_Xn; 9223372036854775807# -> eta_Xn } } }}} If we inline `eta_Xn` (which is only used once) we get {{{ ...(case x_a2Rm of wild_XL { __DEFAULT -> ... 9223372036854775807# -> GHC.Integer.Type.orInteger eta_X2 (GHC.Integer.Type.bitInteger x_a2Rm) )... }}} Now GHC sees that in the branch of the case it knows that `x = 9223372036854775807#`. So it tries to do constant folding. But the result is a rather big Integer: {{{ Prelude Data.Bits GHC.Exts> bit (I# 3#) :: Integer 8 Prelude Data.Bits GHC.Exts> bit (I# 4#) :: Integer 16 Prelude Data.Bits GHC.Exts> bit (I# 20#) :: Integer 1048576 Prelude Data.Bits GHC.Exts> bit (I# 60#) :: Integer 1152921504606846976 Prelude Data.Bits GHC.Exts> bit (I# 200#) :: Integer 1606938044258990275541962092341162602522202993782792835301376 }}} I'll leave you to imagine how big `bit 9223372036854775807#` is. Solution: the `bitInteger` rule should only work if its argument is "small enough". I suggest that "small enough" means "smaller than wordSizeInBits", ie x<64 on a 64 bit machine. I'm validating a patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 10:03:01 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 10:03:01 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.e01b5fc136770e7fa3d3ec42d170d2be@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I get different results for `wip/T2893` branch. First I need `FlexibleContexts`. Second, all the definitions fail. For the first one I get {{{ T14961.hs:16:8: error: • Could not deduce: c0 a from the context: (c ~=> Monoid, c a) bound by the type signature for: foo :: forall (c :: * -> Constraint) a. (c ~=> Monoid, c a) => a at T14961.hs:16:8-45 • In the ambiguity check for ‘foo’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: foo :: forall c a. c ~=> Monoid => (c a => a) | 16 | foo :: forall c a. c ~=> Monoid => (c a => a) -- ok | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ }}} And the same happens if I simplify the type a bit more to {{{ foo :: forall c a. (forall x. c x => Monoid x) => (c a => a) -- ok }}} Sure enough, this is an ambiguous type! In a call, how do you expect `c` to be instantiated?? I'm at a loss for what you are trying to achieve here. Before we can look at substituting equalities, we need to work out these simpler questions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 10:57:34 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 10:57:34 -0000 Subject: [GHC] #14958: QuantifiedConstraints: Doesn't apply implication for existential? In-Reply-To: <051.4c7a20f12068d6c91dfb6a24439e15b7@haskell.org> References: <051.4c7a20f12068d6c91dfb6a24439e15b7@haskell.org> Message-ID: <066.3541383e091e11a35b33becba3872de4@haskell.org> #14958: QuantifiedConstraints: Doesn't apply implication for existential? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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): This is to do with overlapping instances. We have {{{ Foo :: (forall x. ((forall y. cls y => Num y), cls x) => x) -> Foo }}} So from the expression `Foo 10` we have: Given: {{{ Skolems: x Given: d1: forall y. cls0 y => Num y d2: cls0 x Wanted: Num x }}} Here `cls0` is a unification variable; we don't yet know what it'll tur out to be, and indeed (given the type of `Foo`) it's ambiguous. When trying to solve `Num x` GHC doesn't want to use `d1`, because that make a commitment to solve its sub-goals. If `cls0` turned out to be `Num`, an alternative would be to pick `d2`. So it simply refrains from choosing. (The error message doesn't make this clear, I know.) If you fix `cls0` all is well. For example: {{{ data Foo (cls :: * -> Constraint) where Foo :: forall cls. (forall x. ((forall y. cls y => Num y), cls x) => x) -> Foo cls a :: Foo Fractional a = Foo 10 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 11:27:32 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 11:27:32 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.52acbf383888666391ef6ce43a8db59f@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"efc844f5b955385d69d8e20b80d38311083a6665/ghc" efc844f5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="efc844f5b955385d69d8e20b80d38311083a6665" Fix over-eager constant folding in bitInteger The RULE for bitInteger was trying to constant-fold bitInteger 9223372036854775807# which meant constructing a gigantic Integer at compile time. Very bad idea! Easily fixed. Fixes Trac #14959, #14962. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 11:27:32 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 11:27:32 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.a73b5bcb96d418e491c7124dabc6fe15@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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:"efc844f5b955385d69d8e20b80d38311083a6665/ghc" efc844f5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="efc844f5b955385d69d8e20b80d38311083a6665" Fix over-eager constant folding in bitInteger The RULE for bitInteger was trying to constant-fold bitInteger 9223372036854775807# which meant constructing a gigantic Integer at compile time. Very bad idea! Easily fixed. Fixes Trac #14959, #14962. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 11:58:03 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 11:58:03 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.e6c644aa846f340381eb4ad9499420bf@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mrkgnao): * Attachment "icelandjack-profunctor-optics.jpeg" added. Iceland_jack's encoding -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 11:58:26 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 11:58:26 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.a100f3c5fb65b0b2914fedcc102155c0@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mrkgnao): Sorry for the trouble! I truly don't understand what happened when I made the report: when I check it now, all the definitions fail, just as you said. And, worse, I just rewrote the code that I tried to "simplify" into the example in the original bug report, and it works now! Perhaps it might give you an idea of what I was trying to achieve. {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE QuantifiedConstraints #-} module QC where import Data.Kind import Control.Arrow (left, right, (&&&), (|||)) import Control.Category import Prelude hiding (id, (.)) import Data.Coerce class (forall x. f x => g x) => f ~=> g instance (forall x. f x => g x) => f ~=> g type family (#) (p :: Type -> Type -> Type) (ab :: (Type, Type)) = (r :: Type) | r -> p ab where p # '(a, b) = p a b newtype Glass :: ((Type -> Type -> Type) -> Constraint) -> (Type, Type) -> (Type, Type) -> Type where Glass :: (forall p. z p => p # ab -> p # st) -> Glass z st ab data A_Prism type family ConstraintOf (tag :: Type) = (r :: (Type -> Type -> Type) -> Constraint) where ConstraintOf A_Prism = Choice _Left0 :: Glass Choice '(Either a x, Either b x) '(a, b) _Left0 = Glass left' _Left1 :: c ~=> Choice => Glass c '(Either a x, Either b x) '(a, b) _Left1 = Glass left' -- fails with -- • Could not deduce (Choice p) -- _Left2 -- :: (forall p. c p => ConstraintOf A_Prism p) -- => Glass c '(Either a x, Either b x) '(a, b) -- _Left2 = Glass left' _Left3 :: d ~ ConstraintOf A_Prism => (forall p . c p => d p) => Glass c '(Either a x, Either b x) '(a, b) _Left3 = Glass left' -- fails to typecheck unless at least a partial type signature is provided -- l :: c ~=> Choice => Glass c _ _ -- l = _Left1 . _Left1 newtype Optic o st ab where Optic :: (forall c d. (d ~ ConstraintOf o, c ~=> d) => Glass c st ab) -> Optic o st ab _Left :: Optic A_Prism '(Either a x, Either b x) '(a, b) _Left = Optic _Left1 instance Category (Glass z) where id :: Glass z a a id = Glass id (.) :: Glass z uv ab -> Glass z st uv -> Glass z st ab Glass abuv . Glass uvst = Glass (uvst . abuv) class Profunctor (p :: Type -> Type -> Type) where dimap :: (a -> b) -> (c -> d) -> p b c -> p a d lmap :: (a -> b) -> p b c -> p a c rmap :: (b -> c) -> p a b -> p a c class Profunctor p => Choice (p :: Type -> Type -> Type) where left' :: p a b -> p (Either a c) (Either b c) right' :: p a b -> p (Either c a) (Either c b) }}} Iceland_jack suggested an interesting encoding of profunctor optics (https://pbs.twimg.com/media/DY1y3voX4AAh1Jj.jpg:large) where, instead of specifying the constraint `c` like is usually done in an encoding like {{{ type Optic c s t a b = forall p. c p => p a b -> p s t }}} we just put a bound on it, to get something like {{{ type QOptic c s t a b = forall p d. d ~=> c => Optic d s t a b }}} Then we can make optics where the profunctor satisfies _at least_ such- and-such constraint, but the quantified constraint lets you take it to satisfy something stronger (hence making it less general). This would mean that one could define a class whose instances would have to define something that was at least as good as a `Prism`, say, but the instances were free to define something better like a `Lens` or an `Iso`. Kmett has a sketch of this idea: https://gist.github.com/ekmett/af1c460582b1de467c8461abdf134b6f. I found that interesting, but for the fact that bindings with quantified constraints don't seem very friendly to inference, as I expected (e.g. `:type` doesn't work without `+v`, and, as shown above for the `l` binding, you can't write `_Left1 . _Left1` because the quantified `c` is ambiguous). So I thought of trying to encode things as newtypes: we could have a type tag `o` (like `A_Prism`) above that would, through a type family `ConstraintOf`, give us a constraint that we could then use as a minimum bound. This makes things much less fragile by wrapping the polymorphism inside a constructor, which I found appealing. Now, as in ticket:14860, this would mean trying to quantify a constraint involving a type family, which is not going to work directly. Hence the introduction of the `d` variable, which it seems does get substituted in, as one can check with `:type +v`: {{{ *QC> :t +v _Left1 _Left1 :: (c ~=> Choice) => Glass c '(Either a x, Either b x) '(a, b) }}} Now, this is weird, but I could swear that the trick with the `d` type variable didn't work when I submitted the bug report (likely a result of me reloading the wrong file in GHCi or something silly like that), and I "simplified" it down, poorly, to what I gave you. Apologies :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 11:59:31 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 11:59:31 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.d9c11d5fa74f4f6da9f5028deb77d040@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => simplCore/should_compile/T14959 * status: closed => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:00:00 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:00:00 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.138613b9c13d6f36b4c88b6e5c22c5f1@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: merge => new * resolution: duplicate => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:00:05 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:00:05 -0000 Subject: [GHC] #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit In-Reply-To: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> References: <054.66aee30f7b2d5477cb3a8056f8dd28b7@haskell.org> Message-ID: <069.dc77baa8a98db26553e988bbe3f5621e@haskell.org> #14962: "ghc: Out of memory" upon compiling combination of map/foldl/setBit -------------------------------------+------------------------------------- Reporter: martijnbastiaan | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: crash or panic | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:00:21 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:00:21 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.d5636b5f95ca46454c447e1ea87865a6@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => simplCore/should_compile/T14959 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:21:01 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:21:01 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.7148f553beb24d68da561dc98a4506d5@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It's fine; did not take long. If the code above reflects something you want to do, I could just add it to our regression tests. It seems to be a relatively sophisticated use of `QuantifiedConstraints`! I'm not following the details but I'm sure that you and Iceland Jack will tell us if any further infelicities show up. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:23:30 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:23:30 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules In-Reply-To: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> References: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> Message-ID: <059.19dc2aa74233fde814b08ef47456c386@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * cc: adamgundry, mpickering (added) Comment: Matthew or Adam: might you look? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:36:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:36:57 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.89050d90c4b00e57c95579dff9779abf@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mrkgnao): I think it would be good to add it as a regression test. Optics seem like an area where `QuantifiedConstraints` could simplify many things a lot! Also, is the incompatibility of `QuantifiedConstraints`-using bindings with `:type` in GHCi, or the inability to write, e.g. {{{#!hs _Left1 :: c ~=> Choice => Glass c '(Either a x, Either b x) '(a, b) _Left1 = Glass left' _Left4 = _Left1 {- src/Main.hs:73:10: error: • Could not deduce (Choice x1) arising from a use of ‘_Left1’ from the context: c x1 bound by a quantified context at src/Main.hs:73:1-15 Possible fix: add (Choice x1) to the context of a quantified context • In the expression: _Left1 In an equation for ‘_Left4’: _Left4 = _Left1 -} }}} expected? (I have `-XNoMonomorphismRestriction` on if that's relevant.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:37:24 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:37:24 -0000 Subject: [GHC] #14901: dsrun004 fails with most ways In-Reply-To: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> References: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> Message-ID: <063.50d704bb6d4de70717dedc4254d6258d@haskell.org> #14901: dsrun004 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun004 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): If I change one or more `seq`s into `pseq`, in order for this test to be a little more useful (because `pseq` might prevent some transformations that could make things go wrong with `seq`, so we can hope that the trace is reliably `one` then `two`), ghc isn't happy: {{{#!hs ... import GHC.Conc ... {-# NOINLINE f #-} f :: a -> b -> (# a,b #) f x y = x `pseq` y `pseq` (# x,y #) -- similar with x `pseq` y `seq` (# x,y #) }}} {{{ dsrun014.hs:10:9: error: • Couldn't match a lifted type with an unlifted type When matching types b0 :: * (# a, b #) :: TYPE ('GHC.Types.TupleRep '['GHC.Types.LiftedRep, 'GHC.Types.LiftedRep]) • In the expression: x `pseq` y `pseq` (# x, y #) In an equation for ‘f’: f x y = x `pseq` y `pseq` (# x, y #) • Relevant bindings include y :: b (bound at dsrun014.hs:10:5) x :: a (bound at dsrun014.hs:10:3) f :: a -> b -> (# a, b #) (bound at dsrun014.hs:10:1) dsrun014.hs:10:27: error: • Couldn't match a lifted type with an unlifted type When matching types b0 :: * (# a, b #) :: TYPE ('GHC.Types.TupleRep '['GHC.Types.LiftedRep, 'GHC.Types.LiftedRep]) • In the second argument of ‘pseq’, namely ‘(# x, y #)’ In the second argument of ‘pseq’, namely ‘y `pseq` (# x, y #)’ In the expression: x `pseq` y `pseq` (# x, y #) • Relevant bindings include y :: b (bound at dsrun014.hs:10:5) x :: a (bound at dsrun014.hs:10:3) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 12:38:59 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 12:38:59 -0000 Subject: [GHC] #14901: dsrun014 fails with most ways (was: dsrun004 fails with most ways) In-Reply-To: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> References: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> Message-ID: <063.397e20c1d9ce6603f3ae4ec9192ecb46@haskell.org> #14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * testcase: dsrun004 => dsrun014 Old description: > The `dsrun004` test doesn't seem to pass for a whole bunch of ways, as a > recent `./validate --slow` (against yesterday's master) revealed. > > {{{#!py > # the test options > test('dsrun014', normal, compile_and_run, ['-fobject-code']) > }}} > > {{{#!hs > -- the haskell program we build & run > {-# LANGUAGE UnboxedTuples #-} > > module Main where > > import Debug.Trace > > {-# NOINLINE f #-} > f :: a -> b -> (# a,b #) > f x y = x `seq` y `seq` (# x,y #) > > g :: Int -> Int -> Int > g v w = case f v w of > (# a,b #) -> a+b > > main = print (g (trace "one" 1) (trace "two" 2)) > -- The args should be evaluated in the right order! > }}} > > {{{ > # the failing ways > /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run > dsrun014 [bad stderr] (hpc) > /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run > dsrun014 [bad stderr] (optasm) > /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run > dsrun014 [bad stderr] (threaded2) > /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run > dsrun014 [bad stderr] (dyn) > /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run > dsrun014 [bad stderr] (optllvm) > }}} > > With those 5 ways, the program's trace is `two` then `one` while with > some other ways (like ghci or normal) we get (as expected by the > testsuite) `one` first and `two` afterwards. > > I'm not sure whether the expectation is too strong or whether there's > something fishy going on with those 5 ways. > > Simon, could you perhaps comment on this? Is this a "proper" bug? New description: The `dsrun014` test doesn't seem to pass for a whole bunch of ways, as a recent `./validate --slow` (against yesterday's master) revealed. {{{#!py # the test options test('dsrun014', normal, compile_and_run, ['-fobject-code']) }}} {{{#!hs -- the haskell program we build & run {-# LANGUAGE UnboxedTuples #-} module Main where import Debug.Trace {-# NOINLINE f #-} f :: a -> b -> (# a,b #) f x y = x `seq` y `seq` (# x,y #) g :: Int -> Int -> Int g v w = case f v w of (# a,b #) -> a+b main = print (g (trace "one" 1) (trace "two" 2)) -- The args should be evaluated in the right order! }}} {{{ # the failing ways /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (hpc) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (optasm) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (threaded2) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (dyn) /tmp/ghctest-n4fi8zlk/test spaces/./deSugar/should_run/dsrun014.run dsrun014 [bad stderr] (optllvm) }}} With those 5 ways, the program's trace is `two` then `one` while with some other ways (like ghci or normal) we get (as expected by the testsuite) `one` first and `two` afterwards. I'm not sure whether the expectation is too strong or whether there's something fishy going on with those 5 ways. Simon, could you perhaps comment on this? Is this a "proper" bug? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 13:10:04 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 13:10:04 -0000 Subject: [GHC] #14901: dsrun014 fails with most ways In-Reply-To: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> References: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> Message-ID: <063.e1e9b483269331d8a79e5179060e7a19@haskell.org> #14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): alpmestan, this is a consequence of the fact that `seq` has special typing rules. See `Note [Typing rule for seq]` in http://git.haskell.org/ghc.git/blob/efc844f5b955385d69d8e20b80d38311083a6665:/compiler/typecheck/TcExpr.hs#l334 how this is implemented (and why it's special). `pseq` does not have corresponding special typing rules, which is why it fails when given an unlifted argument. Should `pseq` be given similar magic? I'm not sure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 13:35:36 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 13:35:36 -0000 Subject: [GHC] #14949: Perform builds on non-Debian-based systems on Circle CI In-Reply-To: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> References: <045.268e746ab76f9908ab62816b8881cd4a@haskell.org> Message-ID: <060.29bcb29b27415eff8f3cd166d20093b5@haskell.org> #14949: Perform builds on non-Debian-based systems on Circle CI -------------------------------------+------------------------------------- Reporter: mrkkrp | Owner: mrkkrp Type: bug | Status: new Priority: normal | Milestone: Component: Continuous | Version: 8.2.2 Integration | 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 mrkkrp): Please see this PR: https://github.com/ghc/ghc/pull/114. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:25:13 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:25:13 -0000 Subject: [GHC] #14951: SpecConstr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.73346c27fc78745c3c272ea21eb292be@haskell.org> #14951: SpecConstr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Phab:D4519 Wiki Page: | -------------------------------------+------------------------------------- Changes (by nomeata): * status: new => patch * differential: => Phab:D4519 Comment: I put the code up for review and discussion at Phab:D4519 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:30:33 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:30:33 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.058aa9b9b37af8b2b9dd591982c2a877@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): You want GHC to ''infer'' a type with a quantified constraint. In general that is hard, and quite probably not what you wanted, so GHC doesn't even try. In short: no inferred type has a quantified constraint, only declared types. In GHCi, `:type ` infers the type of `` so you have the same issue. On the other hand `:info ` will work just fine. Does that make sense? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:33:30 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:33:30 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.8201372f6c35e0b318fd09a42429ce54@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): More data. #14951 fixes some regressions that loopification introduces: {{{ name previous change now nofib/allocs/last-piece 642047800 - 11.08% 570920968 bytes nofib/allocs/x2n1 697240 - 45.89% 377272 bytes }}} But it does not fix all the regressions that can be fixed by running !SpecConstr twice (with simplification in between): {{{ Benchmark previous change now nofib/allocs/constraints 20491632 - 3.63% 19747392 bytes nofib/allocs/event 129682800 + 8.44% 140626888 bytes nofib/allocs/fulsom 243329208 - 7.83% 224287496 bytes nofib/allocs/integer 40633632 - 3.06% 39389560 bytes nofib/allocs/last-piece 642047800 - 11.49% 568297080 bytes nofib/allocs/mandel2 1649568 - 26.78% 1207888 bytes nofib/allocs/minimax 5371584 - 8.73% 4902576 bytes nofib/allocs/parstof 3023208 - 3.7% 2911384 bytes nofib/allocs/x2n1 697240 - 45.89% 377272 bytes }}} Which raises the question: Should we just go the easy route and run !SpecConstr twice? (I am measuring the effect of that on master, independent of loopification, in branch `wip/T14951-blunt`.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:34:40 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:34:40 -0000 Subject: [GHC] #14955: Musings on manual type class desugaring In-Reply-To: <049.12855af11ea5950a6983dee948966231@haskell.org> References: <049.12855af11ea5950a6983dee948966231@haskell.org> Message-ID: <064.a3a1a67e03d6fd7ab9dab855643b9197@haskell.org> #14955: Musings on manual type class desugaring -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"034c32f6b8abd15eb9affca972844d3c6842af69/ghc" 034c32f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="034c32f6b8abd15eb9affca972844d3c6842af69" Improve shortOutIndirections slightly I found (when investigating Trac #14955) a binding looking like Rec { exported_id = ....big...lcl_id... ; lcl_id = exported_id } but bizarrely 'lcl_id' was chosen as the loop breaker, and never inlined. It turned out to be an unintended consequence of the shortOutIndirections code in SimplCore. Easily fixed. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:34:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:34:54 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.2d6beef049c1586329ebb236584f9fda@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mrkgnao): Yes, it does. Thanks for humouring me! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:36:10 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:36:10 -0000 Subject: [GHC] #14961: QuantifiedConstraints: introducing classes through equality constraints fails In-Reply-To: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> References: <046.a15bc00dd1f7753011e170d68fde9865@haskell.org> Message-ID: <061.0b5827dfd4959c7f7cf1cdf251ba89e6@haskell.org> #14961: QuantifiedConstraints: introducing classes through equality constraints fails -------------------------------------+------------------------------------- Reporter: mrkgnao | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #14860 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mrkgnao): * status: new => closed * resolution: => invalid -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 14:52:43 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 14:52:43 -0000 Subject: [GHC] #14942: QuantifiedConstraints: GHC can't infer In-Reply-To: <051.958f742763b6ceef29a453a2ee8d4b69@haskell.org> References: <051.958f742763b6ceef29a453a2ee8d4b69@haskell.org> Message-ID: <066.6aeb24a0d92a986246972b49eec083da@haskell.org> #14942: QuantifiedConstraints: GHC can't infer -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: > If we comment out together's type signature GHC cannot infer it back, shouldn't it be able to though? No, that's by design. Currently GHC makes no attempt to ''infer'' a type with a quantified constraint. It's not impossible to do so -- even fairly easy -- but I worry that they'd then pop up unexpectedly in programs where there was simply a type error. For now, write a type signature; but re-raise it if that seems to be becoming onerous. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 17:31:44 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 17:31:44 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.e544198a38d15bc335451faf4c35020b@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 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:D4503 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Well, * `initTcForLookup` initialises the `tcg_rdr_env` to `emptyGlobalRdrEnv`, and `tcl_rdr` to `emptyLocalRdrEnv`. * So in `lookupThName_maybe`, the `lookupLocalRdrEnv` is guaranteed to faile; and in `lookupGlobalOccRn_maybe` only the `lookupExactOrOrig` stuff can succeed. * For `lookupOrig` we are simply looking in the `OrigNameCache`, which is available in `CoreM`. * I think `lookupExact` is even easier, because I think the name must be an External name. Maybe that can help you get further -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 17:43:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 17:43:35 -0000 Subject: [GHC] #14832: QuantifiedConstraints: Adding to the context causes failure In-Reply-To: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> References: <051.dff6dedd461af3d1758ad7cdadcbf206@haskell.org> Message-ID: <066.fc0976d9eb8c7b6e6992e97d58a45730@haskell.org> #14832: QuantifiedConstraints: Adding to the context causes failure -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints wipT2893 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): See also #14937. I'm too snowed under to think about this -- but open to worked-out suggestions if you want to progress it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 17:43:52 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 17:43:52 -0000 Subject: [GHC] #14937: QuantifiedConstraints: Reify implication constraints from terms lacking them In-Reply-To: <044.d2a38f2a080b1fef4440349e47b3df3b@haskell.org> References: <044.d2a38f2a080b1fef4440349e47b3df3b@haskell.org> Message-ID: <059.1d277b9d03f6f238f55949405fed5ef3@haskell.org> #14937: QuantifiedConstraints: Reify implication constraints from terms lacking them -------------------------------------+------------------------------------- Reporter: Bj0rn | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14822 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): See also #14832 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 17:50:33 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 17:50:33 -0000 Subject: [GHC] #14896: QuantifiedConstraints: GHC does doesn't discharge constraints if they are quantified In-Reply-To: <051.1cc6b03dde1d531c03c6cbc0cd468d33@haskell.org> References: <051.1cc6b03dde1d531c03c6cbc0cd468d33@haskell.org> Message-ID: <066.5e93ee4dc0e780295d19f202f60988da@haskell.org> #14896: QuantifiedConstraints: GHC does doesn't discharge constraints if they are quantified -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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. When inferring a type, GHC finds all the unsolved constraints. Supopse they are `(Eq a, Ord a)`. Then it minimises them in a very simple-minded way, dicarding any that are implied by the superclasses of some other constraint. So, since `Eq a` is a superclass of `Ord a`, we discard it. So we infer a type like {{{ f :: Ord a => blah }}} Now suppose we have `(Bifunctor bi, Functor (bi a))`. Yes, the latter is implied by the former, but now it is much more indirect. I'm not yet sure how to do a better job here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 22 18:32:44 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 22 Mar 2018 18:32:44 -0000 Subject: [GHC] #14943: Make (=>) polykinded (:: k -> k -> Constraint) In-Reply-To: <051.6fe39954d13f1f127aabba85c357373f@haskell.org> References: <051.6fe39954d13f1f127aabba85c357373f@haskell.org> Message-ID: <066.553f57abddf58649238561c52823ea5c@haskell.org> #14943: Make (=>) polykinded (:: k -> k -> Constraint) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Yeah... I'm certainly not convinced this is a good idea. This seems needlessly magical, and moreover, oddly asymmetric with the typing rule for `(->)`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 00:03:56 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 00:03:56 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module Message-ID: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.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 enough to trigger a crash on OS X and Linux: Bug1.hs: {{{ module Bug1.hs where import qualified Bug2 test :: IO Bool test = Bug2.failure }}} Bug2.hs: {{{ module Bug2 where failure :: IO Bool failure = return False }}} Shell: {{{ % ghci -fdefer-type-errors -ignore-dot-ghci GHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Prelude> :load Bug [1 of 2] Compiling Bug2 ( Bug2.hs, interpreted ) [2 of 2] Compiling Bug ( Bug.hs, interpreted ) Ok, two modules loaded. *Bug> test ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-apple-darwin): nameModule system $dShow_a1LX Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Name.hs:241:3 in ghc:Name Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This is specific to 8.4.1, in 8.0.2 I get "False" as expected. If I leave off -fdefer-type-errors, it works. It also seems to be ghci only, compiling with -fdefer-type-errors doesn't have the problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 00:10:19 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 00:10:19 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 Message-ID: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: -------------------------------------+------------------------------------- === Short version: Between 8.0.2 and 8.4.1, compile time without optimization got faster. Compile time with optimization got slightly slower. Performance of generated (optimized) code got significantly slower, and GC productivity went down, despite allocation being about the same. I made this a "task", not a "bug", because there's a ways to go to figure out what is causing this. === Long version, copy and pasted from email to glasgow-haskell-users: I just upgraded from 8.0.2 to 8.4.1, and I took the opportunity to do a few informal compile time and run time tests. There's been a lot of talk about compile time regressions, so maybe these will be of interest, informal as they are. I wound up skipping 8.2.1 due to https://ghc.haskell.org/trac/ghc/ticket/13604, but I could still test with 8.2 perfectly well. Just haven't done it yet. In this context, RunTests is more code with no optimization (and -fhpc, if it matters). debug/seq and opt/seq are the same code but with no optimization and -O respectively. I found that -O2 hurt compile time but didn't improve run time, but it's been a long time so I should run that experiment again. compile times: OS X, macbook pro: {{{ RunTests 549.10s user 118.45s system 343% cpu 3:14.53 total 8.0.2 RunTests 548.71s user 117.10s system 347% cpu 3:11.78 total 8.0.2 RunTests 450.92s user 109.63s system 343% cpu 2:43.13 total 8.4.1 RunTests 445.48s user 107.99s system 341% cpu 2:42.19 total 8.4.1 debug/seq 284.47s user 55.95s system 345% cpu 1:38.58 total 8.0.2 debug/seq 283.33s user 55.27s system 343% cpu 1:38.53 total 8.0.2 debug/seq 220.92s user 50.21s system 337% cpu 1:20.32 total 8.4.1 debug/seq 218.39s user 49.20s system 345% cpu 1:17.47 total 8.4.1 opt/seq 732.63s user 70.86s system 338% cpu 3:57.30 total 8.0.2 opt/seq 735.21s user 71.48s system 327% cpu 4:06.31 total 8.0.2 opt/seq 785.12s user 65.42s system 327% cpu 4:19.84 total 8.4.1 opt/seq 765.52s user 64.01s system 321% cpu 4:18.29 total 8.4.1 }}} Linux, PC: {{{ RunTests 781.31s user 58.21s system 363% cpu 3:50.70 total 8.0.2 RunTests 613.11s user 49.84s system 357% cpu 3:05.52 total 8.4.1 debug/seq 429.44s user 31.34s system 362% cpu 2:07.03 total 8.0.2 debug/seq 329.67s user 23.86s system 352% cpu 1:40.38 total 8.4.1 opt/seq 1277.20s user 45.85s system 358% cpu 6:08.68 total 8.0.2 opt/seq 1339.73s user 39.87s system 341% cpu 6:43.50 total 8.4.1 }}} So it looks like non-optimized compile times have gotten significantly better since 8.0.2. However, optimized has gotten a little worse, but not much. The performance numbers are a bit more disappointing. At first it appeared that allocation went down in 8.4.1 while overall time is up significantly. However, the 8.4.1 used newer dependencies, so to try to control for those, I tested again after using a cabal freeze from the 8.4.1 test. Of course I had to remove the ghc distributed packages, like container and 'ghc' itself, but the rest of the deps should be the same. Those have the 'libs' suffix on Linux. From that, it looks like the improved memory in 8.4.1 was due to external dependencies, and in fact 8.4.1 bumped memory usage up again. Ow. In the graphs, 'score' is just the input file. 'max mb' and 'total mb' and 'prd' come from the post-run GC report, specifically '* bytes maximum residency', '* bytes allocated in the heap', and productivity fields. 'derive', 'lily' and 'perform' are just different kinds of processes. They are CPU time bracketing the specific action, after initialization, and the range is min and max over 6 runs, so no fancy criterion-like analysis. Each run is a separate process, so they should be independent. I was hoping for some gains due to the join points stuff, but it kind of looks like things get worse across the board. I don't know why productivity goes down so much, and I don't know why the effect seems so much worse on OS X. Of course the obvious next step is to see where 8.2.1 lies, but I thought I'd see if there's interest before going to the trouble. Of course, I should track down the regressions for my own purposes, but it's a bit of a daunting task. The step of reducing to a minimal example seems a lot harder for performance than for a bug! Probably some old fashioned SCC annotations await me, but that can be a long and confusing process. OS X, macbook pro: {{{ score max mb total mb prd derive lily perform ghc 6 72.26 3279.22 0.88 0.79~0.84 0.70~0.74 0.31~0.33 8.0.2 6 76.63 3419.20 0.58 1.45~1.59 1.05~1.07 0.33~0.36 8.4.1 bloom 70.69 2456.14 0.89 1.32~1.36 0.15~0.16 8.0.2 bloom 67.86 2589.97 0.62 1.94~1.99 0.20~0.22 8.4.1 cerucuk-punyah 138.01 10080.55 0.93 6.98~7.16 1.24~1.30 8.0.2 cerucuk-punyah 130.78 9617.35 0.68 8.91~9.22 1.57~1.68 8.4.1 hex 32.86 2120.95 0.91 0.76~0.88 0.16~0.19 8.0.2 hex 32.67 2194.82 0.66 1.09~1.16 0.28~0.30 8.4.1 p1 67.01 4039.82 0.92 2.63~2.73 0.47~0.50 8.0.2 p1 64.80 3899.85 0.68 3.35~3.43 0.58~0.59 8.4.1 viola-sonata 69.32 6083.65 0.92 2.48~2.56 2.07~2.13 0.25~0.26 8.0.2 viola-sonata 66.76 6120.26 0.68 3.32~3.43 2.90~2.93 0.32~0.34 8.4.1 }}} Linux, PC: {{{ score max mb total mb prd derive lily perform ghc 6 79.76 3310.69 0.89 0.88~0.89 0.73~0.75 0.27~0.27 8.0.2 6 72.21 3421.45 0.90 0.87~0.87 0.72~0.79 0.28~0.28 8.0.2 libs 6 76.56 3419.05 0.77 1.16~1.17 0.87~0.93 0.33~0.33 8.4.1 bloom 69.82 2461.95 0.89 1.35~1.36 0.17~0.17 8.0.2 bloom 63.45 2554.89 0.90 1.33~1.35 0.18~0.18 8.0.2 libs bloom 67.79 2589.85 0.79 1.64~1.65 0.20~0.20 8.4.1 cerucuk-punyah 137.05 10113.41 0.94 7.44~7.50 1.31~1.33 8.0.2 cerucuk-punyah 128.09 10278.03 0.94 7.50~7.55 1.37~1.38 8.0.2 libs cerucuk-punyah 131.20 9617.22 0.84 7.35~7.40 1.49~1.50 8.4.1 hex 32.02 2096.87 0.92 0.73~0.74 0.18~0.18 8.0.2 hex 32.05 2200.30 0.91 0.73~0.80 0.19~0.19 8.0.2 libs hex 32.46 2144.22 0.83 0.89~0.90 0.20~0.20 8.4.1 p1 65.88 4054.66 0.93 2.84~2.87 0.49~0.50 8.0.2 p1 62.60 4127.68 0.94 2.83~2.92 0.51~0.51 8.0.2 libs p1 64.72 3899.72 0.81 2.80~2.81 0.54~0.55 8.4.1 viola-sonata 68.68 6086.49 0.93 2.55~2.56 2.10~2.12 0.27~0.27 8.0.2 viola-sonata 65.05 6212.57 0.93 2.52~2.55 2.07~2.16 0.28~0.28 8.0.2 libs viola-sonata 66.85 6120.15 0.83 2.91~2.92 2.48~2.51 0.30~0.31 8.4.1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 02:24:11 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 02:24:11 -0000 Subject: [GHC] #14948: A program which benefits from a late specialisation pass In-Reply-To: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> References: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> Message-ID: <064.0525dd52ad8145fcd2690d436d91be02@haskell.org> #14948: A program which benefits from a late specialisation pass -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 dfeuer): I don't know if this is related. I asked Johan Tibell the other day why `unordered-containers` marks almost everything `INLINE` instead of `INLINABLE`. He replied that when an `INLINE` function calls an `INLINABLE` one, we end up calling to specialize. He also indicated that he'd opened a ticket about this long ago; I don't know which one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 02:24:40 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 02:24:40 -0000 Subject: [GHC] #14948: A program which benefits from a late specialisation pass In-Reply-To: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> References: <049.24236ea92957ef283e42d36b4dedf46c@haskell.org> Message-ID: <064.45de2635c40e4d589e90693af6f6823f@haskell.org> #14948: A program which benefits from a late specialisation pass -------------------------------------+------------------------------------- Reporter: mpickering | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 02:35:22 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 02:35:22 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.cc706ced5a14d6fe0a8146358b3071d7@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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): Could we skirt the problem using typeclass machinery? Instead of {{{#!hs bTwice :: ∀ (r :: RuntimeRep) (a :: TYPE r). Bool → a → (a → a) → a }}} What if we have {{{#!hs bTwice :: ∀ (r :: RuntimeRep) (a :: TYPE r). KnownRep r => Bool → a → (a → a) → a }}} To call this function, we consult the `KnownRep` dictionary to discover its calling conventions. Obviously everything will be terrible if it doesn't specialize, but maybe there's a way to make it work soundly otherwise? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 02:36:17 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 02:36:17 -0000 Subject: [GHC] #14917: Allow levity polymorhism in binding position In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.6286672f53fec5366fd3cff9a85cb135@haskell.org> #14917: Allow levity polymorhism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 02:36:52 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 02:36:52 -0000 Subject: [GHC] #14917: Allow levity polymorphism in binding position (was: Allow levity polymorhism in binding position) In-Reply-To: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> References: <049.d67991f1b0cd65b675056d1b1f0986b9@haskell.org> Message-ID: <064.a78f73afa465eaa5664733eb959f8c75@haskell.org> #14917: Allow levity polymorphism in binding position -------------------------------------+------------------------------------- Reporter: andrewthad | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | LevityPolymorphism 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 Fri Mar 23 02:45:55 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 02:45:55 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.d14b1945e05617fba0c35e96d8807b2c@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.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 chak): * cc: chak@… (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 04:35:05 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 04:35:05 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.a6a2f83f741cfc8744d4af370a2be017@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by kavon): I've been playing around with `wip/T14068-inline`, and the behavior I was seeing occurs with this simple example: {{{ countDown n = case n of 0 -> 0 n -> countDown (n - 1) ... countDown 10 {- non-tail call -} ... }}} countDown satisfies our `RecursiveTailCalled` requirement right out of the gate, and is marked as such by OccurAnal. With loopification turned off, the first simplification pass will give us: {{{ countDown :: forall t p. (Eq t, Num t, Num p) => t -> p [LclIdX, Arity=4, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 90 30 0] 550 0}] countDown = \ (@ t_a2HQ) (@ p_a1vP) ($dEq_a2OT :: Eq t_a2HQ) ($dNum_a2OU :: Num t_a2HQ) ($dNum_a2OV :: Num p_a1vP) (eta_B1 :: t_a2HQ) -> letrec { countDown_a1vH [Occ=LoopBreaker] :: t_a2HQ -> p_a1vP [LclId, Arity=1] countDown_a1vH = \ (n_aX3 :: t_a2HQ) -> case == @ t_a2HQ $dEq_a2OT n_aX3 (fromInteger @ t_a2HQ $dNum_a2OU 0) of { False -> countDown_a1vH (- @ t_a2HQ $dNum_a2OU n_aX3 (fromInteger @ t_a2HQ $dNum_a2OU 1)); True -> fromInteger @ p_a1vP $dNum_a2OV 0 }; } in countDown_a1vH eta_B1 }}} Thanks to the eta-expansion, `countDown_a1vH` can now be turned into a full join point. Thus, we didn't gain anything by performing loopification so early, though we also lose nothing since we end up with the same code after some clean up... just a small observation. A more troubling behavior I've spotted happens in `queens`, where we end up with some good looking code after we loopify and then inline the once- called `safe`, but all of that progress seems to be undone by FloatOut. Simplification will then redo all of that work. I wonder if it would be more efficient to use loopification after outward let-floating? Also: I think I've narrowed down where the slowdown comes from in `queens`. I'll post the details in a later comment since I need to be up early tomorrow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 07:08:44 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 07:08:44 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails Message-ID: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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: -------------------------------------+------------------------------------- A simple program that works in 8.2.1 fails in 8.4.1 when compiled with -O. (Sorry, haven't tested 8.2.2.) GHC with -dcore-lint reports an error. See attached files. In one file I declared: {{{#!hs module Sep where data Sep = Sep { bugVanishesWithoutThis :: [()] , middle :: [String] , orThis :: [()] } catSep :: Sep -> Sep -> Sep catSep (Sep a b c) (Sep x y z) = Sep (a ++ x) (b ++ y) (c ++ z) cc :: Sep -> Bool cc boost = elem "foo" $ middle boost }}} and in a second file, simple code fails when compiled with -O: {{{#!hs module Main (main) where import Sep main :: IO () main = print $ cc bb bb :: Sep bb = catSep b1 b2 b1 :: Sep b1 = Sep [] ["foo"] [] b2 :: Sep b2 = Sep [] ["bar"] [] }}} This should print "True", and does so for GHC 8.2.1, and GHC 8.4.1 without -O, but prints "False" for GHC 8.4.1 with -O. I was unable to reproduce the bug with a single file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 07:09:00 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 07:09:00 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.4f5bb1d45dbb339d2f4e982d425fb8f2@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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 blynn): * Attachment "bug.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 07:09:20 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 07:09:20 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.671a69d86888e76cd073f9c0a8729969@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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 blynn): * Attachment "Sep.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 07:10:39 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 07:10:39 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.5c0464515ba38af56c92b8d8eb0624ea@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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 blynn): * Attachment "corelint.dump" added. dump of -O -dcore-lint -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 07:12:41 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 07:12:41 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.89aa6b087bf867f5778d56ec4a42a81b@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 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 blynn): * cc: benlynn@… (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 08:14:58 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 08:14:58 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.dfadcf8588e7988c73e815682dd98adc@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 simonpj): * failure: None/Unknown => Runtime performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 08:18:34 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 08:18:34 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.2512398d3ecd14768009c225652998a4@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description: > === Short version: > > Between 8.0.2 and 8.4.1, compile time without optimization got faster. > Compile time with optimization got slightly slower. > > Performance of generated (optimized) code got significantly slower, and > GC productivity went down, despite allocation being about the same. > > I made this a "task", not a "bug", because there's a ways to go to figure > out what is causing this. > > === Long version, copy and pasted from email to glasgow-haskell-users: > > I just upgraded from 8.0.2 to 8.4.1, and I took the opportunity to do a > few > informal compile time and run time tests. There's been a lot of talk > about > compile time regressions, so maybe these will be of interest, informal as > they are. > > I wound up skipping 8.2.1 due to > https://ghc.haskell.org/trac/ghc/ticket/13604, > but I could still test with 8.2 perfectly well. Just haven't done it > yet. > > In this context, RunTests is more code with no optimization (and -fhpc, > if it > matters). debug/seq and opt/seq are the same code but with no > optimization and > -O respectively. I found that -O2 hurt compile time but didn't improve > run > time, but it's been a long time so I should run that experiment again. > > compile times: > > OS X, macbook pro: > > {{{ > RunTests 549.10s user 118.45s system 343% cpu 3:14.53 total > 8.0.2 > RunTests 548.71s user 117.10s system 347% cpu 3:11.78 total > 8.0.2 > RunTests 450.92s user 109.63s system 343% cpu 2:43.13 total > 8.4.1 > RunTests 445.48s user 107.99s system 341% cpu 2:42.19 total > 8.4.1 > > debug/seq 284.47s user 55.95s system 345% cpu 1:38.58 total > 8.0.2 > debug/seq 283.33s user 55.27s system 343% cpu 1:38.53 total > 8.0.2 > debug/seq 220.92s user 50.21s system 337% cpu 1:20.32 total > 8.4.1 > debug/seq 218.39s user 49.20s system 345% cpu 1:17.47 total > 8.4.1 > > opt/seq 732.63s user 70.86s system 338% cpu 3:57.30 total > 8.0.2 > opt/seq 735.21s user 71.48s system 327% cpu 4:06.31 total > 8.0.2 > opt/seq 785.12s user 65.42s system 327% cpu 4:19.84 total > 8.4.1 > opt/seq 765.52s user 64.01s system 321% cpu 4:18.29 total > 8.4.1 > }}} > > Linux, PC: > > {{{ > RunTests 781.31s user 58.21s system 363% cpu 3:50.70 total > 8.0.2 > RunTests 613.11s user 49.84s system 357% cpu 3:05.52 total > 8.4.1 > > debug/seq 429.44s user 31.34s system 362% cpu 2:07.03 total > 8.0.2 > debug/seq 329.67s user 23.86s system 352% cpu 1:40.38 total > 8.4.1 > > opt/seq 1277.20s user 45.85s system 358% cpu 6:08.68 total > 8.0.2 > opt/seq 1339.73s user 39.87s system 341% cpu 6:43.50 total > 8.4.1 > }}} > > So it looks like non-optimized compile times have gotten significantly > better > since 8.0.2. However, optimized has gotten a little worse, but not much. > > The performance numbers are a bit more disappointing. At first it > appeared > that allocation went down in 8.4.1 while overall time is up > significantly. > However, the 8.4.1 used newer dependencies, so to try to control for > those, I > tested again after using a cabal freeze from the 8.4.1 test. Of course I > had > to remove the ghc distributed packages, like container and 'ghc' itself, > but > the rest of the deps should be the same. Those have the 'libs' suffix on > Linux. > > From that, it looks like the improved memory in 8.4.1 was due to external > dependencies, and in fact 8.4.1 bumped memory usage up again. Ow. > > In the graphs, 'score' is just the input file. 'max mb' and 'total mb' > and > 'prd' come from the post-run GC report, specifically '* bytes maximum > residency', '* bytes allocated in the heap', and productivity fields. > 'derive', 'lily' and 'perform' are just different kinds of processes. > They are > CPU time bracketing the specific action, after initialization, and the > range is > min and max over 6 runs, so no fancy criterion-like analysis. Each run > is a > separate process, so they should be independent. > > I was hoping for some gains due to the join points stuff, but it kind of > looks > like things get worse across the board. I don't know why productivity > goes > down so much, and I don't know why the effect seems so much worse on OS > X. > > Of course the obvious next step is to see where 8.2.1 lies, but I thought > I'd > see if there's interest before going to the trouble. Of course, I should > track > down the regressions for my own purposes, but it's a bit of a daunting > task. > The step of reducing to a minimal example seems a lot harder for > performance > than for a bug! Probably some old fashioned SCC annotations await me, > but that > can be a long and confusing process. > > OS X, macbook pro: > {{{ > score max mb total mb prd derive lily perform > ghc > 6 72.26 3279.22 0.88 0.79~0.84 0.70~0.74 0.31~0.33 > 8.0.2 > 6 76.63 3419.20 0.58 1.45~1.59 1.05~1.07 0.33~0.36 > 8.4.1 > > bloom 70.69 2456.14 0.89 1.32~1.36 0.15~0.16 > 8.0.2 > bloom 67.86 2589.97 0.62 1.94~1.99 0.20~0.22 > 8.4.1 > > cerucuk-punyah 138.01 10080.55 0.93 6.98~7.16 1.24~1.30 > 8.0.2 > cerucuk-punyah 130.78 9617.35 0.68 8.91~9.22 1.57~1.68 > 8.4.1 > > hex 32.86 2120.95 0.91 0.76~0.88 0.16~0.19 > 8.0.2 > hex 32.67 2194.82 0.66 1.09~1.16 0.28~0.30 > 8.4.1 > > p1 67.01 4039.82 0.92 2.63~2.73 0.47~0.50 > 8.0.2 > p1 64.80 3899.85 0.68 3.35~3.43 0.58~0.59 > 8.4.1 > > viola-sonata 69.32 6083.65 0.92 2.48~2.56 2.07~2.13 0.25~0.26 > 8.0.2 > viola-sonata 66.76 6120.26 0.68 3.32~3.43 2.90~2.93 0.32~0.34 > 8.4.1 > }}} > > Linux, PC: > > {{{ > score max mb total mb prd derive lily perform > ghc > > 6 79.76 3310.69 0.89 0.88~0.89 0.73~0.75 0.27~0.27 > 8.0.2 > 6 72.21 3421.45 0.90 0.87~0.87 0.72~0.79 0.28~0.28 > 8.0.2 libs > 6 76.56 3419.05 0.77 1.16~1.17 0.87~0.93 0.33~0.33 > 8.4.1 > > bloom 69.82 2461.95 0.89 1.35~1.36 0.17~0.17 > 8.0.2 > bloom 63.45 2554.89 0.90 1.33~1.35 0.18~0.18 > 8.0.2 libs > bloom 67.79 2589.85 0.79 1.64~1.65 0.20~0.20 > 8.4.1 > > cerucuk-punyah 137.05 10113.41 0.94 7.44~7.50 1.31~1.33 > 8.0.2 > cerucuk-punyah 128.09 10278.03 0.94 7.50~7.55 1.37~1.38 > 8.0.2 libs > cerucuk-punyah 131.20 9617.22 0.84 7.35~7.40 1.49~1.50 > 8.4.1 > > hex 32.02 2096.87 0.92 0.73~0.74 0.18~0.18 > 8.0.2 > hex 32.05 2200.30 0.91 0.73~0.80 0.19~0.19 > 8.0.2 libs > hex 32.46 2144.22 0.83 0.89~0.90 0.20~0.20 > 8.4.1 > > p1 65.88 4054.66 0.93 2.84~2.87 0.49~0.50 > 8.0.2 > p1 62.60 4127.68 0.94 2.83~2.92 0.51~0.51 > 8.0.2 libs > p1 64.72 3899.72 0.81 2.80~2.81 0.54~0.55 > 8.4.1 > > viola-sonata 68.68 6086.49 0.93 2.55~2.56 2.10~2.12 0.27~0.27 > 8.0.2 > viola-sonata 65.05 6212.57 0.93 2.52~2.55 2.07~2.16 0.28~0.28 > 8.0.2 libs > viola-sonata 66.85 6120.15 0.83 2.91~2.92 2.48~2.51 0.30~0.31 > 8.4.1 > }}} New description: === Short version: Between 8.0.2 and 8.4.1, compile time without optimization got faster. Compile time with optimization got slightly slower. Performance of generated (optimized) code got significantly slower, and GC productivity went down, despite allocation being about the same. I made this a "task", not a "bug", because there's a ways to go to figure out what is causing this. == Long version, copy and pasted from email to glasgow-haskell-users: I just upgraded from 8.0.2 to 8.4.1, and I took the opportunity to do a few informal compile time and run time tests. There's been a lot of talk about compile time regressions, so maybe these will be of interest, informal as they are. I wound up skipping 8.2.1 due to https://ghc.haskell.org/trac/ghc/ticket/13604, but I could still test with 8.2 perfectly well. Just haven't done it yet. In this context, RunTests is more code with no optimization (and -fhpc, if it matters). debug/seq and opt/seq are the same code but with no optimization and -O respectively. I found that -O2 hurt compile time but didn't improve run time, but it's been a long time so I should run that experiment again. ------------------------------ == Compile time performance: OS X, macbook pro: {{{ RunTests 549.10s user 118.45s system 343% cpu 3:14.53 total 8.0.2 RunTests 548.71s user 117.10s system 347% cpu 3:11.78 total 8.0.2 RunTests 450.92s user 109.63s system 343% cpu 2:43.13 total 8.4.1 RunTests 445.48s user 107.99s system 341% cpu 2:42.19 total 8.4.1 debug/seq 284.47s user 55.95s system 345% cpu 1:38.58 total 8.0.2 debug/seq 283.33s user 55.27s system 343% cpu 1:38.53 total 8.0.2 debug/seq 220.92s user 50.21s system 337% cpu 1:20.32 total 8.4.1 debug/seq 218.39s user 49.20s system 345% cpu 1:17.47 total 8.4.1 opt/seq 732.63s user 70.86s system 338% cpu 3:57.30 total 8.0.2 opt/seq 735.21s user 71.48s system 327% cpu 4:06.31 total 8.0.2 opt/seq 785.12s user 65.42s system 327% cpu 4:19.84 total 8.4.1 opt/seq 765.52s user 64.01s system 321% cpu 4:18.29 total 8.4.1 }}} Linux, PC: {{{ RunTests 781.31s user 58.21s system 363% cpu 3:50.70 total 8.0.2 RunTests 613.11s user 49.84s system 357% cpu 3:05.52 total 8.4.1 debug/seq 429.44s user 31.34s system 362% cpu 2:07.03 total 8.0.2 debug/seq 329.67s user 23.86s system 352% cpu 1:40.38 total 8.4.1 opt/seq 1277.20s user 45.85s system 358% cpu 6:08.68 total 8.0.2 opt/seq 1339.73s user 39.87s system 341% cpu 6:43.50 total 8.4.1 }}} So it looks like non-optimized compile times have gotten significantly better since 8.0.2. However, optimized has gotten a little worse, but not much. ----------------------- == Runtime performance The run-time performance numbers are a bit more disappointing. At first it appeared that allocation went down in 8.4.1 while overall time is up significantly. However, the 8.4.1 used newer dependencies, so to try to control for those, I tested again after using a cabal freeze from the 8.4.1 test. Of course I had to remove the ghc distributed packages, like container and 'ghc' itself, but the rest of the deps should be the same. Those have the 'libs' suffix on Linux. From that, it looks like the improved memory in 8.4.1 was due to external dependencies, and in fact 8.4.1 bumped memory usage up again. Ow. In the graphs, 'score' is just the input file. 'max mb' and 'total mb' and 'prd' come from the post-run GC report, specifically '* bytes maximum residency', '* bytes allocated in the heap', and productivity fields. 'derive', 'lily' and 'perform' are just different kinds of processes. They are CPU time bracketing the specific action, after initialization, and the range is min and max over 6 runs, so no fancy criterion-like analysis. Each run is a separate process, so they should be independent. I was hoping for some gains due to the join points stuff, but it kind of looks like things get worse across the board. I don't know why productivity goes down so much, and I don't know why the effect seems so much worse on OS X. Of course the obvious next step is to see where 8.2.1 lies, but I thought I'd see if there's interest before going to the trouble. Of course, I should track down the regressions for my own purposes, but it's a bit of a daunting task. The step of reducing to a minimal example seems a lot harder for performance than for a bug! Probably some old fashioned SCC annotations await me, but that can be a long and confusing process. OS X, macbook pro: {{{ score max mb total mb prd derive lily perform ghc 6 72.26 3279.22 0.88 0.79~0.84 0.70~0.74 0.31~0.33 8.0.2 6 76.63 3419.20 0.58 1.45~1.59 1.05~1.07 0.33~0.36 8.4.1 bloom 70.69 2456.14 0.89 1.32~1.36 0.15~0.16 8.0.2 bloom 67.86 2589.97 0.62 1.94~1.99 0.20~0.22 8.4.1 cerucuk-punyah 138.01 10080.55 0.93 6.98~7.16 1.24~1.30 8.0.2 cerucuk-punyah 130.78 9617.35 0.68 8.91~9.22 1.57~1.68 8.4.1 hex 32.86 2120.95 0.91 0.76~0.88 0.16~0.19 8.0.2 hex 32.67 2194.82 0.66 1.09~1.16 0.28~0.30 8.4.1 p1 67.01 4039.82 0.92 2.63~2.73 0.47~0.50 8.0.2 p1 64.80 3899.85 0.68 3.35~3.43 0.58~0.59 8.4.1 viola-sonata 69.32 6083.65 0.92 2.48~2.56 2.07~2.13 0.25~0.26 8.0.2 viola-sonata 66.76 6120.26 0.68 3.32~3.43 2.90~2.93 0.32~0.34 8.4.1 }}} Linux, PC: {{{ score max mb total mb prd derive lily perform ghc 6 79.76 3310.69 0.89 0.88~0.89 0.73~0.75 0.27~0.27 8.0.2 6 72.21 3421.45 0.90 0.87~0.87 0.72~0.79 0.28~0.28 8.0.2 libs 6 76.56 3419.05 0.77 1.16~1.17 0.87~0.93 0.33~0.33 8.4.1 bloom 69.82 2461.95 0.89 1.35~1.36 0.17~0.17 8.0.2 bloom 63.45 2554.89 0.90 1.33~1.35 0.18~0.18 8.0.2 libs bloom 67.79 2589.85 0.79 1.64~1.65 0.20~0.20 8.4.1 cerucuk-punyah 137.05 10113.41 0.94 7.44~7.50 1.31~1.33 8.0.2 cerucuk-punyah 128.09 10278.03 0.94 7.50~7.55 1.37~1.38 8.0.2 libs cerucuk-punyah 131.20 9617.22 0.84 7.35~7.40 1.49~1.50 8.4.1 hex 32.02 2096.87 0.92 0.73~0.74 0.18~0.18 8.0.2 hex 32.05 2200.30 0.91 0.73~0.80 0.19~0.19 8.0.2 libs hex 32.46 2144.22 0.83 0.89~0.90 0.20~0.20 8.4.1 p1 65.88 4054.66 0.93 2.84~2.87 0.49~0.50 8.0.2 p1 62.60 4127.68 0.94 2.83~2.92 0.51~0.51 8.0.2 libs p1 64.72 3899.72 0.81 2.80~2.81 0.54~0.55 8.4.1 viola-sonata 68.68 6086.49 0.93 2.55~2.56 2.10~2.12 0.27~0.27 8.0.2 viola-sonata 65.05 6212.57 0.93 2.52~2.55 2.07~2.16 0.28~0.28 8.0.2 libs viola-sonata 66.85 6120.15 0.83 2.91~2.92 2.48~2.51 0.30~0.31 8.4.1 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 09:16:35 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 09:16:35 -0000 Subject: [GHC] #14711: Machine readable output of coverage In-Reply-To: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> References: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> Message-ID: <065.06455e83dddf480c6de4109d48b963f7@haskell.org> #14711: Machine readable output of coverage -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Code Coverage | Version: 8.2.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4522 Wiki Page: | -------------------------------------+------------------------------------- Changes (by jproyo): * differential: => Phab:D4522 Comment: Hi Team, I am a newcomer and i have been trying to add this functionality. I have committed a review to Phabricator D4522 but i am not getting build pass because since i added a new flag to `hpc report` output command help i had to change `libraries/hpc` submodule testsuite in order to get the test pass successfully. I have committed the review with arc diff as the wiki indicates but it is complaining because my submodule changes are not in the upstream. Obviously i didnt want to push my submodule changes to not affect master branch build until review is done. Apart from this i dont have push permissions. How can i commit a review to Phab which contains changes in some component, in this case hpc, and in a submodule either? Best, -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 10:09:13 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 10:09:13 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.7b8898a6f8421fc86080090e21b23f97@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.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 monoidal): The same happens with just one module: {{{ test :: IO Bool test = return True }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 10:35:13 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 10:35:13 -0000 Subject: [GHC] #14711: Machine readable output of coverage In-Reply-To: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> References: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> Message-ID: <065.94d56277b13eb687582d3365c6c1033c@haskell.org> #14711: Machine readable output of coverage -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: jproyo Type: feature request | Status: new Priority: normal | Milestone: Component: Code Coverage | Version: 8.2.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4522 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: (none) => jproyo -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 10:38:00 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 10:38:00 -0000 Subject: [GHC] #14711: Machine readable output of coverage In-Reply-To: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> References: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> Message-ID: <065.9771d780fe508cf9f75d51dc793f4231@haskell.org> #14711: Machine readable output of coverage -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: jproyo Type: feature request | Status: patch Priority: normal | Milestone: Component: Code Coverage | Version: 8.2.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4522 Wiki Page: | Phab:4523 -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * differential: Phab:D4522 => Phab:D4522 Phab:4523 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 10:38:41 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 10:38:41 -0000 Subject: [GHC] #14711: Machine readable output of coverage In-Reply-To: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> References: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> Message-ID: <065.3f8b69a2eb6c398f4e901731bf70cc7c@haskell.org> #14711: Machine readable output of coverage -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: jproyo Type: feature request | Status: patch Priority: normal | Milestone: Component: Code Coverage | Version: 8.2.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4522 Wiki Page: | Phab:D4523 -------------------------------------+------------------------------------- Changes (by Phyx-): * differential: Phab:D4522 Phab:4523 => Phab:D4522 Phab:D4523 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 11:11:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 11:11:31 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.8a4f84c12666f75f9ad35f72372b3289@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Can you explain more precisely why float-out un-does good work? I'm not sure whether float-out does or does not float join bindings. I suspect it should not? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 13:46:21 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 13:46:21 -0000 Subject: [GHC] #14901: dsrun014 fails with most ways In-Reply-To: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> References: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> Message-ID: <063.e44fb505980fe4cb7da4e9ae15251c42@haskell.org> #14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): I tried to extend that code to do the same thing for `pseq` but it looks like that did not quite work (see [https://gist.github.com/alpmestan/2ed121470f5ed3b4e27b79a22111ab27 this gist]). I'm probably missing something obvious here though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 13:57:17 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 13:57:17 -0000 Subject: [GHC] #14901: dsrun014 fails with most ways In-Reply-To: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> References: <048.91a44e1a4a1d334cf6b8d4bc97b4746a@haskell.org> Message-ID: <063.a7df0e279333ec4cff3b00f267cae62a@haskell.org> #14901: dsrun014 fails with most ways -------------------------------------+------------------------------------- Reporter: alpmestan | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: dsrun014 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Oh, well I can't just expect GHC to magically use that "id" can I... I'll look at how the mapping is done for seq and then do the same thing for `pseq`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 14:09:05 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 14:09:05 -0000 Subject: [GHC] #14966: Symbols in -ddump-asm output don't match real output Message-ID: <049.cc1659c4f62612281fb136dd047a3c92@haskell.org> #14966: Symbols in -ddump-asm output don't match real output -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 (NCG) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Symbols in the .s files generated by NCG are properly Z-encoded, but they aren't in the -ddump-asm output. One trivial example: {{{ {-# OPTIONS_GHC -ddump-to-file -ddump-asm -keep-s-files #-} module Fact where fact :: Int -> Int fact 0 = 1 fact n = n * fact (n - 1) }}} The contents of Fact.s: {{{ .section .rdata .align 1 .align 1 r23Y_bytes: .asciz "main" .section .data .align 8 .align 1 r24i_closure: .quad ghczmprim_GHCziTypes_TrNameS_con_info .quad r23Y_bytes ... }}} The contents of Fact.dump-asm: {{{ ==================== Asm code ==================== 2018-03-23 14:00:27.8082773 UTC .section .rdata .align 1 .align 1 $trModule1_r23Y_bytes: .asciz "main" ==================== Asm code ==================== 2018-03-23 14:00:27.8172758 UTC .section .data .align 8 .align 1 $trModule2_r24i_closure: .quad GHC.Types.TrNameS_con_info .quad $trModule1_r23Y_bytes ... }}} This is confirmed on multiple GHC versions, up to 8.5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 15:58:41 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 15:58:41 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.3f23e8b8ccdbc3831a21d2d5dc147175@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: DWARF 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 RyanGlScott): * keywords: => DWARF Comment: Note that, AFAICT, this requires a build of GHC 8.4.1 with DWARF support to trigger. I cannot reproduce the bug on a DWARF-less 8.4.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:01:40 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:01:40 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.b941be218d284e80afafa87c3a38617b@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I must be doing something wrong here. I created a file named `Bug.hs` with the contents of comment:2, and tried loading it like so: {{{ $ ~/Software/ghc-8.4.1/bin/ghci -fdefer-type-errors -ignore-dot-ghciGHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Prelude> :load Bug [1 of 1] Compiling Main ( Bug.hs, interpreted ) Ok, one module loaded. }}} Which appears to work without issue. What am I missing? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:06:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:06:31 -0000 Subject: [GHC] #5041: Incorrect Read deriving for MagicHash constructors In-Reply-To: <044.9b7a543c5bb57a51cf0f260d7ff16f86@haskell.org> References: <044.9b7a543c5bb57a51cf0f260d7ff16f86@haskell.org> Message-ID: <059.776d23c8f8fa8566930f53f4331a7971@haskell.org> #5041: Incorrect Read deriving for MagicHash constructors -------------------------------------+------------------------------------- Reporter: dolio | Owner: (none) Type: bug | Status: new Priority: low | Milestone: ⊥ Component: Compiler | Version: 7.0.2 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_run/T5041 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"d5577f44eaf3b9dfdfc77828038782bf818c176a/ghc" d5577f44/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d5577f44eaf3b9dfdfc77828038782bf818c176a" Special-case record fields ending with hash when deriving Read Summary: In commit dbd81f7e86514498218572b9d978373b1699cc5b, a regression was inadvertently introduced which caused derived `Read` instances for record data types with fields ending in a `#` symbol (using `MagicHash`) would no longer parse on valid output. This is ultimately due to the same reasons as #5041, as we cannot parse a field name like `foo#` as a single identifier. We fix this issue by employing the same workaround as in #5041: first parse the identifier name `foo`, then then symbol `#`. This is accomplished by the new `readFieldHash` function in `GHC.Read`. This will likely warrant a `base-4.11.1.0` release. Test Plan: make test TEST=T14918 Reviewers: tdammers, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14918 Differential Revision: https://phabricator.haskell.org/D4502 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:06:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:06:31 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.56812661982a3a4970e2ca2fdad101e7@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"d5577f44eaf3b9dfdfc77828038782bf818c176a/ghc" d5577f44/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d5577f44eaf3b9dfdfc77828038782bf818c176a" Special-case record fields ending with hash when deriving Read Summary: In commit dbd81f7e86514498218572b9d978373b1699cc5b, a regression was inadvertently introduced which caused derived `Read` instances for record data types with fields ending in a `#` symbol (using `MagicHash`) would no longer parse on valid output. This is ultimately due to the same reasons as #5041, as we cannot parse a field name like `foo#` as a single identifier. We fix this issue by employing the same workaround as in #5041: first parse the identifier name `foo`, then then symbol `#`. This is accomplished by the new `readFieldHash` function in `GHC.Read`. This will likely warrant a `base-4.11.1.0` release. Test Plan: make test TEST=T14918 Reviewers: tdammers, hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14918 Differential Revision: https://phabricator.haskell.org/D4502 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:06:31 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:06:31 -0000 Subject: [GHC] #13324: Allow PartialTypeSignatures in the instance context of a standalone deriving declaration In-Reply-To: <050.05d716a2c5be2cade611e1ab44e0e3c6@haskell.org> References: <050.05d716a2c5be2cade611e1ab44e0e3c6@haskell.org> Message-ID: <065.b798cc1833301e04a4d2187200c0bbea@haskell.org> #13324: Allow PartialTypeSignatures in the instance context of a standalone deriving declaration -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10607 | Differential Rev(s): Phab:D4383 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"affdea82bb70e5a912b679a169c6e9a230e4c93e/ghc" affdea82/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="affdea82bb70e5a912b679a169c6e9a230e4c93e" Allow PartialTypeSignatures in standalone deriving contexts Summary: At its core, this patch is a simple tweak that allows a user to write: ```lang=haskell deriving instance _ => Eq (Foo a) ``` Which is functionally equivalent to: ```lang=haskell data Foo a = ... deriving Eq ``` But with the added flexibility that `StandaloneDeriving` gives you (namely, the ability to use it anywhere, not just in the same module that `Foo` was declared in). This fixes #13324, and should hopefully address a use case brought up in #10607. Currently, only the use of a single, extra-constraints wildcard is permitted in a standalone deriving declaration. Any other wildcard is rejected, so things like `deriving instance (Eq a, _) => Eq (Foo a)` are currently forbidden. There are quite a few knock-on changes brought on by this change: * The `HsSyn` type used to represent standalone-derived instances was previously `LHsSigType`, which isn't sufficient to hold wildcard types. This needed to be changed to `LHsSigWcType` as a result. * Previously, `DerivContext` was a simple type synonym for `Maybe ThetaType`, under the assumption that you'd only ever be in the `Nothing` case if you were in a `deriving` clause. After this patch, that assumption no longer holds true, as you can also be in this situation with standalone deriving when an extra-constraints wildcard is used. As a result, I changed `DerivContext` to be a proper datatype that reflects the new wrinkle that this patch adds, and plumbed this through the relevant parts of `TcDeriv` and friends. * Relatedly, the error-reporting machinery in `TcErrors` also assumed that if you have any unsolved constraints in a derived instance, then you should be able to fix it by switching over to standalone deriving. This was always sound advice before, but with this new feature, it's possible to have unsolved constraints even when you're standalone-deriving something! To rectify this, I tweaked some constructors of `CtOrigin` a bit to reflect this new subtlety. This requires updating the Haddock submodule. See my fork at https://github.com/RyanGlScott/haddock/commit/067d52fd4be15a1842cbb05f42d9d482de0ad3a7 Test Plan: ./validate Reviewers: simonpj, goldfire, bgamari Reviewed By: simonpj Subscribers: goldfire, rwbarton, thomie, mpickering, carter GHC Trac Issues: #13324 Differential Revision: https://phabricator.haskell.org/D4383 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:06:32 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:06:32 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.01d5d6f2be9c5b39c2ab6ac2433776ae@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, | typeclass, auto Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13324 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"affdea82bb70e5a912b679a169c6e9a230e4c93e/ghc" affdea82/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="affdea82bb70e5a912b679a169c6e9a230e4c93e" Allow PartialTypeSignatures in standalone deriving contexts Summary: At its core, this patch is a simple tweak that allows a user to write: ```lang=haskell deriving instance _ => Eq (Foo a) ``` Which is functionally equivalent to: ```lang=haskell data Foo a = ... deriving Eq ``` But with the added flexibility that `StandaloneDeriving` gives you (namely, the ability to use it anywhere, not just in the same module that `Foo` was declared in). This fixes #13324, and should hopefully address a use case brought up in #10607. Currently, only the use of a single, extra-constraints wildcard is permitted in a standalone deriving declaration. Any other wildcard is rejected, so things like `deriving instance (Eq a, _) => Eq (Foo a)` are currently forbidden. There are quite a few knock-on changes brought on by this change: * The `HsSyn` type used to represent standalone-derived instances was previously `LHsSigType`, which isn't sufficient to hold wildcard types. This needed to be changed to `LHsSigWcType` as a result. * Previously, `DerivContext` was a simple type synonym for `Maybe ThetaType`, under the assumption that you'd only ever be in the `Nothing` case if you were in a `deriving` clause. After this patch, that assumption no longer holds true, as you can also be in this situation with standalone deriving when an extra-constraints wildcard is used. As a result, I changed `DerivContext` to be a proper datatype that reflects the new wrinkle that this patch adds, and plumbed this through the relevant parts of `TcDeriv` and friends. * Relatedly, the error-reporting machinery in `TcErrors` also assumed that if you have any unsolved constraints in a derived instance, then you should be able to fix it by switching over to standalone deriving. This was always sound advice before, but with this new feature, it's possible to have unsolved constraints even when you're standalone-deriving something! To rectify this, I tweaked some constructors of `CtOrigin` a bit to reflect this new subtlety. This requires updating the Haddock submodule. See my fork at https://github.com/RyanGlScott/haddock/commit/067d52fd4be15a1842cbb05f42d9d482de0ad3a7 Test Plan: ./validate Reviewers: simonpj, goldfire, bgamari Reviewed By: simonpj Subscribers: goldfire, rwbarton, thomie, mpickering, carter GHC Trac Issues: #13324 Differential Revision: https://phabricator.haskell.org/D4383 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:08:26 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:08:26 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.d35603b035938f6c7d726c5bb42fde87@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | deriving/should_run/T14918 Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => deriving/should_run/T14918 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:10:10 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:10:10 -0000 Subject: [GHC] #13324: Allow PartialTypeSignatures in the instance context of a standalone deriving declaration In-Reply-To: <050.05d716a2c5be2cade611e1ab44e0e3c6@haskell.org> References: <050.05d716a2c5be2cade611e1ab44e0e3c6@haskell.org> Message-ID: <065.f6ca47c3540fbaaf5b80a0d02a350404@haskell.org> #13324: Allow PartialTypeSignatures in the instance context of a standalone deriving declaration -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/T13324_compile, | partial- | sigs/should_fail/T13324_fail1, | partial- | sigs/should_fail/T13324_fail2 Blocked By: | Blocking: Related Tickets: #10607 | Differential Rev(s): Phab:D4383 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => partial-sigs/should_compile/T13324_compile, partial- sigs/should_fail/T13324_fail1, partial-sigs/should_fail/T13324_fail2 * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 16:11:49 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 16:11:49 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.54db8dfc85b4e65d0e570ab6d6c91f34@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, | typeclass, auto Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13324 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): songzh, I finally delivered on my promise to implement the ability to use `PartialTypeSignatures` in standalone `deriving` declarations //à la// `deriving _ => Eq (Foo a)`. Does this make things easier for you on your end? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 17:31:25 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 17:31:25 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.b9a92dc39711d5c7cd8644981722ab22@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: DWARF 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 simonpj): Wow. How on earth could DWARF trigger a Core Lint error???!!! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 17:36:18 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 17:36:18 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.dffa10119a018a1144ce40c5cbcf775f@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: DWARF 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 simonpj): Actually I think it may be directly related to #14779, which is fixed in 8.4.2. The DWARF bit may be the 'ticks' which are floating around. The Lint error (in corelint.dump) relates to a top level literal string with a tick wrapped around it. It is still astonishing to me that we get different output though -- how on earth does that happen? Maybe it's because that tick wrapped around the literal string is confusing the code generator too. Does this all work right in 8.4.2? How you even build GHC "with DWARF support" or otherwise? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 17:40:51 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 17:40:51 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.de84258c531c5b80456fdf19526f8477@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.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 can repro the original 2-module report, with the GHC 8.4.2 branch, and with HEAD. Definite bug here! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 17:45:37 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 17:45:37 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.e45a6cd2a5a8b7ef8ea4a781685636ba@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by kavon): * Attachment "FloatOut_snippet.txt" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 17:46:07 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 17:46:07 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.45595d6798a2ae1c42007a52b03f4cba@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by kavon): Here are the details on FloatOut: Using `wip/T14068-inline`, I compiled `queens` with `-O2 -ddump-occur-anal -ddump-simpl-iterations -ddump-call- arity -dverbose-core2core` to watch every Core transformation, and noticed that after Specialize, we have nicely inlined the "safe" loop (`safe_s5vS`) into the folding function: {{{ ... inside gen ... GHC.Base.foldr @ [Int] @ a_d3jr (\ (ds_d3jv :: [Int]) (ds_d3ju [OS=OneShot] :: a_d3jr) -> GHC.Base.foldr @ Int @ a_d3jr (\ (ds_d3jx :: Int) (ds_d3jw [OS=OneShot] :: a_d3jr) -> case joinrec { safe_s5vS [Occ=LoopBreaker] :: Int -> Int -> [Int] -> Bool [LclId[JoinId(3)], Arity=3] safe_s5vS (x_X14P :: Int) (d_X14R :: Int) (ds_X3kg :: [Int]) = ... BODY OF SAFE ... } in jump safe_s5vS ds_d3jx (GHC.Types.I# 1#) ds_d3jv of { False -> ds_d3jw; True -> c_d3js (GHC.Types.: @ Int ds_d3jx ds_d3jv) ds_d3jw }) }}} Right after Specialize, SetLevels tells FloatOut to move that join point to the top level: {{{ GHC.Base.foldr @ [GHC.Types.Int] @ a_d3jr (\ > > -> GHC.Base.foldr @ GHC.Types.Int @ a_d3jr (\ > > -> case letrec { > > = \ > > > -> ... }}} So we end up with an ordinary top-level Rec: {{{ Rec { safe_s5w0 [Occ=LoopBreaker] :: Int -> Int -> [Int] -> Bool [LclId, Arity=3] safe_s5w0 = \ (x_X14P :: Int) (d_X14R :: Int) (ds_X3kg :: [Int]) -> ... ... GHC.Base.foldr @ Int @ a_d3jr (\ (ds_d3jx :: Int) (ds_d3jw [OS=OneShot] :: a_d3jr) -> case safe_s5w0 ds_d3jx lvl_s5w1 ds_d3jv of { False -> ds_d3jw; True -> c_d3js (GHC.Types.: @ Int ds_d3jx ds_d3jv) ds_d3jw }) ... }}} We end up recovering the good code that existed before FloatOut after two further iterations of Simplification. FloatOut does try to float join points (see the Note [Join points] in its file). Perhaps there's something wrong with the "join ceiling" (Note [Join ceiling]) implementation in SetLevels? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 17:53:42 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 17:53:42 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.6a8dc034f2340c3c84ece4e9293c715d@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, the entire join-ceiling machinery is wonky. I have a long-gestated patch about this, not yet completed alas, but this conversation may help me to make progress on it. I think float-out should not be moving join points at all -- except perhaps if they can go all the way to top level. Why top level? Well * Then the function it was part of before becomes smaller, and hence may inline. * At top level there is no closure to allocate. I suppose that if lifted to top level then it might be loopified afresh. Question: how beneficial is it to loopify a top-level function? Danger: once loopified, it becomes non-recursive and might be inlined again -- which would be funny but not very productive. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 18:06:10 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 18:06:10 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.fe220cc2656d43ec8dd0cbbc9fbedf75@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.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 monoidal): After `:load Bug` you need to examine the value `test` in ghci. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 18:27:37 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 18:27:37 -0000 Subject: [GHC] #14943: Make (=>) polykinded (:: k -> k -> Constraint) In-Reply-To: <051.6fe39954d13f1f127aabba85c357373f@haskell.org> References: <051.6fe39954d13f1f127aabba85c357373f@haskell.org> Message-ID: <066.9fe486d902a52e543d432d9c6ac6e74a@haskell.org> #14943: Make (=>) polykinded (:: k -> k -> Constraint) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: | QuantifiedConstraints, wipT2893 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): No, I don't see a need for this. You could always define such an infix type family yourself, couldn't you? Then you wouldn't need to mess with built-in syntax. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 18:36:00 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 18:36:00 -0000 Subject: [GHC] #14711: Machine readable output of coverage In-Reply-To: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> References: <050.d858ad27520ca4b1ee3c013a327a8c68@haskell.org> Message-ID: <065.fa8113d726659b3954339d8c0a713aba@haskell.org> #14711: Machine readable output of coverage -------------------------------------+------------------------------------- Reporter: Koterpillar | Owner: jproyo Type: feature request | Status: patch Priority: normal | Milestone: Component: Code Coverage | Version: 8.2.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4522 Wiki Page: | Phab:D4523 Phab:D4524 -------------------------------------+------------------------------------- Changes (by jproyo): * differential: Phab:D4522 Phab:D4523 => Phab:D4522 Phab:D4523 Phab:D4524 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 18:47:47 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 18:47:47 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.0d5017f157fd3e9f54e2d77c0be33faa@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): As an experiment, I build GHC against that commit using this patch: {{{#!diff diff --git a/rts/RetainerProfile.c b/rts/RetainerProfile.c index 7a9b9cc..c6eff0a 100644 --- a/rts/RetainerProfile.c +++ b/rts/RetainerProfile.c @@ -442,6 +442,7 @@ push( StgClosure *c, retainer c_child_r, StgClosure **first_child ) { stackElement se; bdescr *nbd; // Next Block Descriptor + char *barf_me; #if defined(DEBUG_RETAINER) // debugBelch("push(): stackTop = 0x%x, currentStackBoundary = 0x%x\n", stackTop, currentStack @@ -633,7 +634,8 @@ push( StgClosure *c, retainer c_child_r, StgClosure **first_child ) case IND: case INVALID_OBJECT: default: - barf("Invalid object *c in push()"); + asprintf(&barf_me, "Invalid object *c in push(): %d", get_itbl(c)->type); + barf(barf_me); return; } }}} And this is what I received after running `cgraytrace-exe` built with this patched GHC: {{{ Rendering to sample.png... cgraytrace-exe: internal error: Invalid object *c in push(): 37 (GHC version 8.5.20171211 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} It looks like 37 [http://git.haskell.org/ghc.git/blob/affdea82bb70e5a912b679a169c6e9a230e4c93e:/includes/rts/storage/ClosureTypes.h#l59 corresponds to] the `BLOCKING_QUEUE` closure type. `push()` does not have a case in its giant `switch` statement for `BLOCKING_QUEUE`, which at least explains why it falls through. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 19:00:40 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 19:00:40 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.74d3e9ada55cb57cd82c40cb91a9b189@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > Question: how beneficial is it to loopify a top-level function? Well, we still want to use jumps for the recursive calls, rather than normal function calls, even if it is top-level, right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 19:05:05 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 19:05:05 -0000 Subject: [GHC] #14951: SpecConstr needs two runs when one should suffice In-Reply-To: <046.2335cd5876de5516a20812036c470d04@haskell.org> References: <046.2335cd5876de5516a20812036c470d04@haskell.org> Message-ID: <061.45b23fd1aea74df3959f3703f67f39d1@haskell.org> #14951: SpecConstr needs two runs when one should suffice -------------------------------------+------------------------------------- Reporter: nomeata | Owner: (none) Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14844 | Differential Rev(s): Phab:D4519 Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): Ok, here is some very motivation data: If I run !SpecConstr twice, with simplification in between (and without the patch in Phab:D4519), then there are significant performance improvements: {{{ Nofib allocations Benchmark name previous change now nofib/allocs/event 129683224 + 8.44% 140627312 bytes nofib/allocs/fulsom 243329632 - 7.83% 224287920 bytes nofib/allocs/mandel2 922640 - 13.89% 794448 bytes nofib/allocs/minimax 5371584 - 8.73% 4902576 bytes nofib/allocs/parstof 3038584 - 3.63% 2928248 bytes Nofib instruction Benchmark name previous change now nofib/instr/compress2 549006516 - 6.36% 514104497 nofib/instr/fulsom 755145483 - 3.41% 729394470 nofib/instr/ida 261218740 - 3.98% 250820469 nofib/instr/k-nucleotide 2140743692 - 3.97% 2055743369 nofib/instr/minimax 9099200 - 4.38% 8700706 }}} I checked that these are really due to the second !SpecConstr (and not due to the extra simplification). I did not investigate them individually, and unfortunately, Phab:D4519 does _not_ achieve any of these improvements. Is there a reasonably simple way to make !SpecConstr more idempotent? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 23 21:40:24 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 23 Mar 2018 21:40:24 -0000 Subject: [GHC] #14068: Loopification using join points In-Reply-To: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> References: <046.e16e22cbe3c046431dc8ebed421f2e67@haskell.org> Message-ID: <061.bb8d7f2f9dd5468e09e340a28541f3a3@haskell.org> #14068: Loopification using join points -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: JoinPoints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13966 #14067 | Differential Rev(s): Phab:D3811 #14827 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by kavon): Replying to [comment:52 nomeata]: > > Question: how beneficial is it to loopify a top-level function? > > Well, we still want to use jumps for the recursive calls, rather than normal function calls, even if it is top-level, right? In the end, they'll still be emitted as jumps since they're tail calls. Considering the transformation in isolation (i.e., ignoring knock-on effects like inlining), using join-point throws instead of tail-recursive calls theoretically allows us to cheapen the iteration overhead in the following ways: 1. For joinrecs whose RHS contains a non-tail call, we can avoid a stack check and stack pointer bumps on each iteration, since the join continuation can keep reusing the stack frame setup on the initial entry to the function. This depends on whether StackLayout in Cmm is optimized to do this. 2. Optimizing argument-passing, such as by moving static arguments out of the recursive throws, spilling rarely used arguments in high-pressure loops, or allowing code generation to pick registers with a smaller instruction encoding (which LLVM loves to do for x86_64). 3. Aligning a hot loop's header. Many x86_64 CPUs prefer 16-byte aligned jump targets, but because we add info tables just before a function label, the alignment of a function's body may only be 8-byte aligned. Code generators can more easily align the target of a join-point throw since it is less likely to have info table attached to it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 04:46:43 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 04:46:43 -0000 Subject: [GHC] #14967: Optimizer Casting Caf with nominal type Message-ID: <042.add8f351aaf885809089532f69f1f66e@haskell.org> #14967: Optimizer Casting Caf with nominal type -------------------------------------+------------------------------------- Reporter: etn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: coerce, | Operating System: Unknown/Multiple nominal | Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When you make a function with a constant result, the optimizer will turn it into a cast of a CAF, even if doing so coerces a nominal parameter into a different one. Minimal Example program: {{{#!hs {-# LANGUAGE RoleAnnotations #-} import Debug.Trace (trace) type role Nom nominal data Nom a = Nom Int deriving Show class Gen g where gen :: g instance Gen (Nom a) where gen = trace "genD" $ Nom 0 main = print (gen :: Nom Int) >> print (gen :: Nom ()) >> print (gen :: Nom Char) }}} This program shows that only one value of type Nom is created and shared, even though doing so requires coercing a nominal role I discovered this while checking core for sharing after creating a constraint result caching mechanism. An IOref ended up being shared for multiple different constraint result holders -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 10:26:23 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 10:26:23 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances Message-ID: <044.8604cb7a4154bec744684958eded781f@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 (Type checker) | Keywords: | Operating System: Unknown/Multiple QuantifiedConstraints | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here's a type family that I tried to write using QuantifiedConstraints. {{{#!hs {-# LANGUAGE TypeOperators #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE QuantifiedConstraints #-} module QCTypeInstance where import GHC.Exts (Constraint) type family Functors (fs :: [(* -> *) -> * -> *]) :: Constraint type instance Functors '[] = (() :: Constraint) type instance Functors (t ': ts) = (forall f. Functor f => Functor (t f), Functors ts) }}} Unfortunately, GHC complains that it's illegal to have polymorphism on the right hand side of a type instance definition. {{{ $ ../ghc-wip/T2893/inplace/bin/ghc-stage2 --interactive QCTypeInstance.hs GHCi, version 8.5.20180322: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling QCTypeInstance ( QCTypeInstance.hs, interpreted ) QCTypeInstance.hs:13:15: error: • Illegal polymorphic type: forall (f :: * -> *). Functor f => Functor (t f) • In the type instance declaration for ‘Functors’ | 13 | type instance Functors (t ': ts) = (forall f. Functor f => Functor (t f), Functors ts) | ^^^^^^^^ }}} Would it be possible to lift this restriction and allow quantified constraints as right hand sides of type family instances? Or are there fundamental difficulties with what I'm trying to do? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 13:01:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 13:01:55 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.9fc6602de45302d4b685ab58f407a7f2@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #9269 Comment: This is a particular occurrence of a more general restriction, which is explained in https://ghc.haskell.org/trac/ghc/ticket/9269#comment:1. So yes, there are fundamental difficulties here that have yet to be worked out. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 14:03:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 14:03:55 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.60ee35100263d25b3e599ac4a7986db8@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by josef): Right. I'm aware to the difficulties discussed in ticket #9269. My questions is really whether we can hope to do better when the result kind of a type family is of kind `Constraint` rather than `*`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 15:10:25 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 15:10:25 -0000 Subject: [GHC] #13896: Use response file to invoke hsc2hs In-Reply-To: <046.8d005e1593e32147d596c190fbabb716@haskell.org> References: <046.8d005e1593e32147d596c190fbabb716@haskell.org> Message-ID: <061.23e1597052966067ae96175fa9ee37aa@haskell.org> #13896: Use response file to invoke hsc2hs ---------------------------------+---------------------------------------- Reporter: bgamari | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: hsc2hs | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by ckoparkar): * owner: (none) => ckoparkar Comment: Ben, I'd like to work on this. Mikhail (23Skidoo) outlined the solution [https://github.com/haskell/cabal/issues/3122#issuecomment-181585821 here]: > We're probably bumping into the same command-line length restriction we did with Haddock. If this is the case, the solution is to add support for response files to hsc2hs and use that in Cabal. One way to implement this idea would be to have something similar to [https://github.com/haskell/haddock/blob/ghc-8.4/driver/ResponseFile.hs haddock's implementation] in `hsc2hs`. Or, we could also have just one implementation somewhere, and have `haddock` and `hsc2hs` use that. What's the proper place to house this in GHC ? `base` or `process` seem like the obvious candidates. Although `haddock` doesn't seem to depend on `process` right now. I haven't looked at the specifics of implementing this, but the overall roadmap I'd follow would be: (1) Copy [https://github.com/haskell/haddock/blob/ghc-8.4/driver/ResponseFile.hs haddock's implementation] to either `base` or `process` (or somewhere else ?) (2) Use that in `hsc2hs` and `haddock` (and remove the relevant bits from `haddock`) (3) Update `Cabal` appropriately Does this sound like a good idea ? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 15:12:21 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 15:12:21 -0000 Subject: [GHC] #14969: panic on incorrect syntax Message-ID: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> #14969: panic on incorrect syntax -------------------------------------+------------------------------------- Reporter: johnleo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 a fresh build of 8.5: {{{ GHCi, version 8.5.20180323: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/leo/.ghci Prelude> 3 _ 4 ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180323 for x86_64-apple-darwin): ASSERT failed! 2 1 t_a4j6[tau:1] Maybe a_a4j7[tau:2] Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1157:37 in ghc:Outputable pprPanic, called at compiler/utils/Outputable.hs:1213:5 in ghc:Outputable assertPprPanic, called at compiler/typecheck/TcMType.hs:720:54 in ghc:TcMType }}} I believe this fails in earlier versions as well, but I haven't tested it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 15:31:17 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 15:31:17 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.11e12ccf3375997e8177ff696510439c@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm not sure what the return kind has anything to do with this. Ultimately, the issue is impredicativity, which is going to be a problem regardless of whether you're working over `*`, `Constraint` (as in your example), `Bool` (as in the example in https://ghc.haskell.org/trac/ghc/ticket/9269#comment:1), or something else. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 15:56:09 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 15:56:09 -0000 Subject: [GHC] #13896: Use response file to invoke hsc2hs In-Reply-To: <046.8d005e1593e32147d596c190fbabb716@haskell.org> References: <046.8d005e1593e32147d596c190fbabb716@haskell.org> Message-ID: <061.e4de47736779ec0793a1fe1ef92a683e@haskell.org> #13896: Use response file to invoke hsc2hs ---------------------------------+---------------------------------------- Reporter: bgamari | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: hsc2hs | Version: 8.0.1 Resolution: | Keywords: newcomer 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 ckoparkar): While looking through some old GitHub PR's, I found this [https://github.com/haskell/cabal/issues/1681#issuecomment-101175802 thread] where 23Skidoo proposed this exact same idea before: >> Fuuzetsu: Right. I actually realised that we could have just one generic implementation in Cabal and Haddock could import that and feed args through it before doing Haddock-y stuff. It'd ensure consistent implementation which I believe is what we're after. > 23Skidoo: process or base are probably more appropriate places for this - I bet that getArgsWithResponseFiles could be generally useful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 16:25:26 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 16:25:26 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.ca6f81b6c48d53ec150400d361636062@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 varosi): @klapaucius, "Multicore Garbage Collection with Local Heaps" by Simon Marlow and Simon Peyton Jones in chapter 6.1.1 state: "Nevertheless, we do find that on average there is a local minimum around 1MB on **this hardware**. ... **staying within the cache** becomes more beneficial as contention for main memory increases." I could experiment more on different processors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 16:28:45 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 16:28:45 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.69ed4bd27eba288f7318d2584de66ce1@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 varosi): How can I experiment with non-optimized version as I doesn't have reference for comparison? I could try to build some optimized version. Replying to [comment:13 sjakobi]: > Replying to [comment:12 varosi]: > > Great! Is it possible to share your Windows executable so I could experiment on a few machines from a few cores up to close to hundred? > > You can download a binary distribution [https://drive.google.com/file/d/1sNf93dZ9KEZT6yYdfSCM3fAVxn7YyFil/view?usp=sharing here]. It's not an optimized build though, so at least building with it should be slower than with official releases. > > Regarding running on Windows machines with close to a hundred cores, the current implementation will only detect caches within its current processor group of at most 64 logical processors (see "Remarks" [https://msdn.microsoft.com/en- us/library/windows/desktop/ms683194(v=vs.85).aspx here]). As long as there aren't any larger caches outside of the processor group it will still set the allocation area to the correct size. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 20:13:31 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 20:13:31 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.f602319219667eac2d55560efc5518fb@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Oops, I overlooked that important detail! Commit a211dca8236fb8c7ec632278f761121beeac1438 (`Fix defer-out-of-scope- variables`) is what caused this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 20:26:51 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 20:26:51 -0000 Subject: [GHC] #14967: Optimizer Casting Caf with nominal type In-Reply-To: <042.add8f351aaf885809089532f69f1f66e@haskell.org> References: <042.add8f351aaf885809089532f69f1f66e@haskell.org> Message-ID: <057.8f36051eb5b0eda0a9e8cce2f6b2df34@haskell.org> #14967: Optimizer Casting Caf with nominal type -------------------------------------+------------------------------------- Reporter: etn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: coerce, | nominal Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by etn): After looking for an example where this breaks without unsafe operations, I realized that this is almost certainly a safe transformation under the assumption of referential transparency. What this now amounts to is that there needs to be a way to prevent this from occurring in the case that a value cannot be shared between types. This issue came up when implementing Applicative, and I have realized that it is probably impossible to avoid this unless we can disable thunk-rewriting for particular thunks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 22:22:39 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 22:22:39 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules In-Reply-To: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> References: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> Message-ID: <059.7398e5f1979ca55d3bc57ccda43f647b@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | overloadedrecflds/should_fail/T14953 Blocked By: | Blocking: Related Tickets: #13352 | Differential Rev(s): Phab:D4527 Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * testcase: => overloadedrecflds/should_fail/T14953 * status: new => patch * differential: => Phab:D4527 * related: => #13352 * milestone: => 8.6.1 Comment: Fixing the panic was comparatively straightforward, though there is a bigger issue here that re-exports of duplicate record fields are prohibited in surprising cases (see #13352). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 22:35:24 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 22:35:24 -0000 Subject: [GHC] #14848: -XDuplicateRecordFields breaks record expression splices In-Reply-To: <048.60548a7facfb2bb72ce43f7899267ddd@haskell.org> References: <048.60548a7facfb2bb72ce43f7899267ddd@haskell.org> Message-ID: <063.0c3490ae0477aeca0d71deb3eabc33de@haskell.org> #14848: -XDuplicateRecordFields breaks record expression splices -------------------------------------+------------------------------------- Reporter: dailectic | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: ORF Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by adamgundry): I think a possible fix here is to apply the approach described in `Note [Reifying field labels] from TcSplice` in the `HsRecFld` case of `DsMeta.repE`. That is, rather than representing the field as a `NameG` containing the mangled selector name (which isn't a legal variable name, let alone in scope), we could represent it as a `NameQ` containing the field label. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 24 23:16:14 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 24 Mar 2018 23:16:14 -0000 Subject: [GHC] #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled Message-ID: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled -------------------------------------+------------------------------------- Reporter: rotaerk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.2.2 libraries/base | 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: -------------------------------------+------------------------------------- When you run 'error', it shows the usual stack trace. When you enable profiling with the -prof flag to ghc, and you run 'error', it shows the usual stack trace plus an additional prof-specific stack trace. When you run 'errorWithoutStackTrace' with profiling enabled, it strips the usual stack trace of 'error', but still displays the prof-specific stack trace. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 07:44:06 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 07:44:06 -0000 Subject: [GHC] #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled In-Reply-To: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> References: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> Message-ID: <061.55c8c14ed894cce4891f3cf7e440e7bc@haskell.org> #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled -------------------------------------+------------------------------------- Reporter: rotaerk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.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 osa1): * cc: simonmar (added) Comment: Why do you think this is a bug? We're talking about two kinds of stacks here 1. Stack trace constructed by user-provided `HasCallStack` constraints 2. Stack trace constructed by the RTS and generated code via (sometimes auto-generated) `SCC` annotations (aka. "cost-centre stack") and it's quite possible that these two stack traces show different things, they have different purposes. `errorWithoutStackTrace` overrides (1) but it can't override (2), (2) is a lower-level thing. Paging simonmar as he made `error` include the CCS stack in profiling mode in Phab:D1426. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 10:36:46 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 10:36:46 -0000 Subject: [GHC] #14971: Use appropriatly sized comparison instruction for small values. Message-ID: <047.ebf633502b771144a04c11718d3a50dd@haskell.org> #14971: Use appropriatly sized comparison instruction for small values. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: (CodeGen) | 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 defaults all comparisons originating from Cmm switch statements to 64bit on x64. This incurs a small overhead in instruction size. Fixing this manually gave a speedup of ~1,5% in microbenchmarks. In detail we generate Cmm of the form: {{{ _s8Dg::P64 = R1; _c8EF::P64 = _s8Dg::P64 & 7; switch [1 .. 2] _c8EF::P64 { case 1 : goto c8Ey; case 2 : goto c8EC; } }}} Which results in assembly like: {{{ andl $7,%ebx cmpq $1,%rbx }}} It's obvious that c8EF fits into a byte, but is sized up to 64 bits. Changing this would enable us to use cmpl instead of cmpq and save us a byte on each comparison. While this isn't major in my microbenchmarks it resultet in a speedup of ~1,5% for such constructs in inner loops. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 13:22:42 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 13:22:42 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.c2370186951d6ce1d89f8b19c3c3cece@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: Nolan Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Nolan): * owner: (none) => Nolan Old description: > The file Test.hs has following definitions: > {{{ > whnf :: a -> IO () > whnf a = a `seq` (return ()) > > foo :: [Int] > foo = [1..] > }}} > > Calling ghci as: > {{{ > ghci Test.hs -ignore-dot-ghci > }}} > > and bebugging foo like this: > {{{ > *Main> :b foo > Breakpoint 0 activated at Test.hs:5:7-11 > *Main> foo > Stopped at Test.hs:5:7-11 > _result :: [Int] = _ > [Test.hs:5:7-11] *Main> :p foo > foo = (_t1::[Int]) > [Test.hs:5:7-11] *Main> whnf _t1 > }}} > > results in this segault: > {{{ > : internal error: TSO object entered! > (GHC version 7.6.3 for x86_64_unknown_linux) > Please report this as a GHC bug: > http://www.haskell.org/ghc/reportabug > [1] 5445 abort (core dumped) ghci Test.hs -ignore-dot-ghci > }}} New description: The file Test.hs has following definition: {{{ foo :: [Int] foo = [1..] }}} Calling ghci as: {{{ ghci Test.hs -ignore-dot-ghci }}} and bebugging foo like this: {{{ *Main> :break foo Breakpoint 0 activated at main.hs:2:7-11 *Main> foo Stopped in Main.foo, main.hs:2:7-11 _result :: [Int] = _ [main.hs:2:7-11] [main.hs:2:7-11] *Main> :print foo foo = (_t1::[Int]) [main.hs:2:7-11] [main.hs:2:7-11] *Main> _t1 }}} results in this segault: {{{ : internal error: TSO object entered! (GHC version 8.5.20180302 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug [1] 5445 abort (core dumped) ghci Test.hs -ignore-dot-ghci }}} -- Comment: I simplified example. whnf function is not required to trigger this bug. You can also notice that context of execution (i.e. [main.hs:2:7-11]) prints twice which looks like a bug and probably deserves a ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 13:31:25 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 13:31:25 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.e8cf0b1d98268306cf4628df8b084e6d@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Nolan): * owner: Nolan => (none) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 14:12:09 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 14:12:09 -0000 Subject: [GHC] #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled In-Reply-To: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> References: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> Message-ID: <061.3c50ac7e7e45f1ec9343ff45462b5045@haskell.org> #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled -------------------------------------+------------------------------------- Reporter: rotaerk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.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: | -------------------------------------+------------------------------------- Comment (by rotaerk): I don't know for sure that it's a bug. The ''apparent'' intent of errorWithoutStackTrace was not being followed, so I wanted to draw attention to it. If someone with familiarity with the decisions behind the implementation declares this to be intended behavior, the ticket can be closed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 14:14:01 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 14:14:01 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.efcfb8b41ddd3ba6fd272a9eb2bcbbb7@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers 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 voanhduy1512): Hello, I am new to Haskell (never use in prod) and ghc but i think i can help. I need to follow this process https://ghc.haskell.org/trac/ghc/wiki/WorkingConventions/DocumentationChanges to update the document right? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 15:40:00 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 15:40:00 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.062f000e98f329cb70af65291393fb75@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: voanhduy1512 Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4528 Wiki Page: | -------------------------------------+------------------------------------- Changes (by voanhduy1512): * owner: (none) => voanhduy1512 * differential: => Phab:D4528 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 18:56:33 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 18:56:33 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.09519af5362d81275da121e87de027e6@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Thanks for the simplification. Which GHC version did you use to try this? I don't see the prompt printed twice on 8.4.1 and HEAD> -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 19:02:11 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 19:02:11 -0000 Subject: [GHC] #14298: Let Template Haskell dynamically add something with which to link In-Reply-To: <050.5b84ef44d6dba8c28fe71b17d035f8a7@haskell.org> References: <050.5b84ef44d6dba8c28fe71b17d035f8a7@haskell.org> Message-ID: <065.4f99d9dfd85a1dfa9882a26e6d945ba9@haskell.org> #14298: Let Template Haskell dynamically add something with which to link -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.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:D4064 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"ceb914771aece0aa6d87339227ce406c7179d1d1/ghc" ceb91477/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ceb914771aece0aa6d87339227ce406c7179d1d1" Support adding objects from TH The user facing TH interface changes are: * 'addForeignFile' is renamed to 'addForeignSource' * 'qAddForeignFile'/'addForeignFile' now expect 'FilePath's * 'RawObject' is now a constructor for 'ForeignSrcLang' * 'qAddTempFile'/'addTempFile' let you request a temporary file from the compiler. Test Plan: unsure about this, added a TH test Reviewers: goldfire, bgamari, angerman Reviewed By: bgamari, angerman Subscribers: hsyl20, mboes, carter, simonmar, bitonic, ljli, rwbarton, thomie GHC Trac Issues: #14298 Differential Revision: https://phabricator.haskell.org/D4217 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 19:02:27 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 19:02:27 -0000 Subject: [GHC] #14931: Segfault compiling file that uses Template Haskell with -prof In-Reply-To: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> References: <050.e2cf8fbf897aaae2dabf491f41b7b399@haskell.org> Message-ID: <065.54afae8b84677973c8db8bf147a666cc@haskell.org> #14931: Segfault compiling file that uses Template Haskell with -prof -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"7bb1fde13be3b319bb567b1faa84436600aa47ab/ghc" 7bb1fde/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7bb1fde13be3b319bb567b1faa84436600aa47ab" testsuite: Add test for #14931 Reviewers: alpmestan Reviewed By: alpmestan Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14931 Differential Revision: https://phabricator.haskell.org/D4518 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 19:02:56 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 19:02:56 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.b25429e19eb80c2d151fcbb5b606385d@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9893042604cda5260cb0f7b674ed5c34b419e403/ghc" 9893042/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9893042604cda5260cb0f7b674ed5c34b419e403" Fix two pernicious bugs in DeriveAnyClass The way GHC was handling `DeriveAnyClass` was subtly wrong in two notable ways: * In `inferConstraintsDAC`, we were //always// bumping the `TcLevel` of newly created unification variables, under the assumption that we would always place those unification variables inside an implication constraint. But #14932 showed precisely the scenario where we had `DeriveAnyClass` //without// any of the generated constraints being used inside an implication, which made GHC incorrectly believe the unification variables were untouchable. * Even worse, we were using the generated unification variables from `inferConstraintsDAC` in every single iteration of `simplifyDeriv`. In #14933, however, we have a scenario where we fill in a unification variable with a skolem in one iteration, discard it, proceed on to another iteration, use the same unification variable (still filled in with the old skolem), and try to unify it with a //new// skolem! This results in an utter disaster. The root of both these problems is `inferConstraintsDAC`. This patch fixes the issue by no longer generating unification variables directly in `inferConstraintsDAC`. Instead, we store the original variables from a generic default type signature in `to_metas`, a new field of `ThetaOrigin`, and in each iteration of `simplifyDeriv`, we generate fresh meta tyvars (avoiding the second issue). Moreover, this allows us to more carefully fine-tune the `TcLevel` under which we create these meta tyvars, fixing the first issue. Test Plan: make test TEST="T14932 T14933" Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14932, #14933 Differential Revision: https://phabricator.haskell.org/D4507 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 19:02:56 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 19:02:56 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic In-Reply-To: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> References: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> Message-ID: <065.a88031e7d21a9af7ea79bd62f6bebbae@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9893042604cda5260cb0f7b674ed5c34b419e403/ghc" 9893042/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9893042604cda5260cb0f7b674ed5c34b419e403" Fix two pernicious bugs in DeriveAnyClass The way GHC was handling `DeriveAnyClass` was subtly wrong in two notable ways: * In `inferConstraintsDAC`, we were //always// bumping the `TcLevel` of newly created unification variables, under the assumption that we would always place those unification variables inside an implication constraint. But #14932 showed precisely the scenario where we had `DeriveAnyClass` //without// any of the generated constraints being used inside an implication, which made GHC incorrectly believe the unification variables were untouchable. * Even worse, we were using the generated unification variables from `inferConstraintsDAC` in every single iteration of `simplifyDeriv`. In #14933, however, we have a scenario where we fill in a unification variable with a skolem in one iteration, discard it, proceed on to another iteration, use the same unification variable (still filled in with the old skolem), and try to unify it with a //new// skolem! This results in an utter disaster. The root of both these problems is `inferConstraintsDAC`. This patch fixes the issue by no longer generating unification variables directly in `inferConstraintsDAC`. Instead, we store the original variables from a generic default type signature in `to_metas`, a new field of `ThetaOrigin`, and in each iteration of `simplifyDeriv`, we generate fresh meta tyvars (avoiding the second issue). Moreover, this allows us to more carefully fine-tune the `TcLevel` under which we create these meta tyvars, fixing the first issue. Test Plan: make test TEST="T14932 T14933" Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14932, #14933 Differential Revision: https://phabricator.haskell.org/D4507 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 19:03:42 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 19:03:42 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules In-Reply-To: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> References: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> Message-ID: <059.2178c974b5e0b44b9701b8684feed6df@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | overloadedrecflds/should_fail/T14953 Blocked By: | Blocking: Related Tickets: #13352 | Differential Rev(s): Phab:D4527 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"fb462f948b4a10406fab84fd5878149c11aafe8a/ghc" fb462f94/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fb462f948b4a10406fab84fd5878149c11aafe8a" Fix panic on module re-exports of DuplicateRcordFields Test Plan: new test overloadedrecflds/should_fail/T14953 Reviewers: mpickering, simonpj, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14953 Differential Revision: https://phabricator.haskell.org/D4527 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 19:04:01 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 19:04:01 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.89e0faa1544bf4959283540e640d7068@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: voanhduy1512 Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"c16df6061abd33c67797b1cd676a980457f52533/ghc" c16df60/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c16df6061abd33c67797b1cd676a980457f52533" document: fix trac issue #14229 Accroding to https://git.haskell.org/ghc.git/commitdiff/49672659113371c3bee691e6d913d f8e6f60a1d8, `-Wredundant-constraints` is no longer turn on by default. Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4528 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 21:03:20 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 21:03:20 -0000 Subject: [GHC] #14972: MacOS panic on TH Message-ID: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I recently did a clean build of master (affdea82bb70e5a912b679a169c6e9a230e4c93e) and, while everything successfully finished, I'm getting panics every time I try to use this GHC for something that involves TH. For example: {{{#!hs {-# language TemplateHaskell #-} pure [] main = pure [] }}} Crashes with {{{ $ ./inplace/bin/ghc-stage2 th.hs [1 of 1] Compiling Main ( th.hs, th.o ) ghc-stage2: loadArchive: Failed reading header from `/Users/atheriault/Documents/code/ghc/libraries/integer-gmp/dist- install/build/gmp' ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180325 for x86_64-apple-darwin): loadArchive "/Users/atheriault/Documents/code/ghc/libraries /integer-gmp/dist-install/build/gmp": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Normally I'd assume I haven't correctly configured something, yet I had no problem building and running GHC on this machine a month or so ago... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 21:15:23 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 21:15:23 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.80596280286b54c84e2860d074b20602@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Nolan): I use most current version from git repository. I've just built it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 21:29:18 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 21:29:18 -0000 Subject: [GHC] #14971: Use appropriatly sized comparison instruction for small values. In-Reply-To: <047.ebf633502b771144a04c11718d3a50dd@haskell.org> References: <047.ebf633502b771144a04c11718d3a50dd@haskell.org> Message-ID: <062.c77909793828799bb3a74f17ddf98283@haskell.org> #14971: Use appropriatly sized comparison instruction for small values. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: (CodeGen) | Resolution: | Keywords: CodeGen Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => CodeGen Comment: Sounds good! 1.5% is a lot. How did you get that figure? Do you have a patch :-)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Mar 25 22:46:18 2018 From: ghc-devs at haskell.org (GHC) Date: Sun, 25 Mar 2018 22:46:18 -0000 Subject: [GHC] #13362: GHC first generation of GC to be as large as largest cache size by default In-Reply-To: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> References: <045.9df30bf1acd19df01317b133116e51f6@haskell.org> Message-ID: <060.c8fbb0b342f0c86b8d3d9f861d9b02d8@haskell.org> #13362: GHC first generation of GC to be as large as largest cache size by default -------------------------------------+------------------------------------- Reporter: varosi | Owner: sjakobi Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.0.2 Resolution: | Keywords: numa cache gc | newcomers 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 sjakobi): Replying to [comment:15 varosi]: > How can I experiment with non-optimized version as I doesn't have reference for comparison? I could try to build some optimized version. Building your own binary should be pretty straightforward. In order to investigate the effects of my patch you don't really need a different build anyway. You can simply find out what size your L3 cache has and pass that size to the `-A` RTS flag. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 00:11:58 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 00:11:58 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.2d723790c08388773ad1306bda1b584b@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9a00bfba122cd7138892c934c9cc3376dc2abe98/ghc" 9a00bfba/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9a00bfba122cd7138892c934c9cc3376dc2abe98" rts/RetainerProfile: Dump closure type if push() fails While investigating #14947, I noticed that the `barf`ed error message in `push()` doesn't print out the closure type that causes it to crash. Let's do so. Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: alexbiehl, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4525 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 00:12:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 00:12:12 -0000 Subject: [GHC] #14925: Non-ASCII type names get garbled when their `TypeRep` is shown In-Reply-To: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> References: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> Message-ID: <069.f499e13270f8489579a7dedf26d74812@haskell.org> #14925: Non-ASCII type names get garbled when their `TypeRep` is shown -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: new Priority: low | Milestone: Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Typeable | TypeRep Unicode ASCII UTF-8 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | typecheck/T14925 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"0703c00f7172608ee6d7ff7d422fe3755339e9bc/ghc" 0703c00/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0703c00f7172608ee6d7ff7d422fe3755339e9bc" testsuite: Add test for #14925 Test Plan: Validate Reviewers: alpmestan Reviewed By: alpmestan Subscribers: alpmestan, leftaroundabout, rwbarton, thomie, carter GHC Trac Issues: #14925 Differential Revision: https://phabricator.haskell.org/D4512 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 00:12:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 00:12:26 -0000 Subject: [GHC] #14916: Missing checks when deriving special classes In-Reply-To: <047.da5641b8bbed13bc8200a08817691187@haskell.org> References: <047.da5641b8bbed13bc8200a08817691187@haskell.org> Message-ID: <062.f54a613f62ce6b9365906756cce841ea@haskell.org> #14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4501 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"20f14b4fd4eaf2c3ab375b8fc6d40ee9e6db94fd/ghc" 20f14b4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="20f14b4fd4eaf2c3ab375b8fc6d40ee9e6db94fd" Fix #14916 with an additional validity check in deriveTyData Manually-written instances and standalone-derived instances have the benefit of having the `checkValidInstHead` function run over them, which catches manual instances of built-in types like `(~)` and `Coercible`. However, instances generated from `deriving` clauses weren't being passed through `checkValidInstHead`, leading to confusing results as in #14916. `checkValidInstHead` also has additional validity checks for language extensions like `FlexibleInstances` and `MultiParamTypeClasses`. Up until now, GHC has never required these language extensions for `deriving` clause, so to avoid unnecessary breakage, I opted to suppress these language extension checks for `deriving` clauses, just like we currently suppress them for `SPECIALIZE instance` pragmas. Test Plan: make test TEST=T14916 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14916 Differential Revision: https://phabricator.haskell.org/D4501 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 00:12:41 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 00:12:41 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 In-Reply-To: <046.3db25c336062f0dea40eba4721995b57@haskell.org> References: <046.3db25c336062f0dea40eba4721995b57@haskell.org> Message-ID: <061.a989d992967c36764a55c088e3d4a043@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Debugging | (amd64) information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"0cbb13b3dfd70b4c9665109cd6c4a150cb7b99df/ghc" 0cbb13b3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0cbb13b3dfd70b4c9665109cd6c4a150cb7b99df" Don't refer to blocks in debug info when -g1 -g1 removes block information, but it turns out that procs can refer to block information through parents. Note [Splitting DebugBlocks] explains the parentage relationship. Test Plan: * ./validate * added a new test Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14894 Differential Revision: https://phabricator.haskell.org/D4496 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 00:12:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 00:12:55 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced In-Reply-To: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> References: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> Message-ID: <065.4cd1906351f840e711b8d448103d18c2@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: sighingnow Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 8.2.2 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:D4469 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a3986d7fa59d96a77ac0f25bcf1dcf96b8746994/ghc" a3986d7/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a3986d7fa59d96a77ac0f25bcf1dcf96b8746994" Fix scoped type variables in TH for several constructs Namely class methods, default signatures and pattern synonyms. When scoped type variables occur inside class default methods, default signatures and pattern synonyms, avoid re-create explicit type variables when represent the type signatures. This patch should fix Trac#14885. Signed-off-by: HE, Tao Test Plan: make test TEST="T14885a T14885b T14885c" Reviewers: goldfire, bgamari, simonpj, RyanGlScott Reviewed By: simonpj, RyanGlScott Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14885 Differential Revision: https://phabricator.haskell.org/D4469 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 00:59:30 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 00:59:30 -0000 Subject: [GHC] #14821: -O2 forces -optlo-O3 in a way that cannot be overridden at command line In-Reply-To: <047.f0bbe76f7e62f3251e5a424f7cdfd4d3@haskell.org> References: <047.f0bbe76f7e62f3251e5a424f7cdfd4d3@haskell.org> Message-ID: <062.f9fd5366ad1d616bb4fe36058a21f577@haskell.org> #14821: -O2 forces -optlo-O3 in a way that cannot be overridden at command line -------------------------------------+------------------------------------- Reporter: joeyhess | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4421 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"41db237e1290b650e52eb07323eca71de941e184/ghc" 41db237e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="41db237e1290b650e52eb07323eca71de941e184" llvmGen: Pass -optlo flags last to opt LLVM, like GHC, processes flags in the order that they appear. Consequently, we need to ensure the user-provided flags appear last so they can override flags produced by GHC. See #14821. Test Plan: `ghc -O2 -optlo-O2 -v3 $FILE` and ensure that `opt` and `llc` are invoked with `-O2`. Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14821 Differential Revision: https://phabricator.haskell.org/D4421 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:00:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:00:19 -0000 Subject: [GHC] #14821: -O2 forces -optlo-O3 in a way that cannot be overridden at command line In-Reply-To: <047.f0bbe76f7e62f3251e5a424f7cdfd4d3@haskell.org> References: <047.f0bbe76f7e62f3251e5a424f7cdfd4d3@haskell.org> Message-ID: <062.38f85463827d8785d627ffaf55f71fc4@haskell.org> #14821: -O2 forces -optlo-O3 in a way that cannot be overridden at command line -------------------------------------+------------------------------------- Reporter: joeyhess | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (LLVM) | Version: 8.0.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4421 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:02:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:02:27 -0000 Subject: [GHC] #14885: TH breaks the scoping of quoted default method implementations when spliced In-Reply-To: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> References: <050.b7b2b61683a9014a2abd94af597f684a@haskell.org> Message-ID: <065.85dbae66ca757a43d0f02cb072b57367@haskell.org> #14885: TH breaks the scoping of quoted default method implementations when spliced -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: sighingnow Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.2.2 Resolution: fixed | 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:D4469 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:02:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:02:57 -0000 Subject: [GHC] #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse In-Reply-To: <050.0ece8699aa4ecc920883092df1385787@haskell.org> References: <050.0ece8699aa4ecc920883092df1385787@haskell.org> Message-ID: <065.da60a0a8a51687ae3a06f9e2be1a0564@haskell.org> #14918: GHC 8.4.1 regression: derived Read instances with field names containing # no longer parse -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | deriving/should_run/T14918 Blocked By: | Blocking: Related Tickets: #5041, #14364 | Differential Rev(s): Phab:D4502 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `master` and `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:06:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:06:03 -0000 Subject: [GHC] #14894: HEAD fails to build with -g1 In-Reply-To: <046.3db25c336062f0dea40eba4721995b57@haskell.org> References: <046.3db25c336062f0dea40eba4721995b57@haskell.org> Message-ID: <061.80d6b21340f19996dd25a854e49d519d@haskell.org> #14894: HEAD fails to build with -g1 -------------------------------------+------------------------------------- Reporter: niteria | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Debugging | (amd64) information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:06:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:06:51 -0000 Subject: [GHC] #14916: Missing checks when deriving special classes In-Reply-To: <047.da5641b8bbed13bc8200a08817691187@haskell.org> References: <047.da5641b8bbed13bc8200a08817691187@haskell.org> Message-ID: <062.b3db4f46463db813ba566f653c01e596@haskell.org> #14916: Missing checks when deriving special classes -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Poor/confusing | Unknown/Multiple error message | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4501 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.4.2 Old description: > For the following program > {{{ > {-# LANGUAGE DeriveAnyClass #-} > module T where > > import Data.Coerce > import Data.Typeable > > data A = MkA deriving ((~) A) > data B = MkB deriving (Coercible B) > }}} > the deriving clause for `A` is accepted without complaints, and the > deriving clause for `B` fails with the following error: > {{{ > T.hs:8:24: error: > Top-level bindings for unlifted types aren't allowed: > | > 8 | data B = MkB deriving (Coercible B) > | ^^^^^^^^^^^ > }}} > > Corresponding standalone deriving instances trigger errors > saying "Manual instances of this class are not permitted". > Probably similar error messages should be triggered here. New description: For the following program {{{#!hs {-# LANGUAGE DeriveAnyClass #-} module T where import Data.Coerce import Data.Typeable data A = MkA deriving ((~) A) data B = MkB deriving (Coercible B) }}} the deriving clause for `A` is accepted without complaints, and the deriving clause for `B` fails with the following error: {{{ T.hs:8:24: error: Top-level bindings for unlifted types aren't allowed: | 8 | data B = MkB deriving (Coercible B) | ^^^^^^^^^^^ }}} Corresponding standalone deriving instances trigger errors saying "Manual instances of this class are not permitted". Probably similar error messages should be triggered here. -- Comment: Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:08:02 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:08:02 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.a2201cf9608d4260b08a287b4a7578ff@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: voanhduy1512 Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Thanks voanhduy1512! Have you checked whether any of the other issues brought up in this ticket still need fixing? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:08:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:08:47 -0000 Subject: [GHC] #14953: Panic when exporting duplicate record fields from separate modules In-Reply-To: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> References: <044.ff3dc5f178897345335e0d0b4d7772fa@haskell.org> Message-ID: <059.cf670c9c8ad5d9f4f486b8fbbb6ab819@haskell.org> #14953: Panic when exporting duplicate record fields from separate modules -------------------------------------+------------------------------------- Reporter: lyxia | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | overloadedrecflds/should_fail/T14953 Blocked By: | Blocking: Related Tickets: #13352 | Differential Rev(s): Phab:D4527 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Old description: > `A.hs` > > {{{ > {-# LANGUAGE DuplicateRecordFields #-} > module A where > data R = R {unR :: Int} > }}} > > --- > > `B.hs` > > {{{ > {-# LANGUAGE DuplicateRecordFields #-} > module B where > data R = R {unR :: Int} > }}} > > --- > > `C.hs` > > {{{ > {-# LANGUAGE DuplicateRecordFields #-} > > module C (module A, module B) where > > import A > import B > }}} > > --- > > Output of `ghc C.hs`: > > {{{ > C.hs:3:21: error:ghc-stage2: panic! (the 'impossible' happened) > (GHC version 8.5.20180224 for x86_64-unknown-linux): > exportClashErr > $sel:unR:R > Call stack: > CallStack (from HasCallStack): > callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in > ghc:Outputable > pprPanic, called at compiler/typecheck/TcRnExports.hs:740:22 in > ghc:TcRnExports > > }}} New description: `A.hs` {{{#!hs {-# LANGUAGE DuplicateRecordFields #-} module A where data R = R {unR :: Int} }}} --- `B.hs` {{{#!hs {-# LANGUAGE DuplicateRecordFields #-} module B where data R = R {unR :: Int} }}} --- `C.hs` {{{#!hs {-# LANGUAGE DuplicateRecordFields #-} module C (module A, module B) where import A import B }}} --- Output of `ghc C.hs`: {{{ C.hs:3:21: error:ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180224 for x86_64-unknown-linux): exportClashErr $sel:unR:R Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/typecheck/TcRnExports.hs:740:22 in ghc:TcRnExports }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:10:25 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:10:25 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.5fb68a7550642c9d62f93c06f305ff7d@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.6.1 Comment: RyanGlScott, do you think this is `ghc-8.4` material? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:10:58 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:10:58 -0000 Subject: [GHC] #14298: Let Template Haskell dynamically add something with which to link In-Reply-To: <050.5b84ef44d6dba8c28fe71b17d035f8a7@haskell.org> References: <050.5b84ef44d6dba8c28fe71b17d035f8a7@haskell.org> Message-ID: <065.afa61eae67c807e84dbb29592b6f1b57@haskell.org> #14298: Let Template Haskell dynamically add something with which to link -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Template Haskell | Version: 8.2.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:D4064 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 01:18:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 01:18:08 -0000 Subject: [GHC] #14925: Non-ASCII type names get garbled when their `TypeRep` is shown In-Reply-To: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> References: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> Message-ID: <069.a993af60f46e83b1f0058feb04eb42e2@haskell.org> #14925: Non-ASCII type names get garbled when their `TypeRep` is shown -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: patch Priority: low | Milestone: 8.4.2 Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Typeable | TypeRep Unicode ASCII UTF-8 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | typecheck/T14925 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4530 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D4530 * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 02:13:20 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 02:13:20 -0000 Subject: [GHC] #14925: Non-ASCII type names get garbled when their `TypeRep` is shown In-Reply-To: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> References: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> Message-ID: <069.79b28c0f82b22831dac72788a74afc74@haskell.org> #14925: Non-ASCII type names get garbled when their `TypeRep` is shown -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: patch Priority: low | Milestone: 8.4.2 Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Typeable | TypeRep Unicode ASCII UTF-8 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | typecheck/T14925 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4530 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"20ae19fc7297dceaefde8d3443099bfd9cd1e905/ghc" 20ae19fc/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="20ae19fc7297dceaefde8d3443099bfd9cd1e905" base: Fix Unicode handling of TyCon's Show instance Test Plan: `make test TEST=T14925` Reviewers: hvr, dfeuer Reviewed By: dfeuer Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14925 Differential Revision: https://phabricator.haskell.org/D4530 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 02:14:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 02:14:04 -0000 Subject: [GHC] #14925: Non-ASCII type names get garbled when their `TypeRep` is shown In-Reply-To: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> References: <054.383b56a83cf9063aded75e1bab3595b7@haskell.org> Message-ID: <069.18451602262b18f6972711103d35a5bf@haskell.org> #14925: Non-ASCII type names get garbled when their `TypeRep` is shown -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: closed Priority: low | Milestone: 8.4.2 Component: libraries/base | Version: 8.2.1 Resolution: fixed | Keywords: Typeable | TypeRep Unicode ASCII UTF-8 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | typecheck/T14925 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4530 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 03:17:29 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 03:17:29 -0000 Subject: [GHC] #4442: Add unaligned version of indexWordArray# In-Reply-To: <044.4c85d11a3d9c22b5e6021cb85ad43106@haskell.org> References: <044.4c85d11a3d9c22b5e6021cb85ad43106@haskell.org> Message-ID: <059.015fab90019e603493a15cb963d0c9a4@haskell.org> #4442: Add unaligned version of indexWordArray# -------------------------------------+------------------------------------- Reporter: tibbe | Owner: reinerp Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #14447 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by David Feuer ): In [changeset:"efd70cfb4b0b9932a880ab417d75eaf95da3d5e6/ghc" efd70cfb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="efd70cfb4b0b9932a880ab417d75eaf95da3d5e6" Add unaligned bytearray access primops. Fixes #4442. Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #4442 Differential Revision: https://phabricator.haskell.org/D4488 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 03:54:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 03:54:51 -0000 Subject: [GHC] #11188: Confusing "parse error in pattern" for spurious indentation. In-Reply-To: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> References: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> Message-ID: <066.91d109025ab8db17fe219e6deabc15ba@haskell.org> #11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => normal * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. Closing but do feel free to reopen if you can think of anything more we can do here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 03:55:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 03:55:36 -0000 Subject: [GHC] #14959: Heap overflow in optimizer In-Reply-To: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> References: <046.9dbd8256a0101713faa2fec3a411fbd9@haskell.org> Message-ID: <061.ac31e61f678e2277be9a2b3a012dca61@haskell.org> #14959: Heap overflow in optimizer -------------------------------------+------------------------------------- Reporter: darchon | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T14959 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.4.2 Comment: Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 03:55:45 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 03:55:45 -0000 Subject: [GHC] #11188: Confusing "parse error in pattern" for spurious indentation. In-Reply-To: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> References: <051.b8c2bb1173a96cc38d2a08ac891825b7@haskell.org> Message-ID: <066.b095df035db2d34442c4238797e618da@haskell.org> #11188: Confusing "parse error in pattern" for spurious indentation. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #984 | Differential Rev(s): Phab:D4497 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 03:55:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 03:55:54 -0000 Subject: [GHC] #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint In-Reply-To: <043.599dc42c545c1acae74a2386e576be96@haskell.org> References: <043.599dc42c545c1acae74a2386e576be96@haskell.org> Message-ID: <058.eb8bc974a0ad3bbb9da8c90dfb4f58a4@haskell.org> #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: GHCi | Version: 8.5 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:D4490 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 03:58:05 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 03:58:05 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.5d18ee2c79976beedf0f86dbe06aeaeb@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 7.0.3 Resolution: fixed | Keywords: seq, evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #13930 | Differential Rev(s): Phab:D615, Wiki Page: | Phab:D4514 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 04:00:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 04:00:12 -0000 Subject: [GHC] #14934: Repeated "impossible" go_axiom_rule error. In-Reply-To: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> References: <044.08dc1244a2bd7b524347843f30ac9e29@haskell.org> Message-ID: <059.29d4fc3ca34023f2ab84d0ba2ff577b4@haskell.org> #14934: Repeated "impossible" go_axiom_rule error. -------------------------------------+------------------------------------- Reporter: galen | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4508 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 04:02:48 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 04:02:48 -0000 Subject: [GHC] #14906: Release notes have wrong version of base package In-Reply-To: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> References: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> Message-ID: <061.905edd1795d45a35a90c738ebd36491c@haskell.org> #14906: Release notes have wrong version of base package -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: Documentation | Version: 8.4.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:D4491 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 04:02:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 04:02:55 -0000 Subject: [GHC] #14906: Release notes have wrong version of base package In-Reply-To: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> References: <046.aa20801817f0cc1af522b141e94f1c04@haskell.org> Message-ID: <061.39830e71eb959b241e2ed4878d03f300@haskell.org> #14906: Release notes have wrong version of base package -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: Documentation | Version: 8.4.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:D4491 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 05:08:11 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 05:08:11 -0000 Subject: [GHC] #14969: panic on incorrect syntax In-Reply-To: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> References: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> Message-ID: <061.d623c4ce594b20e405bd684f35f462d8@haskell.org> #14969: panic on incorrect syntax -------------------------------------+------------------------------------- Reporter: johnleo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 sighingnow): This panic is caused by the bad `TcLevel` when checking the `TcLevel` invariants, maybe related to ticket:14884. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 05:35:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 05:35:36 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.777ecc463bcd57bf84f5c9e0b4032da5@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: alpmestan Type: task | Status: closed Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 7.10.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:D1021 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Lovely, let's close this then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 05:37:33 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 05:37:33 -0000 Subject: [GHC] #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled In-Reply-To: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> References: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> Message-ID: <061.e1dc47181e73ff5ef0cf9d3ce66f501a@haskell.org> #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled -------------------------------------+------------------------------------- Reporter: rotaerk | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.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: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed I think this is expected. The point (as I understand it) of `errorWithoutStackTrace` is to avoid the (potential) runtime cost of `HasCallStack`. In the case of the CCS stack there is no additional cost to providing the stack-trace. We probably ought to document this, however. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 07:36:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 07:36:28 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.9affa33e871cfb66f279fec788ef885a@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D4531 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 07:37:04 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 07:37:04 -0000 Subject: [GHC] #14815: -XStrict prevents code inlining. In-Reply-To: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> References: <046.08bab70ba7e4277e77ed3f217479b09d@haskell.org> Message-ID: <061.bc03e75938bf2a95bd98e317fd6a821f@haskell.org> #14815: -XStrict prevents code inlining. -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: patch Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4531 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): As discussed last week, I submitted a patch that compares program sizes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 07:50:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 07:50:01 -0000 Subject: [GHC] #14973: Location in GHCi debugger prompt printed twice when default prompt is used Message-ID: <043.77b079247cf81e1c9a49efb3c90c1743@haskell.org> #14973: Location in GHCi debugger prompt printed twice when default prompt is used -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.5 Keywords: debugger | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- (Noticed in #8316) Test.hs: {{{#!haskell foo :: [Int] foo = [ 1 .. 10 ] }}} Reproducer: {{{ $ ghc-stage2 --interactive -ignore-dot-ghci Test.hs GHCi, version 8.5.20180325: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Test.hs, interpreted ) Ok, one module loaded. *Main> :break foo Breakpoint 0 activated at Test.hs:2:7-14 *Main> foo Stopped in Main.foo, Test.hs:2:7-14 _result :: [Int] = _ [Test.hs:2:7-14] [Test.hs:2:7-14] *Main> }}} The `[Test.hs:2:7-14]` part is repeated. Setting the prompt fixes it: {{{ $ ghc-stage2 --interactive Test.hs -ignore-dot-ghci GHCi, version 8.5.20180325: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Test.hs, interpreted ) Ok, one module loaded. *Main> :set prompt "> " > :break foo Breakpoint 0 activated at Test.hs:2:7-14 > foo Stopped in Main.foo, Test.hs:2:7-14 _result :: [Int] = _ [Test.hs:2:7-14] > }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 07:51:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 07:51:35 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.087d22df10092c28f846170e1d9ac4c9@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Thanks, it turns out I have to use the default prompt to reproduce. Reported as #14973. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 08:20:32 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 08:20:32 -0000 Subject: [GHC] #14967: Optimizer Casting Caf with nominal type In-Reply-To: <042.add8f351aaf885809089532f69f1f66e@haskell.org> References: <042.add8f351aaf885809089532f69f1f66e@haskell.org> Message-ID: <057.8bce4a4aebaff80013fa769f69c24a07@haskell.org> #14967: Optimizer Casting Caf with nominal type -------------------------------------+------------------------------------- Reporter: etn | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: invalid | Keywords: coerce, | nominal 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 simonpj): * status: new => closed * resolution: => invalid Comment: Looks ok to me. We get {{{ T14967.$fGenNom_$cgen :: forall a. Nom a T14967.$fGenNom_$cgen = \ (@ a_a2zl) -> trace @ (Nom a_a2zl) T14967.$fGenNom3 (T14967.$fGenNom1 @ a_a2zl) }}} and we invoke this polymorphic function at three different types. But types are erased before code generation, so this turns into {{{ T14967.$fGenNom_$cgen = trace T14967.$fGenNom3 T14967.$fGenNom1 }}} and the three uses of this thunk are of course shared. There no casting involved. Only polymorphic functions. Does that make sense? I'll close as not-a-bug but re-open if you disagree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 08:37:01 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 08:37:01 -0000 Subject: [GHC] #14971: Use appropriatly sized comparison instruction for small values. In-Reply-To: <047.ebf633502b771144a04c11718d3a50dd@haskell.org> References: <047.ebf633502b771144a04c11718d3a50dd@haskell.org> Message-ID: <062.6aff01a4e26992666f3e0c45d4e92e80@haskell.org> #14971: Use appropriatly sized comparison instruction for small values. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: (CodeGen) | Resolution: | Keywords: CodeGen 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 AndreasK): Replying to [comment:1 simonpj]: > Sounds good! 1.5% is a lot. How did you get that figure? Indeed it's more than I would have expected. But these are micro benchmarks so it's hard to predict how much of that will remain when running regular programs. Given that cache behaviour and cpu bottlecks would be different there. I've compiled two criterion benchmarks and changed the assembly by Hand. One example was: {{{ module Main (main) where import Criterion.Main mapInt :: Int -> Int mapInt 1 = 111 mapInt 2 = 211 mapInt 3 = 311 {-# NOINLINE sumAndLookup #-} sumAndLookup :: [Int] -> Int sumAndLookup = sum . map mapInt main = do let value = map (\x -> 1 + x `mod` 3) [1..30] print (sumAndLookup value) defaultMain [ bgroup "opSize" [ bench "caseOfThree" $ whnf sumAndLookup value] ] }}} > Do you have a patch :-)? Not yet. I submitted a project proposal for Summer of Code which includes writing a patch for this. But if that should not work out I still expect to get around to it eventually. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 08:38:48 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 08:38:48 -0000 Subject: [GHC] #14974: 2-fold memory usage regression GHC 8.2.2 -> GHC 8.4.1 compiling `mmark` package Message-ID: <042.6f9317183740e6c428dbe334554fec22@haskell.org> #14974: 2-fold memory usage regression GHC 8.2.2 -> GHC 8.4.1 compiling `mmark` package -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.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: -------------------------------------+------------------------------------- I haven't had time yet to diagnose where the memory is going to, but here's how to reproduce: {{{ cabal get mmark-0.0.5.6 && cd mmark-0.0.5.6/ cat > cabal.project <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o ) Text/MMark/Type.hs:38:1: warning: [-Wunused-imports] The import of ‘Data.Semigroup’ is redundant except perhaps to import instances from ‘Data.Semigroup’ To import instances alone, use: import Data.Semigroup() | 38 | import Data.Semigroup | ^^^^^^^^^^^^^^^^^^^^^ [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o ) Text/MMark/Render.hs:25:1: warning: [-Wunused-imports] The import of ‘Data.Semigroup’ is redundant except perhaps to import instances from ‘Data.Semigroup’ To import instances alone, use: import Data.Semigroup() | 25 | import Data.Semigroup | ^^^^^^^^^^^^^^^^^^^^^ [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> }}} and {{{ Resolving dependencies... Build profile: -w ghc-8.4.1 -O1 In order, the following will be built (use -v for more details): - mmark-0.0.5.6 (lib) (first run) Configuring library for mmark-0.0.5.6.. <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o ) [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o ) [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> hvr at duo:/tmp/mmark-0.0.5.6$ cabal new-build -w ghc-8.2.2 Resolving dependencies... Build profile: -w ghc-8.2.2 -O1 In order, the following will be built (use -v for more details): - mmark-0.0.5.6 (lib) (first run) Configuring library for mmark-0.0.5.6.. <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Type.o ) [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Render.o ) [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> }}} Consequently, - GHC 8.2.2: **2179M in use**, 0.001 INIT (0.000 elapsed), 58.237 MUT (61.472 elapsed), 25.823 GC (25.795 elapsed) - GHC 8.4.1: **4130M in use**, 0.000 INIT (0.000 elapsed), 58.546 MUT (62.124 elapsed), 31.536 GC (31.505 elapsed) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 08:40:02 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 08:40:02 -0000 Subject: [GHC] #14914: Only turn suitable targets into a fallthrough in CmmContFlowOpt. In-Reply-To: <047.e546ff075cab0520de14a4fd1c9b5069@haskell.org> References: <047.e546ff075cab0520de14a4fd1c9b5069@haskell.org> Message-ID: <062.30ba8d711117ce34ab6d2107640c92ae@haskell.org> #14914: Only turn suitable targets into a fallthrough in CmmContFlowOpt. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: (CodeGen) | Resolution: | Keywords: CodeGen 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 AndreasK): * keywords: => CodeGen Comment: It's also worth noting that inverting conditionals has a major effect on codelayout. So this has to be considered when changing the logic behind the inversions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 08:42:46 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 08:42:46 -0000 Subject: [GHC] #14830: Use test instead of cmp for comparison against zero. In-Reply-To: <047.ca37bf7e6f971d0d97b5218e90d6b786@haskell.org> References: <047.ca37bf7e6f971d0d97b5218e90d6b786@haskell.org> Message-ID: <062.c2b9f5b9d1cd6e321027e0a83bd6ef33@haskell.org> #14830: Use test instead of cmp for comparison against zero. -------------------------------------+------------------------------------- Reporter: AndreasK | Owner: (none) Type: task | Status: new Priority: low | Milestone: Component: Compiler (NCG) | Version: Resolution: | Keywords: CodeGen 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 AndreasK): * keywords: => CodeGen -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 11:15:48 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 11:15:48 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.c6003bb699b15821a4e0146e34ece9ff@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 simonmic): * cc: simonmic (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 12:47:14 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 12:47:14 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.4b587e06d2b02bb0c129d62c07c28df5@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm biased, but I think so. I'm amazed `DeriveAnyClass` was working correctly at all before this patch! (Plus, the patch looks larger than it really is—at its core, it's quite small.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 13:39:21 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 13:39:21 -0000 Subject: [GHC] #14975: Refactor (Maybe Coercion) Message-ID: <047.51816057ba89e62ff311692e8071c67c@haskell.org> #14975: Refactor (Maybe Coercion) -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11735 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- As discussed here: https://phabricator.haskell.org/D4395#inline-34607 Define a type {{{#!hs data MCoercion = MRefl | MCo Coercion }}} This is isomorphic to {{{Maybe Coercion}}} but useful in a number of places, and super-helpful documentation. (eg {{{MRefl}}} is much more perspicuous than {{{Nothing}}}. Define this in {{{Coercion.hs}}} I think. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 14:01:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 14:01:54 -0000 Subject: [GHC] #11735: Optimize coercionKind In-Reply-To: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> References: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> Message-ID: <062.5d040bceb44119ed5e21c103d094d895@haskell.org> #11735: Optimize coercionKind -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | 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: #14683 #14975 | Differential Rev(s): D4394 D4395 Wiki Page: | -------------------------------------+------------------------------------- Changes (by tdammers): * differential: => D4394 D4395 * related: => #14683 #14975 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 14:05:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 14:05:22 -0000 Subject: [GHC] #14969: panic on incorrect syntax In-Reply-To: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> References: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> Message-ID: <061.2cacddc9f60e2da7e501b7f8b8df3981@haskell.org> #14969: panic on incorrect syntax -------------------------------------+------------------------------------- Reporter: johnleo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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): Does not happen on 8.4.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 14:43:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 14:43:47 -0000 Subject: [GHC] #11735: Optimize coercionKind In-Reply-To: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> References: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> Message-ID: <062.c0910908967dec62b5534f30166380d3@haskell.org> #11735: Optimize coercionKind -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | 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: #14683 #14975 | Differential Rev(s): D4394 D4395 Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Profile after applying D4395 (coercionKind / Role refactoring): {{{ Mon Mar 26 15:24 2018 Time and Allocation Profiling Report (Final) ghc-stage2 +RTS -p -RTS -B/home/tobias/well- typed/devel/ghc/D4395-modified/inplace/lib ./cases/Grammar.hs -o ./a -fforce-recomp total time = 19.66 secs (19655 ticks @ 1000 us, 1 processor) total alloc = 24,638,084,488 bytes (excludes profiling overheads) COST CENTRE MODULE SRC %time %alloc simplCast Simplify compiler/simplCore/Simplify.hs:(1213,5)-(1215,37) 73.8 76.0 tc_rn_src_decls TcRnDriver compiler/typecheck/TcRnDriver.hs:(494,4)-(556,7) 8.3 8.4 CoreTidy HscMain compiler/main/HscMain.hs:1253:27-67 2.8 2.2 SimplTopBinds SimplCore compiler/simplCore/SimplCore.hs:770:39-74 2.7 1.9 coercionKind Coercion compiler/types/Coercion.hs:1698:3-7 1.8 3.4 zonkTopDecls TcRnDriver compiler/typecheck/TcRnDriver.hs:(445,16)-(446,43) 1.3 1.3 deSugar HscMain compiler/main/HscMain.hs:511:7-44 1.1 0.8 }}} This means that performance is on par, but `simplCast` still scores very high, so we should do more digging there. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 14:50:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 14:50:08 -0000 Subject: [GHC] #14969: panic on incorrect syntax In-Reply-To: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> References: <046.e2ddb687ff62b149f21f1d7eab94d28c@haskell.org> Message-ID: <061.1a549273831fe0e2679865c8f77bbb4f@haskell.org> #14969: panic on incorrect syntax -------------------------------------+------------------------------------- Reporter: johnleo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): To be clear, in comment:2, do you mean that it doesn't build with a standard 8.4.1 bindist, or with 8.4.1 built from source with `ASSERT`ions enabled? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 14:55:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 14:55:52 -0000 Subject: [GHC] #14880: GHC panic: updateRole In-Reply-To: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> References: <050.cdd24a949fb0169408d9edbb528c50d3@haskell.org> Message-ID: <065.6f132576e192b0c12695c8647c9914d0@haskell.org> #14880: GHC panic: updateRole -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): With the `Foo` in comment:3, this also panics: {{{#!hs quux :: forall x arg. Proxy (Foo arg) -> Maybe x quux = undefined }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:11:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:11:22 -0000 Subject: [GHC] #14974: 2-fold memory usage regression GHC 8.2.2 -> GHC 8.4.1 compiling `mmark` package In-Reply-To: <042.6f9317183740e6c428dbe334554fec22@haskell.org> References: <042.6f9317183740e6c428dbe334554fec22@haskell.org> Message-ID: <057.db32b6fc23ed3e983dd5b1c015fd8eea@haskell.org> #14974: 2-fold memory usage regression GHC 8.2.2 -> GHC 8.4.1 compiling `mmark` package -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Description changed by hvr: Old description: > I haven't had time yet to diagnose where the memory is going to, but > here's how to reproduce: > > {{{ > cabal get mmark-0.0.5.6 && cd mmark-0.0.5.6/ > > cat > cabal.project < packages: . > package mmark > ghc-options: -Rghc-timing > EOF > }}} > > Then, `cabal new-build -w ghc-8.4.1` and ``cabal new-build -w ghc-8.2.2` > will respectively output > > {{{ > Resolving dependencies... > Build profile: -w ghc-8.4.1 -O1 > In order, the following will be built (use -v for more details): > - mmark-0.0.5.6 (lib) (first run) > Configuring library for mmark-0.0.5.6.. > < samples), 4M in use, 0.001 INIT (0.000 elapsed), 0.007 MUT (0.025 > elapsed), 0.018 GC (0.018 elapsed) :ghc>> > Preprocessing library for mmark-0.0.5.6.. > Building library for mmark-0.0.5.6.. > [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( > Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o > ) > [2 of 9] Compiling Text.MMark.Parser.Internal ( > Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o > ) > [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o > ) > > Text/MMark/Type.hs:38:1: warning: [-Wunused-imports] > The import of ‘Data.Semigroup’ is redundant > except perhaps to import instances from ‘Data.Semigroup’ > To import instances alone, use: import Data.Semigroup() > | > 38 | import Data.Semigroup > | ^^^^^^^^^^^^^^^^^^^^^ > [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o > ) > [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o > ) > [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o > ) > > Text/MMark/Render.hs:25:1: warning: [-Wunused-imports] > The import of ‘Data.Semigroup’ is redundant > except perhaps to import instances from ‘Data.Semigroup’ > To import instances alone, use: import Data.Semigroup() > | > 25 | import Data.Semigroup > | ^^^^^^^^^^^^^^^^^^^^^ > [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o > ) > [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 > /dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) > [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o > ) > < residency (23 samples), 4130M in use, 0.000 INIT (0.000 elapsed), 58.546 > MUT (62.124 elapsed), 31.536 GC (31.505 elapsed) :ghc>> > < samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.021 MUT (0.207 > elapsed), 0.042 GC (0.042 elapsed) :ghc>> > }}} > > and > > {{{ > Resolving dependencies... > Build profile: -w ghc-8.4.1 -O1 > In order, the following will be built (use -v for more details): > - mmark-0.0.5.6 (lib) (first run) > Configuring library for mmark-0.0.5.6.. > < samples), 4M in use, 0.001 INIT (0.000 elapsed), 0.007 MUT (0.025 > elapsed), 0.018 GC (0.018 elapsed) :ghc>> > Preprocessing library for mmark-0.0.5.6.. > Building library for mmark-0.0.5.6.. > [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( > Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o > ) > [2 of 9] Compiling Text.MMark.Parser.Internal ( > Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o > ) > [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o > ) > [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o > ) > [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o > ) > [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o > ) > [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o > ) > [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 > /dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) > [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o > ) > < residency (23 samples), 4130M in use, 0.000 INIT (0.000 elapsed), 58.546 > MUT (62.124 elapsed), 31.536 GC (31.505 elapsed) :ghc>> > < samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.021 MUT (0.207 > elapsed), 0.042 GC (0.042 elapsed) :ghc>> > hvr at duo:/tmp/mmark-0.0.5.6$ cabal new-build -w ghc-8.2.2 > Resolving dependencies... > Build profile: -w ghc-8.2.2 -O1 > In order, the following will be built (use -v for more details): > - mmark-0.0.5.6 (lib) (first run) > Configuring library for mmark-0.0.5.6.. > < samples), 5M in use, 0.001 INIT (0.000 elapsed), 0.017 MUT (0.037 > elapsed), 0.021 GC (0.021 elapsed) :ghc>> > Preprocessing library for mmark-0.0.5.6.. > Building library for mmark-0.0.5.6.. > [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( > Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o > ) > [2 of 9] Compiling Text.MMark.Parser.Internal ( > Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o > ) > [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Type.o > ) > [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Trans.o > ) > [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Util.o > ) > [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Render.o > ) > [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser.o > ) > [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 > /dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark.o ) > [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Extension.o > ) > < residency (27 samples), 2179M in use, 0.001 INIT (0.000 elapsed), 58.237 > MUT (61.472 elapsed), 25.823 GC (25.795 elapsed) :ghc>> > < (6 samples), 20M in use, 0.001 INIT (0.000 elapsed), 0.028 MUT (0.213 > elapsed), 0.059 GC (0.059 elapsed) :ghc>> > }}} > > > Consequently, > > - GHC 8.2.2: **2179M in use**, 0.001 INIT (0.000 elapsed), 58.237 MUT > (61.472 elapsed), 25.823 GC (25.795 elapsed) > > - GHC 8.4.1: **4130M in use**, 0.000 INIT (0.000 elapsed), 58.546 MUT > (62.124 elapsed), 31.536 GC (31.505 elapsed) New description: I haven't had time yet to diagnose where the memory is going to, but here's how to reproduce: {{{ cabal get mmark-0.0.5.6 && cd mmark-0.0.5.6/ cat > cabal.project <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o ) [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o ) [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> }}} and {{{ Resolving dependencies... Build profile: -w ghc-8.2.2 -O1 In order, the following will be built (use -v for more details): - mmark-0.0.5.6 (lib) (first run) Configuring library for mmark-0.0.5.6.. <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Type.o ) [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Render.o ) [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> }}} Consequently, - GHC 8.2.2: **2179M in use**, 0.001 INIT (0.000 elapsed), 58.237 MUT (61.472 elapsed), 25.823 GC (25.795 elapsed) - GHC 8.4.1: **4130M in use**, 0.000 INIT (0.000 elapsed), 58.546 MUT (62.124 elapsed), 31.536 GC (31.505 elapsed) -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:14:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:14:26 -0000 Subject: [GHC] #14737: Improve performance of Simplify.simplCast In-Reply-To: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> References: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> Message-ID: <062.f9b95ae26f3ff2f9183a8d6aca59a4b3@haskell.org> #14737: Improve performance of Simplify.simplCast -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11735 #14683 | Differential Rev(s): Phab:D4385 Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Now that we have implemented the fix as outlined in D4395, it turns out that while the change is desirable overall, it does not actually improve performance significantly; `simplCast` still appears at the top of the profile, as evidenced here: {{{ Mon Mar 26 15:24 2018 Time and Allocation Profiling Report (Final) ghc-stage2 +RTS -p -RTS -B/home/tobias/well- typed/devel/ghc/D4395-modified/inplace/lib ./cases/Grammar.hs -o ./a -fforce-recomp total time = 19.66 secs (19655 ticks @ 1000 us, 1 processor) total alloc = 24,638,084,488 bytes (excludes profiling overheads) COST CENTRE MODULE SRC %time %alloc simplCast Simplify compiler/simplCore/Simplify.hs:(1213,5)-(1215,37) 73.8 76.0 tc_rn_src_decls TcRnDriver compiler/typecheck/TcRnDriver.hs:(494,4)-(556,7) 8.3 8.4 CoreTidy HscMain compiler/main/HscMain.hs:1253:27-67 2.8 2.2 SimplTopBinds SimplCore compiler/simplCore/SimplCore.hs:770:39-74 2.7 1.9 coercionKind Coercion compiler/types/Coercion.hs:1698:3-7 1.8 3.4 zonkTopDecls TcRnDriver compiler/typecheck/TcRnDriver.hs:(445,16)-(446,43) 1.3 1.3 deSugar HscMain compiler/main/HscMain.hs:511:7-44 1.1 0.8 }}} We clearly shouldn't be spending 15 seconds in `simplCast`, so more digging is required. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:15:06 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:15:06 -0000 Subject: [GHC] #11735: Optimize coercionKind In-Reply-To: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> References: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> Message-ID: <062.54fb89f2bae8de20c67c9923f32ef323@haskell.org> #11735: Optimize coercionKind -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | 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: #14683 #14975 | Differential Rev(s): D4394 D4395 Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Further digging into `simplCast` performance to be handled in #14737. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:28:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:28:13 -0000 Subject: [GHC] #11735: Optimize coercionKind In-Reply-To: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> References: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> Message-ID: <062.203bff00ad48723a016fa4af8125fbb4@haskell.org> #11735: Optimize coercionKind -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | 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: #14683 #14975 | Differential Rev(s): D4394 D4395 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes!! `simplCast` should not take 73% of compiler time!! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:37:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:37:35 -0000 Subject: [GHC] #14123: Figure out invariants surrounding ticks in Core In-Reply-To: <046.0308c769b363c5285c5969fe8d556b65@haskell.org> References: <046.0308c769b363c5285c5969fe8d556b65@haskell.org> Message-ID: <061.b63cfe3ae5f1807637bd9e33f0735c14@haskell.org> #14123: Figure out invariants surrounding ticks in Core -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: task | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13233, #14122, | Differential Rev(s): #8472, #14406, #14779 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * cc: JaffaCake (removed) * cc: simonmar (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:38:36 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:38:36 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.befb0610cd9743a64c638650cd2ffc16@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.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 bgamari): * priority: normal => high Comment: Let's prioritize this for characterisation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:40:37 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:40:37 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.5733b78acd0924264f690ecd1b2b83d3@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.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): elaforge, are these programs public? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:41:45 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:41:45 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.e0a59516def72b3462c4bfa5dbd35907@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: infoneeded Priority: high | Milestone: Component: Compiler | Version: 8.4.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 dfeuer): * status: new => infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:41:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:41:55 -0000 Subject: [GHC] #14964: performance regressions from 8.0.2 to 8.4.1 In-Reply-To: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> References: <047.90da086f6f6ef4027330151b41f8cc58@haskell.org> Message-ID: <062.edd415bff6b8b2df2ad0d04222576a09@haskell.org> #14964: performance regressions from 8.0.2 to 8.4.1 -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: task | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.4.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 simonpj): * priority: high => normal Comment: The productivity number is down sharply, and consistently so, which translates directly into longer run times. Somehow, although residency (well max-memory-in-use at least) is not increasing, GC time is greatly increased. It'd be really good to characterise this some more. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 15:53:17 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 15:53:17 -0000 Subject: [GHC] #14974: 2-fold memory usage regression GHC 8.2.2 -> GHC 8.4.1 compiling `mmark` package In-Reply-To: <042.6f9317183740e6c428dbe334554fec22@haskell.org> References: <042.6f9317183740e6c428dbe334554fec22@haskell.org> Message-ID: <057.8911286e94b4c8986a926ad01b004183@haskell.org> #14974: 2-fold memory usage regression GHC 8.2.2 -> GHC 8.4.1 compiling `mmark` package -------------------------------------+------------------------------------- Reporter: hvr | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.4.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: | -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > I haven't had time yet to diagnose where the memory is going to, but > here's how to reproduce: > > {{{ > cabal get mmark-0.0.5.6 && cd mmark-0.0.5.6/ > > cat > cabal.project < packages: . > package mmark > ghc-options: -Rghc-timing > EOF > }}} > > Then, `cabal new-build -w ghc-8.4.1` and ``cabal new-build -w ghc-8.2.2` > will respectively output > > {{{ > Resolving dependencies... > Build profile: -w ghc-8.4.1 -O1 > In order, the following will be built (use -v for more details): > - mmark-0.0.5.6 (lib) (first run) > Configuring library for mmark-0.0.5.6.. > < samples), 4M in use, 0.001 INIT (0.000 elapsed), 0.007 MUT (0.025 > elapsed), 0.018 GC (0.018 elapsed) :ghc>> > Preprocessing library for mmark-0.0.5.6.. > Building library for mmark-0.0.5.6.. > [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( > Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o > ) > [2 of 9] Compiling Text.MMark.Parser.Internal ( > Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o > ) > [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o > ) > [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o > ) > [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o > ) > [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o > ) > [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o > ) > [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 > /dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) > [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o > ) > < residency (23 samples), 4130M in use, 0.000 INIT (0.000 elapsed), 58.546 > MUT (62.124 elapsed), 31.536 GC (31.505 elapsed) :ghc>> > < samples), 11M in use, 0.000 INIT (0.000 elapsed), 0.021 MUT (0.207 > elapsed), 0.042 GC (0.042 elapsed) :ghc>> > }}} > > and > > {{{ > Resolving dependencies... > Build profile: -w ghc-8.2.2 -O1 > In order, the following will be built (use -v for more details): > - mmark-0.0.5.6 (lib) (first run) > Configuring library for mmark-0.0.5.6.. > < samples), 5M in use, 0.001 INIT (0.000 elapsed), 0.017 MUT (0.037 > elapsed), 0.021 GC (0.021 elapsed) :ghc>> > Preprocessing library for mmark-0.0.5.6.. > Building library for mmark-0.0.5.6.. > [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( > Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o > ) > [2 of 9] Compiling Text.MMark.Parser.Internal ( > Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o > ) > [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Type.o > ) > [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Trans.o > ) > [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Util.o > ) > [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Render.o > ) > [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser.o > ) > [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 > /dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark.o ) > [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, > /tmp/mmark-0.0.5.6/dist- > newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Extension.o > ) > < residency (27 samples), 2179M in use, 0.001 INIT (0.000 elapsed), 58.237 > MUT (61.472 elapsed), 25.823 GC (25.795 elapsed) :ghc>> > < (6 samples), 20M in use, 0.001 INIT (0.000 elapsed), 0.028 MUT (0.213 > elapsed), 0.059 GC (0.059 elapsed) :ghc>> > }}} > > > Consequently, > > - GHC 8.2.2: **2179M in use**, 0.001 INIT (0.000 elapsed), 58.237 MUT > (61.472 elapsed), 25.823 GC (25.795 elapsed) > > - GHC 8.4.1: **4130M in use**, 0.000 INIT (0.000 elapsed), 58.546 MUT > (62.124 elapsed), 31.536 GC (31.505 elapsed) New description: I haven't had time yet to diagnose where the memory is going to, but here's how to reproduce: {{{ cabal get mmark-0.0.5.6 && cd mmark-0.0.5.6/ cat > cabal.project <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Type.o ) [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Render.o ) [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.4.1/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> }}} and {{{ Resolving dependencies... Build profile: -w ghc-8.2.2 -O1 In order, the following will be built (use -v for more details): - mmark-0.0.5.6 (lib) (first run) Configuring library for mmark-0.0.5.6.. <> Preprocessing library for mmark-0.0.5.6.. Building library for mmark-0.0.5.6.. [1 of 9] Compiling Text.MMark.Parser.Internal.Type ( Text/MMark/Parser/Internal/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal/Type.o ) [2 of 9] Compiling Text.MMark.Parser.Internal ( Text/MMark/Parser/Internal.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser/Internal.o ) [3 of 9] Compiling Text.MMark.Type ( Text/MMark/Type.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Type.o ) [4 of 9] Compiling Text.MMark.Trans ( Text/MMark/Trans.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Trans.o ) [5 of 9] Compiling Text.MMark.Util ( Text/MMark/Util.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Util.o ) [6 of 9] Compiling Text.MMark.Render ( Text/MMark/Render.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Render.o ) [7 of 9] Compiling Text.MMark.Parser ( Text/MMark/Parser.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Parser.o ) [8 of 9] Compiling Text.MMark ( Text/MMark.hs, /tmp/mmark-0.0.5.6 /dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark.o ) [9 of 9] Compiling Text.MMark.Extension ( Text/MMark/Extension.hs, /tmp/mmark-0.0.5.6/dist- newstyle/build/x86_64-linux/ghc-8.2.2/mmark-0.0.5.6/build/Text/MMark/Extension.o ) <> <> }}} Consequently, - GHC 8.2.2: **2179M in use**, 0.001 INIT (0.000 elapsed), 58.237 MUT (61.472 elapsed), 25.823 GC (25.795 elapsed) - GHC 8.4.1: **4130M in use**, 0.000 INIT (0.000 elapsed), 58.546 MUT (62.124 elapsed), 31.536 GC (31.505 elapsed) -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:19:19 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:19:19 -0000 Subject: [GHC] #14956: NUMA not detected on Aarch64 NUMA machine In-Reply-To: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> References: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> Message-ID: <060.c5e3e4b3bf8ae5f966b936751a0c36d0@haskell.org> #14956: NUMA not detected on Aarch64 NUMA machine -----------------------------------+---------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: aarch64 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+---------------------------------- Changes (by bgamari): * status: new => infoneeded Comment: Hmm, what does `numactl -H` say? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:23:42 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:23:42 -0000 Subject: [GHC] #14976: WebAssembly support Message-ID: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> #14976: WebAssembly support -------------------------------------+------------------------------------- Reporter: sven | Owner: (none) Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: 8.2.2 Keywords: wasm, | Operating System: Unknown/Multiple webassembly | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I would like to suggest adding a wasm backend to GHC. PureScript is also offering something similar. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:28:29 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:28:29 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand Message-ID: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: -------------------------------------+------------------------------------- 94f02547083cf6df686ea0b95fed050184c533de added a `#pragma GCC diagnostic ignored "-Wsync-nand"` pragma to `libraries/ghc-prim/cbits/atomic.c` to silence `-Werror` failures due to GCC's non-actionable `-Wsync-nand` warning. Unfortunately goldfire reports that Apple's Clang chokes on this with, {{{ libraries/ghc-prim/cbits/atomic.c:127:32: error: unknown warning group '-Wsync-nand', ignored [-Werror,-Wunknown-warning-option] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:28:38 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:28:38 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.50238df4159c3e60f249ddbcec72ca8d@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * failure: None/Unknown => Building GHC failed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:29:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:29:47 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.584d30d4265d32c9430063e01b81301b@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * version: 8.4.1 => 8.5 * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:29:53 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:29:53 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.e5ae97ff2ae546b89e5e41b967bd2caa@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:30:35 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:30:35 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.34ccf36195eb26cabaf0c34745036be4@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Note that this happens only with `-Werror` specified in your build.mk, and removing `-Werror` allows you to proceed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:46:51 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:46:51 -0000 Subject: [GHC] #14976: WebAssembly support In-Reply-To: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> References: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> Message-ID: <058.a364456a918bacee5950c8917403337f@haskell.org> #14976: WebAssembly support -------------------------------------+------------------------------------- Reporter: sven | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: wasm, | webassembly Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): See https://github.com/tweag/asterius for some related work. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:51:28 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:51:28 -0000 Subject: [GHC] #14263: typeKind is quadratic In-Reply-To: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> References: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> Message-ID: <062.4a368a2e24dd941d3c04f5450fc587eb@haskell.org> #14263: typeKind is quadratic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: simonpj Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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: (none) => simonpj Comment: I'm on this -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 16:53:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 16:53:52 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.7da8cae06522d02703a4d8c1bffded4a@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I've got a patch in-flight: add {{{#!c #pragma GCC diagnostic ignored "-Wunknown-warning-option" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 17:39:40 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 17:39:40 -0000 Subject: [GHC] #14978: GADTs don't seem to unpack properly Message-ID: <045.8a53d57116a1e8f00d002cf33ac61964@haskell.org> #14978: GADTs don't seem to unpack properly -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 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: -------------------------------------+------------------------------------- Consider this simple code: {{{#!hs type family Foo a b data Goof a b where Goof :: !(Foo a b :~: Int) -> Goof a b }}} `(:~:)` has just one constructor (`Refl`) with no arguments, so I'd expect it to unpack to a void representation: {{{#!hs GoofConstr :: Foo a b ~N# Int => Goof a b WGoof :: Foo a b :~: Int -> Goof a b WGoof eq = case eq of Refl -> GoofConstr }}} But it doesn't seem to unpack at all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 18:18:40 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 18:18:40 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.48034f1f711b5843f841b328fb28afa4@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Actually, I think the OP's use case should be OK. There is a big difference between the ''type'' `(forall x. x -> x, Int)` and the ''constraint'' `(forall x. A x => B x, Show x)`. The former is an impredicative use of the `(,)` constructor, while the second is not considered to be so. I think this is a simple case of updating the validity checker to allow the new thing. :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 18:20:12 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 18:20:12 -0000 Subject: [GHC] #14972: MacOS panic on TH In-Reply-To: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> References: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> Message-ID: <065.6a3b1e12327c2483c12dfbe8da1f1b7f@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): How did you build GHC? This kind of error occurs if you build with nix and don't use `configurePhase` and `buildPhase`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 18:22:47 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 18:22:47 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.23da311d954707f5910e159f9f320c7b@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm lost. Is there some aspect of quantified constraints that would make this OK: {{{#!hs type instance Functors (t ': ts) = (forall f. Functor f => Functor (t f), Functors ts) }}} But not this (from https://ghc.haskell.org/trac/ghc/ticket/9269#comment:1)? {{{#!hs type instance Foo True = forall a. a -> a -> a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 18:27:22 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 18:27:22 -0000 Subject: [GHC] #14972: MacOS panic on TH In-Reply-To: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> References: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> Message-ID: <065.d388979e3626b118644ae4e8f8f295ee@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by harpocrates): Replying to [comment:1 mpickering]: > How did you build GHC? This kind of error occurs if you build with nix and don't use `configurePhase` and `buildPhase`. I just followed the instructions from the Build page. Pretty much just {{{ $ ./boot $ ./configure --with-ghc=ghc-8.4.1 $ make -j4 V=0 }}} I've been bisecting, but it is slow progress. The problem is not present in `a2d03c69b782212e6c476cfc1870bae493a4ac89`. I'll report back when I hit a commit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 19:17:03 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 19:17:03 -0000 Subject: [GHC] #14660: Improve +RTS -t --machine-readable In-Reply-To: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> References: <043.836b49c779e440e5ecbd0ff4cdeb542d@haskell.org> Message-ID: <058.341766713c114d7e7c972a6d95e918ba@haskell.org> #14660: Improve +RTS -t --machine-readable -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: task | Status: closed Priority: normal | Milestone: 8.6.1 Component: Runtime System | Version: 8.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:D4303 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f0b258bc7e2d4ef32a20c61b7285a21f7680660e/ghc" f0b258b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f0b258bc7e2d4ef32a20c61b7285a21f7680660e" rts, base: Refactor stats.c to improve --machine-readable report There should be no change in the output of the '+RTS -s' (summary) report, or the 'RTS -t' (one-line) report. All data shown in the summary report is now shown in the machine readable report. All data in RTSStats is now shown in the machine readable report. init times are added to RTSStats and added to GHC.Stats. Example of the new output: ``` [("bytes allocated", "375016384") ,("num_GCs", "113") ,("average_bytes_used", "148348") ,("max_bytes_used", "206552") ,("num_byte_usage_samples", "2") ,("peak_megabytes_allocated", "6") ,("init_cpu_seconds", "0.001642") ,("init_wall_seconds", "0.001027") ,("mut_cpu_seconds", "3.020166") ,("mut_wall_seconds", "0.757244") ,("GC_cpu_seconds", "0.037750") ,("GC_wall_seconds", "0.009569") ,("exit_cpu_seconds", "0.000890") ,("exit_wall_seconds", "0.002551") ,("total_cpu_seconds", "3.060452") ,("total_wall_seconds", "0.770395") ,("major_gcs", "2") ,("allocated_bytes", "375016384") ,("max_live_bytes", "206552") ,("max_large_objects_bytes", "159344") ,("max_compact_bytes", "0") ,("max_slop_bytes", "59688") ,("max_mem_in_use_bytes", "6291456") ,("cumulative_live_bytes", "296696") ,("copied_bytes", "541024") ,("par_copied_bytes", "493976") ,("cumulative_par_max_copied_bytes", "104104") ,("cumulative_par_balanced_copied_bytes", "274456") ,("fragmentation_bytes", "2112") ,("alloc_rate", "124170795") ,("productivity_cpu_percent", "0.986838") ,("productivity_wall_percent", "0.982935") ,("bound_task_count", "1") ,("sparks_count", "5836258") ,("sparks_converted", "237") ,("sparks_overflowed", "1990408") ,("sparks_dud ", "0") ,("sparks_gcd", "3455553") ,("sparks_fizzled", "390060") ,("work_balance", "0.555606") ,("n_capabilities", "4") ,("task_count", "10") ,("peak_worker_count", "9") ,("worker_count", "9") ,("gc_alloc_block_sync_spin", "162") ,("gc_alloc_block_sync_yield", "0") ,("gc_alloc_block_sync_spin", "162") ,("gc_spin_spin", "18840855") ,("gc_spin_yield", "10355") ,("mut_spin_spin", "70331392") ,("mut_spin_yield", "61700") ,("waitForGcThreads_spin", "241") ,("waitForGcThreads_yield", "2797") ,("whitehole_gc_spin", "0") ,("whitehole_lockClosure_spin", "0") ,("whitehole_lockClosure_yield", "0") ,("whitehole_executeMessage_spin", "0") ,("whitehole_threadPaused_spin", "0") ,("any_work", "1667") ,("no_work", "1662") ,("scav_find_work", "1026") ,("gen_0_collections", "111") ,("gen_0_par_collections", "111") ,("gen_0_cpu_seconds", "0.036126") ,("gen_0_wall_seconds", "0.036126") ,("gen_0_max_pause_seconds", "0.036126") ,("gen_0_avg_pause_seconds", "0.000081") ,("gen_0_sync_spin", "21") ,("gen_0_sync_yield", "0") ,("gen_1_collections", "2") ,("gen_1_par_collections", "1") ,("gen_1_cpu_seconds", "0.001624") ,("gen_1_wall_seconds", "0.001624") ,("gen_1_max_pause_seconds", "0.001624") ,("gen_1_avg_pause_seconds", "0.000272") ,("gen_1_sync_spin", "3") ,("gen_1_sync_yield", "0") ] ``` Test Plan: Ensure that one-line and summary reports are unchanged. Reviewers: erikd, simonmar, hvr Subscribers: duog, carter, thomie, rwbarton GHC Trac Issues: #14660 Differential Revision: https://phabricator.haskell.org/D4529 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 19:17:49 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 19:17:49 -0000 Subject: [GHC] #14911: Offer a way to augment call stacks In-Reply-To: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> References: <045.218ed287ccbc8e8a12d81aba90528d7e@haskell.org> Message-ID: <060.e604edddfc75b4fdebb6e5beac8bb29e@haskell.org> #14911: Offer a way to augment call stacks -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Core Libraries | Version: 8.4.1 Resolution: | Keywords: CallStacks Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I've opened https://github.com/ghc-proposals/ghc-proposals/pull/117 for the piece of this that I think could use compiler support. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:10:25 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:10:25 -0000 Subject: [GHC] #14891: Cabal bump broke ext-interp tests on Darwin In-Reply-To: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> References: <046.f895764f19b0938bd5a8ebfa164a7477@haskell.org> Message-ID: <061.b25278d9bad5132f97411516a918bd0f@haskell.org> #14891: Cabal bump broke ext-interp tests on Darwin -------------------------------------+------------------------------------- Reporter: bgamari | Owner: hvr Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.4.1 => 8.4.2 Comment: Unfortunately due to an oversight in the release preparation process, the fix for this issue was not included in the 8.4.1 release. It will, however, be present in the soon-to-arrive 8.4.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:10:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:10:55 -0000 Subject: [GHC] #14705: ghc-iserv sometimes segfaults in profiled way In-Reply-To: <046.be67f06c8a68b32fb302ce316ee26108@haskell.org> References: <046.be67f06c8a68b32fb302ce316ee26108@haskell.org> Message-ID: <061.1a13b494a76573e0df385d516e82b471@haskell.org> #14705: ghc-iserv sometimes segfaults in profiled way -------------------------------------+------------------------------------- Reporter: bgamari | Owner: simonmar Type: bug | Status: closed Priority: highest | Milestone: 8.4.2 Component: Profiling | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4437 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.4.1 => 8.4.2 Comment: Unfortunately due to an oversight in the release preparation process, the fix for this issue was not included in the 8.4.1 release. It will, however, be present in the soon-to-arrive 8.4.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:13:43 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:13:43 -0000 Subject: [GHC] #14846: Renamer hangs (because of -XInstanceSigs?) In-Reply-To: <051.a66d690b58cfe062ed0472f10a328f1d@haskell.org> References: <051.a66d690b58cfe062ed0472f10a328f1d@haskell.org> Message-ID: <066.97cfaa093e38af69f3f3947cc9048c50@haskell.org> #14846: Renamer hangs (because of -XInstanceSigs?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.5 Resolution: | Keywords: InstanceSigs | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | polykinds/T14846 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * priority: highest => normal * status: new => merge * milestone: 8.6.1 => 8.4.2 Comment: Patch looks good to me. This is a clear bug and shouldn't be hard to merge. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:15:33 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:15:33 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.09bf28b17d53cb29c0e55c971dbbf2b8@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.5 Resolution: fixed | Keywords: Operating System: Linux | 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: new => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Phab:D4302 was reverted. The failing patch has since been fixed and reapplied. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:31:49 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:31:49 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.98086e0e42a852232c9cfe6381d6df0f@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): The challenge impredicativity causes is in knowing where there is an invisible parameter. (I'm pretty sure that's the challenge, at least.) So if `x :: ty` and we don't know whether or not `ty` is a `forall`-type, we have a problem. This simply doesn't happen with constraints, so we avoid the challenge. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:37:50 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:37:50 -0000 Subject: [GHC] #14846: Renamer hangs (because of -XInstanceSigs?) In-Reply-To: <051.a66d690b58cfe062ed0472f10a328f1d@haskell.org> References: <051.a66d690b58cfe062ed0472f10a328f1d@haskell.org> Message-ID: <066.5fbefe2693dfaffb47e66cc8903ddd69@haskell.org> #14846: Renamer hangs (because of -XInstanceSigs?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: InstanceSigs | TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | polykinds/T14846 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:56:00 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:56:00 -0000 Subject: [GHC] #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file In-Reply-To: <042.c2e6771556eb83c8c227872bff540244@haskell.org> References: <042.c2e6771556eb83c8c227872bff540244@haskell.org> Message-ID: <057.976629d3d77dfe306cf7ac262644c6d5@haskell.org> #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 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): phadej, any update here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 20:58:23 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 20:58:23 -0000 Subject: [GHC] #14972: MacOS panic on TH In-Reply-To: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> References: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> Message-ID: <065.2f57a89337a3cdd15ce31536a22e00e6@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Very odd; I wonder if this is related to #14891 (which is sadly present in 8.4.1). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:26 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.b989ff21aeaa52f8e468fe3572ecb99f@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"97e1f300e4f6aef06863d056dc7992fef6b21538/ghc" 97e1f300/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="97e1f300e4f6aef06863d056dc7992fef6b21538" Fix compilation stopper on macOS with -Werror Commit 94f02547083cf6df686ea0b95fed050184c533de added some pragmas that allow GCC to compile GHC, but stop macOS's clang. This adds another counter-pragma to halp clang lumber along, too. Fixes #14977. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:26 -0000 Subject: [GHC] #14024: typechecker tests T13594 T13822 tc269 T13780c failing in devel2 flavour In-Reply-To: <043.b6a9b6292f832ebb52e568bfcb341f1b@haskell.org> References: <043.b6a9b6292f832ebb52e568bfcb341f1b@haskell.org> Message-ID: <058.116d09072db7cf9130819c3d45457f13@haskell.org> #14024: typechecker tests T13594 T13822 tc269 T13780c failing in devel2 flavour -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:26 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2314038=3A_TypeApplications_regressio?= =?utf-8?q?n_in_GHC_HEAD=3A_=E2=80=98p0=E2=80=99_is_untouchable_i?= =?utf-8?q?nside_the_constraints=3A_=28=29?= In-Reply-To: <050.6967c2fcff26fd2fc4ab5ac2e6230fa5@haskell.org> References: <050.6967c2fcff26fd2fc4ab5ac2e6230fa5@haskell.org> Message-ID: <065.26f63093694f38a49618167db2f7ec73@haskell.org> #14038: TypeApplications regression in GHC HEAD: ‘p0’ is untouchable inside the constraints: () -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.3 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 14119 | Blocking: Related Tickets: #13877 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:26 -0000 Subject: [GHC] #14720: GHC 8.4.1-alpha regression with TypeInType In-Reply-To: <050.3979775ac8fffda86c79c2a678f92178@haskell.org> References: <050.3979775ac8fffda86c79c2a678f92178@haskell.org> Message-ID: <065.d7f9b983ad6875e285da1b974f9b1dec@haskell.org> #14720: GHC 8.4.1-alpha regression with TypeInType -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #13643: Core lint error with TypeInType and TypeFamilyDependencies In-Reply-To: <051.99866398c3b30eccc01358213362b7d9@haskell.org> References: <051.99866398c3b30eccc01358213362b7d9@haskell.org> Message-ID: <066.4b77245296b4c04f73eb9e0467207f4e@haskell.org> #13643: Core lint error with TypeInType and TypeFamilyDependencies -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #13938: Iface type variable out of scope: k1 In-Reply-To: <050.7a3f2d444543ff2efcc9028549798245@haskell.org> References: <050.7a3f2d444543ff2efcc9028549798245@haskell.org> Message-ID: <065.d98555691d29f006c2ba5ec12f49f6a1@haskell.org> #13938: Iface type variable out of scope: k1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: 14119 | Blocking: Related Tickets: #14038 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:26 -0000 Subject: [GHC] #14441: GHC HEAD regression involving type families in kinds In-Reply-To: <050.cffc20d5c60287ccb30e96fd4e02f185@haskell.org> References: <050.cffc20d5c60287ccb30e96fd4e02f185@haskell.org> Message-ID: <065.6e56b0fdeda4530a01f5bcb0f720ba9c@haskell.org> #14441: GHC HEAD regression involving type families in kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: TypeInType, | TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: 12919 | Blocking: Related Tickets: #13790 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #12919: Equality not used for substitution In-Reply-To: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> References: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> Message-ID: <063.71a0a6b74a262c88f507320122937b23@haskell.org> #12919: Equality not used for substitution -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: patch Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T12919 Blocked By: | Blocking: 14441 Related Tickets: #13643 | Differential Rev(s): Phab:D3848 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #13910: Inlining a definition causes GHC to panic (repSplitTyConApp_maybe) In-Reply-To: <050.14bd55ba33332ff15d7c16c4f0c73fad@haskell.org> References: <050.14bd55ba33332ff15d7c16c4f0c73fad@haskell.org> Message-ID: <065.0df97ba5681296b33c56d902275e2842@haskell.org> #13910: Inlining a definition causes GHC to panic (repSplitTyConApp_maybe) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: 14119 | Blocking: Related Tickets: #13877, #14038, | Differential Rev(s): #14175 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #12919: Equality not used for substitution In-Reply-To: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> References: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> Message-ID: <063.a141f39db38390ec8f1b896e2ef5c02b@haskell.org> #12919: Equality not used for substitution -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: patch Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T12919 Blocked By: | Blocking: 14441 Related Tickets: #13643 | Differential Rev(s): Phab:D3848 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"b47a6c3a6d9c5da341184824549a6a835c79de15/ghc" b47a6c3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b47a6c3a6d9c5da341184824549a6a835c79de15" Fix performance of flattener patch (#12919) This patch, authored by alexvieth and reviewed at D4451, makes performance improvements by critically optimizing parts of the flattener. Summary: T3064, T5321FD, T5321Fun, T9872a, T9872b, T9872c all pass. T9872a and T9872c show improvements beyond the -5% threshold. T9872d fails at 10.9% increased allocations. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #14556: Core Lint error: Ill-kinded result in coercion In-Reply-To: <051.0e355f10cac8235c3846ef7abeef362e@haskell.org> References: <051.0e355f10cac8235c3846ef7abeef362e@haskell.org> Message-ID: <066.601f84127051164c63ba70b2752af59d@haskell.org> #14556: Core Lint error: Ill-kinded result in coercion -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14554 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:25:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:25:27 -0000 Subject: [GHC] #14749: T13822 fails In-Reply-To: <046.93c73d475ecf1191c51a59ec09ee2393@haskell.org> References: <046.93c73d475ecf1191c51a59ec09ee2393@haskell.org> Message-ID: <061.1e0ecb610a900d40f1a4de1df625b62a@haskell.org> #14749: T13822 fails -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"e3dbb44f53b2f9403d20d84e27f187062755a089/ghc" e3dbb44f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e3dbb44f53b2f9403d20d84e27f187062755a089" Fix #12919 by making the flattener homegeneous. This changes a key invariant of the flattener. Previously, flattening a type meant flattening its kind as well. But now, flattening is always homogeneous -- that is, the kind of the flattened type is the same as the kind of the input type. This is achieved by various wizardry in the TcFlatten.flatten_many function, as described in Note [flatten_many]. There are several knock-on effects, including some refactoring in the canonicalizer to take proper advantage of the flattener's changed behavior. In particular, the tyvar case of can_eq_nc' no longer needs to take casts into account. Another effect is that flattening a tyconapp might change it into a casted tyconapp. This might happen if the result kind of the tycon contains a variable, and that variable changes during flattening. Because the flattener is homogeneous, it tacks on a cast to keep the tyconapp kind the same. However, this is problematic when flattening CFunEqCans, which need to have an uncasted tyconapp on the LHS and must remain homogeneous. The solution is a more involved canCFunEqCan, described in Note [canCFunEqCan]. This patch fixes #13643 (as tested in typecheck/should_compile/T13643) and the panic in typecheck/should_compile/T13822 (as reported in #14024). Actually, there were two bugs in T13822: the first was just some incorrect logic in tryFill (part of the unflattener) -- also fixed in this patch -- and the other was the main bug fixed in this ticket. The changes in this patch exposed a long-standing flaw in OptCoercion, in that breaking apart an AppCo sometimes has unexpected effects on kinds. See new Note [EtaAppCo] in OptCoercion, which explains the problem and fix. Also here is a reversion of the major change in 09bf135ace55ce2572bf4168124d631e386c64bb, affecting ctEvCoercion. It turns out that making the flattener homogeneous changes the invariants on the algorithm, making the change in that patch no longer necessary. This patch also fixes: #14038 (dependent/should_compile/T14038) #13910 (dependent/should_compile/T13910) #13938 (dependent/should_compile/T13938) #14441 (typecheck/should_compile/T14441) #14556 (dependent/should_compile/T14556) #14720 (dependent/should_compile/T14720) #14749 (typecheck/should_compile/T14749) Sadly, this patch negatively affects performance of type-family- heavy code. The following patch fixes these performance degradations. However, the performance fixes are somewhat invasive and so I've kept them as a separate patch, labeling this one as [skip ci] so that validation doesn't fail on the performance cases. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:27:33 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:27:33 -0000 Subject: [GHC] #14024: typechecker tests T13594 T13822 tc269 T13780c failing in devel2 flavour In-Reply-To: <043.b6a9b6292f832ebb52e568bfcb341f1b@haskell.org> References: <043.b6a9b6292f832ebb52e568bfcb341f1b@haskell.org> Message-ID: <058.9e994a2c05bd822ba3ba302b1150b77c@haskell.org> #14024: typechecker tests T13594 T13822 tc269 T13780c failing in devel2 flavour -------------------------------------+------------------------------------- Reporter: duog | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Test Suite | Version: 8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | typecheck/should_compile/T13822 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => typecheck/should_compile/T13822 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:28:52 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:28:52 -0000 Subject: [GHC] #14556: Core Lint error: Ill-kinded result in coercion In-Reply-To: <051.0e355f10cac8235c3846ef7abeef362e@haskell.org> References: <051.0e355f10cac8235c3846ef7abeef362e@haskell.org> Message-ID: <066.ffcaa0d69034f5efa2333ed2e489ee1c@haskell.org> #14556: Core Lint error: Ill-kinded result in coercion -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.3 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T14556 Blocked By: | Blocking: Related Tickets: #14554 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => dependent/should_compile/T14556 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:31:43 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:31:43 -0000 Subject: [GHC] #13643: Core lint error with TypeInType and TypeFamilyDependencies In-Reply-To: <051.99866398c3b30eccc01358213362b7d9@haskell.org> References: <051.99866398c3b30eccc01358213362b7d9@haskell.org> Message-ID: <066.e265db36568b7184edb7e9547e0d538c@haskell.org> #13643: Core lint error with TypeInType and TypeFamilyDependencies -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | InjectiveFamilies, TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T13643 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_compile/T13643 * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:32:38 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:32:38 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.56a26edc066e53a89cfb0fbddf0a19df@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.4.2 Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge * milestone: 8.6.1 => 8.4.2 Comment: Does this need a merge? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:33:26 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:33:26 -0000 Subject: [GHC] #14749: T13822 fails In-Reply-To: <046.93c73d475ecf1191c51a59ec09ee2393@haskell.org> References: <046.93c73d475ecf1191c51a59ec09ee2393@haskell.org> Message-ID: <061.a4da7826853645b7c85a3514bc6a146a@haskell.org> #14749: T13822 fails -------------------------------------+------------------------------------- Reporter: simonpj | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T14749 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => typecheck/should_compile/T14749 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:34:27 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:34:27 -0000 Subject: [GHC] #12919: Equality not used for substitution In-Reply-To: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> References: <048.c4e450c7b401a6295cbd8b394ff2a079@haskell.org> Message-ID: <063.6fcb70aaf6487d7e5ce5f33d88fed481@haskell.org> #12919: Equality not used for substitution -------------------------------------+------------------------------------- Reporter: int-index | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T12919 Blocked By: | Blocking: 14441 Related Tickets: #13643 | Differential Rev(s): Phab:D3848 Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: patch => closed * resolution: => fixed Comment: At long, long last, this is put to bed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:35:20 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:35:20 -0000 Subject: [GHC] #14441: GHC HEAD regression involving type families in kinds In-Reply-To: <050.cffc20d5c60287ccb30e96fd4e02f185@haskell.org> References: <050.cffc20d5c60287ccb30e96fd4e02f185@haskell.org> Message-ID: <065.c785fcc7cf293d9c953ffa5c67f406d0@haskell.org> #14441: GHC HEAD regression involving type families in kinds -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler | Version: 8.3 Resolution: fixed | Keywords: TypeInType, | TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T14441 Blocked By: 12919 | Blocking: Related Tickets: #13790 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * testcase: => typecheck/should_compile/T14441 * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:36:08 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:36:08 -0000 Subject: [GHC] #14720: GHC 8.4.1-alpha regression with TypeInType In-Reply-To: <050.3979775ac8fffda86c79c2a678f92178@haskell.org> References: <050.3979775ac8fffda86c79c2a678f92178@haskell.org> Message-ID: <065.e77edbcdc2a80ec3d83b4871d02bf417@haskell.org> #14720: GHC 8.4.1-alpha regression with TypeInType -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.4.1-alpha1 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | dependent/should_compile/T14720 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => dependent/should_compile/T14720 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:37:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:37:55 -0000 Subject: [GHC] #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file In-Reply-To: <042.c2e6771556eb83c8c227872bff540244@haskell.org> References: <042.c2e6771556eb83c8c227872bff540244@haskell.org> Message-ID: <057.d52dfaae203d1bab5c5e7c4a0f9bd316@haskell.org> #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 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 asr): As it was expected, I got the same issue with GHC 8.4.1. I'm waiting for a new release of `cabal-install` to see its behaviour on this situation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:42:54 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:42:54 -0000 Subject: [GHC] #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file In-Reply-To: <042.c2e6771556eb83c8c227872bff540244@haskell.org> References: <042.c2e6771556eb83c8c227872bff540244@haskell.org> Message-ID: <057.5234c5220302a94da6ea11abf6ed0e27@haskell.org> #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 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 asr): Replying to [comment:3 asr]: > If I understand correctly, the proposed fixes require at least `Cabal >= 1.24`. Is there a fix which also work with the `Cabal` version (i.e. `Cabal 1.22.*`) shipped with `GHC 7.10.3`? I realise that oldest versions of Cabal just ignore the `custom setup` stance, so please ignore my question. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:58:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:58:13 -0000 Subject: [GHC] #14979: Issue warning is -main-is is used in OPTIONS pragma Message-ID: <046.b1003db4bdf0246f33df03b8fdf706eb@haskell.org> #14979: Issue warning is -main-is is used in OPTIONS pragma -------------------------------------+------------------------------------- Reporter: bgamari | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #2710 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- #2710 notes that `-main-is` does not currently work in an `OPTIONS` pragma. However, in thomie and my opinion `-main-is`, `-rtsopts`, the various way options (e.g. `-debug`, `-prof`, etc.), etc. have no sensible interpretation in this context. I suggest that they should be ignored and we should throw a warning when they are encountered. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 21:58:25 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 21:58:25 -0000 Subject: [GHC] #2710: -main-is flag in {-# OPTIONS #-} pragma not fully supported In-Reply-To: <049.221c5dae52503c4c900cfb790e2e9425@haskell.org> References: <049.221c5dae52503c4c900cfb790e2e9425@haskell.org> Message-ID: <064.5b4669b9565bd6c681913abc43a81c1d@haskell.org> #2710: -main-is flag in {-# OPTIONS #-} pragma not fully supported -------------------------------------+------------------------------------- Reporter: Stephan202 | Owner: (none) Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 6.8.3 Resolution: wontfix | Keywords: -main-is ghc Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #1312 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: infoneeded => closed * resolution: => wontfix Comment: Seeing as there have been no objections in three years I'm going to close this. I've opened #14979 to track the warning. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 22:03:59 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 22:03:59 -0000 Subject: [GHC] #2207: Load the interface details for GHC.* even without -O In-Reply-To: <046.c160dd85a0a0b0a47d62c75151b28378@haskell.org> References: <046.c160dd85a0a0b0a47d62c75151b28378@haskell.org> Message-ID: <061.138044f389ea3b909a848abf897d9330@haskell.org> #2207: Load the interface details for GHC.* even without -O -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.8.2 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => newcomers Comment: Might be interesting to try. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 22:05:55 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 22:05:55 -0000 Subject: [GHC] #3122: Enhance --info In-Reply-To: <044.9e71a36a06ffc4f0a9385ad48ed342a2@haskell.org> References: <044.9e71a36a06ffc4f0a9385ad48ed342a2@haskell.org> Message-ID: <059.3787eb5632642c1b10e2eb422c67c076@haskell.org> #3122: Enhance --info -------------------------------------+------------------------------------- Reporter: igloo | Owner: duncan Type: feature request | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 6.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: I'm going to close this as it's not clearly actionable. If you can think of something that you would like to see `--info` report do open a ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 22:08:57 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 22:08:57 -0000 Subject: [GHC] #3215: Valgrind support In-Reply-To: <043.40f286e92e08e430fc0b2cd8ad0e1b39@haskell.org> References: <043.40f286e92e08e430fc0b2cd8ad0e1b39@haskell.org> Message-ID: <058.69bb68869b443f33bf13505dd85cdedf@haskell.org> #3215: Valgrind support ------------------------------------+-------------------------------- Reporter: cmcq | Owner: (none) Type: feature request | Status: closed Priority: normal | Milestone: ⊥ Component: Runtime System | Version: 6.10.3 Resolution: | Keywords: valgrind Operating System: Linux | Architecture: x86 Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ------------------------------------+-------------------------------- Changes (by bgamari): * status: new => closed Comment: Valgrind has worked reasonably well the few times I have used it to track down RTS issues. I'm going to close this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 22:15:13 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 22:15:13 -0000 Subject: [GHC] #3559: split ghci modules off into their own package In-Reply-To: <044.482aa0aa1f1cefce182fab9f2b16a74b@haskell.org> References: <044.482aa0aa1f1cefce182fab9f2b16a74b@haskell.org> Message-ID: <059.03b8b9e73dae94a12e066e4bc1324c4b@haskell.org> #3559: split ghci modules off into their own package -------------------------------------+------------------------------------- Reporter: igloo | Owner: (none) Type: task | Status: closed Priority: low | Milestone: Component: GHCi | Version: 6.10.4 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix Comment: We now have `libraries/ghci`. I'm not sure what this ticket intended but I'm going to close this as not immediately actionable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Mar 26 22:52:44 2018 From: ghc-devs at haskell.org (GHC) Date: Mon, 26 Mar 2018 22:52:44 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch In-Reply-To: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> References: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> Message-ID: <060.50f7c63aebbb4d6803b3ea993918f248@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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): angerman, did anything ever happen here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 00:55:43 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 00:55:43 -0000 Subject: [GHC] #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch In-Reply-To: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> References: <045.e47b6fb966fc2f07cb627e29fc20cdd0@haskell.org> Message-ID: <060.2256cdbdcb57bb834a0e635db0577c82@haskell.org> #14889: ghc-HEAD broke cross-compilation on multiple tagets due to --via-asm switch -------------------------------------+------------------------------------- Reporter: slyfox | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.6.1 Comment: Fixed by 1ecbe9ccb10f42dc5b133ffb2c7b1e9247b1ba52. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 01:36:32 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 01:36:32 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.041ccd70257c5cd08238f2f8db87b696@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by terrorjack): * status: closed => new * resolution: fixed => Comment: It's not fixed. The same errors occur again when I'm building b47a6c3a6d9c5da341184824549a6a835c79de15, both on Linux and Windows. I'm building with prof libs enabled. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 05:57:36 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 05:57:36 -0000 Subject: [GHC] #14976: WebAssembly support In-Reply-To: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> References: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> Message-ID: <058.0437bed4f3b3f75a759ce33daea1685a@haskell.org> #14976: WebAssembly support -------------------------------------+------------------------------------- Reporter: sven | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: wasm, | webassembly 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 sven): @mpickering I'm already aware of this. Unfortunately tweag/asterius is not usable yet (see https://github.com/tweag/asterius/issues/1). Sorry if it's not clear in the description of my feature request, but I don't want a HS to JS solution, WebAssembly is the way to go anyway. It's obvious that some peoples are going to build their own compiler but I think it's better to have a common initiative and something reliable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 06:27:31 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 06:27:31 -0000 Subject: [GHC] #8316: GHCi debugger segfaults when trying force a certain variable In-Reply-To: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> References: <044.9ebacfadd8f49d7b017849858920cbb4@haskell.org> Message-ID: <059.99c912631b8dc05aff878b05bee3a8b2@haskell.org> #8316: GHCi debugger segfaults when trying force a certain variable -------------------------------------+------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: debugger Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4535 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * differential: => Phab:D4535 Comment: I created a differential with an implementation of the idea in comment:8. The patch seems to do the right thing but there's probably another bug in somewhere else so I'm still getting "TSO entered" errors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 06:29:43 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 06:29:43 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.a504ad22a0f939ae60e255f8ed83c6cf@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I can also confirm that the build is still broken: {{{ rts/Stats.c:741:37: error: error: ‘RTSSummaryStats {aka const struct RTSSummaryStats_}’ has no member named ‘rc_cpu_ns’ TimeToSecondsDbl(sum->rc_cpu_ns), ^ | 741 | TimeToSecondsDbl(sum->rc_cpu_ns), | ^ rts/Stats.c:29:39: error: note: in definition of macro ‘TimeToSecondsDbl’ #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) ^ | 29 | #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) | ^ rts/Stats.c:742:37: error: error: ‘RTSSummaryStats {aka const struct RTSSummaryStats_}’ has no member named ‘rc_elapsed_ns’ TimeToSecondsDbl(sum->rc_elapsed_ns)); ^ | 742 | TimeToSecondsDbl(sum->rc_elapsed_ns)); | ^ rts/Stats.c:29:39: error: note: in definition of macro ‘TimeToSecondsDbl’ #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) ^ | 29 | #define TimeToSecondsDbl(t) ((double)(t) / TIME_RESOLUTION) | ^ rts/Stats.c: In function ‘report_machine_readable’: rts/Stats.c:904:56: error: error: ‘RTSSummaryStats {aka const struct RTSSummaryStats_}’ has no member named ‘hp_cpu_ns’ MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); ^ | 904 | MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); | ^ "inplace/bin/ghc-stage1" -optc-fno-stack-protector -optc-Wall -optc-Werror -optc-Wall -optc-Wextra -optc-Wstrict-prototypes -optc-Wmissing-prototypes -optc-Wmissing-declarations -optc-Winline -optc-Waggregate-return -optc- Wpointer-arith -optc-Wmissing-noreturn -optc-Wnested-externs -optc- Wredundant-decls -optc-Wundef -optc-Iincludes -optc-Iincludes/dist -optc- Iincludes/dist-derivedconstants/header -optc-Iincludes/dist- ghcconstants/header -optc-Irts -optc-Irts/dist/build -optc-DCOMPILING_RTS -optc-fno-strict-aliasing -optc-fno-common -optc-Irts/dist/build/./autogen -optc-Werror=unused-but-set-variable -optc-Wno-error=inline -optc-O2 -optc-fomit-frame-pointer -optc-g -optc-DRtsWay=\"rts_p\" -static -prof -eventlog -O0 -H64m -Wall -fllvm-fill-undef-with-garbage -Werror -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-unit-id rts -dcmm-lint -i -irts -irts/dist/build -Irts/dist/build -irts/dist/build/./autogen -Irts/dist/build/./autogen -O2 -Wcpp-undef -Wnoncanonical-monad-instances -c rts/Threads.c -o rts/dist/build/Threads.p_o rts/Stats.c:867:62: error: note: in definition of macro ‘MR_STAT’ statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) ^ | 867 | statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) | ^ rts/Stats.c:904:36: error: note: in expansion of macro ‘TimeToSecondsDbl’ MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); ^ | 904 | MR_STAT("hc_cpu_seconds", "f", TimeToSecondsDbl(sum->hp_cpu_ns)); | ^ rts/Stats.c:905:57: error: error: ‘RTSSummaryStats {aka const struct RTSSummaryStats_}’ has no member named ‘hp_elapsed_ns’ MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); ^ | 905 | MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); | ^ rts/Stats.c:867:62: error: note: in definition of macro ‘MR_STAT’ statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) ^ | 867 | statsPrintf(" ,(\"" field_name "\", \"%" format "\")\n", value) | ^ rts/Stats.c:905:37: error: note: in expansion of macro ‘TimeToSecondsDbl’ MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); ^ | 905 | MR_STAT("hc_wall_seconds", "f", TimeToSecondsDbl(sum->hp_elapsed_ns)); | ^ `gcc' failed in phase `C Compiler'. (Exit code: 1) rts/ghc.mk:295: recipe for target 'rts/dist/build/Stats.p_o' failed make[1]: *** [rts/dist/build/Stats.p_o] Error 1 make[1]: *** Waiting for unfinished jobs.... Makefile:122: recipe for target 'all' failed make: *** [all] Error 2 Command exited with non-zero status 2 2127.75user 125.66system 9:50.20elapsed 381%CPU (0avgtext+0avgdata 2299464maxresident)k 223824inputs+2528896outputs (1204major+45830428minor)pagefaults 0swaps }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 06:45:27 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 06:45:27 -0000 Subject: [GHC] #14972: MacOS panic on TH In-Reply-To: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> References: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> Message-ID: <065.d7d05311e1a4384d6918eb15c579a9f7@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by harpocrates): Alright. Without really having looked at the contents of commits, I can say something about the behaviour of certain ranges. * 4631ceb261cb08756b955c6b495d5e719d35ab62 is the last commit which builds and doesn't crash when compiling some TH * 8f0b2f5eadf0fcb47c581907205a9db686214a69-df7ac37d43bdbabbde9b09344f9425e8e5a879ff don't build at all (`No rule to make target 'libraries/integer- gmp/include/HsIntegerGmp.h'`) * f6cf4001574e789865d25f89b362a04ef1ca3df4-affdea82bb70e5a912b679a169c6e9a230e4c93e (and probably later) build but crash when I try to compile anything that involves TH In terms of the way in which the crash happens: I've run into both segfaults and panics. Since the possibly offending commit bumps Cabal, I'm not sure if this isn't just another manifestation of https://github.com/haskell/cabal/issues/5222. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 07:10:32 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 07:10:32 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.b17d5f3f8a435e4629b586c215fbba1f@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 osa1): I can somewhat reproduce this with HEAD. I'm currently focusing on the compiled code issues, ignoring GHCi. My setup: I have two files Main.hs: {{{#!haskell {-# LANGUAGE CPP #-} module Main where import Criterion.Main (defaultMain, bench, nfIO) -- Uncomment this to have all the code in one module -- #define SINGLE_MODULE #ifndef SINGLE_MODULE import List #else import Control.Monad (liftM) data List a = Stop | Yield a (List a) instance Semigroup (List a) where x <> y = case x of Stop -> y Yield a r -> Yield a (mappend r y) instance Monoid (List a) where -- {-# INLINE mempty #-} mempty = Stop -- {-# INLINE mappend #-} mappend = (<>) -- {-# NOINLINE toList #-} toList :: Monad m => List a -> m [a] toList m = case m of Stop -> return [] Yield a r -> liftM (a :) (toList r) #endif {-# NOINLINE len #-} len :: IO Int len = do xs <- toList $ (foldr mappend mempty $ map (\x -> Yield x Stop) [1..100000 :: Int]) return (length xs) main :: IO () main = defaultMain [ bench "len" $ nfIO len ] }}} When I'm measuring allocations I remove criterion imports and use this main: {{{ main = len >>= print }}} Note that I have a `NOINLINE` on `len` to avoid optimising it in the benchmark site. The original report does not have this. List.hs: {{{#!haskell module List where import Control.Monad (liftM) data List a = Stop | Yield a (List a) instance Semigroup (List a) where x <> y = case x of Stop -> y Yield a r -> Yield a (mappend r y) instance Monoid (List a) where mempty = Stop mappend = (<>) toList :: Monad m => List a -> m [a] toList m = case m of Stop -> return [] Yield a r -> liftM (a :) (toList r) }}} I have three configurations: - -O0 - -O1 - -O2 - -O0 -DSINGLE_MODULE - -O1 -DSINGLE_MODULE - -O2 -DSINGLE_MODULE I first run all these with `+RTS -s` using `main = len >>= print` as the main function. {{{ ============ -O0 =============================================================== 49,723,096 bytes allocated in the heap 25,729,264 bytes copied during GC 6,576,744 bytes maximum residency (5 sample(s)) 29,152 bytes maximum slop 13 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 41 colls, 0 par 0.011s 0.011s 0.0003s 0.0008s Gen 1 5 colls, 0 par 0.010s 0.010s 0.0020s 0.0047s INIT time 0.000s ( 0.000s elapsed) MUT time 0.011s ( 0.012s elapsed) GC time 0.021s ( 0.021s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.032s ( 0.033s elapsed) %GC time 64.0% (63.8% elapsed) Alloc rate 4,366,732,069 bytes per MUT second Productivity 35.6% of total user, 35.9% of total elapsed ============ -O1 =============================================================== 28,922,528 bytes allocated in the heap 18,195,344 bytes copied during GC 4,066,200 bytes maximum residency (5 sample(s)) 562,280 bytes maximum slop 13 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 22 colls, 0 par 0.008s 0.008s 0.0004s 0.0016s Gen 1 5 colls, 0 par 0.008s 0.008s 0.0016s 0.0029s INIT time 0.000s ( 0.000s elapsed) MUT time 0.009s ( 0.009s elapsed) GC time 0.016s ( 0.016s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.025s ( 0.025s elapsed) %GC time 63.8% (63.9% elapsed) Alloc rate 3,262,174,222 bytes per MUT second Productivity 35.3% of total user, 35.3% of total elapsed ============ -O2 =============================================================== 28,922,528 bytes allocated in the heap 18,195,344 bytes copied during GC 4,066,200 bytes maximum residency (5 sample(s)) 562,280 bytes maximum slop 13 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 22 colls, 0 par 0.008s 0.008s 0.0003s 0.0008s Gen 1 5 colls, 0 par 0.008s 0.008s 0.0017s 0.0029s INIT time 0.000s ( 0.000s elapsed) MUT time 0.008s ( 0.008s elapsed) GC time 0.016s ( 0.016s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.024s ( 0.024s elapsed) %GC time 66.6% (66.6% elapsed) Alloc rate 3,714,684,268 bytes per MUT second Productivity 32.7% of total user, 32.7% of total elapsed ============ -O0 -DSINGLE_MODULE =============================================== 49,723,032 bytes allocated in the heap 25,729,184 bytes copied during GC 6,576,728 bytes maximum residency (5 sample(s)) 29,152 bytes maximum slop 13 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 41 colls, 0 par 0.010s 0.010s 0.0003s 0.0008s Gen 1 5 colls, 0 par 0.010s 0.010s 0.0019s 0.0042s INIT time 0.000s ( 0.000s elapsed) MUT time 0.011s ( 0.011s elapsed) GC time 0.020s ( 0.020s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.031s ( 0.031s elapsed) %GC time 65.0% (65.0% elapsed) Alloc rate 4,609,752,610 bytes per MUT second Productivity 34.8% of total user, 34.8% of total elapsed ============ -O1 -DSINGLE_MODULE =============================================== 16,122,496 bytes allocated in the heap 7,392,664 bytes copied during GC 3,438,424 bytes maximum residency (4 sample(s)) 55,464 bytes maximum slop 7 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 10 colls, 0 par 0.004s 0.004s 0.0004s 0.0008s Gen 1 4 colls, 0 par 0.005s 0.005s 0.0012s 0.0019s INIT time 0.000s ( 0.000s elapsed) MUT time 0.004s ( 0.004s elapsed) GC time 0.009s ( 0.009s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.014s ( 0.014s elapsed) %GC time 66.5% (66.6% elapsed) Alloc rate 3,663,260,346 bytes per MUT second Productivity 32.5% of total user, 32.5% of total elapsed ============ -O2 -DSINGLE_MODULE =============================================== 13,722,496 bytes allocated in the heap 6,798,640 bytes copied during GC 2,158,376 bytes maximum residency (3 sample(s)) 33,248 bytes maximum slop 7 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 9 colls, 0 par 0.007s 0.007s 0.0008s 0.0021s Gen 1 3 colls, 0 par 0.004s 0.005s 0.0015s 0.0030s INIT time 0.000s ( 0.000s elapsed) MUT time 0.004s ( 0.004s elapsed) GC time 0.012s ( 0.012s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.016s ( 0.016s elapsed) %GC time 74.2% (74.3% elapsed) Alloc rate 3,479,572,009 bytes per MUT second Productivity 25.2% of total user, 25.2% of total elapsed }}} Summary: allocations consistently reduce as optimisation level increases. Secondly I run criterion benchmark to measure runtime, using the same configurations: {{{ ============ -O0 =============================================================== benchmarking len time 13.50 ms (13.23 ms .. 13.71 ms) 0.998 R² (0.997 R² .. 0.999 R²) mean 13.55 ms (13.35 ms .. 13.81 ms) std dev 613.5 μs (424.7 μs .. 918.2 μs) variance introduced by outliers: 18% (moderately inflated) ============ -O1 =============================================================== benchmarking len time 15.83 ms (15.62 ms .. 16.02 ms) 0.999 R² (0.998 R² .. 0.999 R²) mean 15.92 ms (15.75 ms .. 16.10 ms) std dev 463.5 μs (340.2 μs .. 669.1 μs) ============ -O2 =============================================================== benchmarking len time 15.70 ms (15.51 ms .. 15.90 ms) 0.999 R² (0.999 R² .. 1.000 R²) mean 15.74 ms (15.59 ms .. 15.87 ms) std dev 355.2 μs (271.2 μs .. 470.7 μs) ============ -O0 -DSINGLE_MODULE =============================================== benchmarking len time 14.85 ms (13.81 ms .. 16.06 ms) 0.976 R² (0.959 R² .. 0.997 R²) mean 13.60 ms (13.22 ms .. 14.14 ms) std dev 1.152 ms (773.1 μs .. 1.614 ms) variance introduced by outliers: 41% (moderately inflated) ============ -O1 -DSINGLE_MODULE =============================================== benchmarking len time 6.802 ms (6.702 ms .. 6.922 ms) 0.997 R² (0.994 R² .. 0.999 R²) mean 6.845 ms (6.765 ms .. 6.945 ms) std dev 261.8 μs (201.3 μs .. 336.8 μs) variance introduced by outliers: 18% (moderately inflated) ============ -O2 -DSINGLE_MODULE =============================================== benchmarking len time 6.614 ms (6.501 ms .. 6.712 ms) 0.998 R² (0.997 R² .. 0.999 R²) mean 6.399 ms (6.317 ms .. 6.472 ms) std dev 239.1 μs (201.7 μs .. 292.5 μs) variance introduced by outliers: 18% (moderately inflated) }}} So; - Everything works as expected in single module case. Both runtime and allocations get lower as optimisation level increases. - In multi-module -O1 and -O2 produce identical outputs, runtime difference is just noise. - In multi-module we get better allocations with -O1 vs. -O0, but runtime gets somewhat worse. This is what we should investigate. To see why we allocate less in multi-module with -O1 I compared the STG outputs (multi-module -O0 vs. multi-module -O1), the answer is fusion kicking in with -O1. We have an intermediate function application for `foldr mappend mempty` in -O0 output which disappears with -O1. Why does the runtime get worse? I don't know but I suspect it's just noise. Really the code is better (as in, it does less work) with -O1 than with -O0. I also compared single-module -O1 with multi-module -O1, the reason why single module is better is becuase the `toList` function is not inlined cross-module but it's inlined within the module. So I think in the compiled case there are no problems. Only remaining question is why GHCi is faster than compiled code. I've attached a tarball with my setup + outputs. It includes Core/STG outputs of all 6 configurations and criterion and +RTS -s outputs as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 07:13:31 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 07:13:31 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.7f88a680719fdfb984ba79bacc2ef0eb@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 osa1): * Attachment "t14208_.tar.xz" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 07:32:54 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 07:32:54 -0000 Subject: [GHC] #11735: Optimize coercionKind In-Reply-To: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> References: <047.4a7a4b5184d1293c5e3d53524b93fe89@haskell.org> Message-ID: <062.33d273bef1e6be7d62f50a5cada598d6@haskell.org> #11735: Optimize coercionKind -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: task | 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: #14683 #14975 | Differential Rev(s): D4394 D4395 #14737 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by tdammers): * related: #14683 #14975 => #14683 #14975 #14737 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:00:35 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:00:35 -0000 Subject: [GHC] #14976: WebAssembly support In-Reply-To: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> References: <043.2fbab8f0c58823e06aed87c5b9fa392c@haskell.org> Message-ID: <058.7fadbb6eac65e792bba7e9f325fd4d72@haskell.org> #14976: WebAssembly support -------------------------------------+------------------------------------- Reporter: sven | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: wasm, | webassembly Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It'd be great to have a collaborative effort to generate WebAssembly. Incidentally, here's another (pre-web-assembly) effort in this Javascript space: Haste: https://ekblad.cc/pubs/thesis.pdf -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:07:01 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:07:01 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.64cc0ff1d9a1c365368efa61b5137a71@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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): > So I think in the compiled case there are no problems. OK good; that's reassuring. Do you know why the single-module case gets better? I suspect it may be that `toList` is specialised. If you add `{-# INLINABLE toList #-}` does the difference go away? Perhaps this isn't a big deal -- it's reasonable for single module to be faster -- but GHC does make real efforts NOT to penalise you for multi- module, so I'm curious. > Only remaining question is why GHCi is faster than compiled code. Can you reproduce this difference? It is indeed puzzling! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:18:32 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:18:32 -0000 Subject: [GHC] #14980: Runtime performance regression with binary operations on vectors Message-ID: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> #14980: Runtime performance regression with binary operations on vectors -------------------------------------+------------------------------------- Reporter: ttylec | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: vector | Operating System: Unknown/Multiple bitwise operations | Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Let me briefly explain our use case: we have a machine learning tools created in Haskell. Basically it builds association rules for a database. In plain English: predicates on data rows. We need to score them, so we need to check how many rows are "matched" by the predicate. In order to optimize performance, our code uses two main representations for data: one is a "human readable", where a values are real values. The second one is binarized representation for categorical data. The latter has is actually a family of representation, since we pack bits into tuples of Word64 and use bitwise operation to implement logic. Simplified but representative code is attached. In GHC 8.0.2 binary representation is faster by one order of magnitude than the "human readable" one: {{{ ➜ ghc-bug stack exec performance-bug-pair-1 "Generated" benchmarking 256 columns/raw unbox vectors time 342.6 μs (338.3 μs .. 348.0 μs) 0.999 R² (0.998 R² .. 1.000 R²) mean 339.3 μs (337.5 μs .. 342.0 μs) std dev 7.203 μs (5.596 μs .. 10.07 μs) variance introduced by outliers: 13% (moderately inflated) benchmarking 256 columns/binary packed time 32.07 μs (29.69 μs .. 34.14 μs) 0.982 R² (0.976 R² .. 0.997 R²) mean 29.97 μs (29.41 μs .. 31.03 μs) std dev 2.428 μs (1.526 μs .. 3.750 μs) variance introduced by outliers: 78% (severely inflated) }}} In GHC 8.2.2 (and later) binary representation performance is similar to "human readable", so no performance gain: {{{ ➜ ghc-bug stack exec performance-bug-pair-1 "Generated" benchmarking 256 columns/raw unbox vectors time 442.4 μs (406.7 μs .. 474.5 μs) 0.978 R² (0.969 R² .. 0.993 R²) mean 399.3 μs (391.3 μs .. 415.1 μs) std dev 34.73 μs (20.36 μs .. 53.29 μs) variance introduced by outliers: 71% (severely inflated) benchmarking 256 columns/binary packed time 378.6 μs (295.8 μs .. 488.0 μs) 0.637 R² (0.492 R² .. 0.780 R²) mean 568.1 μs (437.1 μs .. 747.6 μs) std dev 308.7 μs (233.6 μs .. 386.1 μs) variance introduced by outliers: 98% (severely inflated) }}} However, for certain compilation paths, we still can get similar speedup as with GHC 8.0.2. In the above examples we used 4-tuple of Word64 as binary representation. In the following code we run two tests: one on just Word64 and one of 4-tuple of Word64. The difference is that we just add the Word64 case: {{{ ➜ ghc-bug stack exec performance-bug-pair-2 "Generated" benchmarking 64 columns/raw unbox vectors time 337.6 μs (336.1 μs .. 339.3 μs) 0.999 R² (0.998 R² .. 1.000 R²) mean 349.6 μs (344.4 μs .. 359.7 μs) std dev 23.22 μs (15.39 μs .. 38.22 μs) variance introduced by outliers: 60% (severely inflated) benchmarking 64 columns/binary packed time 21.66 μs (21.53 μs .. 21.79 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 21.68 μs (21.53 μs .. 21.89 μs) std dev 613.2 ns (466.0 ns .. 806.0 ns) variance introduced by outliers: 30% (moderately inflated) benchmarking 256 columns/raw unbox vectors time 344.5 μs (341.6 μs .. 348.2 μs) 0.999 R² (0.999 R² .. 1.000 R²) mean 345.1 μs (342.5 μs .. 349.3 μs) std dev 10.66 μs (7.997 μs .. 16.34 μs) variance introduced by outliers: 25% (moderately inflated) benchmarking 256 columns/binary packed time 28.04 μs (27.70 μs .. 28.46 μs) 0.999 R² (0.999 R² .. 1.000 R²) mean 28.05 μs (27.85 μs .. 28.30 μs) std dev 758.2 ns (628.2 ns .. 907.6 ns) variance introduced by outliers: 27% (moderately inflated) }}} I made a variant of code with simpler accumulating function (in our code we accumulate pair of integers, simplified accumulator work on one integer). GHC 8.2.2 in that case losses speed-up with 4-tuples: {{{ ➜ ghc-bug stack exec performance-bug-2 "Generated" benchmarking 64 columns/raw unbox vectors time 333.8 μs (333.0 μs .. 335.1 μs) 1.000 R² (0.999 R² .. 1.000 R²) mean 333.6 μs (332.4 μs .. 335.8 μs) std dev 5.651 μs (3.233 μs .. 9.582 μs) benchmarking 64 columns/binary packed time 39.06 μs (38.98 μs .. 39.14 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 38.94 μs (38.83 μs .. 39.14 μs) std dev 495.0 ns (310.2 ns .. 782.1 ns) benchmarking 256 columns/raw unbox vectors time 336.9 μs (336.2 μs .. 337.9 μs) 1.000 R² (1.000 R² .. 1.000 R²) mean 337.5 μs (336.2 μs .. 339.8 μs) std dev 5.757 μs (2.946 μs .. 8.979 μs) benchmarking 256 columns/binary packed time 239.8 μs (237.6 μs .. 243.0 μs) 0.998 R² (0.996 R² .. 0.999 R²) mean 251.4 μs (247.9 μs .. 259.8 μs) std dev 11.50 μs (5.662 μs .. 19.79 μs) variance introduced by outliers: 37% (moderately inflated) }}} In GHC 8.0.2 we have speed-up in both cases. What may be related: using random-fu to generate random numbers seems to produce broken code on GHC 8.2.2 (the `performance-bug-rfu.hs` source). Short description of attached sources: - performance-bug-pair-2.hs: using two binary representations - performance-bug-pair-1.hs: using one binary representation (one case commented) - performance-bug-1.hs: using one binary representation with simplified accumulator - performance-bug-2.hs: using two binary representation with simplified accumulator - performance-bug-rfu.hs: using random-fu to generate data (optional) - stack-8.0.yaml: stack file for GHC-8.0.2 - stack-8.2.yaml: stack file for GHC-8.2.2 - stack-nightly.yaml: stack file for GHC-8.4 - performance-bug.cabal: to be able to stack build everything. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:20:07 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:20:07 -0000 Subject: [GHC] #14980: Runtime performance regression with binary operations on vectors In-Reply-To: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> References: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> Message-ID: <060.4118fc76dd5554ef8ea73d13c0c60beb@haskell.org> #14980: Runtime performance regression with binary operations on vectors -------------------------------------+------------------------------------- Reporter: ttylec | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: vector | bitwise operations 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 ttylec): * Attachment "ghc-bug.tar.gz" added. source code -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:29:22 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:29:22 -0000 Subject: [GHC] #14263: typeKind is quadratic In-Reply-To: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> References: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> Message-ID: <062.065d6d3071e49d15d613d43389d48e43@haskell.org> #14263: typeKind is quadratic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: simonpj Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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:"1fce2c3a83f0356146f24674b79b04f66c231e9d/ghc" 1fce2c3a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1fce2c3a83f0356146f24674b79b04f66c231e9d" Avoid quadratic complexity in typeKind I took 10 minute to fix this potential performance hole (Trac #14263) There are no actual bug reports against it, so no regression test. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:29:22 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:29:22 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.377d1584591dd251384ca3cd993c6fe3@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"71d50db1f511d7aee32e6b429cdb912fcf6071b0/ghc" 71d50db/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="71d50db1f511d7aee32e6b429cdb912fcf6071b0" Minor refactor and commments Minor refactor and comments, following Ryan's excellent DeriveAnyClass bug (Trac #14932) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:29:22 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:29:22 -0000 Subject: [GHC] #13900: Core lint in BuildFlavour=perf-llvm In-Reply-To: <046.659e0b338788e413a5940905a0f91074@haskell.org> References: <046.659e0b338788e413a5940905a0f91074@haskell.org> Message-ID: <061.cd6b9e4383f57d6e6067b9bbea1a43ce@haskell.org> #13900: Core lint in BuildFlavour=perf-llvm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"a7628dcd2cb570fe41de247af6aa71a89177a9b9/ghc" a7628dc/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a7628dcd2cb570fe41de247af6aa71a89177a9b9" Deal with join points with RULES Trac #13900 showed that when we have a join point that has a RULE, we must push the continuation into the RHS of the RULE. See Note [Rules and unfolding for join points] It's hard to tickle this bug, so I have not added a regression test. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:31:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:31:12 -0000 Subject: [GHC] #14263: typeKind is quadratic In-Reply-To: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> References: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> Message-ID: <062.93fa3f34b751ea403caff1a88a4056c7@haskell.org> #14263: typeKind is quadratic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: simonpj Type: task | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 08:31:50 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 08:31:50 -0000 Subject: [GHC] #13900: Core lint in BuildFlavour=perf-llvm In-Reply-To: <046.659e0b338788e413a5940905a0f91074@haskell.org> References: <046.659e0b338788e413a5940905a0f91074@haskell.org> Message-ID: <061.b058b2887a0471406e69d9b75d14dc0e@haskell.org> #13900: Core lint in BuildFlavour=perf-llvm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.6.1 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I believe I've nailed this. Can you check if it's now fixed for you? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 09:10:38 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 09:10:38 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.64bc5d58d86d9a5c8a442c6ac7137247@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: DWARF Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: T14965 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D4534 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * testcase: => T14965 * differential: => D4534 Comment: Ben is adding the program from this ticket to the testsuite (CI is green presumably because we don't build (and test) the libraries with `-g3` in our CI scripts). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 09:12:48 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 09:12:48 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.874997a56b23acad206778319cc54a65@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4529 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * status: new => patch * differential: => Phab:D4529 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 09:56:52 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 09:56:52 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine Message-ID: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 8.4.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: -------------------------------------+------------------------------------- I'm testing a small ray-tracer on different many-core machines, like x64 88 core and Aarch64 96 core (on https://packet.net). Parallel GC seems to have throughput problems on more than 24-32 cores. See this Reddit thread about - https://www.reddit.com/r/haskell/comments/85vwlq/our_lovely_ghc_parallel_gc_on_96_core_arm/ There you may find .eventlog file and PNG with a screenshot. May be it's time to resurrect Concurrent GC project again? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 10:15:02 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 10:15:02 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.6ecc303abc3e041af6d7708a333ab544@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4536 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sighingnow): * differential: Phab:D4529 => Phab:D4536 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 10:17:59 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 10:17:59 -0000 Subject: [GHC] #14956: NUMA not detected on Aarch64 NUMA machine In-Reply-To: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> References: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> Message-ID: <060.4e4c0681a7f33f8681b4abe583923315@haskell.org> #14956: NUMA not detected on Aarch64 NUMA machine -----------------------------------+---------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: aarch64 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+---------------------------------- Comment (by varosi): {{{ -bash: numactl: command not found }}} When I install it: {{{ available: 2 nodes (0-1) node 0 cpus: 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 node 0 size: 64397 MB node 0 free: 63935 MB node 1 cpus: 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 node 1 size: 64475 MB node 1 free: 64114 MB node distances: node 0 1 0: 10 20 1: 20 10 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 11:12:15 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 11:12:15 -0000 Subject: [GHC] #14980: Runtime performance regression with binary operations on vectors In-Reply-To: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> References: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> Message-ID: <060.de36f8f2f094cfdfcffdf04863bcab54@haskell.org> #14980: Runtime performance regression with binary operations on vectors -------------------------------------+------------------------------------- Reporter: ttylec | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: vector | bitwise operations 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 ttylec): As a suplement: it is related to optimization. I usually use -O2, but effect is present also with -O2. With -O0 on GHC 8.0.2 there is no speed- up in binarized version. Program compiled with GHC 8.2.2 with -O0 crashes(!) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:08:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:08:33 -0000 Subject: [GHC] #14945: Compiling error related to rts/Stats.c In-Reply-To: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> References: <049.d47fc57be745a9a5acfcc0d120241a39@haskell.org> Message-ID: <064.a0cd04cd42ca08e17690915ac768a737@haskell.org> #14945: Compiling error related to rts/Stats.c -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4536 Wiki Page: | Phab:D4529 -------------------------------------+------------------------------------- Changes (by Phyx-): * differential: Phab:D4536 => Phab:D4536 Phab:D4529 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:40:44 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:40:44 -0000 Subject: [GHC] #13910: Inlining a definition causes GHC to panic (repSplitTyConApp_maybe) In-Reply-To: <050.14bd55ba33332ff15d7c16c4f0c73fad@haskell.org> References: <050.14bd55ba33332ff15d7c16c4f0c73fad@haskell.org> Message-ID: <065.33209e5a491f3c61eb20aa375a75c58f@haskell.org> #13910: Inlining a definition causes GHC to panic (repSplitTyConApp_maybe) -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | dependent/should_compile/T13910 Blocked By: | Blocking: Related Tickets: #13877, #14038, | Differential Rev(s): #14175 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => dependent/should_compile/T13910 * status: new => closed * resolution: => fixed * blockedby: 14119 => * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:41:40 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:41:40 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2314038=3A_TypeApplications_regressio?= =?utf-8?q?n_in_GHC_HEAD=3A_=E2=80=98p0=E2=80=99_is_untouchable_i?= =?utf-8?q?nside_the_constraints=3A_=28=29?= In-Reply-To: <050.6967c2fcff26fd2fc4ab5ac2e6230fa5@haskell.org> References: <050.6967c2fcff26fd2fc4ab5ac2e6230fa5@haskell.org> Message-ID: <065.f29c7629ed9193ccdb32aaf361b86bcb@haskell.org> #14038: TypeApplications regression in GHC HEAD: ‘p0’ is untouchable inside the constraints: () -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.3 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T14038 Blocked By: | Blocking: Related Tickets: #13877 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => dependent/should_compile/T14038 * status: new => closed * resolution: => fixed * blockedby: 14119 => * milestone: 8.4.1 => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:54:41 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:54:41 -0000 Subject: [GHC] #13938: Iface type variable out of scope: k1 In-Reply-To: <050.7a3f2d444543ff2efcc9028549798245@haskell.org> References: <050.7a3f2d444543ff2efcc9028549798245@haskell.org> Message-ID: <065.cc81c97f454c185e35e4fcaa82b736bb@haskell.org> #13938: Iface type variable out of scope: k1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: 14119 | Blocking: Related Tickets: #14038 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"3ebf05f5410a3e89d4dc6d451aea5020706fa5b0/ghc" 3ebf05f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3ebf05f5410a3e89d4dc6d451aea5020706fa5b0" Fix the test for #13938 Only half of the test files were checked in for T13938. This commit adds the missing half. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:55:49 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:55:49 -0000 Subject: [GHC] #13938: Iface type variable out of scope: k1 In-Reply-To: <050.7a3f2d444543ff2efcc9028549798245@haskell.org> References: <050.7a3f2d444543ff2efcc9028549798245@haskell.org> Message-ID: <065.b5b360230da7f7d047d8fb68139d5963@haskell.org> #13938: Iface type variable out of scope: k1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeInType, Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: error/warning at compile-time | dependent/should_compile/T13938 Blocked By: | Blocking: Related Tickets: #14038 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * testcase: => dependent/should_compile/T13938 * resolution: => fixed * blockedby: 14119 => * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:57:13 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:57:13 -0000 Subject: [GHC] #14947: internal error: Invalid object *c in push() In-Reply-To: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> References: <045.1b0222011edccbe034bce0a38cb61ba9@haskell.org> Message-ID: <060.bc2abcf635cebe758541db410c49061b@haskell.org> #14947: internal error: Invalid object *c in push() -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: Profiling | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * priority: normal => high * milestone: => 8.4.2 Comment: Since this is a regression from 8.2, I'm opting to change the milestone and priority. Do change if you feel this isn't warranted. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:57:55 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:57:55 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.1a450b669cb46d711baa80e8f454f33e@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.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): * priority: normal => high * milestone: => 8.4.2 Comment: Since this is a regression from 8.2, I'm opting to change the milestone and priority. Do change if you feel this isn't warranted. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 12:58:54 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 12:58:54 -0000 Subject: [GHC] #14496: Invoking GHC 8.2.1 executable anywhere results in access violation on Windows 10 In-Reply-To: <050.8ec2c012a4031c145e18d1e0d7cbdd1d@haskell.org> References: <050.8ec2c012a4031c145e18d1e0d7cbdd1d@haskell.org> Message-ID: <065.c33f1ad83e72fdadf4564dc7f15d1f01@haskell.org> #14496: Invoking GHC 8.2.1 executable anywhere results in access violation on Windows 10 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: wontfix | Keywords: Operating System: Windows | Architecture: Type of failure: GHC doesn't work | Unknown/Multiple at all | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => wontfix Comment: It seems we never did figure out what was causing this. But 8.2.2 works, so I'm opting to close this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:06:42 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:06:42 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic In-Reply-To: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> References: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> Message-ID: <065.01bccee1df933d86133d1604f7d9f34c@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deriving/should_compile/T14933 Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => deriving/should_compile/T14933 * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:07:21 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:07:21 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.e75cfea197104384c0c386a8c8e9729e@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T14932 Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => deriving/should_compile/T14932 * milestone: 8.6.1 => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:19:16 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:19:16 -0000 Subject: [GHC] #14968: QuantifiedConstraints: Can't be RHS of type family instances In-Reply-To: <044.8604cb7a4154bec744684958eded781f@haskell.org> References: <044.8604cb7a4154bec744684958eded781f@haskell.org> Message-ID: <059.b8c53871a1961b27a21bcbbec6816680@haskell.org> #14968: QuantifiedConstraints: Can't be RHS of type family instances -------------------------------------+------------------------------------- Reporter: josef | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.5 checker) | Keywords: Resolution: | QuantifiedConstraints Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9269 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:6 goldfire]: > This simply doesn't happen with constraints, so we avoid the challenge. Really? Is there some sort of invariant in GHC that upholds this claim? You can certainly have `x :: ty` where `ty :: Constraint` in Core, so this claim is quite surprising to me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:26:51 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:26:51 -0000 Subject: [GHC] #14366: Type family equation refuses to unify wildcard type patterns In-Reply-To: <050.99fc7b3497a7cbec29b57a49c9d2896b@haskell.org> References: <050.99fc7b3497a7cbec29b57a49c9d2896b@haskell.org> Message-ID: <065.617a75fd12b65dfc54c99c237f2f8c3b@haskell.org> #14366: Type family equation refuses to unify wildcard type patterns -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Keywords: TypeFamilies, Resolution: | TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): After reading #14938, I now understand at least //why// this is happening. I was operating under the misconception that pattern-matching in type families brings a coercion into scope, which would "force" the two wildcards in `Cast _ _ Refl x = x` to unify. But this isn't the case at all, as https://ghc.haskell.org/trac/ghc/ticket/14938#comment:5 explains—matching on `Refl` //requires// a coercion in order to type- check. Unfortunately, the way type wildcards work is at odds with this, because early on in the renamer, GHC simply renames `Cast _ _ Refl x = x` to something like `Cast _1 _2 Refl x = x`. Because `_1` and `_2` aren't the same, matching on `Refl :: _1 :~: _1` isn't going to work. It seems like we'd need to somehow defer the gensymming of wildcard names until during typechecking to make this work. But the details of that are beyond me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:41:36 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:41:36 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.ffa40704be27914b75950ccbadd5b6ed@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 osa1): * cc: osa1 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:53:36 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:53:36 -0000 Subject: [GHC] #14226: Common Block Elimination pass doesn't eliminate common blocks In-Reply-To: <046.64e654c74c7432ac06e937473b6324b1@haskell.org> References: <046.64e654c74c7432ac06e937473b6324b1@haskell.org> Message-ID: <061.0ff489f92baeb42933b20de8679370e3@haskell.org> #14226: Common Block Elimination pass doesn't eliminate common blocks -------------------------------------+------------------------------------- Reporter: bgamari | Owner: michalt Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 (CodeGen) | Keywords: newcomer, Resolution: | CodeGen Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9157, #14754 | Differential Rev(s): Phab:D3973, Wiki Page: | Phab:D3999 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d5c4d46a62ce6a0cfa6440344f707136eff18119/ghc" d5c4d46a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d5c4d46a62ce6a0cfa6440344f707136eff18119" CmmPipeline: add a second pass of CmmCommonBlockElim The sinking pass often gets rid of unnecessary registers registers/assignements exposing more opportunities for CBE, so this commit adds a second round of CBE after the sinking pass and should fix #12915 (and some examples in #14226). Nofib results: * Binary size: 0.9% reduction on average * Compile allocations: 0.7% increase on average * Runtime: noisy, two separate runs of nofib showed a tiny reduction on average, (~0.2-0.3%), but I think this is mostly noise * Compile time: very noisy, but generally within +/- 0.5% (one run faster, one slower) One interesting part of this change is that running CBE invalidates results of proc-point analysis. But instead of re-doing the whole analysis, we can use the map that CBE creates for replacing/comparing block labels (maps a redundant label to a useful one) to update the results of proc-point analysis. This lowers the overhead compared to the previous experiment in #12915. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #12915, #14226 Differential Revision: https://phabricator.haskell.org/D4417 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:53:36 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:53:36 -0000 Subject: [GHC] #12915: cmmImplementSwitchPlans creates duplicate blocks In-Reply-To: <048.450627ba0680e3fafd8b0486acc85c67@haskell.org> References: <048.450627ba0680e3fafd8b0486acc85c67@haskell.org> Message-ID: <063.a08b45340d519cd25522703fa82b70e8@haskell.org> #12915: cmmImplementSwitchPlans creates duplicate blocks -------------------------------------+------------------------------------- Reporter: alexbiehl | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d5c4d46a62ce6a0cfa6440344f707136eff18119/ghc" d5c4d46a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d5c4d46a62ce6a0cfa6440344f707136eff18119" CmmPipeline: add a second pass of CmmCommonBlockElim The sinking pass often gets rid of unnecessary registers registers/assignements exposing more opportunities for CBE, so this commit adds a second round of CBE after the sinking pass and should fix #12915 (and some examples in #14226). Nofib results: * Binary size: 0.9% reduction on average * Compile allocations: 0.7% increase on average * Runtime: noisy, two separate runs of nofib showed a tiny reduction on average, (~0.2-0.3%), but I think this is mostly noise * Compile time: very noisy, but generally within +/- 0.5% (one run faster, one slower) One interesting part of this change is that running CBE invalidates results of proc-point analysis. But instead of re-doing the whole analysis, we can use the map that CBE creates for replacing/comparing block labels (maps a redundant label to a useful one) to update the results of proc-point analysis. This lowers the overhead compared to the previous experiment in #12915. Signed-off-by: Michal Terepeta Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #12915, #14226 Differential Revision: https://phabricator.haskell.org/D4417 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 13:53:49 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 13:53:49 -0000 Subject: [GHC] #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails In-Reply-To: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> References: <044.b955c5c690cd54fa2244c5effa4f7808@haskell.org> Message-ID: <059.beb5c4810fadba72cf79f72f63e2afa5@haskell.org> #14965: GHC 8.4.1 bug: -O + separate compilation + three list fields + concatenation; core-lint fails -------------------------------------+------------------------------------- Reporter: blynn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: DWARF Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: T14965 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D4534 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d1fb5831f574953661a3716720fbc798781d37eb/ghc" d1fb5831/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d1fb5831f574953661a3716720fbc798781d37eb" testsuite: Add test for #14965 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 14:06:33 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 14:06:33 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.7566949d345664a6d4bb4fee2caf87b0@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 osa1): > Do you know why the single-module case gets better? I suspect it may be that toList is specialised. Yes, as also said in my previous comment, the reason is `toList` being specialised only when it's in the same module. Multi-module {{{ Main.len1 :: GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, GHC.Types.Int #) [GblId, Arity=1, Str=, Unf=OtherCon []] = [] \r [s_s5yc] case Main.len_go 1# of sat_s5yd { __DEFAULT -> case List.toList GHC.Base.$fMonadIO sat_s5yd s_s5yc of { (#,#) ipv_s5yf [Occ=Once] ipv1_s5yg [Occ=Once] -> let { sat_s5yi [Occ=Once] :: GHC.Types.Int [LclId] = [ipv1_s5yg] \u [] case GHC.List.$wlenAcc ipv1_s5yg 0# of ww2_s5yh { __DEFAULT -> GHC.Types.I# [ww2_s5yh]; }; } in (#,#) [ipv_s5yf sat_s5yi]; }; }; -- toList in another module List.toList [Occ=LoopBreaker] :: forall (m :: * -> *) a. GHC.Base.Monad m => List.List a -> m [a] [GblId, Arity=2, Caf=NoCafRefs, Str=, Unf=OtherCon []] = [] \r [$dMonad_s36Z m1_s370] case m1_s370 of { List.Stop -> GHC.Base.return $dMonad_s36Z GHC.Types.[]; List.Yield a1_s372 [Occ=OnceL] r_s373 [Occ=Once] -> let { sat_s377 [Occ=Once] :: [a_a1fh] -> m_a1fg [a_a1fh] [LclId] = [$dMonad_s36Z a1_s372] \r [x1_s375] let { sat_s376 [Occ=Once] :: [a_a1fh] [LclId] = CCCS :! [a1_s372 x1_s375]; } in GHC.Base.return $dMonad_s36Z sat_s376; } in let { sat_s374 [Occ=Once] :: m_a1fg [a_a1fh] [LclId] = [$dMonad_s36Z r_s373] \u [] List.toList $dMonad_s36Z r_s373; } in GHC.Base.>>= $dMonad_s36Z sat_s374 sat_s377; }; }}} Single module: {{{ Main.len1 :: GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, GHC.Types.Int #) [GblId, Arity=1, Caf=NoCafRefs, Str=, Unf=OtherCon []] = [] \r [s_s5uU] case Main.len_go 1# of sat_s5uV { __DEFAULT -> case Main.len2 sat_s5uV s_s5uU of { (#,#) ipv_s5uX [Occ=Once] ipv1_s5uY [Occ=Once] -> let { sat_s5v0 [Occ=Once] :: GHC.Types.Int [LclId] = [ipv1_s5uY] \u [] case GHC.List.$wlenAcc ipv1_s5uY 0# of ww2_s5uZ { __DEFAULT -> GHC.Types.I# [ww2_s5uZ]; }; } in (#,#) [ipv_s5uX sat_s5v0]; }; }; Main.len2 [Occ=LoopBreaker] :: forall a. Main.List a -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, [a] #) [GblId, Arity=2, Caf=NoCafRefs, Str=, Unf=OtherCon []] = [] \r [m_s5uw eta_s5ux] case m_s5uw of { Main.Stop -> (#,#) [eta_s5ux GHC.Types.[]]; Main.Yield a1_s5uz [Occ=Once] r_s5uA [Occ=Once] -> case Main.len2 r_s5uA eta_s5ux of { (#,#) ipv_s5uC [Occ=Once] ipv1_s5uD [Occ=Once] -> let { sat_s5uE [Occ=Once] :: [a_X1Bw] [LclId] = CCCS :! [a1_s5uz ipv1_s5uD]; } in (#,#) [ipv_s5uC sat_s5uE]; }; }; }}} > If you add {-# INLINABLE toList #-} does the difference go away? With `INLINE toList` or `INLINABLE toList` multi-module and single-module become identical with -O1 and -O2. (there are some small changes in the STG outputs but nothing that changes runtime or allocations) > Can you reproduce this difference? It is indeed puzzling! I can, by running the criterion benchmark in GHCi: {{{ $ ghc-stage2 --interactive Main.hs GHCi, version 8.5.20180322: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/omer/rcbackup/.ghci [1 of 2] Compiling List ( List.hs, interpreted ) [2 of 2] Compiling Main ( Main.hs, interpreted ) Ok, two modules loaded. λ:1> main benchmarking len time 10.79 ms (10.68 ms .. 10.98 ms) 0.993 R² (0.979 R² .. 1.000 R²) mean 10.66 ms (10.54 ms .. 10.98 ms) std dev 480.8 μs (147.7 μs .. 952.1 μs) variance introduced by outliers: 20% (moderately inflated) λ:2> Leaving GHCi. $ ghc-stage2 --interactive Main.hs -DSINGLE_MODULE GHCi, version 8.5.20180322: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/omer/rcbackup/.ghci [1 of 1] Compiling Main ( Main.hs, interpreted ) Ok, one module loaded. λ:1> main benchmarking len time 11.30 ms (11.20 ms .. 11.42 ms) 0.999 R² (0.998 R² .. 0.999 R²) mean 10.77 ms (10.64 ms .. 10.90 ms) std dev 346.5 μs (317.7 μs .. 398.6 μs) }}} `-O1` and `-O2` with `-DSINGLE_MODULE` is faster than GHCi, but otherwise GHCi is faster than the other 4 configurations. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 14:30:20 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 14:30:20 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.6986f7df34f93f2c6bfd6db5ad3e3683@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 osa1): Just updated the previous comment: `toList` is never inlined, but when it's in the same module as the using code or marked as `INLINABLE` it gets specialized. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 14:44:38 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 14:44:38 -0000 Subject: [GHC] #14975: Refactor (Maybe Coercion) In-Reply-To: <047.51816057ba89e62ff311692e8071c67c@haskell.org> References: <047.51816057ba89e62ff311692e8071c67c@haskell.org> Message-ID: <062.a5ff594c3520b8b495bb9928185174e5@haskell.org> #14975: Refactor (Maybe Coercion) -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: task | 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: #11735 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): A few questions that pop up: - Shouldn't this go in `TyCoRep.hs`, and then be re-exported from `Coercion.hs`, like the other coercion-related types? - Defined like this (`*` rather than `* -> *`), we'll miss out on `Functor`, `Applicative`, `Alternative`, etc.; are we going to regret this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 14:45:39 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 14:45:39 -0000 Subject: [GHC] #14980: Runtime performance regression with binary operations on vectors In-Reply-To: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> References: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> Message-ID: <060.bd9b2d97c688fc306212959ad3caa014@haskell.org> #14980: Runtime performance regression with binary operations on vectors -------------------------------------+------------------------------------- Reporter: ttylec | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: vector | bitwise operations Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high Comment: Thank you for the very complete ticket and repro! We'll have a look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 15:30:37 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 15:30:37 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.ded00222d1b003a1905b1e606959afed@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 jberryman): I only spent a few minutes looking at the eventlog in threadscope, but the thing that looked instantly fishy to me was that it looks like we stop the world at every minor GC (there are only a dozen collections of gen 1). Another thing to observe is that it looks like the spark creation is healthy, and all work is sparked within the first third or so of program execution (i.e. those little pauses aren't yields because no work is ready to be done, which is what I thought might be happening at first glance. Supposedly RTS flags used were: `-N -A15m -qb0 -qn8`. Attaching op's screenshot from the reddit thread -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 15:31:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 15:31:12 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.66a9aab0a6393f4c49ab52bd9e825ec3@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 jberryman): * Attachment "ARM96coreIssue.png" added. threadscope zoomed in -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 16:15:25 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 16:15:25 -0000 Subject: [GHC] #14980: Runtime performance regression with binary operations on vectors In-Reply-To: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> References: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> Message-ID: <060.44e8e8697dd835917090261336b7e6b7@haskell.org> #14980: Runtime performance regression with binary operations on vectors -------------------------------------+------------------------------------- Reporter: ttylec | Owner: (none) Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: vector | bitwise operations 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 ttylec): It came to my mind that different stack snapshots could bring different `vector` version along GHC. But that's not the case, both have 0.12.0.1. Please let me know if I can be of any assistance. I tried to debug it more but I have no CS background (I am mathematical physicist) so you need to treat me as a newbie. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 16:52:03 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 16:52:03 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.4f24185e51102c1e60fe3ac04d6fcc8b@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 varosi): Minor GC should not do stop the world? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 18:46:01 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 18:46:01 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.1efb40a0d15a262d37f21a0758ad19b8@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 jberryman): varosi, my understanding is that only collecting the oldest generation should stop the world. It's possible I'm mistaken or misinterpreting the threadscope profile though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 20:00:57 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 20:00:57 -0000 Subject: [GHC] #14975: Refactor (Maybe Coercion) In-Reply-To: <047.51816057ba89e62ff311692e8071c67c@haskell.org> References: <047.51816057ba89e62ff311692e8071c67c@haskell.org> Message-ID: <062.1e6b8123252984196ce1a850145657d1@haskell.org> #14975: Refactor (Maybe Coercion) -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: task | 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: #11735 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Yes, it makes sense to put this in `TyCoRep`, so that only some modules gain access to the constructors. I'm not so worried about `Functor` and friends. If this turns out to bite, we can always fix it later. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 20:05:03 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 20:05:03 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.6730b190a0dc3113637484d98f9fddd1@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 varosi): Yes, Threadscope show that nursery GC is stopping the world. But is that behavior okay? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 20:13:25 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 20:13:25 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.26e7ebf3927594b6284a1571e94dc667@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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): Minor GCs indeed do necessarily stop-the-world. This is a known limitation which affects large core-counts particularly badly. However, fixing this in a copying garbage collector is quite tricky. There have been a few attempts at avoiding this stop-the-world. The most recent attempt is the Simons' "Multicore Garbage Collection with Local Heaps". You can still find the prototype implementation (against GHC 6.10, IIRC) on the `wip/local-heaps` branch but it not merged as the performance improvement of brought by this change was outweighed by its enormous complexity. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 21:57:12 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 21:57:12 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.cce1c59968f55dd17cc7ae2c3146212b@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 harendra): In case you need another data point, my original streaming library that made me file this issue still exhibits the same behavior. GHCi is 6x faster than my regular compiled code. I tried even compiling everything including all dependencies with exactly the same optimization flags to make sure there is no funny business due to mixing of opt flags. You can see the behavior in the tree available on github here: https://github.com/composewell/streamly/tree/199e20dd4b62ac2dafea0a40dc2ce3d97c307542 You can clone the repo and run the experiment like this: {{{ $ stack bench benchmarked streaming ops time 34.39 ms (32.99 ms .. 35.67 ms) 0.995 R² (0.991 R² .. 0.998 R²) mean 33.97 ms (33.24 ms .. 35.43 ms) $ stack runghc benchmark/Main.hs benchmarked streaming ops time 6.215 ms (5.684 ms .. 6.860 ms) 0.945 R² (0.896 R² .. 0.978 R²) mean 6.610 ms (6.333 ms .. 6.991 ms) }}} If I change the optimization flags to -O0 for benchmark stanza in cabal file I can get close to ghci performance. The code that I am benchmarking is like this: {{{ {-# INLINE streamlyOp #-} streamlyOp :: IO Int streamlyOp = do xs <- S.toList $ S.serially $ S.each [1..100000 :: Int] & fmap (+1) & fmap (+1) & fmap (+1) & fmap (+1) return (Prelude.length xs) }}} It seems the problem is with the `fmap` operation (I may be wrong), it is 6 times slower in case of GHC, and every other fmap I add, the benchmark timings increase but the ratio remains the same. I tried using an INLINE on fmap, I also tried to SPECIALIZE it to IO and INT type but no change. The `fmap` op is defined in `src/Streamly/Streams.hs` file like this: {{{ instance Monad m => Functor (StreamT m) where fmap f (StreamT (Stream m)) = StreamT $ Stream $ \_ stp yld -> let yield a Nothing = yld (f a) Nothing yield a (Just r) = yld (f a) (Just (getStreamT (fmap f (StreamT r)))) in m Nothing stp yield }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 22:06:52 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 22:06:52 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.428b9664d4488ac08c6bc13112a3ada3@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): `fmap` in that module doesn't have an `INLINE` pragma on it? Should it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 22:08:30 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 22:08:30 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.1beb6eeb3434651330e31596bafe0dbf@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 harendra): I tried using INLINE, and I tried SPECIALIZE as well but it made no difference. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 22:16:25 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 22:16:25 -0000 Subject: [GHC] #14478: Abstract pattern synonyms (for hsig and hs-boot) In-Reply-To: <045.8d2821cb171cb8f59be6aa602942a2eb@haskell.org> References: <045.8d2821cb171cb8f59be6aa602942a2eb@haskell.org> Message-ID: <060.e7eae3684f360df627ec14c0fbed60d6@haskell.org> #14478: Abstract pattern synonyms (for hsig and hs-boot) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: | Keywords: backpack 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 lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 22:38:19 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 22:38:19 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.565a90b5356adf151be9ea57fa4e8e0b@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): I can reproduce this when all the dependencies are installed with `ghc benchmarks/Main.hs -isrc/ -O2` which is slow and `ghc benchmarks/Main.hs -isrc`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 23:33:41 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 23:33:41 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.a8a476bfa2fb58adc5fda7061d04c427@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): I noticed two things from a brief look. 1. `fmap` is not SATed. Which means the static `f` won't be eliminated. 2. A bad(?) loopbreaker is chosen in `Prelude.foldrM`, `yield` rather than `go`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Mar 27 23:59:35 2018 From: ghc-devs at haskell.org (GHC) Date: Tue, 27 Mar 2018 23:59:35 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.7ff5974641294d0b256311e36121d5e2@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): Another possible answer is that your library has a lot of recursive functions in it and the base types are written in CPS which means things don't optimise too well. Again, this is not an answer as to why the optimiser makes the program slower. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 00:16:42 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 00:16:42 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.8e98e4e30201c52ca09ae4e7ce22c524@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 harendra): @mpickering is there something to read about how things do and don't get optimized with CPS especially with GHC? What are the pitfalls and why it does not optimize well? I am very much interested in this, any pointers will be appreciated. I was using the direct style before and I had some trouble with it, I had to use a lot of SPECIALIZE to IO types to extract decent performance wherever I was using monad polymorphic instances. The performance did not seem to be much better compared to CPS. Maybe I am wrongly attributing the problem to CPS-vs-Direct style and it might have been something stupid that I did, at that time. But I never had any similar problem in CPS style and then I never went back to direct. Though I want to try and see if direct would be any better but it will take some time and effort to do that. However, there is some proof that direct style is not very much different in that the "streaming" library performance is more or less the same as this library and "streaming" is actually more or less the same thing but written in direct style. See the performance comparison between "streaming" and "streamly" here: https://github.com/composewell/streaming- benchmarks/blob/master/charts-1/CheaperOperations.svg -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 01:48:20 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 01:48:20 -0000 Subject: [GHC] #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file In-Reply-To: <042.c2e6771556eb83c8c227872bff540244@haskell.org> References: <042.c2e6771556eb83c8c227872bff540244@haskell.org> Message-ID: <057.3d6adaffd778c851c1ff4f64ae92cff2@haskell.org> #14775: GHC 8.4.1-alpha3 regression: Build error when `build-type: Custom` and `license: OtherLicense` are in the .cabal file -------------------------------------+------------------------------------- Reporter: asr | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.4.1-alpha3 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 asr): * status: new => closed * resolution: => fixed Comment: The issue in the OP was fixed in `cabal-install` upstream (tested in the 2.2 branch on [https://github.com/haskell/cabal/commit/74781c78492590b85e21b13ff8675c6e5875dd4c this] commit), so I'm closing it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 07:44:35 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 07:44:35 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.78a4c33feb9b6e68bd993f03e0ecd44c@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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): > If I change the optimization flags to -O0 for benchmark stanza in cabal file I can get close to ghci performance. That contradicts what Omer found in comment:27. Nevertheless, if what you say is true, it'd be easier to debug with -O0 than GHCi (which brings the bytecode generator into the picture). > GHCi is 6x faster than my regular compiled code This is totally bonkers and we MUST find out what is happening :-). I suggest not getting diverted into speculation about CPS. We have a repro case; let's just dig into it and find out what is going on. My suggestions * In comment:31 Does the same thing happen with -O0 vs -O, or only with GHCi vs -O? * In all repros, do the huge differences also show up in the bytes- allocated numbers? (If so, we don't need the Criterion apparatus.) * I notice that in comment:27, in the 2-module case, comparing -O0 and -O1: * Allocation is about halved in -O1 * But runtime actually increases That is most peculiar. * Matthew says in comment:34 "I can reproduce this..". That's great. But what is "this" precisely? Which version of GHC? What timing data? What happened to allocation and GC numbers? Somehow a 6x increase in execution time ought not to be hard to find! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 10:28:13 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 10:28:13 -0000 Subject: [GHC] #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best In-Reply-To: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> References: <047.6317840cf59137baa377ba42bf7a7392@haskell.org> Message-ID: <062.47d8feaba5cf4f366467abca1c8e82c5@haskell.org> #14208: Performance with O0 is much better than the default or with -O2, runghc performs the best -------------------------------------+------------------------------------- Reporter: harendra | Owner: osa1 Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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 mpickering): I cloned the repo - https://github.com/composewell/streamly/tree/199e20dd4b62ac2dafea0a40dc2ce3d97c307542 Checked out commit - 199e20dd4b62ac2dafea0a40dc2ce3d97c307542 I could build all the dependencies with ghc-8.2.2. Then I ran in in the root of the repo {{{ ghc benchmarks/Main.hs -isrc/ -O2 }}} and then ran the executable. The benchmark numbers were slower than doing the same without `-O2`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 12:38:50 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 12:38:50 -0000 Subject: [GHC] #14975: Refactor (Maybe Coercion) In-Reply-To: <047.51816057ba89e62ff311692e8071c67c@haskell.org> References: <047.51816057ba89e62ff311692e8071c67c@haskell.org> Message-ID: <062.6924499c191651da6d9b62f610b8aa1e@haskell.org> #14975: Refactor (Maybe Coercion) -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: task | 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: #11735 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): > I'm not so worried about Functor and friends. If this turns out to bite, we can always fix it later. Oh, I wouldn't expect it to actually bite, just to not give us some of the useful instances that `Maybe` has, which might make it a bit more awkward to work with. But it's probably not going to be a problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 13:39:57 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 13:39:57 -0000 Subject: [GHC] #14972: MacOS panic on TH In-Reply-To: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> References: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> Message-ID: <065.22cae4c2ae12e7a57f79d5a037805ffb@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): This is even simpler to reproduce: `ghc --interactive` doesn't work on Mac OS X: {{{ MacBook-Pro-97:unifier-ghc ezyang$ ~/Dev/ghc/inplace/bin/ghc-stage2 --interactive GHCi, version 8.5.20180327: http://www.haskell.org/ghc/ :? for help ghc-stage2: loadArchive: Failed reading header from `/Users/ezyang/Dev/ghc/libraries/integer-gmp/dist-install/build/gmp' ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.5.20180327 for x86_64-apple-darwin): loadArchive "/Users/ezyang/Dev/ghc/libraries/integer-gmp/dist- install/build/gmp": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This was a 'perf' build of: {{{ commit b58282a009ae67cbd4befbe062452026c82afd51 (HEAD -> master, origin/master, origin/HEAD) Author: Ben Gamari Date: Tue Mar 27 09:57:01 2018 -0400 More format string fixes }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 14:11:18 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 14:11:18 -0000 Subject: [GHC] #855: Improvements to SpecConstr In-Reply-To: <046.89327e0966303574a45f2952dca0e6f5@haskell.org> References: <046.89327e0966303574a45f2952dca0e6f5@haskell.org> Message-ID: <061.a14632c178f5d1a0ab039a68ae0ec27c@haskell.org> #855: Improvements to SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: task | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.4.2 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: N/A Blocked By: | Blocking: 915 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): A quick update: `ex1` is optimized to similar code as above, but without resorting to forced `SPEC` now. E.g., inference of `ArgOcc`s is now much better, because it looks at occs from specialised RHSs now (specialising for lambdas gives rise to new occs). This entailed a rewrite of the spec loop. Also I had to pass on occs from recursive calls to achieve something like the static argument transformation. I'll write things up in a wiki page once I'm done trying to optimize `ex{2,3}`. This is the code currently generated for `ex1`: {{{ -- RHS size: {terms: 41, types: 23, coercions: 0, joins: 3/3} Main.$wex1 [InlPrag=NOINLINE] :: GHC.Prim.Int# -> GHC.Prim.Int# [GblId, Arity=1, Caf=NoCafRefs, Str=, Unf=OtherCon []] Main.$wex1 = \ (ww_s4m8 :: GHC.Prim.Int#) -> joinrec { $s$wgo_s4or :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> Bool -> GHC.Prim.Int# [LclId[JoinId(4)], Arity=4, Str=] $s$wgo_s4or (sc_s4oq :: GHC.Prim.Int#) (sc1_s4op :: GHC.Prim.Int#) _ [Occ=Dead] _ [Occ=Dead] = jump $s$wgo2_s4nk sc1_s4op sc_s4oq; $s$wgo1_s4o0 :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# [LclId[JoinId(3)], Arity=3, Str=] $s$wgo1_s4o0 (sc_s4nZ :: GHC.Prim.Int#) (sc1_s4nY :: GHC.Prim.Int#) (sc2_s4nX :: GHC.Prim.Int#) = jump $s$wgo_s4or (GHC.Prim.+# sc2_s4nX sc_s4nZ) sc1_s4nY sc_s4nZ GHC.Types.False; $s$wgo2_s4nk [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# [LclId[JoinId(2)], Arity=2, Str=, Unf=OtherCon []] $s$wgo2_s4nk (sc_s4nj :: GHC.Prim.Int#) (sc1_s4ni :: GHC.Prim.Int#) = case GHC.Prim.<# sc_s4nj ww_s4m8 of { __DEFAULT -> sc1_s4ni; 1# -> jump $s$wgo1_s4o0 (GHC.Prim.*# sc_s4nj sc_s4nj) (GHC.Prim.+# sc_s4nj 1#) sc1_s4ni }; } in jump $s$wgo2_s4nk 1# 0# }}} `-flate-dmd-anal` gets rid of the superfluous `$s$wgo_s4or`, but what pass is responsible for contracting the recursive group into a single binding (by inlining until we hit the loopbreaker)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 16:50:21 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 16:50:21 -0000 Subject: [GHC] #14982: LLVM default -mcpu setting inhibits customization Message-ID: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> #14982: LLVM default -mcpu setting inhibits customization -------------------------------------+------------------------------------- Reporter: tommd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.1 (LLVM) | 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 GHC 8.4.1 we are now passing a default `-mcpu` selection to llvm. This default is passed regardless of any explicit command line option such as `-optlc=-mcpu=native`. If/when the user explicitly specifies the architecture we now get a failed build. The error message from LLVM is: {{{ llc: for the -mcpu option: may only occur zero or one times! `llc' failed in phase `LLVM Compiler'. (Exit code: 1) }}} This is when compiling with GHC 8.4.1 as such: {{{ ghc-8.4.1 -fforce-recomp -fllvm -optlc=-mcpu=native -O2 tt.hs }} I suggest we either check for a user option of `mcpu` before adding the default or revert this behavior and allow llvm to take it's (optimistic and less portable) default. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 18:34:46 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 18:34:46 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.903ade7cefac8c6e24cc96d2dd13ea9f@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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 varosi): Because single core performance will not rise too much more and the future is in many-core CPUs, are there a plans to reconsider bringing local heaps back in some future time? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 20:40:10 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 20:40:10 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.463e8f3615c637c0060fd223225671e5@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 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:D4503 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ulysses4ever): This makes a lot sense, thanks! I've started doing this. For the other, simpler part of the refactoring, namely, the module canocalization thing, I've submitted update to the Phab. I'm not sure where to put that refactored function though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 22:24:25 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 22:24:25 -0000 Subject: [GHC] #14391: Make the simplifier independent of the typechecker In-Reply-To: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> References: <046.0a550c305c7e5731d1526aa1438cdf9f@haskell.org> Message-ID: <061.107c5a62cd3a86dabafd14fcbcf10151@haskell.org> #14391: Make the simplifier independent of the typechecker -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ulysses4ever Type: task | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.3 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:D4503 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ulysses4ever): Done with TH part closely following your directions. See Phab. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 22:31:39 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 22:31:39 -0000 Subject: [GHC] #14728: Is (GeneralizedNewtypeDeriving + associated type classes) completely bogus? In-Reply-To: <050.b01b3d3c472df373e991905eeea1c1f9@haskell.org> References: <050.b01b3d3c472df373e991905eeea1c1f9@haskell.org> Message-ID: <065.610c7076f4a5b2544aef2f6d046df3c5@haskell.org> #14728: Is (GeneralizedNewtypeDeriving + associated type classes) completely bogus? -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: deriving, Resolution: fixed | TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4402 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): So `flatten_args` has been merged into GHC, so in theory, this ticket is unblocked now. However, after looking at `flatten_args`, I have no idea how it relates to this idea. What I was expected (after reading the description in comment:3) was some sort of function of type: {{{#!hs Type -> Coercion -> Type }}} Where in the example in comment:3, the `Type` argument would be `S (Identity a) x`, the `Coercion` argument would be the newtype axiom `g :: Identity a ~R# a`, and the result `Type` would be `S a (x |> g)`. But `flatten_args` doesn't look very much like this at all, so I'm plain stumped. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 23:56:35 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 23:56:35 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.03e1bb059770b30367c0f0d4394b3cf1@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: voanhduy1512 Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by voanhduy1512): Replying to [comment:7 bgamari]: > Thanks voanhduy1512! Have you checked whether any of the other issues brought up in this ticket still need fixing? I think there are other missing doc, likes no mentions about `deferred- type-errors`, `type-holes` ... I will send another patch to address all missing pieces that i can identify. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Mar 28 23:58:30 2018 From: ghc-devs at haskell.org (GHC) Date: Wed, 28 Mar 2018 23:58:30 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.44de496a17f4a4216d92d7a8b03fcf71@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * status: infoneeded => new Comment: Hoping my example is the new reproducer. If not this can be set back to infoneeded or closed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 00:13:11 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 00:13:11 -0000 Subject: [GHC] #4308: LLVM compiles Updates.cmm badly In-Reply-To: <045.3cd0e08697bdbaa8e7fd07a798201172@haskell.org> References: <045.3cd0e08697bdbaa8e7fd07a798201172@haskell.org> Message-ID: <060.4d31115d0bf4a477d61e7428c6f42b5a@haskell.org> #4308: LLVM compiles Updates.cmm badly -------------------------------------+------------------------------------- Reporter: dterei | Owner: (none) Type: bug | Status: infoneeded Priority: low | Milestone: Component: Compiler (LLVM) | Version: 6.13 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * status: new => infoneeded Comment: The current issue, live register tracking is not as good as we'd like, is a bit vague. Would it be possible to give an example of the problem? Also it is 6 years old. Should a new bug be opened and this one closed? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 00:22:31 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 00:22:31 -0000 Subject: [GHC] #10010: LLVM/optimized code for sqrt incorrect for negative values In-Reply-To: <044.d19bdbb75724dc36db07410233c6837c@haskell.org> References: <044.d19bdbb75724dc36db07410233c6837c@haskell.org> Message-ID: <059.db1045a28e582fe23c4d0f2ff7361890@haskell.org> #10010: LLVM/optimized code for sqrt incorrect for negative values -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): This appears to be fixed in ghc 8.4.1 and llvm 6.0. The supported llvm for 8.4.1 is 5.0 but I have 6.0 as I'm on a Mac and did a brew update which overwrote 5.0 and installed 6.0. Can somebody verify with llvm 5.0? The following shows it works as described above: {{{ bash-3.2$ ghc --version The Glorious Glasgow Haskell Compilation System, version 8.4.1 bash-3.2$ opt -version LLVM (http://llvm.org/): LLVM version 6.0.0 Optimized build. Default target: x86_64-apple-darwin17.4.0 Host CPU: nehalem bash-3.2$ llc -version LLVM (http://llvm.org/): LLVM version 6.0.0 Optimized build. Default target: x86_64-apple-darwin17.4.0 Host CPU: nehalem ... ghc -O -fllvm Sqrt.hs [1 of 1] Compiling Main ( Sqrt.hs, Sqrt.o ) You are using an unsupported version of LLVM! Currently only 5.0 is supported. We will try though... Linking Sqrt ... bash-3.2$ ./Sqrt NaN bash-3.2$ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 00:23:36 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 00:23:36 -0000 Subject: [GHC] #10010: LLVM/optimized code for sqrt incorrect for negative values In-Reply-To: <044.d19bdbb75724dc36db07410233c6837c@haskell.org> References: <044.d19bdbb75724dc36db07410233c6837c@haskell.org> Message-ID: <059.77896b3b77eac9a349449352f70ee0b6@haskell.org> #10010: LLVM/optimized code for sqrt incorrect for negative values -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * cc: George (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 00:27:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 00:27:54 -0000 Subject: [GHC] #11764: ghc internal error building llvm-general-3.5.1.2 In-Reply-To: <049.1e7850c7fbe53a08db3314e9a97a33fc@haskell.org> References: <049.1e7850c7fbe53a08db3314e9a97a33fc@haskell.org> Message-ID: <064.f8cf84ec23ff839a8eee5e02680591d5@haskell.org> #11764: ghc internal error building llvm-general-3.5.1.2 -------------------------------------+------------------------------------- Reporter: andrew.wja | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: cabal install | llvm-general Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): This seems to be still broken on ghc 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 00:56:20 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 00:56:20 -0000 Subject: [GHC] #13062: `opt' failed in phase `LLVM Optimiser'. (Exit code: -11) In-Reply-To: <045.6fe81b99a732ea595c519e1d0b94d988@haskell.org> References: <045.6fe81b99a732ea595c519e1d0b94d988@haskell.org> Message-ID: <060.09f41374fd1568ee14483c0b143952ad@haskell.org> #13062: `opt' failed in phase `LLVM Optimiser'. (Exit code: -11) -------------------------------------+------------------------------------- Reporter: 2bdkid | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: LLVM | Optimiser -11 Operating System: Linux | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): I assume this bug is specific to ARM. Just in case it is of any value, it doesn't reproduce on my Mac with ghc 8.4.1 {{{ $ cabal install -f has-llvm unicode-transforms Resolving dependencies... Downloading bitarray-0.0.1.1... Configuring bitarray-0.0.1.1... Building bitarray-0.0.1.1... Installed bitarray-0.0.1.1 Downloading unicode-transforms-0.3.3... Configuring unicode-transforms-0.3.3... Building unicode-transforms-0.3.3... Installed unicode-transforms-0.3.3 Updating documentation index /Users/gcolpitts/Library/Haskell/share/doc/x86_64-osx-ghc-8.4.1/index.html }}} Probably worth trying with ghc 8.4.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 00:57:19 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 00:57:19 -0000 Subject: [GHC] #13062: `opt' failed in phase `LLVM Optimiser'. (Exit code: -11) In-Reply-To: <045.6fe81b99a732ea595c519e1d0b94d988@haskell.org> References: <045.6fe81b99a732ea595c519e1d0b94d988@haskell.org> Message-ID: <060.b9c59d1629beee7e3b97df157fa64875@haskell.org> #13062: `opt' failed in phase `LLVM Optimiser'. (Exit code: -11) -------------------------------------+------------------------------------- Reporter: 2bdkid | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: LLVM | Optimiser -11 Operating System: Linux | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * cc: George (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 04:27:50 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 04:27:50 -0000 Subject: [GHC] #14983: Have custom type errors imply Void Message-ID: <051.6622dd708a6eb063fa490f3eeb9a127f@haskell.org> #14983: Have custom type errors imply Void -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Unknown/Multiple CustomTypeErrors | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is a very minor issue, but `TypeError` (CustomTypeErrors) should entail a constraint like {{{#!hs import Data.Void class (forall x. x) => No where no :: Void }}} so users don't have to use `undefined` or `error ..`: {{{#!hs instance TypeError (Text "Can't show functions) => Show (a -> b) where show :: (a -> b) -> String show = no & absurd }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 04:28:17 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 04:28:17 -0000 Subject: [GHC] #14983: Have custom type errors imply Void In-Reply-To: <051.6622dd708a6eb063fa490f3eeb9a127f@haskell.org> References: <051.6622dd708a6eb063fa490f3eeb9a127f@haskell.org> Message-ID: <066.56493832fa3c43983f1d4cce84bb2aae@haskell.org> #14983: Have custom type errors imply Void -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | CustomTypeErrors 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: Old description: > This is a very minor issue, but `TypeError` (CustomTypeErrors) should > entail a constraint like > > {{{#!hs > import Data.Void > > class (forall x. x) => No where > no :: Void > }}} > > so users don't have to use `undefined` or `error ..`: > > {{{#!hs > instance TypeError (Text "Can't show functions) => Show (a -> b) where > show :: (a -> b) -> String > show = no & absurd > }}} New description: This is a very minor issue, but `TypeError` (CustomTypeErrors) should entail a constraint like {{{#!hs import Data.Void class (forall x. x) => No where no :: Void }}} so users don't have to use `undefined` or `error ..`: {{{#!hs instance TypeError (Text "Can't show functions") => Show (a -> b) where show :: (a -> b) -> String show = no & absurd }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 07:47:35 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 07:47:35 -0000 Subject: [GHC] #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled In-Reply-To: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> References: <046.a5415cff0c88c89467e1859ff9e5e10d@haskell.org> Message-ID: <061.0b2300a9f549742919b9b74ccd6893cf@haskell.org> #14970: GHC.Err.errorWithoutStackTrace produces stack trace when profiling enabled -------------------------------------+------------------------------------- Reporter: rotaerk | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: libraries/base | Version: 8.2.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 simonmar): * owner: (none) => simonmar * milestone: => 8.4.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 07:51:08 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 07:51:08 -0000 Subject: [GHC] #14737: Improve performance of Simplify.simplCast In-Reply-To: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> References: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> Message-ID: <062.9992b1672410119b6fb19fc7aa7af84f@haskell.org> #14737: Improve performance of Simplify.simplCast -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11735 #14683 | Differential Rev(s): Phab:D4385 Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Preliminary result: digging into `simplCast` some deeper, one of the biggest contributors is the call to `isReflexiveCo`. By rewriting it from this: {{{ isReflexiveCo = isJust . isReflexiveCo_maybe }}} ...to this: {{{ isReflexiveCo (Refl {}) = True isReflexiveCo co = eqType ty1 ty2 where Pair ty1 ty2 = coercionKind co }}} ...cuts execution time for compiling `Grammar.hs` down from 20 seconds to 12. For reference, isReflexiveCo_maybe is defined as: {{{ isReflexiveCo_maybe (Refl r ty) = Just (ty, r) isReflexiveCo_maybe co | ty1 `eqType` ty2 = Just (ty1, r) | otherwise = Nothing where (Pair ty1 ty2, r) = coercionKindRole co }}} So we're really just replicating the logic here, with two differences that seem to improve performance drastically: - We skip calculating the role, using `coercionKind` rather than `coercionKindRole`. - Instead of `Maybe`, we use boolean logic directly, since we are not interested in the actual roles and types, we just want to know if there are any. In theory, neither of these should matter, because the expensive calculations should mostly just thunk up and never get evaluated, but we still see a huge improvement. So this could be due to one or more of the following: - We might evaluate more deeply into `coercionKindRole` than expected - The boolean logic might unbox and optimize into more efficient code requiring fewer allocations - `coercionKindRole` could have some unexpected inefficiencies compared to `coercionKind` - Writing it like this might lead to more beneficial inlining behavior -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 08:14:49 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 08:14:49 -0000 Subject: [GHC] #14984: Rgression: 8.4.1 says "Could not deduce" when before 8.4 it could Message-ID: <044.36004bdef7af2fbfc785798bfc40dba3@haskell.org> #14984: Rgression: 8.4.1 says "Could not deduce" when before 8.4 it could -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.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: -------------------------------------+------------------------------------- Have some code: {{{#!hs import Test.QuickCheck import Test.QuickCheck.Monadic testPropertyIO :: Testable a => PropertyM IO a -> Property testPropertyIO = monadicIO . (=<<) stop }}} That compiles fine with ghc 7.10 through 8.2, but with 8.4.1 fails with: {{{ test/Test/Mafia/IO.hs:18:18: error: ? Could not deduce (Testable a0) arising from a use of ?monadicIO? from the context: Testable a bound by the type signature for: testPropertyIO :: forall a. Testable a => PropertyM IO a -> Property at test/Test/Mafia/IO.hs:17:1-58 The type variable ?a0? is ambiguous These potential instances exist: instance [safe] Testable prop => Testable (Gen prop) -- Defined in ?Test.QuickCheck.Property? instance [safe] Testable Discard -- Defined in ?Test.QuickCheck.Property? instance [safe] Testable Property -- Defined in ?Test.QuickCheck.Property? ...plus three others ...plus two instances involving out-of-scope types (use -fprint-potential-instances to see them all) ? In the first argument of ?(.)?, namely ?monadicIO? In the expression: monadicIO . (=<<) stop In an equation for ?testPropertyIO?: testPropertyIO = monadicIO . (=<<) stop }}} Either the compiler has been incorrectly accepting this as valid for a number of releases or this is a regression. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 08:37:15 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 08:37:15 -0000 Subject: [GHC] #14266: AllowAmbiguousTypes doesn't play well with default class methods In-Reply-To: <051.38c1a194c842b23e120b2589c2db8665@haskell.org> References: <051.38c1a194c842b23e120b2589c2db8665@haskell.org> Message-ID: <066.c1ee1f8855c701e220993982046da4f1@haskell.org> #14266: AllowAmbiguousTypes doesn't play well with default class methods -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by glaebhoerl): * cc: glaebhoerl (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 12:28:26 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 12:28:26 -0000 Subject: [GHC] #14684: combineIdenticalAlts is only partially implemented In-Reply-To: <049.66bb6a9ebb8aeb6bc16c5fd3f9c006db@haskell.org> References: <049.66bb6a9ebb8aeb6bc16c5fd3f9c006db@haskell.org> Message-ID: <064.294a04e7b86f923ebfc169cddf26831e@haskell.org> #14684: combineIdenticalAlts is only partially implemented -------------------------------------+------------------------------------- Reporter: mpickering | Owner: sjakobi Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4542 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjakobi): * differential: Phab:D4419 => Phab:D4542 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 12:45:27 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 12:45:27 -0000 Subject: [GHC] #14983: Have custom type errors imply Void In-Reply-To: <051.6622dd708a6eb063fa490f3eeb9a127f@haskell.org> References: <051.6622dd708a6eb063fa490f3eeb9a127f@haskell.org> Message-ID: <066.def0b6994b0f9e2c1ff3b4b8f7cb6a69@haskell.org> #14983: Have custom type errors imply Void -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: task | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: | CustomTypeErrors | QuantifiedConstraints wipT2893 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: CustomTypeErrors => CustomTypeErrors QuantifiedConstraints wipT2893 Comment: Can't you just do this? {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableSuperClasses #-} module Foo where import Data.Void import GHC.TypeLits class (forall x. x) => No where no :: Void class (TypeError a, forall x. x) => MyTypeError a instance MyTypeError (Text "Can't show functions") => Show (a -> b) where show = absurd no }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 12:52:15 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 12:52:15 -0000 Subject: [GHC] #14984: Regression: 8.4.1 says "Could not deduce" when before 8.4 it could (was: Rgression: 8.4.1 says "Could not deduce" when before 8.4 it could) In-Reply-To: <044.36004bdef7af2fbfc785798bfc40dba3@haskell.org> References: <044.36004bdef7af2fbfc785798bfc40dba3@haskell.org> Message-ID: <059.2afd8c2968ee0789a1732d2d5d95a191@haskell.org> #14984: Regression: 8.4.1 says "Could not deduce" when before 8.4 it could -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.4.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 RyanGlScott): I must be missing something, because this program does not typecheck for me on GHC 8.2.2 //or// 8.4.1: {{{ $ /opt/ghc/8.2.2/bin/ghci Bug2.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug2.hs, interpreted ) Bug2.hs:5:18: error: • Could not deduce (Testable a0) arising from a use of ‘monadicIO’ from the context: Testable a bound by the type signature for: testPropertyIO :: forall a. Testable a => PropertyM IO a -> Property at Bug2.hs:4:1-58 The type variable ‘a0’ is ambiguous These potential instances exist: instance [safe] Testable prop => Testable (Gen prop) -- Defined in ‘Test.QuickCheck.Property’ instance [safe] Testable Discard -- Defined in ‘Test.QuickCheck.Property’ instance [safe] Testable Property -- Defined in ‘Test.QuickCheck.Property’ ...plus three others ...plus two instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the first argument of ‘(.)’, namely ‘monadicIO’ In the expression: monadicIO . (=<<) stop In an equation for ‘testPropertyIO’: testPropertyIO = monadicIO . (=<<) stop | 5 | testPropertyIO = monadicIO . (=<<) stop | ^^^^^^^^^ Failed, no modules loaded. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 13:07:00 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 13:07:00 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.3bb0131d2446ed71154ecaea36c1e3a8@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Here is a smaller example that highlights the problem without vectors. The only difference between the two functions is the use of `[2,3..n]` instead of `[2..n]`, which desugar to different functions. This results in a difference in a huge difference in allocation as well as runtime: {{{ $ ./repro 2 +RTS -s # [2,3..n] () 960,056,856 bytes allocated in the heap 21,536 bytes copied during GC 44,576 bytes maximum residency (2 sample(s)) 29,152 bytes maximum slop 2 MB total memory in use (0 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 918 colls, 0 par 0.005s 0.003s 0.0000s 0.0000s Gen 1 2 colls, 0 par 0.000s 0.000s 0.0001s 0.0002s INIT time 0.000s ( 0.000s elapsed) MUT time 0.123s ( 0.125s elapsed) GC time 0.005s ( 0.003s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.129s ( 0.129s elapsed) %GC time 4.1% (2.5% elapsed) Alloc rate 7,778,808,106 bytes per MUT second Productivity 95.8% of total user, 97.4% of total elapsed }}} {{{ $ ./repro 1 +RTS -s # [2..n] () 56,872 bytes allocated in the heap 3,480 bytes copied during GC 44,576 bytes maximum residency (1 sample(s)) 25,056 bytes maximum slop 2 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.048s ( 0.048s elapsed) GC time 0.000s ( 0.000s elapsed) EXIT time 0.000s ( 0.000s elapsed) Total time 0.048s ( 0.048s elapsed) %GC time 0.2% (0.2% elapsed) Alloc rate 1,188,432 bytes per MUT second Productivity 99.6% of total user, 99.6% of total elapsed }}} This happens in `ST`, but not in `IO`, so probably related to some hack. Also the difference vanishes when we allow the functions to inline. Here's some Core for `g` (the offending function): {{{ -- RHS size: {terms: 235, types: 242, coercions: 61, joins: 4/13} $wg $wg = \ @ s ww w -> let { $wc = } in case <# ww 3# of { __DEFAULT -> let { y' y' = -# ww 1# } in letrec { go_up go_up = \ x eta -> case ># x y' of { __DEFAULT -> $wc x ((go_up (+# x 1#)) `cast` ) eta; 1# -> $wc x (lvl `cast` ) eta }; } in $wc 2# ((go_up 3#) `cast` ) w; 1# -> case <# ww 2# of { __DEFAULT -> $wc 2# (lvl `cast` ) w; 1# -> (# w, () #) } } }}} From my understanding of join points, `$wc` is only nearly a join point, because `go_up` with its transitive tail call to `$wc` appears in argument position. It would be great if we could get rid of this! The `IO` variant (`g 40000000 >>= print`) doesn't have this weakness, it's all join points there. Hence my suspicion about some `IO` hack that let's GHC eta-expand stuff more aggresively, but I'm not sure how that's helping. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 14:19:19 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 14:19:19 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.f2f9c6eb47fca83e1e32bc63fe771753@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * Attachment "repro.hs" added. Reproduction for comment:44 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 14:22:24 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 14:22:24 -0000 Subject: [GHC] #14985: GHC flags missing from the user guide flag reference. Message-ID: <045.558c7d10873300588fb1ac48f975b7ec@haskell.org> #14985: GHC flags missing from the user guide flag reference. -------------------------------------+------------------------------------- Reporter: merijn | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I was making a list of flags from the source of GHC command line parser and found the following flags having no entry in the flag reference: `-sig-of`, `-relative-dynlib-paths`, `-dll-split`, `-ddump-file-prefix`, `-haddock`, `-haddock-opts`, `-dno-llvm-mangler`, `-ffloat-lam-args`, `-ffloat-all-lams` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:00:45 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:00:45 -0000 Subject: [GHC] #14981: GHC parallel GC is not doing well on modern many-core machine In-Reply-To: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> References: <045.edcae7298a9f211a21f281dc6371e306@haskell.org> Message-ID: <060.db1f0b90f09c6aa3bddca6522d1d30ca@haskell.org> #14981: GHC parallel GC is not doing well on modern many-core machine -------------------------------------+------------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.4.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): > Are there a plans to reconsider bringing local heaps back in some future time? Not at the moment, at least not with the same approach that was tried in the local heaps paper. Unfortunately maintaining the local heap invariant ends up being rather expensive both in complexity budget and computation (since objects which may be encountered by other capabilities must be evacuated out to the global heap). GHC is not at all unusual in the stop-the-world nature of its minor GC and there are well-understood ways of dealing with it: simply increase the size of the nursery to reduce the frequency of minor GCs (and therefore synchronization). I have seen GHC run very well on a few dozen cores with a `+RTS -A128MB`. Depending upon the allocation load, it may also help to reduce `+RTS -qn` to reduce the number of cores which need to synchronize. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:03:09 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:03:09 -0000 Subject: [GHC] #13062: `opt' failed in phase `LLVM Optimiser'. (Exit code: -11) In-Reply-To: <045.6fe81b99a732ea595c519e1d0b94d988@haskell.org> References: <045.6fe81b99a732ea595c519e1d0b94d988@haskell.org> Message-ID: <060.ef3cdfe71bbeae5edcc31f42572fbe7c@haskell.org> #13062: `opt' failed in phase `LLVM Optimiser'. (Exit code: -11) -------------------------------------+------------------------------------- Reporter: 2bdkid | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 8.0.1 Resolution: worksforme | Keywords: LLVM | Optimiser -11 Operating System: Linux | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => worksforme Comment: Indeed I also suspect this is an ARM-specific LLVM crash. Closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:08:50 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:08:50 -0000 Subject: [GHC] #10010: LLVM/optimized code for sqrt incorrect for negative values In-Reply-To: <044.d19bdbb75724dc36db07410233c6837c@haskell.org> References: <044.d19bdbb75724dc36db07410233c6837c@haskell.org> Message-ID: <059.b68891ba1c5cb43d5b4dfddf1cc64b9c@haskell.org> #10010: LLVM/optimized code for sqrt incorrect for negative values -------------------------------------+------------------------------------- Reporter: glguy | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (LLVM) | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | libraries/base/tests/Numeric/sqrt Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => libraries/base/tests/Numeric/sqrt * milestone: => 8.2.1 Comment: I'm rather surprised that wasn't caught by any existing testcase. Added a test in Phab:D4543. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:09:43 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:09:43 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.d89331bb0ae2478475494e0598875cda@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: voanhduy1512 Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Thanks again for picking this up! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:16:42 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:16:42 -0000 Subject: [GHC] #11764: ghc internal error building llvm-general-3.5.1.2 In-Reply-To: <049.1e7850c7fbe53a08db3314e9a97a33fc@haskell.org> References: <049.1e7850c7fbe53a08db3314e9a97a33fc@haskell.org> Message-ID: <064.377ef00b9349cfc533f9670bb7de8d2d@haskell.org> #11764: ghc internal error building llvm-general-3.5.1.2 -------------------------------------+------------------------------------- Reporter: andrew.wja | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: cabal install | llvm-general Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > $ cabal install llvm-general > Resolving dependencies... > Configuring llvm-general-3.5.1.2... > Building llvm-general-3.5.1.2... > Failed to install llvm-general-3.5.1.2 > Build log ( /home/andrew/.cabal/logs/llvm-general-3.5.1.2.log ): > [1 of 1] Compiling Main ( /tmp/cabal-tmp-12630/llvm- > general-3.5.1.2/dist/setup/setup.hs, /tmp/cabal-tmp-12630/llvm- > general-3.5.1.2/dist/setup/Main.o ) > Linking /tmp/cabal-tmp-12630/llvm-general-3.5.1.2/dist/setup/setup ... > Configuring llvm-general-3.5.1.2... > Building llvm-general-3.5.1.2... > Preprocessing library llvm-general-3.5.1.2... > [ 1 of 93] Compiling LLVM.General.Internal.FFI.ByteRangeCallback ( > src/LLVM/General/Internal/FFI/ByteRangeCallback.hs, > dist/build/LLVM/General/Internal/FFI/ByteRangeCallback.o ) > [ 2 of 93] Compiling LLVM.General.Internal.FFI.Transforms ( > src/LLVM/General/Internal/FFI/Transforms.hs, > dist/build/LLVM/General/Internal/FFI/Transforms.o ) > [ 3 of 93] Compiling LLVM.General.Internal.Inject ( > src/LLVM/General/Internal/Inject.hs, > dist/build/LLVM/General/Internal/Inject.o ) > [ 4 of 93] Compiling LLVM.General.Internal.FFI.Context ( > src/LLVM/General/Internal/FFI/Context.hs, > dist/build/LLVM/General/Internal/FFI/Context.o ) > [ 5 of 93] Compiling LLVM.General.Internal.FFI.CommandLine ( > src/LLVM/General/Internal/FFI/CommandLine.hs, > dist/build/LLVM/General/Internal/FFI/CommandLine.o ) > [ 6 of 93] Compiling LLVM.General.Internal.FFI.Iterate ( > src/LLVM/General/Internal/FFI/Iterate.hs, > dist/build/LLVM/General/Internal/FFI/Iterate.o ) > [ 7 of 93] Compiling LLVM.General.Internal.FFI.PtrHierarchy ( > src/LLVM/General/Internal/FFI/PtrHierarchy.hs, > dist/build/LLVM/General/Internal/FFI/PtrHierarchy.o ) > [ 8 of 93] Compiling LLVM.General.Internal.FFI.BasicBlock ( > src/LLVM/General/Internal/FFI/BasicBlock.hs, > dist/build/LLVM/General/Internal/FFI/BasicBlock.o ) > [ 9 of 93] Compiling LLVM.General.Internal.FFI.User ( > src/LLVM/General/Internal/FFI/User.hs, > dist/build/LLVM/General/Internal/FFI/User.o ) > [10 of 93] Compiling LLVM.General.Internal.FFI.GlobalAlias ( > src/LLVM/General/Internal/FFI/GlobalAlias.hs, > dist/build/LLVM/General/Internal/FFI/GlobalAlias.o ) > [11 of 93] Compiling LLVM.General.Internal.FFI.LLVMCTypes ( > dist/build/LLVM/General/Internal/FFI/LLVMCTypes.hs, > dist/build/LLVM/General/Internal/FFI/LLVMCTypes.o ) > [12 of 93] Compiling LLVM.General.Internal.FFI.Attribute ( > src/LLVM/General/Internal/FFI/Attribute.hs, > dist/build/LLVM/General/Internal/FFI/Attribute.o ) > [13 of 93] Compiling LLVM.General.Internal.FFI.GlobalValue ( > src/LLVM/General/Internal/FFI/GlobalValue.hs, > dist/build/LLVM/General/Internal/FFI/GlobalValue.o ) > [14 of 93] Compiling LLVM.General.Internal.FFI.Instruction ( > src/LLVM/General/Internal/FFI/Instruction.hs, > dist/build/LLVM/General/Internal/FFI/Instruction.o ) > [15 of 93] Compiling LLVM.General.Internal.FFI.Type ( > src/LLVM/General/Internal/FFI/Type.hs, > dist/build/LLVM/General/Internal/FFI/Type.o ) > [16 of 93] Compiling LLVM.General.Internal.FFI.Value ( > src/LLVM/General/Internal/FFI/Value.hs, > dist/build/LLVM/General/Internal/FFI/Value.o ) > [17 of 93] Compiling LLVM.General.Internal.FFI.BinaryOperator ( > src/LLVM/General/Internal/FFI/BinaryOperator.hs, > dist/build/LLVM/General/Internal/FFI/BinaryOperator.o ) > [18 of 93] Compiling LLVM.General.Internal.FFI.DataLayout ( > src/LLVM/General/Internal/FFI/DataLayout.hs, > dist/build/LLVM/General/Internal/FFI/DataLayout.o ) > [19 of 93] Compiling LLVM.General.Internal.FFI.SMDiagnostic ( > src/LLVM/General/Internal/FFI/SMDiagnostic.hs, > dist/build/LLVM/General/Internal/FFI/SMDiagnostic.o ) > [20 of 93] Compiling LLVM.General.Internal.FFI.Module ( > src/LLVM/General/Internal/FFI/Module.hs, > dist/build/LLVM/General/Internal/FFI/Module.o ) > [21 of 93] Compiling LLVM.General.Internal.FFI.ExecutionEngine ( > src/LLVM/General/Internal/FFI/ExecutionEngine.hs, > dist/build/LLVM/General/Internal/FFI/ExecutionEngine.o ) > [22 of 93] Compiling LLVM.General.Internal.FFI.Function ( > src/LLVM/General/Internal/FFI/Function.hs, > dist/build/LLVM/General/Internal/FFI/Function.o ) > [23 of 93] Compiling LLVM.General.Internal.FFI.InlineAssembly ( > src/LLVM/General/Internal/FFI/InlineAssembly.hs, > dist/build/LLVM/General/Internal/FFI/InlineAssembly.o ) > [24 of 93] Compiling LLVM.General.Internal.FFI.InstructionDefs ( > dist/build/LLVM/General/Internal/FFI/InstructionDefs.hs, > dist/build/LLVM/General/Internal/FFI/InstructionDefs.o ) > [25 of 93] Compiling LLVM.General.Internal.InstructionDefs ( > src/LLVM/General/Internal/InstructionDefs.hs, > dist/build/LLVM/General/Internal/InstructionDefs.o ) > [26 of 93] Compiling LLVM.General.Internal.FFI.MemoryBuffer ( > src/LLVM/General/Internal/FFI/MemoryBuffer.hs, > dist/build/LLVM/General/Internal/FFI/MemoryBuffer.o ) > [27 of 93] Compiling LLVM.General.Internal.FFI.Metadata ( > src/LLVM/General/Internal/FFI/Metadata.hs, > dist/build/LLVM/General/Internal/FFI/Metadata.o ) > [28 of 93] Compiling LLVM.General.Internal.FFI.GlobalVariable ( > src/LLVM/General/Internal/FFI/GlobalVariable.hs, > dist/build/LLVM/General/Internal/FFI/GlobalVariable.o ) > [29 of 93] Compiling LLVM.General.Internal.FFI.RawOStream ( > src/LLVM/General/Internal/FFI/RawOStream.hs, > dist/build/LLVM/General/Internal/FFI/RawOStream.o ) > [30 of 93] Compiling LLVM.General.Internal.FFI.Assembly ( > src/LLVM/General/Internal/FFI/Assembly.hs, > dist/build/LLVM/General/Internal/FFI/Assembly.o ) > [31 of 93] Compiling LLVM.General.Internal.FFI.Bitcode ( > src/LLVM/General/Internal/FFI/Bitcode.hs, > dist/build/LLVM/General/Internal/FFI/Bitcode.o ) > [32 of 93] Compiling LLVM.General.Internal.FFI.Target ( > src/LLVM/General/Internal/FFI/Target.hs, > dist/build/LLVM/General/Internal/FFI/Target.o ) > [33 of 93] Compiling LLVM.General.Internal.FFI.Threading ( > src/LLVM/General/Internal/FFI/Threading.hs, > dist/build/LLVM/General/Internal/FFI/Threading.o ) > [34 of 93] Compiling LLVM.General.Internal.FFI.Cleanup ( > src/LLVM/General/Internal/FFI/Cleanup.hs, > dist/build/LLVM/General/Internal/FFI/Cleanup.o ) > [35 of 93] Compiling LLVM.General.Internal.FFI.Constant ( > src/LLVM/General/Internal/FFI/Constant.hs, > dist/build/LLVM/General/Internal/FFI/Constant.o ) > ghc: internal error: stg_ap_pv_ret > (GHC version 7.10.3 for x86_64_unknown_linux) > Please report this as a GHC bug: > http://www.haskell.org/ghc/reportabug > cabal: Error: some packages failed to install: > llvm-general-3.5.1.2 failed during the building phase. The exception was: > ExitFailure (-6) New description: {{{ $ cabal install llvm-general Resolving dependencies... Configuring llvm-general-3.5.1.2... Building llvm-general-3.5.1.2... Failed to install llvm-general-3.5.1.2 Build log ( /home/andrew/.cabal/logs/llvm-general-3.5.1.2.log ): [1 of 1] Compiling Main ( /tmp/cabal-tmp-12630/llvm- general-3.5.1.2/dist/setup/setup.hs, /tmp/cabal-tmp-12630/llvm- general-3.5.1.2/dist/setup/Main.o ) Linking /tmp/cabal-tmp-12630/llvm-general-3.5.1.2/dist/setup/setup ... Configuring llvm-general-3.5.1.2... Building llvm-general-3.5.1.2... Preprocessing library llvm-general-3.5.1.2... [ 1 of 93] Compiling LLVM.General.Internal.FFI.ByteRangeCallback ( src/LLVM/General/Internal/FFI/ByteRangeCallback.hs, dist/build/LLVM/General/Internal/FFI/ByteRangeCallback.o ) [ 2 of 93] Compiling LLVM.General.Internal.FFI.Transforms ( src/LLVM/General/Internal/FFI/Transforms.hs, dist/build/LLVM/General/Internal/FFI/Transforms.o ) [ 3 of 93] Compiling LLVM.General.Internal.Inject ( src/LLVM/General/Internal/Inject.hs, dist/build/LLVM/General/Internal/Inject.o ) [ 4 of 93] Compiling LLVM.General.Internal.FFI.Context ( src/LLVM/General/Internal/FFI/Context.hs, dist/build/LLVM/General/Internal/FFI/Context.o ) [ 5 of 93] Compiling LLVM.General.Internal.FFI.CommandLine ( src/LLVM/General/Internal/FFI/CommandLine.hs, dist/build/LLVM/General/Internal/FFI/CommandLine.o ) [ 6 of 93] Compiling LLVM.General.Internal.FFI.Iterate ( src/LLVM/General/Internal/FFI/Iterate.hs, dist/build/LLVM/General/Internal/FFI/Iterate.o ) [ 7 of 93] Compiling LLVM.General.Internal.FFI.PtrHierarchy ( src/LLVM/General/Internal/FFI/PtrHierarchy.hs, dist/build/LLVM/General/Internal/FFI/PtrHierarchy.o ) [ 8 of 93] Compiling LLVM.General.Internal.FFI.BasicBlock ( src/LLVM/General/Internal/FFI/BasicBlock.hs, dist/build/LLVM/General/Internal/FFI/BasicBlock.o ) [ 9 of 93] Compiling LLVM.General.Internal.FFI.User ( src/LLVM/General/Internal/FFI/User.hs, dist/build/LLVM/General/Internal/FFI/User.o ) [10 of 93] Compiling LLVM.General.Internal.FFI.GlobalAlias ( src/LLVM/General/Internal/FFI/GlobalAlias.hs, dist/build/LLVM/General/Internal/FFI/GlobalAlias.o ) [11 of 93] Compiling LLVM.General.Internal.FFI.LLVMCTypes ( dist/build/LLVM/General/Internal/FFI/LLVMCTypes.hs, dist/build/LLVM/General/Internal/FFI/LLVMCTypes.o ) [12 of 93] Compiling LLVM.General.Internal.FFI.Attribute ( src/LLVM/General/Internal/FFI/Attribute.hs, dist/build/LLVM/General/Internal/FFI/Attribute.o ) [13 of 93] Compiling LLVM.General.Internal.FFI.GlobalValue ( src/LLVM/General/Internal/FFI/GlobalValue.hs, dist/build/LLVM/General/Internal/FFI/GlobalValue.o ) [14 of 93] Compiling LLVM.General.Internal.FFI.Instruction ( src/LLVM/General/Internal/FFI/Instruction.hs, dist/build/LLVM/General/Internal/FFI/Instruction.o ) [15 of 93] Compiling LLVM.General.Internal.FFI.Type ( src/LLVM/General/Internal/FFI/Type.hs, dist/build/LLVM/General/Internal/FFI/Type.o ) [16 of 93] Compiling LLVM.General.Internal.FFI.Value ( src/LLVM/General/Internal/FFI/Value.hs, dist/build/LLVM/General/Internal/FFI/Value.o ) [17 of 93] Compiling LLVM.General.Internal.FFI.BinaryOperator ( src/LLVM/General/Internal/FFI/BinaryOperator.hs, dist/build/LLVM/General/Internal/FFI/BinaryOperator.o ) [18 of 93] Compiling LLVM.General.Internal.FFI.DataLayout ( src/LLVM/General/Internal/FFI/DataLayout.hs, dist/build/LLVM/General/Internal/FFI/DataLayout.o ) [19 of 93] Compiling LLVM.General.Internal.FFI.SMDiagnostic ( src/LLVM/General/Internal/FFI/SMDiagnostic.hs, dist/build/LLVM/General/Internal/FFI/SMDiagnostic.o ) [20 of 93] Compiling LLVM.General.Internal.FFI.Module ( src/LLVM/General/Internal/FFI/Module.hs, dist/build/LLVM/General/Internal/FFI/Module.o ) [21 of 93] Compiling LLVM.General.Internal.FFI.ExecutionEngine ( src/LLVM/General/Internal/FFI/ExecutionEngine.hs, dist/build/LLVM/General/Internal/FFI/ExecutionEngine.o ) [22 of 93] Compiling LLVM.General.Internal.FFI.Function ( src/LLVM/General/Internal/FFI/Function.hs, dist/build/LLVM/General/Internal/FFI/Function.o ) [23 of 93] Compiling LLVM.General.Internal.FFI.InlineAssembly ( src/LLVM/General/Internal/FFI/InlineAssembly.hs, dist/build/LLVM/General/Internal/FFI/InlineAssembly.o ) [24 of 93] Compiling LLVM.General.Internal.FFI.InstructionDefs ( dist/build/LLVM/General/Internal/FFI/InstructionDefs.hs, dist/build/LLVM/General/Internal/FFI/InstructionDefs.o ) [25 of 93] Compiling LLVM.General.Internal.InstructionDefs ( src/LLVM/General/Internal/InstructionDefs.hs, dist/build/LLVM/General/Internal/InstructionDefs.o ) [26 of 93] Compiling LLVM.General.Internal.FFI.MemoryBuffer ( src/LLVM/General/Internal/FFI/MemoryBuffer.hs, dist/build/LLVM/General/Internal/FFI/MemoryBuffer.o ) [27 of 93] Compiling LLVM.General.Internal.FFI.Metadata ( src/LLVM/General/Internal/FFI/Metadata.hs, dist/build/LLVM/General/Internal/FFI/Metadata.o ) [28 of 93] Compiling LLVM.General.Internal.FFI.GlobalVariable ( src/LLVM/General/Internal/FFI/GlobalVariable.hs, dist/build/LLVM/General/Internal/FFI/GlobalVariable.o ) [29 of 93] Compiling LLVM.General.Internal.FFI.RawOStream ( src/LLVM/General/Internal/FFI/RawOStream.hs, dist/build/LLVM/General/Internal/FFI/RawOStream.o ) [30 of 93] Compiling LLVM.General.Internal.FFI.Assembly ( src/LLVM/General/Internal/FFI/Assembly.hs, dist/build/LLVM/General/Internal/FFI/Assembly.o ) [31 of 93] Compiling LLVM.General.Internal.FFI.Bitcode ( src/LLVM/General/Internal/FFI/Bitcode.hs, dist/build/LLVM/General/Internal/FFI/Bitcode.o ) [32 of 93] Compiling LLVM.General.Internal.FFI.Target ( src/LLVM/General/Internal/FFI/Target.hs, dist/build/LLVM/General/Internal/FFI/Target.o ) [33 of 93] Compiling LLVM.General.Internal.FFI.Threading ( src/LLVM/General/Internal/FFI/Threading.hs, dist/build/LLVM/General/Internal/FFI/Threading.o ) [34 of 93] Compiling LLVM.General.Internal.FFI.Cleanup ( src/LLVM/General/Internal/FFI/Cleanup.hs, dist/build/LLVM/General/Internal/FFI/Cleanup.o ) [35 of 93] Compiling LLVM.General.Internal.FFI.Constant ( src/LLVM/General/Internal/FFI/Constant.hs, dist/build/LLVM/General/Internal/FFI/Constant.o ) ghc: internal error: stg_ap_pv_ret (GHC version 7.10.3 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug cabal: Error: some packages failed to install: llvm-general-3.5.1.2 failed during the building phase. The exception was: ExitFailure (-6) }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:18:11 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:18:11 -0000 Subject: [GHC] #11764: ghc internal error building llvm-general-3.5.1.2 In-Reply-To: <049.1e7850c7fbe53a08db3314e9a97a33fc@haskell.org> References: <049.1e7850c7fbe53a08db3314e9a97a33fc@haskell.org> Message-ID: <064.1d8c069c9ff11eb18c638e7b4a184b6a@haskell.org> #11764: ghc internal error building llvm-general-3.5.1.2 -------------------------------------+------------------------------------- Reporter: andrew.wja | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: cabal install | llvm-general Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * priority: normal => high * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:36:08 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:36:08 -0000 Subject: [GHC] #14229: Contraditions in users_guide/using-warnings.html In-Reply-To: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> References: <054.d6f9d16cc1b1fa988ffa9396c0d0581c@haskell.org> Message-ID: <069.31a98b975745417f3d8446e28b867490@haskell.org> #14229: Contraditions in users_guide/using-warnings.html -------------------------------------+------------------------------------- Reporter: MikolajKonarski | Owner: voanhduy1512 Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 8.2.1 Resolution: | Keywords: newcomers Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4528 Wiki Page: | -------------------------------------+------------------------------------- Comment (by MikolajKonarski): Indeed, thank you, voanhduy1512. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:41:23 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:41:23 -0000 Subject: [GHC] #14977: Clang doesn't support -Wsync-nand In-Reply-To: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> References: <046.24e425041591ab630ce4f4705c36a15b@haskell.org> Message-ID: <061.ed247d76cb55571ff725d720fa2a57f2@haskell.org> #14977: Clang doesn't support -Wsync-nand -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.5 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | 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 * milestone: 8.4.2 => 8.6.1 Comment: Nope, this only affects ed6f9fb9d5a684d2159c29633159c3254cf04deb which isn't present on `ghc-8.4`. Thanks for checking though! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:46:38 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:46:38 -0000 Subject: [GHC] #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint In-Reply-To: <043.599dc42c545c1acae74a2386e576be96@haskell.org> References: <043.599dc42c545c1acae74a2386e576be96@haskell.org> Message-ID: <058.d40e06d84270cb804fdb1c3b462aa8dc@haskell.org> #14905: GHCi segfaults with +RTS -Di after hitting a breakpoint -------------------------------------+------------------------------------- Reporter: osa1 | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: GHCi | Version: 8.5 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:D4490 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with bd85d96305bf7e70d0dda957fcc3124f2b04e410. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:47:12 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:47:12 -0000 Subject: [GHC] #14932: DeriveAnyClass produces unjustifiably untouchable unification variables In-Reply-To: <050.9f4e9be95913004697959a884a0f5742@haskell.org> References: <050.9f4e9be95913004697959a884a0f5742@haskell.org> Message-ID: <065.b453e142882424e069e274e0eae13ba7@haskell.org> #14932: DeriveAnyClass produces unjustifiably untouchable unification variables -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T14932 Blocked By: | Blocking: Related Tickets: #13272, #14933 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with d8dbe2936c923471a13e214113b0e43222e95592. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:47:34 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:47:34 -0000 Subject: [GHC] #14933: DeriveAnyClass can cause "No skolem info" GHC panic In-Reply-To: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> References: <050.0d832a2fc91201b0b2d7eff7327f3a42@haskell.org> Message-ID: <065.3d70616852dd12f878e182e03eaa1238@haskell.org> #14933: DeriveAnyClass can cause "No skolem info" GHC panic -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: fixed | Keywords: deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash or panic | deriving/should_compile/T14933 Blocked By: | Blocking: Related Tickets: #14932 | Differential Rev(s): Phab:D4507 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with d8dbe2936c923471a13e214113b0e43222e95592. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:48:01 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:48:01 -0000 Subject: [GHC] #14740: Unboxed tuple allowed in context: ((##)) => () In-Reply-To: <051.8b8e98ba0843035c110393441bb1b895@haskell.org> References: <051.8b8e98ba0843035c110393441bb1b895@haskell.org> Message-ID: <066.84127ff89f98cc1e0f5a4918d05e5769@haskell.org> #14740: Unboxed tuple allowed in context: ((##)) => () -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: sighingnow Type: bug | Status: closed Priority: normal | Milestone: 8.4.2 Component: Compiler | Version: 8.5 (Parser) | Resolution: fixed | Keywords: UnboxedTuples Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T14740 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4359 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with 43f63a6b07b183490f17f37d88aa68d00bf49445. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:49:41 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:49:41 -0000 Subject: [GHC] #13930: Cabal configure regresses in space/time In-Reply-To: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> References: <046.5b2c9cbc56e2d7d878c20dcde39f4651@haskell.org> Message-ID: <061.2f99df6859cd9f5f606972d2e163761d@haskell.org> #13930: Cabal configure regresses in space/time -------------------------------------+------------------------------------- Reporter: bgamari | Owner: tdammers Type: bug | Status: infoneeded Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13982, #5129 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:50:08 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:50:08 -0000 Subject: [GHC] #14155: GHC mentions unlifted types out of the blue (to me anyway) In-Reply-To: <051.e9a8763157e763f2ef920c4bfc2f101b@haskell.org> References: <051.e9a8763157e763f2ef920c4bfc2f101b@haskell.org> Message-ID: <066.9fa109a250db8f16a66ce10f15aebfd7@haskell.org> #14155: GHC mentions unlifted types out of the blue (to me anyway) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.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 bgamari): * milestone: 8.4.2 => 8.6.1 Comment: Bumping off to 8.6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:50:30 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:50:30 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.64a5c73bc113fda286b7710f3b87d6aa@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > Here is some serious performance regression in the following code: > > {{{ > > {-# LANGUAGE BangPatterns #-} > {-# LANGUAGE ScopedTypeVariables #-} > {-# LANGUAGE FlexibleContexts #-} > > module Main where > > import Prelude > import qualified Foreign.Storable as Storable > import qualified Control.Monad.State.Strict as S > import Control.Monad.IO.Class > import Foreign.Marshal.Alloc (mallocBytes) > import Criterion.Main > > newtype Foo a = Foo a > > intSize :: Int > intSize = Storable.sizeOf (undefined :: Int) > > slow :: Int -> IO () > slow i = do > ptr <- mallocBytes $ 2 * intSize > Storable.pokeByteOff ptr intSize (0 :: Int) > let go 0 = pure () > go j = do > Foo (!_, !off) <- S.get > !(x :: Int) <- liftIO $ Storable.peekByteOff ptr off > liftIO $ Storable.pokeByteOff ptr off $! (x + 1) > go (j - 1) > S.evalStateT (go i) (Foo ((0::Int),(intSize::Int))) > > fast :: Int -> IO () > fast i = do > ptr <- mallocBytes $ 2 * intSize > Storable.pokeByteOff ptr intSize (0 :: Int) > let go 0 = pure () > go j = do > (!_, !off) <- S.get > !(x :: Int) <- liftIO $ Storable.peekByteOff ptr off > liftIO $ Storable.pokeByteOff ptr off $! (x + 1) > go (j - 1) > S.evalStateT (go i) ((0::Int),(intSize::Int)) > > main :: IO () > main = defaultMain > [ bgroup "slow" > $ (\(i :: Int) -> bench ("10e" <> show i) > $ perRunEnv (return ()) > $ \v -> slow (10 ^ i)) <$> [7..8] > > , bgroup "fast" > $ (\(i :: Int) -> bench ("10e" <> show i) > $ perRunEnv (return ()) > $ \v -> fast (10 ^ i)) <$> [7..8] > ] > }}} > > Compiled with flags: > `-threaded -funbox-strict-fields -O2 -fconstraint-solver-iterations=100 > -fexcess-precision -fexpose-all-unfoldings -flate-dmd-anal -fspec-constr- > keen -fspecialise-aggressively -fstatic-argument-transformation -fmax- > worker-args=200` > > The `slow` function executes 2 times slower than the `fast` one. The only > difference is that the state is wrapped in a newtype. It was working > properly in GHC 8.2 (both functions were equally fast - as fast as the > current `fast` function). New description: Here is some serious performance regression in the following code: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE FlexibleContexts #-} module Main where import Prelude import qualified Foreign.Storable as Storable import qualified Control.Monad.State.Strict as S import Control.Monad.IO.Class import Foreign.Marshal.Alloc (mallocBytes) import Criterion.Main newtype Foo a = Foo a intSize :: Int intSize = Storable.sizeOf (undefined :: Int) slow :: Int -> IO () slow i = do ptr <- mallocBytes $ 2 * intSize Storable.pokeByteOff ptr intSize (0 :: Int) let go 0 = pure () go j = do Foo (!_, !off) <- S.get !(x :: Int) <- liftIO $ Storable.peekByteOff ptr off liftIO $ Storable.pokeByteOff ptr off $! (x + 1) go (j - 1) S.evalStateT (go i) (Foo ((0::Int),(intSize::Int))) fast :: Int -> IO () fast i = do ptr <- mallocBytes $ 2 * intSize Storable.pokeByteOff ptr intSize (0 :: Int) let go 0 = pure () go j = do (!_, !off) <- S.get !(x :: Int) <- liftIO $ Storable.peekByteOff ptr off liftIO $ Storable.pokeByteOff ptr off $! (x + 1) go (j - 1) S.evalStateT (go i) ((0::Int),(intSize::Int)) main :: IO () main = defaultMain [ bgroup "slow" $ (\(i :: Int) -> bench ("10e" <> show i) $ perRunEnv (return ()) $ \v -> slow (10 ^ i)) <$> [7..8] , bgroup "fast" $ (\(i :: Int) -> bench ("10e" <> show i) $ perRunEnv (return ()) $ \v -> fast (10 ^ i)) <$> [7..8] ] }}} Compiled with flags: `-threaded -funbox-strict-fields -O2 -fconstraint-solver-iterations=100 -fexcess-precision -fexpose-all-unfoldings -flate-dmd-anal -fspec-constr- keen -fspecialise-aggressively -fstatic-argument-transformation -fmax- worker-args=200` The `slow` function executes 2 times slower than the `fast` one. The only difference is that the state is wrapped in a newtype. It was working properly in GHC 8.2 (both functions were equally fast - as fast as the current `fast` function). -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:51:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:51:57 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.e5804029462e7435e77515ce267e673a@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): RyanGlScott, did you happen to see whether the `WARN` mentioned in that patch fired in the case of this program? I suppose it likely did. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 15:57:22 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 15:57:22 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.9595272e9bd6a596dad34e626dec2490@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I wasn't using a build with assertions enabled, so I couldn't tell. I'll check shortly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:14:34 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:14:34 -0000 Subject: [GHC] #14982: LLVM default -mcpu setting inhibits customization In-Reply-To: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> References: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> Message-ID: <059.1c51f9505287bf9c8f58ed4b71e11ce2@haskell.org> #14982: LLVM default -mcpu setting inhibits customization -------------------------------------+------------------------------------- Reporter: tommd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler (LLVM) | Version: 8.4.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: angerman (added) * milestone: 8.6.1 => 8.4.2 Comment: Any thoughts on what we should do here, Moritz? I'm leaning towards just reverting the `-mcpu` change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:16:49 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:16:49 -0000 Subject: [GHC] #14956: NUMA not detected on Aarch64 NUMA machine In-Reply-To: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> References: <045.7cfcebfe74212ddac33eec03cf3c48a1@haskell.org> Message-ID: <060.2919ee29e151e7cbc6ea63f7669595b8@haskell.org> #14956: NUMA not detected on Aarch64 NUMA machine -----------------------------------+---------------------------------- Reporter: varosi | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 8.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: aarch64 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -----------------------------------+---------------------------------- Comment (by bgamari): Are you sure your compiler was built with NUMA support enabled? Note that this is not true of the binary distributions since this would incur a dependency on `libnuma`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:19:54 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:19:54 -0000 Subject: [GHC] #14263: typeKind is quadratic In-Reply-To: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> References: <047.347eff46dcda74aa975a5781e6cb08f5@haskell.org> Message-ID: <062.aa9c2d31c878a2098283f9b5d1721a8d@haskell.org> #14263: typeKind is quadratic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: simonpj Type: task | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:21:48 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:21:48 -0000 Subject: [GHC] #14936: GHC 8.4 performance regressions when using newtypes In-Reply-To: <046.51c083465a95f77099b97377aa2723e3@haskell.org> References: <046.51c083465a95f77099b97377aa2723e3@haskell.org> Message-ID: <061.a58771fa0f4bc72cb022e313c11a79d2@haskell.org> #14936: GHC 8.4 performance regressions when using newtypes -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: 8.4.2 Component: Compiler | Version: 8.4.1 Resolution: | Keywords: SpecConstr Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): bgamari, your suspicions have been confirmed: {{{ $ ghc2/inplace/bin/ghc-stage2 -O2 -fforce-recomp -DDEBUG Bug.hs [1 of 1] Compiling Bug2 ( Bug.hs, Bug.o ) WARNING: file compiler/specialise/SpecConstr.hs, line 2078 SpecConstr: bad covars: [sg_s2Ba] $wslowGo_s2A8 (-# ds_X2vv 1#) (wild_Xi `cast` (Sym (N:Foo[0] <(Int, Int)>_R) :: ((Int, Int) :: *) ~R# (Foo (Int, Int) :: *))) w_s2A3 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:32:16 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:32:16 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.58307eb6c2d76966a8ddd61fb3099cad@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): It seems that for `IO`, GHC decides that it's OK to inline `c` from the [https://hackage.haskell.org/package/base-4.11.0.0/docs/src/GHC.Enum.html#efdtIntUpFB fusion helper of enumFromThenTo], but not so for `ST s`. For our case, `c` is the `` computation (see the worker `$wc` in comment:44) performed for each outer list element and would be duplicated by inlining: It's mentioned thrice in the definition of `efdtIntUpFB`. Consequently, `c` has almost always `Guidance=NEVER`, except in the `IO` case, where it miraculously gets `Guidance=IF_ARGS [20 420 0] 674 0` just when it is inlined. Not sure what this decision is based on. The inlining decision for `eftIntFB` is much easier: `c` [https://hackage.haskell.org/package/base-4.11.0.0/docs/src/GHC.Enum.html#eftIntFB only happens once there]. I'm not sure if `IO` gets special treatment by the inliner, but I see a few ways out: * Do the same hacks for `ST`, if there are any which apply (ugly) * Reduce the number of calls to `c` in the implementation of `efdtIntUpFB`, probably for worse branch prediction * Figure out why the floated out expression of `\x -> (nop x *>)` occuring in `forM_ nop = flip mapM_ nop = foldr ((>>) . nop) (return ())` doesn't get eta-expanded in the `ST` case, whereas the relevant `IO` code is. I hope that by fixing this, the `c` expression inlines again. Here's how it inlines for `IO`: {{{ (>>) . nop = \x -> (nop x >>) = \x -> (nop x *>) -- notice how it's no different than ST up until here = \x -> (thenIO (nop x)) }}} The inliner probably stops here, but because of eta-expansion modulo coercions to `\x k s -> thenIO (nop x) k s`, we can inline [https://hackage.haskell.org/package/base-4.11.0.0/docs/src/GHC.Base.html#thenIO thenIO]: {{{ \x k s -> thenIO (nop x) y s = \x k s -> case nop x s of (# new_s, _ #) -> k new_s) }}} which is much better and probably more keenly inlined than `\x -> (nop x *>)` in the `ST` case. What makes GHC eta-expand one, but not the other? This is just a wild guess and the only real difference I could make out in diffs. Maybe someone with actual insights into the simplifier can comment on this claim (that the inliner gives up on `c` due to the missed eta- expansion and inlining)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:32:45 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:32:45 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.26921b843d80e5fd1a77b6dc874810fc@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * cc: sgraf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:36:12 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:36:12 -0000 Subject: [GHC] #14980: Runtime performance regression with binary operations on vectors In-Reply-To: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> References: <045.ab336d0088ca69d4e469f8fa0aa0a8ee@haskell.org> Message-ID: <060.eae5eae2ff2ea859b7e874be10c98b9a@haskell.org> #14980: Runtime performance regression with binary operations on vectors -------------------------------------+------------------------------------- Reporter: ttylec | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: vector | bitwise operations Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari * milestone: => 8.6.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:48:45 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:48:45 -0000 Subject: [GHC] #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 In-Reply-To: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> References: <050.db94ecc603495ad4a4c3a0e35b8ec360@haskell.org> Message-ID: <065.dbd853b0a8e8a5adca92cb6075d1308e@haskell.org> #14052: Significant GHCi speed regression with :module and `let` in GHC 8.2.1 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: osa1 Type: bug | Status: closed Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.2.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11547 | Differential Rev(s): Phab:D4478 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Revert merged to `ghc-8.4` with a4c427918509cffe05c2b8c5ae1f21adfd757a7b. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 16:48:49 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 16:48:49 -0000 Subject: [GHC] #14048: Data instances of kind Constraint In-Reply-To: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> References: <051.8c6d06ccd49f550c423f65db1edff09f@haskell.org> Message-ID: <066.0414fc04189b34cfcf2b7b4b1b92a1bc@haskell.org> #14048: Data instances of kind Constraint -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.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: #12369 | Differential Rev(s): Phab:D4479 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-8.4` with a2e02a5f868d487667a26005ddcb557178b26475. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 18:49:23 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 18:49:23 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.dc6d7d6623f1bb366347e2dcc4c3670d@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): Your example seems to be different than mine in that when I compile yours with ghc 8.4.1 and -O there is no difference in allocation unlike mine. What flags did you compile with? {{{ ghc -O repro.hs +RTS [1 of 1] Compiling Main ( repro.hs, repro.o ) Linking repro ... bash-3.2$ ./repro 1 +RTS -s () 56,880 bytes allocated in the heap 3,480 bytes copied during GC 44,576 bytes maximum residency (1 sample(s)) 25,056 bytes maximum slop 2 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.0002s 0.0002s INIT time 0.000s ( 0.002s elapsed) MUT time 0.051s ( 0.052s elapsed) GC time 0.000s ( 0.000s elapsed) EXIT time 0.000s ( 0.003s elapsed) Total time 0.051s ( 0.057s elapsed) %GC time 0.3% (0.4% elapsed) Alloc rate 1,118,716 bytes per MUT second Productivity 99.3% of total user, 95.6% of total elapsed bash-3.2$ ./repro 2 +RTS -s () 56,880 bytes allocated in the heap 3,480 bytes copied during GC 44,576 bytes maximum residency (1 sample(s)) 25,056 bytes maximum slop 2 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.0002s 0.0002s INIT time 0.000s ( 0.002s elapsed) MUT time 0.051s ( 0.051s elapsed) GC time 0.000s ( 0.000s elapsed) EXIT time 0.000s ( 0.005s elapsed) Total time 0.051s ( 0.059s elapsed) %GC time 0.3% (0.3% elapsed) Alloc rate 1,120,655 bytes per MUT second Productivity 99.3% of total user, 95.7% of total elapsed }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 19:23:10 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 19:23:10 -0000 Subject: [GHC] #9406: unexpected failure for T7837(profasm) In-Reply-To: <042.6cf0b0817037f8cfba5de5652e277f8a@haskell.org> References: <042.6cf0b0817037f8cfba5de5652e277f8a@haskell.org> Message-ID: <057.7d76cacc8bf103b678ba6803f9905ff4@haskell.org> #9406: unexpected failure for T7837(profasm) -------------------------------------+------------------------------------- Reporter: jrp | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Profiling | Version: 7.8.3 Resolution: | Keywords: T7837 Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: T7837 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) Comment: I just ran `./validate --slow` and T7837 is not broken with the prof ways after all. Will change the expectation in a diff soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 19:40:46 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 19:40:46 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.f9cbd4d229b9768805b68c212f94454b@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Yuck! I was under the impression I used GHC 8.4.1 via a `nix-shell` when in reality I was using another locally installed 8.2.2. So, back to minimization, I guess. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 20:23:08 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 20:23:08 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.927c8b5cbb3bd797d91d5221994a1c86@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): It seems I uploaded the variant where I used `IO` instead of `ST`, where things still inline. When you substitute `ST s` for `IO` and use `print $ runST $ ...` instead of `... >>= print`, it should reproduce with 8.4.1. Now here's the funny part: I managed to make this reproduce even for `IO` by duplicating the call to `nop`. So it seems like `c` really just hits the threshold where the inliner gives up. The only solution I can think of is what I described in my second point above: Implement `efdtIntUpFB` in a way that doesn't duplicate `c`. In general we should avoid to call `c` in `build`s more than once because of scenarios like this. Huge `c`s aren't uncommon at all (do blocks in `forM_` bodies, the functions passed as first argument to `foldr`, etc.) and otherwise we can't guarantee that everything inlines. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 20:26:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 20:26:57 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.7fec98647bcee70c2067f74ff462031c@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): I can't attach the fixed reproduction, so use this gist instead: https://gist.github.com/sgraf812/6089d81fbc95af9c5f817ff9dc417401 I'll see if I can craft a variant of `efdtInt*` that doesn't duplicate `c`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 21:21:36 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 21:21:36 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.ab62659fca88912cbda07e389de5a5e0@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > In general we should avoid to call c in builds more than once because of scenarios like this. I vaguely having seen a Note about this somewhere, but I cannot find it right now. But yes, a single occurrence of `c` is beneficial. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 21:22:28 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 21:22:28 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.2186a3940228efd11462a9320cfe7a28@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): This definition of `efdtIntUpFB` only has a single occurence of `c` and `n` and consequently fixes th issue. But this probably doesn't have the same performance for the non-fused case. {{{ data CounterState = More | Last | End -- Requires x2 >= x1 {-# INLINE [0] efdtIntUpFB #-} -- See Note [Inline FB functions] in GHC.List efdtIntUpFB :: (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> r efdtIntUpFB c n x1 x2 y = -- Be careful about overflow! let !first_state | isTrue# (y <# x2) = if isTrue# (y <# x1) then End else Last | otherwise = More -- Common case: x1 <= x2 <= y !delta = x2 -# x1 -- >= 0 !y' = y -# delta -- x1 <= y' <= y; hence y' is representable next_state End _ = End next_state Last _ = End next_state More x | isTrue# (x ># y') = Last | otherwise = More -- Invariant: x <= y -- Note that: z <= y' => z + delta won't overflow -- so we are guaranteed not to overflow if/when we recurse emit End _ = n emit st x | let x' = x +# delta = I# x `c` emit (next_state st x') x' in emit first_state x1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 21:26:57 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 21:26:57 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.af93df38f5e62404b767ff1331fba4ac@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): @nomeata: Ah, right before my nose. Very reassuring. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 22:32:02 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 22:32:02 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.b8e99532feb546a1a8be221cdbe9422f@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): How about this (untested), which seems a lot simpler {{{ efdtIntUpFB :: (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> r efdtIntUpFB c n x1 x2 y -- Be careful about overflow! | isTrue# (y <# x1) = n | otherwise = go_up x1 -- Common case: x1 <= y where !delta = x2 -# x1 -- >= 0 !y' = y -# delta -- x1 <= y' <= y; hence y' is representable -- Invariant: x <= y -- Note that: x <= y' => x + delta won't overflow -- so we are guaranteed not to overflow if/when we recurse go_up x = I# x `c` if isTrue# (x ># y') then n else go_up (x +# delta) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 22:47:13 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 22:47:13 -0000 Subject: [GHC] #14737: Improve performance of Simplify.simplCast In-Reply-To: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> References: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> Message-ID: <062.db4d9012326d7549ea2b1dde5712ac41@haskell.org> #14737: Improve performance of Simplify.simplCast -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11735 #14683 | Differential Rev(s): Phab:D4385 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, use that defn of `isReflexiveCo`; and then delete `isReflexiveCo_maybe` because it is not otherwise called. However, that may still leave `simplCast` at the top... does it? If it was taking 78% of 20sec before, that's 16 sec. So reducing that to near-zero (which it should be) would take use to 5s, not 12s. What happens if you leave out the call to `isReflexiveCo` altogether? It'll get done in the next round anyway, by `optCoercion`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Mar 29 22:48:48 2018 From: ghc-devs at haskell.org (GHC) Date: Thu, 29 Mar 2018 22:48:48 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.8183c11161236fb950f90f03a59f3475@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): I just ran some quick `quickCheck $ withMaxSuccess 100000 $ \i j k -> take 1000 [i,j..k] == take 1000 (efdtInt (unI# i) (unI# j) (unI# k))` tests and both versions pass. Given that simonpj's is much more to the point, let's run with that one! Although the duplicate `n` has potential to cause pain... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 00:19:30 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 00:19:30 -0000 Subject: [GHC] #14984: Regression: 8.4.1 says "Could not deduce" when before 8.4 it could In-Reply-To: <044.36004bdef7af2fbfc785798bfc40dba3@haskell.org> References: <044.36004bdef7af2fbfc785798bfc40dba3@haskell.org> Message-ID: <059.5ff96ae0536d590c6e2a27a9cc34a232@haskell.org> #14984: Regression: 8.4.1 says "Could not deduce" when before 8.4 it could -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.4.1 checker) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by erikd): * status: new => closed * resolution: => invalid Comment: Sorry, this was my mistake. This was caused by a change in `QuickCheck` between `2.9.*` and `2.10.0` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 07:52:45 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 07:52:45 -0000 Subject: [GHC] #14684: combineIdenticalAlts is only partially implemented In-Reply-To: <049.66bb6a9ebb8aeb6bc16c5fd3f9c006db@haskell.org> References: <049.66bb6a9ebb8aeb6bc16c5fd3f9c006db@haskell.org> Message-ID: <064.608e1586fdf07efa2e41148edbfdfc5a@haskell.org> #14684: combineIdenticalAlts is only partially implemented -------------------------------------+------------------------------------- Reporter: mpickering | Owner: sjakobi Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4542 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Should combineAlts get the same optimization as combineIdenticalAlts? Might combineAlts even be the better place to apply the optimization? Actually I think you are right -- CSE probably would be a better place. And then (because it doesn't happen all the time), you can probably do this stuff regardless of -O2. (Having a flag might still be good just so you can switch it on and off at will.) I added some comments to Phab which will be useful either way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 08:25:05 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 08:25:05 -0000 Subject: [GHC] #14986: ghc panics when compiling stage 2 Message-ID: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> #14986: ghc panics when compiling stage 2 -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Keywords: | Operating System: Windows Architecture: x86_64 | Type of failure: Building GHC (amd64) | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I'm compiling a recent commit (0017a7b618353bf984d701f6d8ee2810a425e5b3), yet ghc always panics when ghc-stage1 is compiling ghc-prim. The error is as follows: {{{ "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/CString.hs -o libraries/ghc-prim/dist- install/build/GHC/CString.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- install/build/GHC/IntWord64.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Base.hs-boot -o libraries/base/dist- install/build/GHC/Base.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Real.hs-boot -o libraries/base/dist- install/build/GHC/Real.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/IO.hs-boot -o libraries/base/dist- install/build/GHC/IO.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./Data/Semigroup/Internal.hs-boot -o libraries/base/dist- install/build/Data/Semigroup/Internal.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Tuple.hs -o libraries/ghc-prim/dist- install/build/GHC/Tuple.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Magic.hs -o libraries/ghc-prim/dist- install/build/GHC/Magic.o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/CString.hs -o libraries/ghc-prim/dist- install/build/GHC/CString.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- install/build/GHC/IntWord64.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Base.hs-boot -o libraries/base/dist- install/build/GHC/Base.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Real.hs-boot -o libraries/base/dist- install/build/GHC/Real.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/IO.hs-boot -o libraries/base/dist- install/build/GHC/IO.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./Data/Semigroup/Internal.hs-boot -o libraries/base/dist- install/build/Data/Semigroup/Internal.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Tuple.hs -o libraries/ghc-prim/dist-install/build/GHC/Tuple.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Magic.hs -o libraries/ghc-prim/dist-install/build/GHC/Magic.p_o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Classes.hs -o libraries/ghc-prim/dist- install/build/GHC/Classes.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Debug.hs -o libraries/ghc-prim/dist- install/build/GHC/Debug.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/dist-install/build/GHC/PrimopWrappers.hs -o libraries/ghc-prim/dist-install/build/GHC/PrimopWrappers.o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Classes.hs -o libraries/ghc-prim/dist- install/build/GHC/Classes.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Debug.hs -o libraries/ghc-prim/dist-install/build/GHC/Debug.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim /dist-install/build/GHC/PrimopWrappers.hs -o libraries/ghc-prim/dist- install/build/GHC/PrimopWrappers.p_o ghc-stage1.exe: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-mingw32): Each block should be reachable from only one ProcPoint Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug make[1]: *** [libraries/ghc-prim/ghc.mk:4: libraries/ghc-prim/dist- install/build/GHC/Classes.o] Error 1 make[1]: *** Waiting for unfinished jobs.... ghc-stage1.exe: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-mingw32): Each block should be reachable from only one ProcPoint Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug make[1]: *** [libraries/ghc-prim/ghc.mk:4: libraries/ghc-prim/dist- install/build/GHC/Classes.p_o] Error 1 make: *** [Makefile:127: all] Error 2 }}} I'm using the following build.mk for those builds here: {{{ GhcEnableTablesNextToCode = NO INTEGER_LIBRARY = integer-simple SRC_HC_OPTS = -O -H64m GhcStage1HcOpts = -O GhcStage2HcOpts = -O2 GhcLibHcOpts = -O2 BUILD_PROF_LIBS = YES SplitObjs = YES SplitSections = NO BUILD_SPHINX_HTML = YES BUILD_SPHINX_PDF = NO HADDOCK_DOCS = YES EXTRA_HADDOCK_OPTS += --quickjump --hyperlinked-source }}} Still working to figure out a minimal combination of the build flags to trigger a similar error. Meanwhile, has anyone seen a similar error for a different commit/platform/build config? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 09:21:07 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 09:21:07 -0000 Subject: [GHC] #14737: Improve performance of Simplify.simplCast In-Reply-To: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> References: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> Message-ID: <062.a86363d9a28805abb1d4ae74354b6501@haskell.org> #14737: Improve performance of Simplify.simplCast -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11735 #14683 | Differential Rev(s): Phab:D4385 Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): > However, that may still leave simplCast at the top... does it? If it was taking 78% of 20sec before, that's 16 sec. So reducing that to near-zero (which it should be) would take use to 5s, not 12s. Correct; `isReflexiveCo` accounted for about half the execution time spent in `simplCast`. With this change, `isReflexiveCo` drops to 1.1% of overall execution time, and `simplCast` to about 61%. So this is a big improvement, but we're not done yet. The remaining main culprit is `pushCoTyArg`. > What happens if you leave out the call to isReflexiveCo altogether? It'll get done in the next round anyway, by optCoercion. I'll try that, but considering that `isReflexiveCo` is no longer critical, I don't expect it to make much of a difference. For reference, here's the current profiler output: {{{ Wed Mar 28 20:44 2018 Time and Allocation Profiling Report (Final) ghc-stage2 +RTS -p -RTS -B/home/tobias/well- typed/devel/ghc/T14737/inplace/lib ./cases/Grammar.hs -o ./a -fforce- recomp total time = 12.35 secs (12354 ticks @ 1000 us, 1 processor) total alloc = 14,410,284,936 bytes (excludes profiling overheads) COST CENTRE MODULE SRC %time %alloc pushCoTyArg Simplify compiler/simplCore/Simplify.hs:1229:63-83 54.6 55.5 tc_rn_src_decls TcRnDriver compiler/typecheck/TcRnDriver.hs:(494,4)-(556,7) 13.1 14.3 CoreTidy HscMain compiler/main/HscMain.hs:1253:27-67 4.8 3.9 SimplTopBinds SimplCore compiler/simplCore/SimplCore.hs:770:39-74 4.2 3.2 coercionKind Coercion compiler/types/Coercion.hs:1701:3-7 2.8 6.0 simplCast Simplify compiler/simplCore/Simplify.hs:(1213,5)-(1215,37) 2.5 2.5 zonkTopDecls TcRnDriver compiler/typecheck/TcRnDriver.hs:(445,16)-(446,43) 2.3 2.2 deSugar HscMain compiler/main/HscMain.hs:511:7-44 1.5 1.3 isReflexiveCo Simplify compiler/simplCore/Simplify.hs:1260:40-55 1.1 1.0 Parser HscMain compiler/main/HscMain.hs:(316,5)-(384,20) 1.1 1.6 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 10:03:13 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 10:03:13 -0000 Subject: [GHC] #14987: Memory usage exploding for complex pattern matching Message-ID: <047.01959a6ab9a68448aba5b4dbc4570db8@haskell.org> #14987: Memory usage exploding for complex pattern matching -------------------------------------+------------------------------------- Reporter: vmiraldo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It seems like complex pattern matching is consuming a prohibitive amount of memory. From a discussion in ghc-devs, [https://mail.haskell.org/pipermail/ghc-devs/2018-March/015538.html], the exhaustiveness checker could be the culprit. We have tried with 7.10.3, 8.0.2, 8.4.1 and ghc-HEAD. They show similar results. The "-fmax-pmchecker-iterations=0" option seems to help slightly. Bigger cases will run out of memory even with the option enabled. I'm attaching a "minimal" example to help diagnosing. The majority of the code has been generated by Template Haskell. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 10:04:27 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 10:04:27 -0000 Subject: [GHC] #14987: Memory usage exploding for complex pattern matching In-Reply-To: <047.01959a6ab9a68448aba5b4dbc4570db8@haskell.org> References: <047.01959a6ab9a68448aba5b4dbc4570db8@haskell.org> Message-ID: <062.82892de47fe371da24ab273f05a8a894@haskell.org> #14987: Memory usage exploding for complex pattern matching -------------------------------------+------------------------------------- Reporter: vmiraldo | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vmiraldo): * Attachment "Minimal.hs" added. Self-contained repro for the bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 10:34:08 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 10:34:08 -0000 Subject: [GHC] #14986: ghc panics when compiling stage 2 In-Reply-To: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> References: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> Message-ID: <064.de981f9f078870a64c79b29f6b45617a@haskell.org> #14986: ghc panics when compiling stage 2 -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by terrorjack): I rebuilt using quick.mk, only preserving GhcEnableTablesNextToCode=NO and INTEGER_LIBRARY=integer-simple, the problem remains. The last commit known to build without a hassle is efd70cfb4b0b9932a880ab417d75eaf95da3d5e6. I'm chasing the first commit to break. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 12:47:17 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 12:47:17 -0000 Subject: [GHC] #14986: CmmCommonBlockElim conflicts with GhcEnableTablesNextToCode=NO In-Reply-To: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> References: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> Message-ID: <064.ee744a17e58af1e49cc79781ec02700f@haskell.org> #14986: CmmCommonBlockElim conflicts with GhcEnableTablesNextToCode=NO -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) Comment: FWIW, I ran a `./validate --slow` against master yesterday and many tests are failing in the `optllvm` way (specifically) with this same `panic`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 13:16:44 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 13:16:44 -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.3cf7a648531d9c0abe0aed12dd024667@haskell.org> #12442: Pure unifier usually doesn't need to unify kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T12442 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2433 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) Comment: I ran `./validate --slow` yesterday and `T12442` is failing in all test ways: {{{ /tmp/ghctest-kabnnx7e/test spaces/./dependent/should_compile/T12442.run T12442 [exit code non-0] (normal) /tmp/ghctest-kabnnx7e/test spaces/./dependent/should_compile/T12442.run T12442 [exit code non-0] (hpc) /tmp/ghctest-kabnnx7e/test spaces/./dependent/should_compile/T12442.run T12442 [exit code non-0] (optasm) /tmp/ghctest-kabnnx7e/test spaces/./dependent/should_compile/T12442.run T12442 [exit code non-0] (profasm) /tmp/ghctest-kabnnx7e/test spaces/./dependent/should_compile/T12442.run T12442 [exit code non-0] (optllvm) }}} Always with the same panic: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcTyClsDecls.hs, line 1531 }}} This sounds like an actual problem, but if you don't mind I'll leave it to you Richard & Simon to decide/figure out whether this ticket should be re- opened or whether this is a new, unrelated problem that deserves its own ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 13:29:41 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 13:29:41 -0000 Subject: [GHC] #12176: Failure of bidirectional type inference at the kind level In-Reply-To: <047.cd9ca4aa1f9d2a50e3f65696b41c1e1c@haskell.org> References: <047.cd9ca4aa1f9d2a50e3f65696b41c1e1c@haskell.org> Message-ID: <062.c2f3c91b49e449ed2364bb45bf74625f@haskell.org> #12176: Failure of bidirectional type inference at the kind level -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T12176 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * cc: alpmestan (added) Comment: I recently ran `./validate --slow` and saw the test for this ticket (`T12176`) fail in all 5 ways that it supports. Just like with the test for #12442, it fails with: {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcTyClsDecls.hs, line 1531 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 14:15:33 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 14:15:33 -0000 Subject: [GHC] #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. In-Reply-To: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> References: <054.a86ea93f3c5474927cb76817167bc36f@haskell.org> Message-ID: <069.f6ad25d122fd9fe43cd296a966aa4730@haskell.org> #14927: Hyperbolic area sine is unstable for (even moderately) big negative arguments. -------------------------------------+------------------------------------- Reporter: leftaroundabout | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.2.1 Resolution: | Keywords: Floating | IEEE754 trigonometric Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by leftaroundabout): Fix available at [https://github.com/leftaroundabout/ghc/tree/testing /float-inverses]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 14:26:36 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 14:26:36 -0000 Subject: [GHC] #12176: Failure of bidirectional type inference at the kind level In-Reply-To: <047.cd9ca4aa1f9d2a50e3f65696b41c1e1c@haskell.org> References: <047.cd9ca4aa1f9d2a50e3f65696b41c1e1c@haskell.org> Message-ID: <062.9a885aad3463d88f6534f51a0c44b2f1@haskell.org> #12176: Failure of bidirectional type inference at the kind level -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T12176 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Nevermind, it seems like I somehow ended up not building with the patch from 4 days ago. This test passes from a fresh build with the tip of `master` from today. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 14:27:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 14:27:48 -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.d300decc835eceb0ec142c7de5d59117@haskell.org> #12442: Pure unifier usually doesn't need to unify kinds -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | dependent/should_compile/T12442 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2433 Wiki Page: | -------------------------------------+------------------------------------- Comment (by alpmestan): Nevermind, I somehow got things wrong, this test passes with a fresh master from today. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 16:44:57 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 16:44:57 -0000 Subject: [GHC] #14728: Is (GeneralizedNewtypeDeriving + associated type classes) completely bogus? In-Reply-To: <050.b01b3d3c472df373e991905eeea1c1f9@haskell.org> References: <050.b01b3d3c472df373e991905eeea1c1f9@haskell.org> Message-ID: <065.50ad72dcd94563663fe6af4490b2bce2@haskell.org> #14728: Is (GeneralizedNewtypeDeriving + associated type classes) completely bogus? -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.2.2 checker) | Keywords: deriving, Resolution: fixed | TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4402 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I completely take back what I said in comment:15 about this being unblocked—that couldn't be further from the truth! In fact, after talking with goldfire and kcsongor about this, we've come to the realization that all of the ideas in comment:3 are completely untenable at present. The issue is that we're trying to construct the type `(x |> g)`, where `x` is a type and `g` is a coercion. However, in order for this to kind-check, `g` must be nominally roled. This is never the case in GND, as we always use newtype axioms, which are by definition representationally roled! This pretty much makes this idea dead in the water, at least until we figure out a way to have representational casts in kinds (which is likely a ways away). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 18:27:04 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 18:27:04 -0000 Subject: [GHC] #14890: Make Linux slow validate green In-Reply-To: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> References: <046.a107a76cbb0183d36ada5ee5738b1b26@haskell.org> Message-ID: <061.de6d34d7f431248694cdaaf0d4f6d03f@haskell.org> #14890: Make Linux slow validate green -------------------------------------+------------------------------------- Reporter: bgamari | Owner: alpmestan Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.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): D4546 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alpmestan): * differential: => D4546 Comment: First batch of test expectation changes at [https://phabricator.haskell.org/D4546 D4546]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 19:42:36 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 19:42:36 -0000 Subject: [GHC] #7500: GHC: internal error: getMBlock: mmap: Operation not permitted In-Reply-To: <044.eabb9958fe5ab887b82f630f93f2c2f2@haskell.org> References: <044.eabb9958fe5ab887b82f630f93f2c2f2@haskell.org> Message-ID: <059.a6f2292697248b3f3a9d17fa058acc2f@haskell.org> #7500: GHC: internal error: getMBlock: mmap: Operation not permitted ----------------------------------+---------------------------------------- Reporter: guest | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.4.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+---------------------------------------- Comment (by mcandre): I get this low-level error message in FreeBSD / HardenedBSD. Could we update the BSD ports of GHC to improve this error message as well? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 20:22:53 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 20:22:53 -0000 Subject: [GHC] #14988: Memory strain while compiling HLint Message-ID: <046.841e8f99e82b8877c23858d1ca47b3db@haskell.org> #14988: Memory strain while compiling HLint -------------------------------------+------------------------------------- Reporter: mcandre | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: FreeBSD Architecture: x86_64 | Type of failure: Compile-time (amd64) | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I want to setup a build bot for generating Haskell binaries in an automated fashion, however even with 4 GB of RAM, cabal is unable to build HLint in HardenedBSD. Specifically, GHC is choking on mmap errors while compiling HLint's huge dependency tree. Can we somehow shrink the massive memory usage of GHC, so that common packages HLint can be built on medium-low build bots? Imagine GHC running on a RaspberryPi: You're gonna have a bad time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 20:32:48 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 20:32:48 -0000 Subject: [GHC] #14737: Improve performance of Simplify.simplCast In-Reply-To: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> References: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> Message-ID: <062.ee1132a038a20442b6a5afa9fefe60db@haskell.org> #14737: Improve performance of Simplify.simplCast -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11735 #14683 | Differential Rev(s): Phab:D4385 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Try getting rid of the first equation for `puchCoTyArg` {{{ pushCoTyArg co ty | tyL `eqType` tyR = Just (ty, mkRepReflCo (piResultTy tyR ty)) }}} This is another big pile of type-equalities, rather like calling `isReflexiveCo` at the wrong moment. Claim: if it happens that `tyL` = `tyR`, but we go ahead with all that `mkCoherenceLeftCo` stuff anyway, then the coercion optimiser will get rid of it later. '''Richard''': will it? But try that change anyway. NO WAY should `pushCoTyArg` take 54% of compile time! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 22:16:50 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 22:16:50 -0000 Subject: [GHC] #14737: Improve performance of Simplify.simplCast In-Reply-To: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> References: <047.69092b5e7fccc6314d7cb05c5e8b2174@haskell.org> Message-ID: <062.f248d0b2d67964739c7f31dab6367ffa@haskell.org> #14737: Improve performance of Simplify.simplCast -------------------------------------+------------------------------------- Reporter: tdammers | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #11735 #14683 | Differential Rev(s): Phab:D4385 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Yes, I think Simon's comment:10 is correct. Try removing that. Note that Phab:D4395 currently removes the `piResultTy` from that case, but it's quite possible that the `eqType` call is what's taking up the time. You might also try removing the similar clause from `pushCoValArg`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 03:52:20 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 03:52:20 -0000 Subject: [GHC] #14972: MacOS panic on TH In-Reply-To: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> References: <050.216fa0d0ad85b79e36c3fe0a299b4fca@haskell.org> Message-ID: <065.b743c95170c58e21f9692e6b6408ca36@haskell.org> #14972: MacOS panic on TH -------------------------------------+------------------------------------- Reporter: harpocrates | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by harpocrates): Another observation: if I `make install`, the installed GHC does not run into any of these problems. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 05:49:29 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 05:49:29 -0000 Subject: [GHC] #14822: -XQuantifiedConstraints: Turn term-level entailments (:-) into constraints (=>) In-Reply-To: <051.11128ae44d764b8f1b3394d8184f1010@haskell.org> References: <051.11128ae44d764b8f1b3394d8184f1010@haskell.org> Message-ID: <066.b69c003a1c4b9d3cb4d5c66256d0e165@haskell.org> #14822: -XQuantifiedConstraints: Turn term-level entailments (:-) into constraints (=>) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 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 don't make use of `Bool` being closed. I don't seek to discharge `forall b. C b` as you claim, rather `pi b. C b`. I found a way to emulate what I want with `unsafeCoerce`. Here is an example for the open kind `Type`: {{{#!hs {-# Language KindSignatures, GADTs, ConstraintKinds, QuantifiedConstraints, TypeOperators, MultiParamTypeClasses, FlexibleInstances, UndecidableInstances, AllowAmbiguousTypes, TypeApplications, ScopedTypeVariables, RankNTypes #-} import Data.Kind import Unsafe.Coerce -- constraints data Dict :: Constraint -> Type where Dict :: c => Dict c class (a => b) => Implies a b instance (a => b) => Implies a b type a |- b = Dict (a `Implies` b) -- Representation of two types: Int and Bool data S :: Type -> Type where SInt :: S Int SBool :: S Bool -- Can be passed explicitly class SI a where s :: S a instance SI Int where s = SInt instance SI Bool where s = SBool -- Can be eliminated like with an if-then-else sElim :: S a -> (Int ~ a => res) -> (Bool ~ a => res) -> res sElim SInt i _ = i sElim SBool _ b = b -- (SI a) entails (Str a) class Str a where str :: String instance Str Int where str = "INT" instance Str Bool where str = "BOOL" newtype Wrap a = Wrap a instance SI a => Str (Wrap a) where str = sElim (s @a) (str @a) (str @a) wit :: forall ty. SI ty |- Str ty wit = wrapElim Dict where wrapElim :: (SI ty |- Str (Wrap ty)) -> (SI ty |- Str ty) wrapElim = unsafeCoerce -- >> siStr @Int -- "INT!" -- >> siStr @Bool -- "BOOL!" siStr :: forall ty. SI ty => String siStr = go wit where go :: SI ty => (SI ty |- Str ty) -> String go Dict = str @ty ++ "!" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 05:59:45 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 05:59:45 -0000 Subject: [GHC] #14982: LLVM default -mcpu setting inhibits customization In-Reply-To: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> References: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> Message-ID: <059.48dfa01f8fb138f97f1089206bdd5af9@haskell.org> #14982: LLVM default -mcpu setting inhibits customization -------------------------------------+------------------------------------- Reporter: tommd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.2 Component: Compiler (LLVM) | Version: 8.4.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 angerman): The code in question pulls the `mcpu` (and `mattr`) from the new `llvm- targets` file. As such a hack around it right now would be to just modify the `llvm-targets` file. This however is a rather ugly hack as it would apply the logic globally. I guess we could just, as suggested, trop the `mcpu` from `llc` if a custom one is given. I'm not sure how to handle `mattr` though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 08:06:49 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 08:06:49 -0000 Subject: [GHC] #14822: -XQuantifiedConstraints: Turn term-level entailments (:-) into constraints (=>) In-Reply-To: <051.11128ae44d764b8f1b3394d8184f1010@haskell.org> References: <051.11128ae44d764b8f1b3394d8184f1010@haskell.org> Message-ID: <066.658f2adba235e2518d052954fdee0140@haskell.org> #14822: -XQuantifiedConstraints: Turn term-level entailments (:-) into constraints (=>) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints, wipT2893 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): Using #14292 this can be `coerce`d rather than `unsafeCoerce`d if only we turn on `-XIncoherentInstances` and mark some parameters `representational` {{{#!hs type role Implies nominal representational type role Str representational }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 08:48:02 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 08:48:02 -0000 Subject: [GHC] #14982: LLVM default -mcpu setting inhibits customization In-Reply-To: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> References: <044.53df70951b1c182c6fcc3c10dbfa5883@haskell.org> Message-ID: <059.c71872de6910a2bc0da1431fe0a4bff2@haskell.org> #14982: LLVM default -mcpu setting inhibits customization -------------------------------------+------------------------------------- Reporter: tommd | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.4.2 Component: Compiler (LLVM) | Version: 8.4.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): D4548 Wiki Page: | -------------------------------------+------------------------------------- Changes (by angerman): * status: new => patch * differential: => D4548 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 09:10:56 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 09:10:56 -0000 Subject: [GHC] #8763: forM_ [1..N] does not get fused (10 times slower than go function) In-Reply-To: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> References: <042.6416bb310965de24a032dfcecd66fba0@haskell.org> Message-ID: <057.1c94dfd5339a683d9e7b0f0c953112e6@haskell.org> #8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | 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: #7206 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Nofib suggests that this regresses allocations in `integer` by 6.0% and counted instructions by 0.1%. I had a look at the simplified Core and it seems that it's entirely due to the new definition, although I'm not sure where exactly this allocates more. Maybe it's due to an increase in closure size of `go_up` because of `single`?. Here's the [https://www.diffchecker.com/FrxIUoRQ Core diff] and the [https://github.com/sgraf812/ghc/blob/cf4c1a52916fbf1b6acadd9a2477672b876a860e/libraries/base/GHC/Enum.hs#L540 new definition of efdtIntUpFB for reference]. It seems that `c` is still not inlined, even with the new definition. I assume that's because there are multiple occurences of `c` which were probably duplicated before the inliner had a chance to inline the argument `c`. It better had introduced a join point before. Maybe loopification helps here? Indeed [https://ghc.haskell.org/trac/ghc/ticket/14068#comment:47 #14068] suggests that something beneficial happens, maybe more so with this patch. Or we could introduce some kind of annotation mechanism to tell GHC to be careful not to duplicate occurences of certain parameters that occur once (`f {-# HUGE #-} c n = ...`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 09:12:04 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 09:12:04 -0000 Subject: [GHC] #10822: GHC inconsistently handles \\?\ for long paths on Windows In-Reply-To: <047.7e6bb9965cce015f93541e4a1a931ae5@haskell.org> References: <047.7e6bb9965cce015f93541e4a1a931ae5@haskell.org> Message-ID: <062.24314915f9cedd0b22784d5a10121425@haskell.org> #10822: GHC inconsistently handles \\?\ for long paths on Windows ---------------------------------+---------------------------------------- Reporter: snoyberg | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4416 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Tamar Christina ): In [changeset:"4de585a5c1ac3edc2914cebcac1753b514051a89/ghc" 4de585a5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4de585a5c1ac3edc2914cebcac1753b514051a89" Remove MAX_PATH restrictions from RTS, I/O manager and various utilities Summary: This shims out fopen and sopen so that they use modern APIs under the hood along with namespaced paths. This lifts the MAX_PATH restrictions from Haskell programs and makes the new limit ~32k. There are only some slight caveats that have been documented. Some utilities have not been upgraded such as lndir, since all these things are different cabal packages I have been forced to copy the source in different places which is less than ideal. But it's the only way to keep sdist working. Test Plan: ./validate Reviewers: hvr, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #10822 Differential Revision: https://phabricator.haskell.org/D4416 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 09:15:17 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 09:15:17 -0000 Subject: [GHC] #10822: GHC inconsistently handles \\?\ for long paths on Windows In-Reply-To: <047.7e6bb9965cce015f93541e4a1a931ae5@haskell.org> References: <047.7e6bb9965cce015f93541e4a1a931ae5@haskell.org> Message-ID: <062.8c75b8163bc160d6571a0052c044eb2c@haskell.org> #10822: GHC inconsistently handles \\?\ for long paths on Windows ---------------------------------+---------------------------------------- Reporter: snoyberg | Owner: (none) Type: bug | Status: upstream Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4416 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by Phyx-): * status: patch => upstream Comment: underlying toolchain needs fixing now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 09:30:03 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 09:30:03 -0000 Subject: [GHC] #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` Message-ID: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` -------------------------------------+------------------------------------- Reporter: sgraf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Keywords: | Operating System: Windows Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash or panic Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The attached file is from reduced from NoFib's `spectral/integer`. When I compile this with `-O2 -fllvm`, I get the following panic on HEAD: {{{ ghc-stage2.exe: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-mingw32): Each block should be reachable from only one ProcPoint }}} FWIW, I don't have the LLVM toolchain installed, but this is still in GHC's backend. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 09:34:02 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 09:34:02 -0000 Subject: [GHC] #10927: IndexError: pop from empty list In-Reply-To: <045.caca6922033a1cb1a5f73e4552615a1e@haskell.org> References: <045.caca6922033a1cb1a5f73e4552615a1e@haskell.org> Message-ID: <060.7efa821409e6149ffdae0a242f011779@haskell.org> #10927: IndexError: pop from empty list -------------------------------------+------------------------------------- Reporter: schwab | Owner: hvr Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Trac & Git | 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: | -------------------------------------+------------------------------------- Comment (by sgraf): This happens again for me as of recently. It used to work a few days earlier. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 09:36:41 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 09:36:41 -0000 Subject: [GHC] #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` In-Reply-To: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> References: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> Message-ID: <059.b098c58f937c195cdcc8ef9dba0e0b3b@haskell.org> #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` -------------------------------------+------------------------------------- Reporter: sgraf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * Attachment "Main.hs" added. Reproduction -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 14:19:53 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 14:19:53 -0000 Subject: [GHC] #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` In-Reply-To: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> References: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> Message-ID: <059.1f7221b1771e4ece5cd3539132f43333@haskell.org> #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` -------------------------------------+------------------------------------- Reporter: sgraf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): I blame common block elimination. This is the output post sink assignments: {{{ ... c2m1: // global call (I64[R1])(R1) returns to c2m0, args: 8, res: 8, upd: 8; c2m0: // global switch [1 .. 2] (R1 & 7) { case 1 : goto u2mH; case 2 : goto c2m5; } ... c2mi: // global call (I64[R1])(R1) returns to c2mg, args: 8, res: 8, upd: 8; c2mg: // global switch [1 .. 2] (R1 & 7) { case 1 : goto u2mI; case 2 : goto c2mt; } ... c2mu: // global call (I64[R1])(R1) returns to c2mr, args: 8, res: 8, upd: 8; c2mr: // global switch [1 .. 2] (R1 & 7) { case 1 : goto c2mA; case 2 : goto u2mJ; } u2mJ: // global Sp = Sp + 8; goto c2mE; ... u2mI: // global Sp = Sp + 8; goto c2mE; u2mH: // global Sp = Sp + 8; goto c2mE; c2mE: // global call Main.$wfail_info() args: 8, res: 0, upd: 8; }}} And this is post common block elimination 2: {{{ ... c2m1: // global call (I64[R1])(R1) returns to c2m0, args: 8, res: 8, upd: 8; c2m0: // global switch [1 .. 2] (R1 & 7) { case 1 : goto u2mJ; case 2 : goto c2m5; } ... c2mi: // global call (I64[R1])(R1) returns to c2mg, args: 8, res: 8, upd: 8; c2mg: // global switch [1 .. 2] (R1 & 7) { case 1 : goto u2mJ; case 2 : goto c2mt; } ... c2mu: // global call (I64[R1])(R1) returns to c2mr, args: 8, res: 8, upd: 8; c2mr: // global switch [1 .. 2] (R1 & 7) { case 1 : goto c2mA; case 2 : goto u2mJ; } ... u2mJ: // global Sp = Sp + 8; goto c2mE; c2mE: // global call Main.$wfail_info() args: 8, res: 0, upd: 8; }}} The non-proc-point blocks u2m* have been merged into a single block u2MJ, which should have become a proc point in turn, because c2m{0,g,r} are multiple proc points (they are continuations) the block now "belongs" to. This is essentially diamond control flow introduced by the merging of blocks. {{{ c2m0 c2mg c2mr | | | u2mJ u2mI u2mH \ | / c2mE ===> c2m0 c2mg c2mr \ | / u2mJ | c2mE }}} In SSA world, this could entail inserting new Phi functions into the merged block, which corresponds to our notion of proc points, if I understand right. I find the parallels to SSA form very helpful. To stay in that analogy, c2mE was a proc point before common block elimination, but is no longer, because the dominance frontier of defs visible in c2m* changed from c2mE to u2mJ. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 14:21:28 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 14:21:28 -0000 Subject: [GHC] #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` In-Reply-To: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> References: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> Message-ID: <059.20c1929a69900de5b646c93b2fd20871@haskell.org> #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` -------------------------------------+------------------------------------- Reporter: sgraf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgraf): * Attachment "Main.2.hs" added. Reproduction with only 2 branches instead of 3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 15:01:50 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 15:01:50 -0000 Subject: [GHC] #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` In-Reply-To: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> References: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> Message-ID: <059.9483b97054881f9957a92d8c330eeec9@haskell.org> #14989: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm` -------------------------------------+------------------------------------- Reporter: sgraf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): This is probably the culprit: https://github.com/ghc/ghc/blob/ca535f95a742d885c4082c9dc296c151fb3c1e12/compiler/cmm/CmmPipeline.hs#L122-L127 `cbe_fix` doesn't quite cut it because of the change in dominance frontiers outlined above. The most efficient solution would be to only consider the merged blocks and their successors. I just realized that the second CBE pass is new and also that stack layout happens before. Doesn't a change in proc points affect stack layout? I'd do the fix myself (inserting a proper call to `minimalProcPointSet`), but I feel like I don't understand enough of the interactions and where to conjure `new_proc_points` from after that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 15:03:22 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 15:03:22 -0000 Subject: [GHC] #14989: CBE pass 2 invalidates proc points (was: "Each block should be reachable from only one ProcPoint" compiling `integer` with `-fllvm`) In-Reply-To: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> References: <044.fb8bf40a724d06cac113a1a4bb72ec8e@haskell.org> Message-ID: <059.10c3a5ca0dfe731724cb819cebecbc77@haskell.org> #14989: CBE pass 2 invalidates proc points -------------------------------------+------------------------------------- Reporter: sgraf | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash or panic | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 15:04:19 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 15:04:19 -0000 Subject: [GHC] #14990: "Valid refinement suggestions" have the wrong types Message-ID: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> #14990: "Valid refinement suggestions" have the wrong types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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've recently discovered that the "valid suggestions" feature for typed holes is quite powerful. For example, if I say {{{#!hs module Bug where import Prelude (Integer, Num(..)) x :: Integer x = _ 5 }}} and compile it with {{{ > ghc Bug.hs -frefinement-level-substitutions=2 }}} I get {{{ Bug.hs:6:5: error: • Found hole: _ :: Integer -> Integer • In the expression: _ In the expression: _ 5 In an equation for ‘x’: x = _ 5 • Relevant bindings include x :: Integer (bound at Bug.hs:6:1) Valid substitutions include negate :: forall a. Num a => a -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) abs :: forall a. Num a => a -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) signum :: forall a. Num a => a -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) fromInteger :: forall a. Num a => Integer -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) Valid refinement substitutions include (-) _ :: forall a. Num a => a -> a -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) (*) _ :: forall a. Num a => a -> a -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) (+) _ :: forall a. Num a => a -> a -> a (imported from ‘Prelude’ at Bug.hs:3:26-32 (and originally defined in ‘GHC.Num’)) | 6 | x = _ 5 | ^ }}} Note the ''refinement suggestions'', that look not only for single identifiers that fill the hole but for function calls that could, as well. However, the formatting of the refinement suggestions is incorrect, stating, for example, that `(+) _ :: forall a. Num a => a -> a -> a`. This is plain wrong. We ''could'' say `(+) _ :: a0 -> a0` where `Num a0`, and that would be right, but even better would be something like {{{ (+) x1 :: Integer -> Integer where x1 :: Integer }}} Now, I know that the first parameter to `(+)` must be an integer. In a more polymorphic situation, it could be {{{ (+) x1 :: a0 -> a0 where x1 :: a0 (Num a0) holds }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 15:17:33 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 15:17:33 -0000 Subject: [GHC] #14111: strange error when using data families with levity polymorphism and unboxed sums and data families In-Reply-To: <045.61bc63eee0a790503467c9479892f97e@haskell.org> References: <045.61bc63eee0a790503467c9479892f97e@haskell.org> Message-ID: <060.c43181a97671b8d007310dfc7a8451b9@haskell.org> #14111: strange error when using data families with levity polymorphism and unboxed sums and data families -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14457 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Last night, I tried working on this (in a sleep-deprived haze). I actually managed to come up with something that makes the original program compile: {{{#!diff diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 39697d6..842050f 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -36,7 +36,7 @@ import TcClassDcl import {-# SOURCE #-} TcInstDcls( tcInstDecls1 ) import TcDeriv (DerivInfo) import TcEvidence ( tcCoercionKind, isEmptyTcEvBinds ) -import TcUnify ( checkConstraints ) +import TcUnify ( checkConstraints, unifyType ) import TcHsType import TcMType import TysWiredIn ( unitTy ) @@ -1801,6 +1801,9 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_tmpl do { ctxt <- tcHsMbContext cxt ; btys <- tcConArgs hs_args ; res_ty' <- tcHsLiftedType res_ty + ; (meta_subst, _meta_tvs) <- newMetaTyVars $ binderVars tmpl_bndrs + ; let head_shape_with_metas = substTy meta_subst res_tmpl + ; _ <- unifyType Nothing res_ty' head_shape_with_metas ; field_lbls <- lookupConstructorFields name ; let (arg_tys, stricts) = unzip btys bound_vars = allBoundVariabless ctxt `unionVarSet` }}} This is nowhere near correct, though, since it causes other programs, such as [http://git.haskell.org/ghc.git/blob/ca535f95a742d885c4082c9dc296c151fb3c1e12:/testsuite/tests/ado/T13242a.hs T13242a], to infinitely loop when compiling. What's worse, I don't understand why. Help? Disclaimer: I have no idea what I'm doing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 15:37:45 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 15:37:45 -0000 Subject: [GHC] #14990: "Valid refinement suggestions" have the wrong types In-Reply-To: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> References: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> Message-ID: <062.9934e0c3ca419e095f46b0981c7bd639@haskell.org> #14990: "Valid refinement suggestions" have the wrong types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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: Tritlo (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 16:06:55 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 16:06:55 -0000 Subject: [GHC] #14111: strange error when using data families with levity polymorphism and unboxed sums and data families In-Reply-To: <045.61bc63eee0a790503467c9479892f97e@haskell.org> References: <045.61bc63eee0a790503467c9479892f97e@haskell.org> Message-ID: <060.cdb8e0db8a5830d82ef0f8a615d5b387@haskell.org> #14111: strange error when using data families with levity polymorphism and unboxed sums and data families -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14457 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): That code looks to me to be in the `ConDeclH98` clause, but Haskell98 constructors are not in play here. That said, these lines might just do the trick in the equivalent place in the `ConDeclGADT` clause. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 16:10:05 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 16:10:05 -0000 Subject: [GHC] #14111: strange error when using data families with levity polymorphism and unboxed sums and data families In-Reply-To: <045.61bc63eee0a790503467c9479892f97e@haskell.org> References: <045.61bc63eee0a790503467c9479892f97e@haskell.org> Message-ID: <060.878c66515136391f1bc5c1ea82ed5019@haskell.org> #14111: strange error when using data families with levity polymorphism and unboxed sums and data families -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14457 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This is in the `ConDeclGADT` clause. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 16:32:56 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 16:32:56 -0000 Subject: [GHC] #14111: strange error when using data families with levity polymorphism and unboxed sums and data families In-Reply-To: <045.61bc63eee0a790503467c9479892f97e@haskell.org> References: <045.61bc63eee0a790503467c9479892f97e@haskell.org> Message-ID: <060.02dd5ab278eb06bdf020c4c28ff36006@haskell.org> #14111: strange error when using data families with levity polymorphism and unboxed sums and data families -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #14457 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Bizarre. My line numbers from HEAD match exactly yours -- but in the `ConDeclH98` clause. And I'm stymied about the infinite loop on T13242a. Oh, wait. Maybe I'm not. Here is the problem case: {{{#!hs data T where A :: forall a. Eq a => a -> T }}} The problem is that `T` is knot-tied, because we're in the act of building it. So we can't then go and unify it. Instead, you should do the same basic thing as you're doing above, but to the ''arguments'' of the tycon, not the whole tyconapp itself. That is, use `tcSplitTyConApp` on the `res_tmpl` and the `res_ty'` and then unify the respective arguments. (You might have to explicitly deal with the possibility that the lists are of different length. I ''think'' lists of different lengths are definitely errors.) Upon further thought, this "unify the args" approach solves this particular case, but it won't solve all cases, because it's possible to mention knot-tied types in the arguments to a GADT result type. I don't know a way out, then, other than to wait until #13737 gets rid of the whole knot-tying business. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 16:44:41 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 16:44:41 -0000 Subject: [GHC] #14111: strange error when using data families with levity polymorphism and unboxed sums and data families In-Reply-To: <045.61bc63eee0a790503467c9479892f97e@haskell.org> References: <045.61bc63eee0a790503467c9479892f97e@haskell.org> Message-ID: <060.236ea98681bc6782c9f18dc173ffd11c@haskell.org> #14111: strange error when using data families with levity polymorphism and unboxed sums and data families -------------------------------------+------------------------------------- Reporter: carter | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 13737 | Blocking: Related Tickets: #14457 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * blockedby: => 13737 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 16:50:12 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 16:50:12 -0000 Subject: [GHC] #14990: "Valid refinement suggestions" have the wrong types In-Reply-To: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> References: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> Message-ID: <062.df33d4da3fca99e2b2d811b5f34a72c8@haskell.org> #14990: "Valid refinement suggestions" have the wrong types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 Sat Mar 31 19:44:58 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 19:44:58 -0000 Subject: [GHC] #14734: QuantifiedConstraints conflated with impredicative polymorphism? In-Reply-To: <051.b13ce9a287df15f46f4472a3cecc22de@haskell.org> References: <051.b13ce9a287df15f46f4472a3cecc22de@haskell.org> Message-ID: <066.8b85f6d715af77a3971a688d78ae1c7e@haskell.org> #14734: QuantifiedConstraints conflated with impredicative polymorphism? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.5 Resolution: invalid | Keywords: | QuantifiedConstraints wipT2893 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): Btw, should the following work? {{{#!hs GHCi, version 8.5.20180128: http://www.haskell.org/ghc/ :? for help Prelude> :set -XGADTs -XQuantifiedConstraints -XConstraintKinds Prelude> data Imp a b where Imp :: (a => b) => Imp a b Prelude> :kind forall a b. Imp a (b => a) forall a b. Imp a (b => a) :: * Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 22:06:40 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 22:06:40 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.08b592816725ee3d4c37de2d11669ac2@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): It took me quite a while to find out what was going on here. I started with a file containing only {{{ test :: IO Bool test = return True }}} Then load into GHCi, with `-fdefer-type-errors` {{{ ghc --interactive -fdefer-type-errors Foo.hs }}} Now just evaluate `test`. Here's what I see from `-ddump-tc -ddump-ds` with a little extra debug tracing, when evaluating `test` at the GHCi prompt: {{{ Typechecked expr do it_a1PP <- {>>=: GHC.Base.bindIO @ Bool @ [()]{let {EvBinds{[W] $dShow_a1Qg = GHC.Show.$fShowBool}} <>, <>} {<> |> _R} fail: "noSyntaxExpr"{}{<>}} /\(@ a_a1Q5). let {EvBinds{[W] $dGHCiSandboxIO_a1Q7 = GHC.GHCi.$fGHCiSandboxIOIO}} GHC.GHCi.ghciStepIO @ IO $dGHCiSandboxIO_a1Q7 @ a_a1Q5 :: ic_tythings: ic_insts: ic_rn_gbl_env (LocalDef) [Foo.test defined at Foo.hs:11:1] newTcEvBinds unique = a1Ql checkSatisfiability { {} checkSatisfiability } {} unflattenGivens [] ds BindStmt /\(@ a_a1Q5). let {EvBinds{[W] $dGHCiSandboxIO_a1Q7 = $fGHCiSandboxIOIO}} ghciStepIO @ IO $dGHCiSandboxIO_a1Q7 @ a_a1Q5 :: forall a_a1PO. IO a_a1PO -> IO a_a1PO @ Bool test |> _R --- (\ (@ a_a1Q5) -> let { $dGHCiSandboxIO_a1Q7 :: GHCiSandboxIO IO [LclId] $dGHCiSandboxIO_a1Q7 = $fGHCiSandboxIOIO } in ghciStepIO @ IO $dGHCiSandboxIO_a1Q7 @ a_a1Q5) @ Bool test *** Core Lint errors : in result of desugar expression *** : warning: In the expression: print @ Bool $dShow_a1Qg it_a1PP $dShow_a1Qg :: Show Bool [LclId] is out of scope *** Offending Program *** bindIO @ Bool @ [()] (let { $dShow_a1Qg :: Show Bool <----- Right binding, wrongly scoped! [LclId] $dShow_a1Qg = $fShowBool } in (\ (@ a_a1Q5) -> let { $dGHCiSandboxIO_a1Q7 :: GHCiSandboxIO IO [LclId] $dGHCiSandboxIO_a1Q7 = $fGHCiSandboxIOIO } in ghciStepIO @ IO $dGHCiSandboxIO_a1Q7 @ a_a1Q5) @ Bool test) (\ (it_a1PP :: Bool) -> thenIO @ () @ [()] (print @ Bool $dShow_a1Qg it_a1PP) (returnIO @ [()] (: @ () (unsafeCoerce# @ 'LiftedRep @ 'LiftedRep @ Bool @ () it_a1PP) ([] @ ())))) *** End of Offense *** }}} Here's the deal. * When you type `ghci> test` to the GHCi prompt, GHC typechecks (roughly) {{{ do { it <- sandbox test ; print it ; return () } }}} This is Plan A in TcRnDriver.tcUserStmt. * When typechecking the initial `BindStmt` of the `do` block, we end up invoking `tcSyntaxOp` in `TcMatches.TcDoStmt` * Bizarrely, we then typecheck the rest of the `do` block inside the `thing_inside` argument to `tcSyntaxOp`. * `TcExpr.tcSyntaxOp` ends up calling `tcSyntaxArgE`, which calls `tcSkolemize`, which builds an implication constraint. * This implication constraint gets wrapped around the first argument of the bind, namely `sandbox test`. But since the `thing_inside` includes the `Show` constraint arising from `print it`, the `Show` dictionary lands up in the evidence bindings for the implication, and hence gets wrapped around the `sandbox test` RHS only. Utterly bogus. * All this happens always, I think. Usually `TcUnify.implicationNeeded` ends up being false, so we don't actually create an implication, and so the evidence bindings don't end up in the wrong place. But in the special case of GHCi with `-fdefer-type-errors` we (unusually) you'll see that `implicationNeeded` returns True. And that's why the bug manifest only in GHCi, and even then only with `-fdefer-type-errors`. Blimey. -------------------------------- All of this is a result of the impenetrable code in `tcSyntaxOp`, which Richard introduced in {{{ commit 00cbbab3362578df44851442408a8b91a2a769fa Author: Richard Eisenberg Date: Wed Jan 13 23:29:17 2016 -0500 ... In addition, this patch does a significant reworking of RebindableSyntax, allowing much more freedom in the types of the rebindable operators. For example, we can now have `negate :: Int -> Bool` and `(>>=) :: m a -> (forall x. a x -> m b) -> m b`. The magic is in tcSyntaxOp. }}} To me it seems Utterly And Completely Wrong for `tcSyntaxOp` to take the continuation as a `thing_inside` argument. Not only is it extremely complicated, but it's also plain wrong. Why can't it just decompose the function type to produce a bunch of types to use as the expected types for the aguments? No Notes explain. The code makes my head spin. Richard, can't this all be radically simplified? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 22:17:18 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 22:17:18 -0000 Subject: [GHC] #14990: "Valid refinement suggestions" have the wrong types In-Reply-To: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> References: <047.1377e2f34a2eeac1354152d47898fe0b@haskell.org> Message-ID: <062.dc681c7876f6e47846446620a26b7c76@haskell.org> #14990: "Valid refinement suggestions" have the wrong types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Tritlo Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.5 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 Tritlo): * owner: (none) => Tritlo Comment: Yes, I agree! Of course the type displayed should be the type of the actual expression and not just the type of the function suggested. That only works in the single identifier case. In the current version, it now shows the type of the additional holes, like this: {{{ • Found hole: _ :: Integer -> Integer • In the expression: _ In the expression: _ 5 In an equation for ‘x’: x = _ 5 • Relevant bindings include x :: Integer (bound at Bug.hs:6:1) Valid substitutions include negate :: forall a. Num a => a -> a abs :: forall a. Num a => a -> a signum :: forall a. Num a => a -> a fromInteger :: forall a. Num a => Integer -> a Valid refinement substitutions include (-) (_ :: Integer) :: forall a. Num a => a -> a -> a (*) (_ :: Integer) :: forall a. Num a => a -> a -> a (+) (_ :: Integer) :: forall a. Num a => a -> a -> a }}} Having any constraints known constraints on these would be very helpful, I agree, and the types of the functions themselves should be the type of the entire expression. In the more polymorphic case, it would say: {{{ (+) (_ :: a0) :: a0 -> a0 where (Num a0) }}} However, I worry that this might then become less useful for IDEs in the future. I think it would be best to have something displayed that can directly replace the hole. How would you present the `(Num a0)` constraint so that it would be picked up by the hole itself? Is it possible to use `ScopedTypeVariables` maybe? And have it say `(+) (_ :: a0) :: Num a0 => a0 -> a0`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Mar 31 22:18:17 2018 From: ghc-devs at haskell.org (GHC) Date: Sat, 31 Mar 2018 22:18:17 -0000 Subject: [GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module In-Reply-To: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> References: <047.c258bd8a8d43881f32b193f6cbfcf8f0@haskell.org> Message-ID: <062.271b6e77f768a347a84871df2d2a9d26@haskell.org> #14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.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): PS: using `WpFun` would mean you could return a single `HsWrapper` to wrap around the bind function, rather than returning wrappers for the function, the arguments, and the result. See its use in `TcUnify.tc_sub_type_ds`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Mar 30 11:50:41 2018 From: ghc-devs at haskell.org (GHC) Date: Fri, 30 Mar 2018 11:50:41 -0000 Subject: [GHC] #14986: CmmCommonBlockElim conflicts with GhcEnableTablesNextToCode=NO (was: ghc panics when compiling stage 2) In-Reply-To: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> References: <049.538cc2718b728b5d864bc8e0416ec932@haskell.org> Message-ID: <064.28ae86a5f56d63997773262629578208@haskell.org> #14986: CmmCommonBlockElim conflicts with GhcEnableTablesNextToCode=NO -------------------------------------+------------------------------------- Reporter: terrorjack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.5 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by terrorjack: Old description: > I'm compiling a recent commit (0017a7b618353bf984d701f6d8ee2810a425e5b3), > yet ghc always panics when ghc-stage1 is compiling ghc-prim. The error is > as follows: > > {{{ > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/./GHC/CString.hs -o libraries/ghc-prim/dist- > install/build/GHC/CString.o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- > install/build/GHC/IntWord64.o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i > -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base > /dist-install/build -ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include > -Ilibraries/base/dist-install/build/include -optP-include > -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- > id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts > -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- > trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances > -odir libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./GHC/Base.hs-boot -o libraries/base/dist- > install/build/GHC/Base.o-boot > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i > -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base > /dist-install/build -ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include > -Ilibraries/base/dist-install/build/include -optP-include > -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- > id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts > -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- > trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances > -odir libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./GHC/Real.hs-boot -o libraries/base/dist- > install/build/GHC/Real.o-boot > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i > -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base > /dist-install/build -ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include > -Ilibraries/base/dist-install/build/include -optP-include > -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- > id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts > -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- > trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances > -odir libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./GHC/IO.hs-boot -o libraries/base/dist- > install/build/GHC/IO.o-boot > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i > -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base > /dist-install/build -ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include > -Ilibraries/base/dist-install/build/include -optP-include > -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- > id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts > -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- > trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances > -odir libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./Data/Semigroup/Internal.hs-boot -o libraries/base/dist- > install/build/Data/Semigroup/Internal.o-boot > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/./GHC/Tuple.hs -o libraries/ghc-prim/dist- > install/build/GHC/Tuple.o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/./GHC/Magic.hs -o libraries/ghc-prim/dist- > install/build/GHC/Magic.o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- > prim/./GHC/CString.hs -o libraries/ghc-prim/dist- > install/build/GHC/CString.p_o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- > prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- > install/build/GHC/IntWord64.p_o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- > all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build > -Ilibraries/base/dist-install/build -ilibraries/base/dist- > install/build/./autogen -Ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/include -Ilibraries/base/dist-install/build/include > -optP-include -optPlibraries/base/dist- > install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 > -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base > -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe > -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./GHC/Base.hs-boot -o libraries/base/dist- > install/build/GHC/Base.p_o-boot > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- > all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build > -Ilibraries/base/dist-install/build -ilibraries/base/dist- > install/build/./autogen -Ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/include -Ilibraries/base/dist-install/build/include > -optP-include -optPlibraries/base/dist- > install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 > -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base > -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe > -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./GHC/Real.hs-boot -o libraries/base/dist- > install/build/GHC/Real.p_o-boot > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- > all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build > -Ilibraries/base/dist-install/build -ilibraries/base/dist- > install/build/./autogen -Ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/include -Ilibraries/base/dist-install/build/include > -optP-include -optPlibraries/base/dist- > install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 > -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base > -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe > -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./GHC/IO.hs-boot -o libraries/base/dist- > install/build/GHC/IO.p_o-boot > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- > all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build > -Ilibraries/base/dist-install/build -ilibraries/base/dist- > install/build/./autogen -Ilibraries/base/dist-install/build/./autogen > -Ilibraries/base/include -Ilibraries/base/dist-install/build/include > -optP-include -optPlibraries/base/dist- > install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 > -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base > -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe > -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/base/dist-install/build -hidir libraries/base/dist- > install/build -stubdir libraries/base/dist-install/build -split-objs -c > libraries/base/./Data/Semigroup/Internal.hs-boot -o libraries/base/dist- > install/build/Data/Semigroup/Internal.p_o-boot > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- > prim/./GHC/Tuple.hs -o libraries/ghc-prim/dist- > install/build/GHC/Tuple.p_o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- > prim/./GHC/Magic.hs -o libraries/ghc-prim/dist- > install/build/GHC/Magic.p_o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/./GHC/Classes.hs -o libraries/ghc-prim/dist- > install/build/GHC/Classes.o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/./GHC/Debug.hs -o libraries/ghc-prim/dist- > install/build/GHC/Debug.o > "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O > -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i > -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build > -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen > -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- > install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- > prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- > safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir > libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- > install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs > -c libraries/ghc-prim/dist-install/build/GHC/PrimopWrappers.hs -o > libraries/ghc-prim/dist-install/build/GHC/PrimopWrappers.o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- > prim/./GHC/Classes.hs -o libraries/ghc-prim/dist- > install/build/GHC/Classes.p_o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- > prim/./GHC/Debug.hs -o libraries/ghc-prim/dist- > install/build/GHC/Debug.p_o > "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static > -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 > -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- > install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc- > prim/dist-install/build/./autogen -Ilibraries/ghc-prim/dist- > install/build/./autogen -Ilibraries/ghc-prim/. -optP-include > -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h > -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- > package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags > -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- > install/build -hidir libraries/ghc-prim/dist-install/build -stubdir > libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim > /dist-install/build/GHC/PrimopWrappers.hs -o libraries/ghc-prim/dist- > install/build/GHC/PrimopWrappers.p_o > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.5.20180329 for x86_64-unknown-mingw32): > Each block should be reachable from only one ProcPoint > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > make[1]: *** [libraries/ghc-prim/ghc.mk:4: libraries/ghc-prim/dist- > install/build/GHC/Classes.o] Error 1 > make[1]: *** Waiting for unfinished jobs.... > ghc-stage1.exe: panic! (the 'impossible' happened) > (GHC version 8.5.20180329 for x86_64-unknown-mingw32): > Each block should be reachable from only one ProcPoint > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > make[1]: *** [libraries/ghc-prim/ghc.mk:4: libraries/ghc-prim/dist- > install/build/GHC/Classes.p_o] Error 1 > make: *** [Makefile:127: all] Error 2 > }}} > > I'm using the following build.mk for those builds here: > > {{{ > GhcEnableTablesNextToCode = NO > INTEGER_LIBRARY = integer-simple > SRC_HC_OPTS = -O -H64m > GhcStage1HcOpts = -O > GhcStage2HcOpts = -O2 > GhcLibHcOpts = -O2 > BUILD_PROF_LIBS = YES > SplitObjs = YES > SplitSections = NO > BUILD_SPHINX_HTML = YES > BUILD_SPHINX_PDF = NO > HADDOCK_DOCS = YES > EXTRA_HADDOCK_OPTS += --quickjump --hyperlinked-source > > }}} > > Still working to figure out a minimal combination of the build flags to > trigger a similar error. Meanwhile, has anyone seen a similar error for a > different commit/platform/build config? New description: A recent commit d5c4d46a62ce6a0cfa6440344f707136eff18119 which adds a second pass of CmmCommonBlockElim is observed to conflict with GhcEnableTablesNextToCode=NO. When building stage2, ghc will produce an "Each block should be reachable from only one ProcPoint" error and panic. Original description below: I'm compiling a recent commit (0017a7b618353bf984d701f6d8ee2810a425e5b3), yet ghc always panics when ghc-stage1 is compiling ghc-prim. The error is as follows: {{{ "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/CString.hs -o libraries/ghc-prim/dist- install/build/GHC/CString.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- install/build/GHC/IntWord64.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Base.hs-boot -o libraries/base/dist- install/build/GHC/Base.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Real.hs-boot -o libraries/base/dist- install/build/GHC/Real.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/IO.hs-boot -o libraries/base/dist- install/build/GHC/IO.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide-all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base /dist-install/build -ilibraries/base/dist-install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist-install/build/./autogen/cabal_macros.h -package- id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno- trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist- install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./Data/Semigroup/Internal.hs-boot -o libraries/base/dist- install/build/Data/Semigroup/Internal.o-boot "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Tuple.hs -o libraries/ghc-prim/dist- install/build/GHC/Tuple.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Magic.hs -o libraries/ghc-prim/dist- install/build/GHC/Magic.o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/CString.hs -o libraries/ghc-prim/dist- install/build/GHC/CString.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- install/build/GHC/IntWord64.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Base.hs-boot -o libraries/base/dist- install/build/GHC/Base.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/Real.hs-boot -o libraries/base/dist- install/build/GHC/Real.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./GHC/IO.hs-boot -o libraries/base/dist- install/build/GHC/IO.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id base-4.11.0.0 -hide- all-packages -i -ilibraries/base/. -ilibraries/base/dist-install/build -Ilibraries/base/dist-install/build -ilibraries/base/dist- install/build/./autogen -Ilibraries/base/dist-install/build/./autogen -Ilibraries/base/include -Ilibraries/base/dist-install/build/include -optP-include -optPlibraries/base/dist- install/build/./autogen/cabal_macros.h -package-id ghc-prim-0.5.2.0 -package-id integer-simple-0.1.1.1 -package-id rts -this-unit-id base -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/base/dist-install/build -hidir libraries/base/dist-install/build -stubdir libraries/base/dist-install/build -split-objs -c libraries/base/./Data/Semigroup/Internal.hs-boot -o libraries/base/dist- install/build/Data/Semigroup/Internal.p_o-boot "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Tuple.hs -o libraries/ghc-prim/dist-install/build/GHC/Tuple.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Magic.hs -o libraries/ghc-prim/dist-install/build/GHC/Magic.p_o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Classes.hs -o libraries/ghc-prim/dist- install/build/GHC/Classes.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/Debug.hs -o libraries/ghc-prim/dist- install/build/GHC/Debug.o "inplace/bin/ghc-stage1.exe" -hisuf hi -osuf o -hcsuf hc -static -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide-all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -Ilibraries /ghc-prim/dist-install/build -ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/dist-install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc- prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -Wno-trustworthy- safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/dist-install/build/GHC/PrimopWrappers.hs -o libraries/ghc-prim/dist-install/build/GHC/PrimopWrappers.o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Classes.hs -o libraries/ghc-prim/dist- install/build/GHC/Classes.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc- prim/./GHC/Debug.hs -o libraries/ghc-prim/dist-install/build/GHC/Debug.p_o "inplace/bin/ghc-stage1.exe" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -eventlog -O -H64m -Wall -this-unit-id ghc-prim-0.5.2.0 -hide- all-packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim /dist-install/build/./autogen -Ilibraries/ghc-prim/dist- install/build/./autogen -Ilibraries/ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist-install/build/./autogen/cabal_macros.h -package-id rts -this-unit-id ghc-prim -XHaskell2010 -O2 -no-user- package-db -rtsopts -Wno-trustworthy-safe -Wno-deprecated-flags -Wnoncanonical-monad-instances -odir libraries/ghc-prim/dist- install/build -hidir libraries/ghc-prim/dist-install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim /dist-install/build/GHC/PrimopWrappers.hs -o libraries/ghc-prim/dist- install/build/GHC/PrimopWrappers.p_o ghc-stage1.exe: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-mingw32): Each block should be reachable from only one ProcPoint Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug make[1]: *** [libraries/ghc-prim/ghc.mk:4: libraries/ghc-prim/dist- install/build/GHC/Classes.o] Error 1 make[1]: *** Waiting for unfinished jobs.... ghc-stage1.exe: panic! (the 'impossible' happened) (GHC version 8.5.20180329 for x86_64-unknown-mingw32): Each block should be reachable from only one ProcPoint Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug make[1]: *** [libraries/ghc-prim/ghc.mk:4: libraries/ghc-prim/dist- install/build/GHC/Classes.p_o] Error 1 make: *** [Makefile:127: all] Error 2 }}} I'm using the following build.mk for those builds here: {{{ GhcEnableTablesNextToCode = NO INTEGER_LIBRARY = integer-simple SRC_HC_OPTS = -O -H64m GhcStage1HcOpts = -O GhcStage2HcOpts = -O2 GhcLibHcOpts = -O2 BUILD_PROF_LIBS = YES SplitObjs = YES SplitSections = NO BUILD_SPHINX_HTML = YES BUILD_SPHINX_PDF = NO HADDOCK_DOCS = YES EXTRA_HADDOCK_OPTS += --quickjump --hyperlinked-source }}} Still working to figure out a minimal combination of the build flags to trigger a similar error. Meanwhile, has anyone seen a similar error for a different commit/platform/build config? -- -- Ticket URL: GHC The Glasgow Haskell Compiler