From ghc-devs at haskell.org Sun May 1 06:15:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 06:15:58 -0000 Subject: [GHC] #11747: `Strict` causes core lint error In-Reply-To: <051.5f1977edc97bd586c2cbc6d3ff3dff5b@haskell.org> References: <051.5f1977edc97bd586c2cbc6d3ff3dff5b@haskell.org> Message-ID: <066.cb75bb0d7efd4c468f90c0785c895db5@haskell.org> #11747: `Strict` causes core lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Strict Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2163 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D2163 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 07:48:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 07:48:37 -0000 Subject: [GHC] #11835: ApplicativeDo failed to desugar last line with pure $ In-Reply-To: <045.10a09841bc3d481ea24884cfac477277@haskell.org> References: <045.10a09841bc3d481ea24884cfac477277@haskell.org> Message-ID: <060.cc015ac52bfe73192bda9ff1531fc2aa@haskell.org> #11835: ApplicativeDo failed to desugar last line with pure $ -------------------------------------+------------------------------------- Reporter: Cosmia | Owner: simonmar Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: ApplicativeDo Operating System: MacOS X | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11607 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => merge * milestone: => 8.0.2 Comment: I updated the documentation: https://phabricator.haskell.org/rGHCd396996298939f647c22b547bc01f1b00e6e2fd9 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 09:34:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 09:34:26 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base Message-ID: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 7.10.3 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Since we have pattern synonyms it's worth considering if some belong in base: [https://hackage.haskell.org/package/lens-4.14/docs/Data-Complex-Lens.html Data.Complex.Lens] contains patterns that could be defined in base, here are some more suggestions: === Data.Array === {{{#!hs pattern ArrayIx :: Ix i => (i, i) -> [(i, e)] -> Array i e pattern ArrayIx low'high xs <- ((\arr -> (bounds arr, assocs arr)) -> (low'high, xs)) where ArrayIx low'high xs = array low'high xs }}} === Data.Bits === {{{#!hs pattern ZeroBits :: (Eq a, Bits a) => a pattern ZeroBits <- ((== zeroBits) -> True) where ZeroBits = zeroBits pattern BitSize :: Bits a => Int -> a pattern BitSize n <- (bitSizeMaybe -> Just n) pattern Signed :: Bits a => a pattern Signed <- (isSigned -> True) pattern Unsigned :: Bits a => a pattern Unsigned <- (isSigned -> False) pattern PopCount :: Bits a => Int -> a pattern PopCount n <- (popCount -> n) }}} === Data.Char === {{{#!hs pattern ControlChar :: Char pattern ControlChar <- (isControl -> True) pattern SpaceChar :: Char pattern SpaceChar <- (isSpace -> True) }}} === Data.Complex === {{{#!hs pattern Conjugate :: Num a => Complex a -> Complex a pattern Conjugate a <- (conjugate -> a) where Conjugate a = conjugate a pattern Polar :: RealFloat a => a -> a -> Complex a pattern Polar m theta <- (polar -> (m, theta)) where Polar m theta = mkPolar m theta -- See https://github.com/ekmett/lens/issues/653 pattern Real :: Num a => a -> Complex a pattern Real r <- r :+ _ where Real r = r :+ 0 pattern Imaginary :: Num a => a -> Complex a pattern Imaginary i <- _ :+ i where Imaginary i = 0 :+ i }}} === GHC.Float === {{{#!hs pattern NegativeZero :: RealFloat a => a pattern NegativeZero <- (isNegativeZero -> True) where NegativeZero = -0 pattern Denormalized :: RealFloat a => a pattern Denormalized <- (isDenormalized -> True) pattern NaN :: RealFloat a => a pattern NaN <- (isNaN -> True) where NaN = 0 / 0 -- How ever negative infinity is handled pattern Infinity :: RealFloat a => a pattern Infinity <- ((== 1 / 0) -> True) where Infinity = 1 / 0 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 09:36:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 09:36:06 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.ab03f4db4177797d4affc3d13256f2fa@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): {{{#!hs pattern II :: Int -> Int# pattern II i <- (I# -> i) where II (I# i) = i pattern FF :: Float -> Float# pattern FF f <- (F# -> f) where FF (F# f) = f }}} also if GHC allowed unlifted types in pattern synonyms, should that be a ticket? {{{ tImB.hs:6:22-25: error: ? ? Expecting a lifted type, but ?Int#? is unlifted ? In the type ?Int#? tImB.hs:10:22-27: error: ? ? Expecting a lifted type, but ?Float#? is unlifted ? In the type ?Float#? Compilation failed. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 13:05:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 13:05:28 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.6d84fc2f6cae5439e0d0d52810014820@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Some random ideas, === Data.Functor.Const === {{{#!hs pattern K :: forall a (b :: k). a -> Const a b pattern K a = Const a pattern K' :: forall a (b :: k). a -> Constant a b pattern K' a = Constant a }}} === GHC.Generics === {{{#!hs isAssociative :: Associativity -> Bool isAssociative LeftAssociative = True isAssociative RightAssociative = True isAssociative NotAssociative = False pattern Associative :: Associative pattern Associative <- (isAssociative -> True) }}} === Data.Ratio === {{{#!hs pattern Denominator :: a -> Ratio a pattern Denominator a <- (denominator -> a) pattern Numerator :: a -> Ratio a pattern Numerator a <- (numerator -> a) pattern (:%) :: Integral a => a -> a -> Ratio a pattern num :% den <- ((\r -> (numerator r, denominator r)) -> (num, den)) where num :% den = num % den }}} === System.Exit === {{{#!hs exitCode :: ExitCode -> Int exitCode = \case ExitSuccess -> 0 ExitFailure n -> n pattern ExitCode :: Int -> ExitCode pattern ExitCode n <- (exitCode -> n) where ExitCode 0 = ExitSuccess ExitCode n = ExitFailure n }}} === Data.Maybe === {{{#!hs pattern Some :: a -> Maybe a pattern Some a = Just a pattern None :: a -> Maybe a pattern None = Nothing }}} === Data.Functor.Identity === {{{#!hs pattern I :: a -> Identity pattern I a = Identity a }}} === Data.Ord === {{{#!hs pattern :: Ordering pattern Less = LT pattern :: Ordering pattern Equal = EQ pattern :: Ordering pattern Greater = GT }}} === Data.Foldable === {{{#!hs pattern Null :: Foldable f => f a pattern Null <- (null -> True) }}} === Data.Bool === {{{#!hs pattern T :: Bool pattern T = True pattern F :: Bool pattern F = False }}} It's fine if these don't get accepted, just throwing them into the universe -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 16:46:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 16:46:59 -0000 Subject: [GHC] #12002: Pragmas after a module declaration are ignored without warning. Message-ID: <050.a06dfff8e83390aaf98ce91845f96e30@haskell.org> #12002: Pragmas after a module declaration are ignored without warning. -------------------------------------+------------------------------------- Reporter: seanparsons | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Normally pragmas are placed above the module declaration like so: {{{#!hs {-# LANGUAGE OverloadedStrings #-} module Main where }}} However if the above 2 lines are flipped around like this: {{{#!hs module Main where {-# LANGUAGE OverloadedStrings #-} }}} Then the behaviour seen by a user is that equivalent to the pragma not being present, because it would appear GHC ignores the multi-line comment it looks like. For a novice (I'm not one but it just tripped me up) this would be incredibly baffling (it was for me), it would be nice to see a warning for this at the least. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 17:24:16 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 17:24:16 -0000 Subject: [GHC] #1407: Add the ability to :set -l{foo} in .ghci files In-Reply-To: <044.ced6846230ff2e238418885a3d68ddd9@haskell.org> References: <044.ced6846230ff2e238418885a3d68ddd9@haskell.org> Message-ID: <059.e201eb39ebab70025d0239611699fc0f@haskell.org> #1407: Add the ability to :set -l{foo} in .ghci files -------------------------------------+------------------------------------- Reporter: guest | Owner: archblob Type: feature request | Status: closed Priority: normal | Milestone: 7.10.3 Component: GHCi | Version: 6.6.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D194 Wiki Page: | Phab:D1310 -------------------------------------+------------------------------------- Comment (by Tamar Christina ): In [changeset:"e6627d1f8964807f19f8773f09cfaacae7ca8ab8/ghc" e6627d1f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e6627d1f8964807f19f8773f09cfaacae7ca8ab8" Fix aggressive cleanup of T1407 Summary: The aggressive cleanup routine of T1407 is removing files that don't belong to it. Constrain the test to only removing files it should by putting all it's generated binaries in it's own output folder. Test Plan: make test -C testsuite/tests/ghci/linking/dyn Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie, #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2165 GHC Trac Issues: #1407 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 18:15:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 18:15:05 -0000 Subject: [GHC] #7353: Make system IO interruptible on Windows In-Reply-To: <048.cfc723cf8062d55ebdf5fa24c2f6c705@haskell.org> References: <048.cfc723cf8062d55ebdf5fa24c2f6c705@haskell.org> Message-ID: <063.5476e87c9d57850b4d1e296bf9397a04@haskell.org> #7353: Make system IO interruptible on Windows -------------------------------------+------------------------------------- Reporter: joeyadams | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.1 Resolution: | Keywords: Operating System: Windows | 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-): Hi @refold, Just checking to see if you're making any progress on this. Cheers -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 18:28:04 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 18:28:04 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.0dfb240890e5000a84077ec67c8f0a27@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): I am very sceptical. Pattern synonyms are still relatively new, and I would say that best practices around them have not evolved yet (e.g.: should they be used for non-injective convenience patterns like `Popcount` at all? Should they be used for anything else but compatible or alternative views on data types?) Also, they clutter the namespace. Therefore, I would prefer if less central libraries would be first to take up pattern synonym and explore usage patterns, until it becomes apparent with which intensity pattern synonym make most sense. More concretely, of your list above, I?d give a +1 only to `Polar`. This is a genuine, self-descriptive constructor-like view on a data type. A bit fishy around 0, but that?s inherent in the general concept and not an issue with the constructor. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 20:05:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 20:05:51 -0000 Subject: [GHC] #7353: Make system IO interruptible on Windows In-Reply-To: <048.cfc723cf8062d55ebdf5fa24c2f6c705@haskell.org> References: <048.cfc723cf8062d55ebdf5fa24c2f6c705@haskell.org> Message-ID: <063.b5e37b00d24ebff81c0ffdfd61151d5c@haskell.org> #7353: Make system IO interruptible on Windows -------------------------------------+------------------------------------- Reporter: joeyadams | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by refold): @Phyx- So far I got the patches to work with GHC 8, will now focus on optimisation. Hopefully will have something ready for review by the end of this month. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 21:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 21:55:56 -0000 Subject: [GHC] #5850: Greater customization of GHCi prompt In-Reply-To: <050.bf03c3e2cbefdd0fabbaa545b275f2dc@haskell.org> References: <050.bf03c3e2cbefdd0fabbaa545b275f2dc@haskell.org> Message-ID: <065.9d15c74a05cbd792047ef6892c1ccb8a@haskell.org> #5850: Greater customization of GHCi prompt -------------------------------------+------------------------------------- Reporter: JamesFisher | Owner: niksaz Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.4.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9994 | Differential Rev(s): Phab:D2084 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"533037cc58a7c50e1c014e27e8b971d53e7b47bd/ghc" 533037c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="533037cc58a7c50e1c014e27e8b971d53e7b47bd" Greater customization of GHCi prompt This patch is trying to redesign the :set prompt option to take not a String but a Haskell function, like [String] -> Int -> IO String, where [String] is the list of the names of the currently loaded modules and Int is the line number. Currently you may set prompt function with **:set promt-function [String] -> Int -> IO String** option and old version is also available - :set prompt String. So, it looks like I've almost completed this patch: 1) Now we have a lot of escape sequences - 13 to be exact. Most of them are similar to bash prompt escape sequences. Thus they are quite handy. 2) We may use the special escape sequence to call shell functions, for example "%call(ls -l -a)". 3) We may use :set prompt-function to set PFunction to handle prompt. It is just [String] -> Int -> IO String. Reviewers: erikd, austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2084 GHC Trac Issues: #5850 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 21:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 21:55:56 -0000 Subject: [GHC] #11830: Disabling idle GC leads to freeze In-Reply-To: <051.01e036a0222a29198e3a9c508112fb05@haskell.org> References: <051.01e036a0222a29198e3a9c508112fb05@haskell.org> Message-ID: <066.faa3297925e086372b8b5c21f7b6fff4@haskell.org> #11830: Disabling idle GC leads to freeze -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.1-rc3 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): Phab:D2129 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"16a51a6c2f265f8670355be03d42b773d93e0684/ghc" 16a51a6c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="16a51a6c2f265f8670355be03d42b773d93e0684" rts: Close livelock window due to rapid ticker enable/disable This fixes #11830, where the RTS would livelock if run with `-I0` due to a regression introduced by bbdc52f3a6e6a28e209fb8f65699121d4ef3a4e3. The reason for this is that the new codepath introduced a subtle race condition: 1. one thread could request that the ticker stop and would block until the ticker in fact stopped 2. meanwhile, another thread could sneak in and restart the ticker this was implemented in such a way where thread (1) would end up blocked forever. The solution here is to simply not block. The worst that will happen is that timer fires again, but is ignored since the ticker is stopped. Test Plan: Validate, try reproduction case in #11830. Need to find a nice testcase. Reviewers: simonmar, erikd, hsyl20, austin Reviewed By: erikd, hsyl20 Subscribers: erikd, thomie Differential Revision: https://phabricator.haskell.org/D2129 GHC Trac Issues: #11830 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 21:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 21:55:56 -0000 Subject: [GHC] #1623: ghci: 20 wakeups per second In-Reply-To: <044.79f0800bada3efe37e69bcbb2dfb2672@haskell.org> References: <044.79f0800bada3efe37e69bcbb2dfb2672@haskell.org> Message-ID: <059.87b944f4aa1be91f1cbd3c806bcdabd9@haskell.org> #1623: ghci: 20 wakeups per second -------------------------------------+------------------------------------- Reporter: igloo | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 6.8.1 Component: Runtime System | Version: 6.6.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"999c464da36e925bd4ffea34c94d3a7b3ab0135c/ghc" 999c464/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="999c464da36e925bd4ffea34c94d3a7b3ab0135c" rts/itimer/pthread: Stop timer when ticker is stopped This reworks the pthread-based itimer implementation to disarm the timer when events aren't needed. Thanks to hsyl20 for the nice design. Test Plan: Validate Reviewers: hsyl20, simonmar, austin Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2131 GHC Trac Issues: #1623, #11965 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 21:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 21:55:56 -0000 Subject: [GHC] #11965: USE_PTHREAD_FOR_ITIMER causes unnecessary wake-ups In-Reply-To: <046.693e963a76f01ad7673f5f3266c31daf@haskell.org> References: <046.693e963a76f01ad7673f5f3266c31daf@haskell.org> Message-ID: <061.ccb8e0c964c4a98965fd6a3a45da3ace@haskell.org> #11965: USE_PTHREAD_FOR_ITIMER causes unnecessary wake-ups -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: high | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #1623 | Differential Rev(s): Phab:D2131 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"999c464da36e925bd4ffea34c94d3a7b3ab0135c/ghc" 999c464/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="999c464da36e925bd4ffea34c94d3a7b3ab0135c" rts/itimer/pthread: Stop timer when ticker is stopped This reworks the pthread-based itimer implementation to disarm the timer when events aren't needed. Thanks to hsyl20 for the nice design. Test Plan: Validate Reviewers: hsyl20, simonmar, austin Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2131 GHC Trac Issues: #1623, #11965 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 21:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 21:55:56 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.d7ce0e10baaa23d30283a38a454d1aa8@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"116d3fe67f0f45d1e3e98e3c091eb4d14a121305/ghc" 116d3fe/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="116d3fe67f0f45d1e3e98e3c091eb4d14a121305" Remove unused getScopedTyVarBinds Test Plan: it compiles Reviewers: simonpj, austin, goldfire, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2160 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 21:55:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 21:55:56 -0000 Subject: [GHC] #11747: `Strict` causes core lint error In-Reply-To: <051.5f1977edc97bd586c2cbc6d3ff3dff5b@haskell.org> References: <051.5f1977edc97bd586c2cbc6d3ff3dff5b@haskell.org> Message-ID: <066.9185bbc735edf1d3d2b008b9a0f7b201@haskell.org> #11747: `Strict` causes core lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Strict Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2163 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"116193225465186ceb8471a007eff15692af903a/ghc" 11619322/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="116193225465186ceb8471a007eff15692af903a" Add T11747 as a test Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2163 GHC Trac Issues: #11747 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 22:01:20 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 22:01:20 -0000 Subject: [GHC] #11747: `Strict` causes core lint error In-Reply-To: <051.5f1977edc97bd586c2cbc6d3ff3dff5b@haskell.org> References: <051.5f1977edc97bd586c2cbc6d3ff3dff5b@haskell.org> Message-ID: <066.5121307774e4e1a3d4377f3c65416da6@haskell.org> #11747: `Strict` causes core lint error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Strict Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2163 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 Comment: This is apparently fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 22:49:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 22:49:31 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.9d1afd2c1fd03693f403b130878d79bb@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"ea34f565d370404f9ea5f8bcf6a8380ffa842c49/ghc" ea34f565/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ea34f565d370404f9ea5f8bcf6a8380ffa842c49" Remove unused equivClassesByUniq It uses `eltsUFM` so it can introduce nondeterminism, but it isn't used so we can delete it. Test Plan: it builds Reviewers: simonpj, goldfire, simonmar, austin, bgamari Reviewed By: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2161 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 22:49:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 22:49:31 -0000 Subject: [GHC] #5529: Newtypes with hidden constructors cannot be passed as FFI arguments In-Reply-To: <057.69981269d7ca6393b7c0b289bf97bb9a@haskell.org> References: <057.69981269d7ca6393b7c0b289bf97bb9a@haskell.org> Message-ID: <072.a9430bc40f86b2e61708677656b20dd6@haskell.org> #5529: Newtypes with hidden constructors cannot be passed as FFI arguments ---------------------------------------+--------------------------------- Reporter: mikhail.vorozhtsov | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: ---------------------------------------+--------------------------------- Comment (by Ben Gamari ): In [changeset:"a28611b14930c9fd73b0028857e1ea8c0e64a38a/ghc" a28611b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a28611b14930c9fd73b0028857e1ea8c0e64a38a" Export constructors for IntPtr and WordPtr This finishes what #5529 started by exporting the constructors for `IntPtr` and `WordPtr` from `Foreign.Ptr`, allowing them to be used in `foreign` declarations. Fixes #11983. Test Plan: `make TEST=T11983` Reviewers: simonpj, hvr, bgamari, austin Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2142 GHC Trac Issues: #11983 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 22:49:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 22:49:31 -0000 Subject: [GHC] #11983: Can't use IntPtr or WordPtr in a foreign import In-Reply-To: <050.a377de086d55ae1ca346bd4cd7fa231a@haskell.org> References: <050.a377de086d55ae1ca346bd4cd7fa231a@haskell.org> Message-ID: <065.95980b33a8dd54d71adff026cbac6616@haskell.org> #11983: Can't use IntPtr or WordPtr in a foreign import -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler (FFI) | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #3008, #5529 | Differential Rev(s): Phab:D2142 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a28611b14930c9fd73b0028857e1ea8c0e64a38a/ghc" a28611b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a28611b14930c9fd73b0028857e1ea8c0e64a38a" Export constructors for IntPtr and WordPtr This finishes what #5529 started by exporting the constructors for `IntPtr` and `WordPtr` from `Foreign.Ptr`, allowing them to be used in `foreign` declarations. Fixes #11983. Test Plan: `make TEST=T11983` Reviewers: simonpj, hvr, bgamari, austin Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2142 GHC Trac Issues: #11983 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 22:49:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 22:49:31 -0000 Subject: [GHC] #11985: Core lint error on record syntax update/pattern synonym In-Reply-To: <051.bfbd96cdb2d8f4dfe3f8d61c3585b311@haskell.org> References: <051.bfbd96cdb2d8f4dfe3f8d61c3585b311@haskell.org> Message-ID: <066.32d705a08911ecc2c4bc84225cf775c0@haskell.org> #11985: Core lint error on record syntax update/pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: mpickering Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2147 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"cd85dc84b36bc5f600eb1b3805024a5b2443e1a3/ghc" cd85dc84/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cd85dc84b36bc5f600eb1b3805024a5b2443e1a3" Make sure record pattern synonym selectors are in scope in GHCi. Beforehand, when a record pattern synonym was defined in GHCi the selectors would not be in scope. This is because of `is_sub_bndr` in `HscTypes.icExtendGblRdrEnv` was throwing away the selectors. This was broken by the fix to #10520 but it is easy to resolve. Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2147 GHC Trac Issues: #11985 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 1 22:49:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 01 May 2016 22:49:31 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2310520=3A_RecordWildCards_causes_?= =?utf-8?q?=E2=80=9Cis_not_a_=28visible=29_field_of_constructor?= =?utf-8?b?4oCdIGluIGdoY2k=?= In-Reply-To: <043.c857f67e883ef833a204da9e13d91bc2@haskell.org> References: <043.c857f67e883ef833a204da9e13d91bc2@haskell.org> Message-ID: <058.af1b2eb21e052903754a8044eccacf85@haskell.org> #10520: RecordWildCards causes ?is not a (visible) field of constructor? in ghci -------------------------------------+------------------------------------- Reporter: ion1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: GHCi | Version: 7.10.1 Resolution: fixed | Keywords: | RecordWildCards 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 Ben Gamari ): In [changeset:"cd85dc84b36bc5f600eb1b3805024a5b2443e1a3/ghc" cd85dc84/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cd85dc84b36bc5f600eb1b3805024a5b2443e1a3" Make sure record pattern synonym selectors are in scope in GHCi. Beforehand, when a record pattern synonym was defined in GHCi the selectors would not be in scope. This is because of `is_sub_bndr` in `HscTypes.icExtendGblRdrEnv` was throwing away the selectors. This was broken by the fix to #10520 but it is easy to resolve. Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2147 GHC Trac Issues: #11985 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 01:09:21 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 01:09:21 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.15f46a7947cee4ef82ecb8947f51be31@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ekmett): I'm pretty much in the same camp as Joachim: The only one of these that I think really passes muster as a pattern that models a constructor is `Polar`. It doesn't destroy information when you pattern match with it and then reconstruct. (It does, however, destroy the phase information if the magnitude is 0 if you construct then deconstruct). The rest seem all better managed as view patterns, using existing combinators so that their lossy nature is much more clear. It is worthy of discussion to explore whether we're ready to start incorporating patterns into the bulk of `base`, but I personally think I'd like to see them endure a couple of releases without the sorts of major overhauls they have going on with how to put signatures on them, etc. before they started taking a more prominent role in a place where they'd be as hard to dislodge as `base`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 06:57:20 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 06:57:20 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.a14e50f2a2606103c33a1703fa7a5d12@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | https://github.com/TobyGoodwin/odd- | ghc-pattern-bug Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Hm, this is a weird one. I still don't understand the typechecker so can't fix this myself, but I did some debugging. Here's a simpler function that fails: {{{#!haskell fn2 :: Key User -> (Entity Message, Entity Folder) -> IO () fn2 usr cluster = let (Entity msgKey msg, Entity fldrKey fldr) = cluster in do print $ messageName msg print $ folderName fldr }}} Interestingly, the error message is about {{{Folder}}}, but if I replace {{{Message}}} with an empty tuple. {{{#!haskell fn2 :: Key User -> ((), Entity Folder) -> IO () fn2 usr cluster = let ((), Entity fldrKey fldr) = cluster in do print $ folderName fldr }}} It works. I also tried swapping the tuple elements: {{{#!haskell fn2 :: Key User -> (Entity Folder, Entity Message) -> IO () fn2 usr cluster = let (Entity fldrKey fldr, Entity msgKey msg) = cluster in do print $ messageName msg print $ folderName fldr }}} and it failed with an error message about {{{Message}}}: {{{ Message.hs:45:25: error: ? Couldn't match expected type ?Message? with actual type ?Message? ? In the first argument of ?messageName?, namely ?msg? In the second argument of ?($)?, namely ?messageName msg? In a stmt of a 'do' block: print $ messageName msg }}} It seems like some kind of side-effect is happening when type checking the first pattern. Oh, I also tried replacing the {{{in}}} part with {{{return ()}}}, and it worked: {{{#!haskell fn2 :: Key User -> (Entity Folder, Entity Message) -> IO () fn2 usr cluster = let (Entity fldrKey fldr, Entity msgKey msg) = cluster in do return () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 07:40:12 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 07:40:12 -0000 Subject: [GHC] #11965: USE_PTHREAD_FOR_ITIMER causes unnecessary wake-ups In-Reply-To: <046.693e963a76f01ad7673f5f3266c31daf@haskell.org> References: <046.693e963a76f01ad7673f5f3266c31daf@haskell.org> Message-ID: <061.f34ba6750cd4e2f23fdd01f945962478@haskell.org> #11965: USE_PTHREAD_FOR_ITIMER causes unnecessary wake-ups -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #1623 | Differential Rev(s): Phab:D2131 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 07:40:45 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 07:40:45 -0000 Subject: [GHC] #5850: Greater customization of GHCi prompt In-Reply-To: <050.bf03c3e2cbefdd0fabbaa545b275f2dc@haskell.org> References: <050.bf03c3e2cbefdd0fabbaa545b275f2dc@haskell.org> Message-ID: <065.80c063edf6af0b91b8e3843bc3511dee@haskell.org> #5850: Greater customization of GHCi prompt -------------------------------------+------------------------------------- Reporter: JamesFisher | Owner: niksaz Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: GHCi | Version: 7.4.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9994 | Differential Rev(s): Phab:D2084 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 08:40:33 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 08:40:33 -0000 Subject: [GHC] #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure In-Reply-To: <046.d81887f1f82ecca81477b67bf0ea3214@haskell.org> References: <046.d81887f1f82ecca81477b67bf0ea3214@haskell.org> Message-ID: <061.a33b24d2da43e4dec0aa6aef8ee921ff@haskell.org> #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 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): Here's a very bare-bones example, {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE RankNTypes #-} module TestCase3 where data Buffer = Buffer data BufferRange = BufferRange Buffer Int data BuildSignal a = BufferFull (BuildStep a) | Done a type BuildStep a = BufferRange -> IO (BuildSignal a) newtype Builder = Builder (forall r. BuildStep r -> BuildStep r) write16Bytes :: Int -> Int -> Builder write16Bytes a b = Builder $ \cont rng@(BufferRange Buffer rem) -> let !fa = f a !fb = f b -- doWrite :: BufferRange -> IO (BuildSignal r) doWrite rng' = writeInt fa >> writeInt fb >> cont rng' in if rem < 16 then return $ BufferFull doWrite else doWrite rng where f x = x + 42 writeInt :: Int -> IO () writeInt = print {-# NOINLINE writeInt #-} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 09:07:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 09:07:17 -0000 Subject: [GHC] #11983: Can't use IntPtr or WordPtr in a foreign import In-Reply-To: <050.a377de086d55ae1ca346bd4cd7fa231a@haskell.org> References: <050.a377de086d55ae1ca346bd4cd7fa231a@haskell.org> Message-ID: <065.d8e701879619479898bf06a9926fe3bd@haskell.org> #11983: Can't use IntPtr or WordPtr in a foreign import -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (FFI) | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #3008, #5529 | Differential Rev(s): Phab:D2142 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 09:07:39 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 09:07:39 -0000 Subject: [GHC] #11985: Core lint error on record syntax update/pattern synonym In-Reply-To: <051.bfbd96cdb2d8f4dfe3f8d61c3585b311@haskell.org> References: <051.bfbd96cdb2d8f4dfe3f8d61c3585b311@haskell.org> Message-ID: <066.e7f940b6a41e6b681b55fefad26655d5@haskell.org> #11985: Core lint error on record syntax update/pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: mpickering Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2147 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 16:28:21 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 16:28:21 -0000 Subject: [GHC] #10266: Split base for Backpack In-Reply-To: <045.81e58b6e2b97dd039d014c76c016ea80@haskell.org> References: <045.81e58b6e2b97dd039d014c76c016ea80@haskell.org> Message-ID: <060.efcdcdad1101f8bd263765907d2a88b2@haskell.org> #10266: Split base for Backpack -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: low | Milestone: Component: libraries/base | Version: 7.11 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 Mon May 2 16:36:15 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 16:36:15 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=238865=3A_Cannot_derive_well-kinded_i?= =?utf-8?q?nstance_of_form_=E2=80=98Category?= In-Reply-To: <048.9835e0581238f6f4bbded51439894fae@haskell.org> References: <048.9835e0581238f6f4bbded51439894fae@haskell.org> Message-ID: <063.261ef8cceede7d67dffd391f9193bbf5@haskell.org> #8865: Cannot derive well-kinded instance of form ?Category -------------------------------------+------------------------------------- Reporter: adinapoli | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.8.1-rc2 Resolution: fixed | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T8865 Blocked By: | Blocking: Related Tickets: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"fa86ac7c14b67f27017d795811265c3a9750024b/ghc" fa86ac7c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fa86ac7c14b67f27017d795811265c3a9750024b" Make validDerivPred ignore non-visible arguments to a class type constructor Summary: GHC choked when trying to derive the following: ``` {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE PolyKinds #-} module Example where class Category (cat :: k -> k -> *) where catId :: cat a a catComp :: cat b c -> cat a b -> cat a c newtype T (c :: * -> * -> *) a b = MkT (c a b) deriving Category ``` Unlike in #8865, where we were deriving `Category` for a concrete type like `Either`, in the above example we are attempting to derive an instance of the form: ``` instance Category * c => Category (T * c) where ... ``` (using `-fprint-explicit-kinds` syntax). But `validDerivPred` is checking if `sizePred (Category * c)` equals the number of free type variables in `Category * c`. But note that `sizePred` counts both type variables //and// type constructors, and `*` is a type constructor! So `validDerivPred` erroneously rejects the above instance. The fix is to make `validDerivPred` ignore non-visible arguments to the class type constructor (e.g., ignore `*` is `Category * c`) by using `filterOutInvisibleTypes`. Fixes #11833. Test Plan: ./validate Reviewers: goldfire, hvr, simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2112 GHC Trac Issues: #11833 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 16:36:15 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 16:36:15 -0000 Subject: [GHC] #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint In-Reply-To: <050.cb2ddf7ed167c7a185a18760753b8ced@haskell.org> References: <050.cb2ddf7ed167c7a185a18760753b8ced@haskell.org> Message-ID: <065.0f5c634bd55a1e359d0b0b8ae8867a60@haskell.org> #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8865, #11837 | Differential Rev(s): Phab:D2112 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"fa86ac7c14b67f27017d795811265c3a9750024b/ghc" fa86ac7c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fa86ac7c14b67f27017d795811265c3a9750024b" Make validDerivPred ignore non-visible arguments to a class type constructor Summary: GHC choked when trying to derive the following: ``` {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE PolyKinds #-} module Example where class Category (cat :: k -> k -> *) where catId :: cat a a catComp :: cat b c -> cat a b -> cat a c newtype T (c :: * -> * -> *) a b = MkT (c a b) deriving Category ``` Unlike in #8865, where we were deriving `Category` for a concrete type like `Either`, in the above example we are attempting to derive an instance of the form: ``` instance Category * c => Category (T * c) where ... ``` (using `-fprint-explicit-kinds` syntax). But `validDerivPred` is checking if `sizePred (Category * c)` equals the number of free type variables in `Category * c`. But note that `sizePred` counts both type variables //and// type constructors, and `*` is a type constructor! So `validDerivPred` erroneously rejects the above instance. The fix is to make `validDerivPred` ignore non-visible arguments to the class type constructor (e.g., ignore `*` is `Category * c`) by using `filterOutInvisibleTypes`. Fixes #11833. Test Plan: ./validate Reviewers: goldfire, hvr, simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2112 GHC Trac Issues: #11833 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 16:37:21 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 16:37:21 -0000 Subject: [GHC] #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint In-Reply-To: <050.cb2ddf7ed167c7a185a18760753b8ced@haskell.org> References: <050.cb2ddf7ed167c7a185a18760753b8ced@haskell.org> Message-ID: <065.2916d53a1a7e0bcb90929f0e91e62a45@haskell.org> #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8865, #11837 | Differential Rev(s): Phab:D2112 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 17:27:18 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 17:27:18 -0000 Subject: [GHC] #11656: Alllow static pointers to local closed definitions In-Reply-To: <044.9cd8af9f533a09aabdba922a1db355ab@haskell.org> References: <044.9cd8af9f533a09aabdba922a1db355ab@haskell.org> Message-ID: <059.7cdc5223cf74cf306e08b38674d0fd65@haskell.org> #11656: Alllow static pointers to local closed definitions -------------------------------------+------------------------------------- Reporter: mboes | Owner: | facundo.dominguez Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 11698 | Blocking: Related Tickets: | Differential Rev(s): Phab:D2104 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Facundo Dom?nguez ): In [changeset:"36d29f7ce332a2b1fbc36de831b0eef7a6405555/ghc" 36d29f7c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="36d29f7ce332a2b1fbc36de831b0eef7a6405555" StaticPointers: Allow closed vars in the static form. Summary: With this patch closed variables are allowed regardless of whether they are bound at the top level or not. The FloatOut pass is always performed. When optimizations are disabled, only expressions that go to the top level are floated. Thus, the applications of the StaticPtr data constructor are always floated. The CoreTidy pass makes sure the floated applications appear in the symbol table of object files. It also collects the floated bindings and inserts them in the static pointer table. The renamer does not check anymore if free variables appearing in the static form are top-level. Instead, the typechecker looks at the tct_closed flag to decide if the free variables are closed. The linter checks that applications of StaticPtr only occur at the top of top-level bindings after the FloatOut pass. The field spInfoName of StaticPtrInfo has been removed. It used to contain the name of the top-level binding that contains the StaticPtr application. However, this information is no longer available when the StaticPtr is constructed, as the binding name is determined now by the FloatOut pass. Test Plan: ./validate Reviewers: goldfire, simonpj, austin, hvr, bgamari Reviewed By: simonpj Subscribers: thomie, mpickering, mboes Differential Revision: https://phabricator.haskell.org/D2104 GHC Trac Issues: #11656 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 17:41:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 17:41:40 -0000 Subject: [GHC] #11656: Alllow static pointers to local closed definitions In-Reply-To: <044.9cd8af9f533a09aabdba922a1db355ab@haskell.org> References: <044.9cd8af9f533a09aabdba922a1db355ab@haskell.org> Message-ID: <059.de7e0728bcabb32a08c353de7cb45af9@haskell.org> #11656: Alllow static pointers to local closed definitions -------------------------------------+------------------------------------- Reporter: mboes | Owner: | facundo.dominguez Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 11698 | Blocking: Related Tickets: | Differential Rev(s): Phab:D2104 Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 19:06:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 19:06:58 -0000 Subject: [GHC] #12003: Improve error message about closed variables Message-ID: <056.291079845e9f4193cf006a03efaa31c3@haskell.org> #12003: Improve error message about closed variables -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple StaticPointers | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11656 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- After allowing local bindings in static definitions the following program {{{ {-# LANGUAGE StaticPointers #-} module M where f x = static g where g = h h = x }}} yields the error {{{ ../tmp/M.hs:4:7: error: ? ?g? is used in a static form but it is not closed. ? In the expression: static g In an equation for ?f?: f x = static g where g = h h = x }}} Where it would be more helpful to get a message like {{{ ../tmp/M.hs:4:7: error: ? ?g? is used in a static form but it is not closed because it uses ?h? which uses ?x? which is not let-bound. ? In the expression: static g In an equation for ?f?: f x = static g where g = h h = x }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 19:18:50 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 19:18:50 -0000 Subject: [GHC] #12003: Improve error message about closed variables In-Reply-To: <056.291079845e9f4193cf006a03efaa31c3@haskell.org> References: <056.291079845e9f4193cf006a03efaa31c3@haskell.org> Message-ID: <071.a78307401f98fbfe69c27b4d10374319@haskell.org> #12003: Improve error message about closed variables -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11656 | Differential Rev(s): Phab:D2167 Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: new => patch * differential: => Phab:D2167 @@ -23,1 +23,1 @@ - Where it would be more helpful to get a message like + where it would be more helpful to get a message like New description: After allowing local bindings in static definitions the following program {{{ {-# LANGUAGE StaticPointers #-} module M where f x = static g where g = h h = x }}} yields the error {{{ ../tmp/M.hs:4:7: error: ? ?g? is used in a static form but it is not closed. ? In the expression: static g In an equation for ?f?: f x = static g where g = h h = x }}} where it would be more helpful to get a message like {{{ ../tmp/M.hs:4:7: error: ? ?g? is used in a static form but it is not closed because it uses ?h? which uses ?x? which is not let-bound. ? In the expression: static g In an equation for ?f?: f x = static g where g = h h = x }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 19:19:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 19:19:16 -0000 Subject: [GHC] #12003: Improve error message about closed variables In-Reply-To: <056.291079845e9f4193cf006a03efaa31c3@haskell.org> References: <056.291079845e9f4193cf006a03efaa31c3@haskell.org> Message-ID: <071.846e57c51941d79a9df69849cf443805@haskell.org> #12003: Improve error message about closed variables -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11656 | Differential Rev(s): Phab:D2167 Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * cc: mboes (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 19:24:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 19:24:23 -0000 Subject: [GHC] #7353: Make system IO interruptible on Windows In-Reply-To: <048.cfc723cf8062d55ebdf5fa24c2f6c705@haskell.org> References: <048.cfc723cf8062d55ebdf5fa24c2f6c705@haskell.org> Message-ID: <063.26e3edb046d5d25286adf295776c0a36@haskell.org> #7353: Make system IO interruptible on Windows -------------------------------------+------------------------------------- Reporter: joeyadams | Owner: refold Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: => refold Comment: @refold that sounds great, thanks for doing this! Let me know if you need any help. In the mean time I'll assign the ticket to you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 21:56:54 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 21:56:54 -0000 Subject: [GHC] #12004: Windows unexpected failures Message-ID: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> #12004: Windows unexpected failures ----------------------------------------+--------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+--------------------------------- Not sure if these are known or not, sorry if they are. In the 8.0 branch, aab92412cf4cb77d988d36fb013018695c271ccd: {{{ OVERALL SUMMARY for test run started at Mon May 2 11:38:07 2016 PDT 0:40:00 spent to go through 5076 total tests, which gave rise to 14703 test cases, of which 9620 were skipped 73 had missing libraries 4857 expected passes 141 expected failures 0 caused framework failures 0 unexpected passes 12 unexpected failures 0 unexpected stat failures Unexpected failures: ghci.debugger/scripts break011 [bad stdout] (ghci) ghci/prog003 prog003 [bad exit code] (ghci) ghci/scripts T5566 [bad exit code] (ghci) rts testmblockalloc [bad exit code] (normal) rts/T11223 T11223_link_order_a_b_2_fail [bad exit code] (normal) rts/T11223 T11223_link_order_a_b_succeed [bad exit code] (normal) rts/T11223 T11223_link_order_b_a_2_succeed [bad exit code] (normal) rts/T11223 T11223_link_order_b_a_succeed [bad exit code] (normal) rts/T11223 T11223_simple_duplicate_lib [bad exit code] (normal) rts/T11223 T11223_simple_link [bad exit code] (normal) rts/T11223 T11223_simple_link_lib [bad exit code] (normal) rts/T11223 T11223_simple_unused_duplicate_lib [bad exit code] (normal) }}} In HEAD, 36d29f7ce332a2b1fbc36de831b0eef7a6405555: {{{ OVERALL SUMMARY for test run started at Mon May 2 14:07:48 2016 PDT 0:42:17 spent to go through 5112 total tests, which gave rise to 14803 test cases, of which 9680 were skipped 72 had missing libraries 4903 expected passes 140 expected failures 0 caused framework failures 0 unexpected passes 8 unexpected failures 0 unexpected stat failures Unexpected failures: ghci.debugger/scripts break011 [bad stdout] (ghci) ghci/prog003 prog003 [bad exit code] (ghci) partial-sigs/should_compile PatBind [exit code non-0] (normal) plugins plugins01 [bad exit code] (normal) rts T7037 [bad stdout] (normal) rts T9405 [bad exit code] (normal) rts testmblockalloc [bad exit code] (normal) rts/T11223 T11223_simple_duplicate_lib [bad exit code] (normal) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 21:58:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 21:58:08 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.ae33db9079b9301755041875f54005bc@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "break011.run.stdout" added. break011 output - master branch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 21:59:05 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 21:59:05 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.fa34d3ac4311753dd1776921fe3100de@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "prog003.run.stdout" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 21:59:43 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 21:59:43 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.2031ab31b9254cd306dba9b798ce6fd1@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "PatBind.comp.stderr" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:00:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:00:14 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.e5730d79183f341d4980da14411b251f@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "plugins01.run.stderr" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:00:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:00:22 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.3cd55d1e4fd0a0bba45f872dca26bc0e@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "plugins01.run.stdout" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:01:07 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:01:07 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.25e30c2cd483a6a3f197fa28138d3589@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "T9405.run.stderr" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:01:25 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:01:25 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.6933a1d72ca30061f5795f16d01d6dbe@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "T9405.run.stdout" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:02:20 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:02:20 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.cc5cb0d7d276e8f522e947ca38fa967c@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "testmblockalloc.run.stderr" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:05:01 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:05:01 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.beafadb3ffdc5c249f695c2ff629f412@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by enolan): * Attachment "T11223_simple_duplicate_lib.run.stderr" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:06:33 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:06:33 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.603f7ca1275ce91bede4383f7cfb599b@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Description changed by enolan: @@ -71,0 +71,2 @@ + + (attachments from the master branch) New description: Not sure if these are known or not, sorry if they are. In the 8.0 branch, aab92412cf4cb77d988d36fb013018695c271ccd: {{{ OVERALL SUMMARY for test run started at Mon May 2 11:38:07 2016 PDT 0:40:00 spent to go through 5076 total tests, which gave rise to 14703 test cases, of which 9620 were skipped 73 had missing libraries 4857 expected passes 141 expected failures 0 caused framework failures 0 unexpected passes 12 unexpected failures 0 unexpected stat failures Unexpected failures: ghci.debugger/scripts break011 [bad stdout] (ghci) ghci/prog003 prog003 [bad exit code] (ghci) ghci/scripts T5566 [bad exit code] (ghci) rts testmblockalloc [bad exit code] (normal) rts/T11223 T11223_link_order_a_b_2_fail [bad exit code] (normal) rts/T11223 T11223_link_order_a_b_succeed [bad exit code] (normal) rts/T11223 T11223_link_order_b_a_2_succeed [bad exit code] (normal) rts/T11223 T11223_link_order_b_a_succeed [bad exit code] (normal) rts/T11223 T11223_simple_duplicate_lib [bad exit code] (normal) rts/T11223 T11223_simple_link [bad exit code] (normal) rts/T11223 T11223_simple_link_lib [bad exit code] (normal) rts/T11223 T11223_simple_unused_duplicate_lib [bad exit code] (normal) }}} In HEAD, 36d29f7ce332a2b1fbc36de831b0eef7a6405555: {{{ OVERALL SUMMARY for test run started at Mon May 2 14:07:48 2016 PDT 0:42:17 spent to go through 5112 total tests, which gave rise to 14803 test cases, of which 9680 were skipped 72 had missing libraries 4903 expected passes 140 expected failures 0 caused framework failures 0 unexpected passes 8 unexpected failures 0 unexpected stat failures Unexpected failures: ghci.debugger/scripts break011 [bad stdout] (ghci) ghci/prog003 prog003 [bad exit code] (ghci) partial-sigs/should_compile PatBind [exit code non-0] (normal) plugins plugins01 [bad exit code] (normal) rts T7037 [bad stdout] (normal) rts T9405 [bad exit code] (normal) rts testmblockalloc [bad exit code] (normal) rts/T11223 T11223_simple_duplicate_lib [bad exit code] (normal) }}} (attachments from the master branch) -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:26:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:26:08 -0000 Subject: [GHC] #12005: Constraint instances not shown in `:info` Message-ID: <051.e0728f3c0e56a4361f8b5139b7d323c2@haskell.org> #12005: Constraint instances not shown in `:info` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ $ ghci -ignore-dot-ghci -XKindSignatures -XRank2Types -XConstraintKinds -XAllowAmbiguousTypes -XInstanceSigs GHCi, version 8.1.20160428: http://www.haskell.org/ghc/ :? for help Prelude> import Data.Kind Prelude Data.Kind> class Defer (p :: Constraint) where defer :: (p => r) -> r Prelude Data.Kind> instance Defer () where defer :: r -> r; defer = id Prelude Data.Kind> :i Defer class Defer (p :: Constraint) where defer :: (p => r) -> r {-# MINIMAL defer #-} -- Defined at :2:1 }}} Same happens with the [https://github.com/ekmett/constraints/blob/master/src/Data/Constraint/Deferrable.hs Data.Constraint.Deferrable] which defines: {{{#!hs instance (Typeable a, Typeable b) => Deferrable (a ~ b) instance (Deferrable a, Deferrable b) => Deferrable (a, b) instance (Deferrable a, Deferrable b, Deferrable c) => Deferrable (a, b, c) }}} but no instances are shown: {{{ ghci> import Data.Constraint.Deferrable ghci> :i Deferrable class Deferrable (p :: Constraint) where deferEither :: proxy p -> (p => r) -> Either String r {-# MINIMAL deferEither #-} -- Defined in ?Data.Constraint.Deferrable? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:47:27 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:47:27 -0000 Subject: [GHC] #12006: Can't infer constraint of pattern synonyms Message-ID: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> #12006: Can't infer constraint of pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: TypeSynonyms | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Can't infer constraint of: {{{#!hs -- pattern Real' :: Num a => a -> Complex a pattern Real' r <- r :+ _ where Real' r = r :+ 0 }}} {{{ teR4.hs:12:25: error: ? ? No instance for (Num t) arising from the literal ?0? Possible fix: add (Num t) to the context of the type signature for: Main.$bReal' :: t -> Complex t ? In the second argument of ?(:+)?, namely ?0? In the expression: r :+ 0 In an equation for ?$bReal'?: $bReal' r = r :+ 0 Compilation failed. }}} Should it be able to? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 22:57:51 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 22:57:51 -0000 Subject: [GHC] #12006: Can't infer constraint of pattern synonyms In-Reply-To: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> References: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> Message-ID: <066.3cec145e21b280491d34d51ffca963bb@haskell.org> #12006: Can't infer constraint of pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: TypeSynonyms => PatternSynonyms Comment: The problem here is that the type signature of the builder is fixed by the type of the matcher. By fixed, I mean literally fixed, we first typecheck the matcher with either the signature or infer the type and then we create an `Id` for the builder with precisely the same type. So the problem here is that the inferred type for the matcher doesn't require the `Num` constraint and so the builder type is `t -> Complex t` rather than `Num t => t -> Complex t` as you desire. From what I could work out from reading the source, the way it is like this is for mainly because of implementation problems. There is some more confused discussion on this ticket -https://ghc.haskell.org/trac/ghc/ticket/8581 - it is something I hope to look at again one day. Thank you for all these reports, they are very useful, I am interested in any pattern synonyms tickets so feel free to add me to cc to make sure that I see them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 23:13:32 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 23:13:32 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.10008381de237d1c2c6ed780f6d77b71@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: RyanGlScott Type: feature request | Status: patch Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 11837 | Blocking: Related Tickets: | Differential Rev(s): Phab:D2168 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2168 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 23:27:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 23:27:08 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.40246a9de22b369ea317ee534d4347a3@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Great responses, there are obviously no best practices yet for this extension. As the dust settles, will we only accept ''constructor-like'' patterns? Are non-constructor-like patterns wholly undesirable or are there examples where they are worth it? I personally use all of these to good effect, let's wait until we understand them better. Let's identify and categorise some of these examples: === Literal synonyms === Bidirectional patterns, nothing fancy {{{#!hs pattern I a = Identity a pattern K a = Const a pattern Less = LT }}} === ?Getter? patterns === Unidirectional patterns, these are essentially ?Getter?s {{{#!hs pattern Real r <- r :+ _ pattern Imaginary i <- _ :+ i }}} === Constructor-Like Patterns === (Implicitly) bidirectional patterns that don't lose information {{{#!hs pattern Real, Imaginary :: (Num a, Eq a) => a -> Complex pattern Real r = r :+ 0 (Implicitly) pattern Imaginary i = 0 :+ i }}} In this case this is the identity function on complex numbers: {{{#!hs f :: (Num a, Eq a) => Complex a -> Complex a f (Real r) = Real r f complex = complex }}} @ekmett argues for this property [https://github.com/ekmett/lens/issues/653 here]. === Non-Constructor-Like Patterns === Explicitly bidirectional patterns that do lose information {{{#!hs pattern Real, Imaginary :: Num a => a -> Complex a pattern Real r <- r :+ _ where Real r = r :+ 0 pattern Imaginary i <- _ :+ i where Imaginary i = 0 :+ i }}} We lose the constructor property, but matching never fails so it's closer to the lens `_realPart`. ---- We can keep this ticket open until the extension and understanding matures, same as #11349 where [https://github.com/RyanGlScott/proxied/blob/master/src/Data/Proxyless.hs Data.Proxyless] was created in response. It has been said of me that I embrace pattern synonyms to ?almost an absurd level? so someone needs to show restraint `:--)` tickets such as #11977 show that this extension still isn't even fully understood and I look forward to seeing how it evolves -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 23:28:57 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 23:28:57 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.a6e2612550dc0264a703542bfa81a443@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Since `Polar` was the pick of the litter, it's worth mentioning that with record syntax: {{{#!hs pattern Polar :: RealFloat a => a -> a -> Complex a pattern Polar {m, theta} <- (polar -> (m, theta)) where Polar m theta = mkPolar m theta }}} we can write {{{ ghci> (3 :+ 1) { m = 2 } 1.8973665961010275 :+ 0.6324555320336759 ghci> ghci> set (_polar._1) 2 (3 :+ 1) 1.8973665961010275 :+ 0.6324555320336759 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 2 23:49:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 02 May 2016 23:49:22 -0000 Subject: [GHC] #12006: Can't infer constraint of pattern synonyms In-Reply-To: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> References: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> Message-ID: <066.a871450e53b597724363d981931bc2c8@haskell.org> #12006: Can't infer constraint of pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Sure thing, I was starting to worry I was spamming with tickets :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 00:31:09 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 00:31:09 -0000 Subject: [GHC] #12007: Pattern families regression Message-ID: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code compiles fine for me in GHC 7.10.1, but fails in GHC 8.1.20160502 {{{ {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE ViewPatterns #-} data Foo a = Foo a a pattern A a1 a2 = Foo a1 a2 pattern B a1 a2 = A a1 a2 }}} The problem is the nested pattern. Compiling gives: {{{ [1 of 1] Compiling Main ( Bug1.hs, interpreted ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160502 for x86_64-unknown-linux): kindPrimRep.go rep_a85f Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 00:32:36 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 00:32:36 -0000 Subject: [GHC] #12007: Pattern families regression In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.b6065e4b1a70df595b1a8ec51525a3cf@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by MikeIzbicki): * version: 7.10.3 => 8.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 00:59:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 00:59:03 -0000 Subject: [GHC] #12007: Pattern families regression In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.b83b8c0a5dca857edc9d3a26f59b0520@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I think this only happens when loading the file into ghci? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 01:02:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 01:02:52 -0000 Subject: [GHC] #12007: Pattern families regression In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.1c2a4de5f262dc25a11badfd1b3c3dee@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Defining it in ghci seems to work {{{ ghci> data Foo a = Foo a a ghci> pattern A x y = Foo x y ghci> pattern B x y = A x y ghci> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 01:34:48 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 01:34:48 -0000 Subject: [GHC] #12007: Pattern families regression In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.21ce84a9f47243325ca895e4d6ad81b7@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * cc: goldfire (added) Comment: So I could trigger the same panic with the example here https://ghc.haskell.org/trac/ghc/ticket/11549#comment:1 with rc-3 but it is fixed in HEAD. Here is the core which I think is causing the panic. Maybe Richard can look and see if he thinks anything dodgy is going on? Maybe there is some improper use of runtime rep polymorphism. {{{ -- RHS size: {terms: 18, types: 21, coercions: 0} T12007.$mB :: forall r_a19o t_a19m. Foo t_a19m -> (t_a19m -> t_a19m -> r_a19o) -> (GHC.Prim.Void# -> r_a19o) -> r_a19o [GblId, Arity=3, Caf=NoCafRefs] T12007.$mB = \ (@ (rep_a19n :: GHC.Types.RuntimeRep)) (@ (r_a19o :: TYPE rep_a19n)) (@ t_a19m) (scrut_a19q :: Foo t_a19m) (cont_a19r :: t_a19m -> t_a19m -> r_a19o) (fail_a19s :: GHC.Prim.Void# -> r_a19o) -> let { cont1_a19h :: t_a19m -> t_a19m -> r_a19o [LclId, Arity=2] cont1_a19h = \ (a1_a18K :: t_a19m) (a2_a18L :: t_a19m) -> cont_a19r a1_a18K a2_a18L } in case scrut_a19q of { Foo a1_a18I a2_a18J -> cont_a19r a1_a18I a2_a18J } }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 02:03:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 02:03:26 -0000 Subject: [GHC] #12008: GHCi autocomplete text following cursor/insertion point Message-ID: <051.6865ab63c011178a397c82e9c802fac6@haskell.org> #12008: GHCi autocomplete text following cursor/insertion point -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The autocomplete doesn't look at what follows the cursor. `?` denotes insertion point, don't mind the smiley {{{ ghci> import Control.?.Fail }}} Tab is pressed, this is what I'd like happen: {{{ ghci> import Control.Monad.Fail }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 02:54:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 02:54:26 -0000 Subject: [GHC] #12007: Pattern families regression In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.2506fcb0e0ce8e83860d055db62dc3ea@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MikeIzbicki): Replying to [comment:4 mpickering]: > So I could trigger the same panic with the example here https://ghc.haskell.org/trac/ghc/ticket/11549#comment:1 with rc-3 > > but it is fixed in HEAD. > I just updated my GHC repo and rebuilt GHC today before submitting, so I thought I tested it with HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 04:52:32 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 04:52:32 -0000 Subject: [GHC] #9136: Constant folding in Core could be better In-Reply-To: <046.597f40143bfc9d7f6c9f647fe93147a2@haskell.org> References: <046.597f40143bfc9d7f6c9f647fe93147a2@haskell.org> Message-ID: <061.0c4a3ba9e8b736621959c4c38b7d8ece@haskell.org> #9136: Constant folding in Core could be better -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) Comment: I just came across the core output `((1 +# ((x -# 1) +# 1)) +# 1) +# 1` from some array indexing code, and thought that this kind of constant folding would be nice. However I don't have a standalone benchmark (yet) and consequently I don't know how much speed improvement could be achieved by the optimization. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 04:54:49 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 04:54:49 -0000 Subject: [GHC] #9136: Constant folding in Core could be better In-Reply-To: <046.597f40143bfc9d7f6c9f647fe93147a2@haskell.org> References: <046.597f40143bfc9d7f6c9f647fe93147a2@haskell.org> Message-ID: <061.f52971e5e6badbd09346c1a0c68109d0@haskell.org> #9136: Constant folding in Core could be better -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by maoe): * cc: maoe (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 06:22:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 06:22:37 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.c5fcbb4c6a578d84bb0dc994fcb4f71b@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: patch Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): phab:D2159 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by erikd): The whole issue arises because we enter the function `overwritingClosure` with a closure of type `WHITEHOLE` and that happens because `executeMessage` (in rts/Messages.c calls `doneWithMsgThrowTo`. So lets look at the interesting part of `executeMessage` with some extra comments explaining what I think is happening: {{{#!C void executeMessage (Capability *cap, Message *m) { const StgInfoTable *i; loop: write_barrier(); // allow m->header to be modified by another thread i = m->header.info; if (i == &stg_MSG_TRY_WAKEUP_info) { StgTSO *tso = ((MessageWakeup *)m)->tso; debugTraceCap(DEBUG_sched, cap, "message: try wakeup thread %ld", (W_)tso->id); tryWakeupThread(cap, tso); } else if (i == &stg_MSG_THROWTO_info) { MessageThrowTo *t = (MessageThrowTo *)m; uint32_t r; //** This shadows the outer variable named `i`, but that seems ok. const StgInfoTable *i; //** lockClosure writes `&stg_WHITEHOLE_info` to `p->header.info` and returns //** the old value of `p->header.info`. i = lockClosure((StgClosure*)m); //** t->header.info == &stg_WHITEHOLE_info if (i != &stg_MSG_THROWTO_info) { unlockClosure((StgClosure*)m, i); goto loop; } debugTraceCap(DEBUG_sched, cap, "message: throwTo %ld -> %ld", (W_)t->source->id, (W_)t->target->id); ASSERT(t->source->why_blocked == BlockedOnMsgThrowTo); ASSERT(t->source->block_info.closure == (StgClosure *)m); r = throwToMsg(cap, t); //** t->header.info == &stg_WHITEHOLE_info switch (r) { case THROWTO_SUCCESS: { // this message is done StgTSO *source = t->source; //** doneWithMsgThrowTo calls overwritingClosure with //** t->header.info == &stg_WHITEHOLE_info doneWithMsgThrowTo(t); tryWakeupThread(cap, source); break; } }}} @simonmar, on IRC you said that in `overwritingClosure` the closure type should not be `WHITEHOLE`, but the above code suggests that it can be. If the `t->header.info` value is supposed to be changed back to `&stg_MSG_THROWTO_info` (or something else), where is that supposed to happen? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 06:54:20 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 06:54:20 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 Message-ID: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Found this working on #11978. {{{ $ cat hello.hs main :: IO () main = putStrLn "Hello" $ ghc -fforce-recomp -prof -threaded -debug --make hello.hs -o hello [1 of 1] Compiling Main ( hello-world.hs, hello-world.o ) Linking hello ... $ ./hello +RTS -hb -DS -N1 7f68030c1700: cap 0: initialised Hello 7f68030c1700: cap 0: shutting down hello-world: internal error: ASSERTION FAILED: file rts/LdvProfile.c, line 48 (GHC version 7.10.3 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted }}} Also tried this with git HEAD and get the same result. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 07:13:23 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 07:13:23 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.1255f6866d9df346bc47f41451dae511@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): Adding a `printf` before the `ASSERT`: {{{#!C printf ("%s %d : era %u %lu\n", __func__, __LINE__, era, (LDVW(c) & LDV_CREATE_MASK) >> LDV_SHIFT) ; }}} results in: {{{ 7fca8b085700: cap 0: shutting down processHeapClosureForDead 47 : era 1 1 processHeapClosureForDead 47 : era 1 1 . . . processHeapClosureForDead 47 : era 1 1 processHeapClosureForDead 47 : era 1 1 processHeapClosureForDead 47 : era 1 715827882 hello: internal error: ASSERTION FAILED: file rts/LdvProfile.c, line 50 }}} The value `715827882` in hex is `0x2aaaaaaa`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 07:55:49 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 07:55:49 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows Message-ID: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> #12010: Incorrect return types for recv() and send() on Windows --------------------------------------+---------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 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: --------------------------------------+---------------------------------- They return signed 32 bit ints on Windows, even on a 64 bit OS, rather than Linux's 64 bit ssize_t. This means when recv() returned -1 to signal an error we thought it was 4294967295. It was converted to an int, -1 and the buffer was memcpy'd which caused a segfault. Other bad stuff happened with send()s. The problem is in `blockingReadRawBufferPtr` and `blockingWriteRawBufferPtr` in `GHC.IO.FD` which are only called in the threaded RTS. See also note CSsize in System.Posix.Internals. I have a patch and a test incoming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 08:26:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 08:26:41 -0000 Subject: [GHC] #12008: GHCi autocomplete text following cursor/insertion point In-Reply-To: <051.6865ab63c011178a397c82e9c802fac6@haskell.org> References: <051.6865ab63c011178a397c82e9c802fac6@haskell.org> Message-ID: <066.3d73d52379e7a58d4cab1e20cb5bf1db@haskell.org> #12008: GHCi autocomplete text following cursor/insertion point -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | 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: #10576, #11483 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: Geraldus (added) * type: bug => feature request * component: Compiler => GHCi * related: => #10576, #11483 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 08:28:38 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 08:28:38 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.fe915236b3dcddd91fb3fc0ac93541e5@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: patch Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): phab:D2159 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by simonmar): Yeah, this actually looks like a bug. `overwritingClosure()` wants to see the `MSG_THROWTO` closure, but we have locked it with `lockClosure()`, which replaces the header with a `WHITEHOLE`. We can't replace the header before calling `overwritingClosure()`, because that would cause race conditions - another thread could execute the `MSG_THROWTO`. We can't replace the header with `MSG_NULL` before calling `overwritingClosure()`, because a `MSG_NULL` is smaller than a `MSG_THROWTO`, and we won't overwrite the payload correctliy. So I think the only alternative is to have another version of `overwritingClosure()` that takes the size of the original closure as an argument. The size is `sizeofW(MessageThrowTo)`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 08:29:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 08:29:06 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.d0dd6dcf0cce92dca18bdd390dbccf8e@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: patch Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): phab:D2159 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by simonmar): Forgot to say: good catch! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 08:53:14 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 08:53:14 -0000 Subject: [GHC] #12007: Pattern families regression In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.c5a848dca8639154ea2217f7c6eeadb6@haskell.org> #12007: Pattern families regression -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Sorry I was unclear in my last comment. The examples form the comment triggered the same kind of error in older builds but are now fixed. I can still reproduce the error you report but only when loading the file into ghci. I'm suggesting that whatever check is used to reject the now fixed examples should also reject the internally generated matching function which causes this panic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 08:58:52 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 08:58:52 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci (was: Pattern families regression) In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.0fb99fac4aa695c96b4c123f02710b8d@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => PatternSynonyms -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 08:59:38 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 08:59:38 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.f0ce001b0541e965d8d03e073074f5ce@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Mike, does this happen for you when you compile the file normally? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 10:54:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 10:54:27 -0000 Subject: [GHC] #9868: ghc: panic! Dynamic linker not initialised In-Reply-To: <046.5f3f9e960e287bc6e82a07e7ce17a8b6@haskell.org> References: <046.5f3f9e960e287bc6e82a07e7ce17a8b6@haskell.org> Message-ID: <061.9aaea11ae4b37dc6bc712c252ec84fdb@haskell.org> #9868: ghc: panic! Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: Jamedjo | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 (Linker) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by k-bx): Having this problem after upgrading Ubuntu to 16.04. Trying to clear ~/.stack/snapshots/ and retry for now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 11:51:35 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 11:51:35 -0000 Subject: [GHC] #12006: Can't infer constraint of pattern synonyms In-Reply-To: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> References: <051.0010ab4b5d754f78b3aff41e20d7502c@haskell.org> Message-ID: <066.8d653fe80494ba8478d495abc5786ff4@haskell.org> #12006: Can't infer constraint of pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes, I think in principle it should be possible to infer a type that works for both builder and matcher. I'm not quite sure how hard that would be; probably not terrible. Of course you can always work around the difficulty by providing a signature. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 13:24:01 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 13:24:01 -0000 Subject: [GHC] #9868: ghc: panic! Dynamic linker not initialised In-Reply-To: <046.5f3f9e960e287bc6e82a07e7ce17a8b6@haskell.org> References: <046.5f3f9e960e287bc6e82a07e7ce17a8b6@haskell.org> Message-ID: <061.aa857e2f102ba620e5ba9fcde53b742d@haskell.org> #9868: ghc: panic! Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: Jamedjo | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 (Linker) | Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by k-bx): ^ this helped -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 14:33:43 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 14:33:43 -0000 Subject: [GHC] #11338: Unwind information is incorrect in region surrounding a safe foreign call In-Reply-To: <046.63160c8569d055bb9627f95207d1d3a0@haskell.org> References: <046.63160c8569d055bb9627f95207d1d3a0@haskell.org> Message-ID: <061.54cb9f8828a84c44fe7056429720ea97@haskell.org> #11338: Unwind information is incorrect in region surrounding a safe foreign call -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: #11337, #11353 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * cc: simonmar (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 14:33:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 14:33:58 -0000 Subject: [GHC] #11337: Unwind information incorrect between Sp adjustment and end of block In-Reply-To: <046.ad6cfe437905abbd08df71a5221c1d83@haskell.org> References: <046.ad6cfe437905abbd08df71a5221c1d83@haskell.org> Message-ID: <061.433f03f3abe67f12b2a41e56394e2a68@haskell.org> #11337: Unwind information incorrect between Sp adjustment and end of block -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Debugging | Unknown/Multiple information is incorrect | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * cc: simonmar (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 14:45:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 14:45:12 -0000 Subject: [GHC] #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 In-Reply-To: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> References: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> Message-ID: <061.f494d97ee18f4fe5ef60d23d5f62f065@haskell.org> #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 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.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 14:48:23 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 14:48:23 -0000 Subject: [GHC] #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 In-Reply-To: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> References: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> Message-ID: <061.ab13ddf09e4107736acbf9e32b36fa2a@haskell.org> #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: infoneeded Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc1 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): * status: new => infoneeded * failure: None/Unknown => Compile-time performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 14:51:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 14:51:58 -0000 Subject: [GHC] #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 In-Reply-To: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> References: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> Message-ID: <061.81378a2bf85f12ef74fe486a6785c3fc@haskell.org> #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc1 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): * status: infoneeded => new Comment: Oh dear, this one somehow slipped through the cracks during the release cycle; I'll try to have a look this week. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 14:52:08 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 14:52:08 -0000 Subject: [GHC] #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 In-Reply-To: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> References: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> Message-ID: <061.bd78b5a5cfdc2ce67413f4581951d189@haskell.org> #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc1 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: => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 18:01:49 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 18:01:49 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.94132c910766da9f3b94ac032bf6778c@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MikeIzbicki): Replying to [comment:8 mpickering]: > Mike, does this happen for you when you compile the file normally? No. It only happens when I load it in ghci. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 3 20:52:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 03 May 2016 20:52:03 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.808b17001986754494ccc6100774823b@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: 8.0.1 => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 01:46:38 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 01:46:38 -0000 Subject: [GHC] #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? Message-ID: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC.Magic says that GHC.Exts should be used instead, but only 'lazy' and 'inline' are rexported there, 'oneshot' and 'runRW#' are both not provided by GHC.Exts is this an oversight or deliberate? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 02:09:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 02:09:49 -0000 Subject: [GHC] #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() Message-ID: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() -------------------------------------+------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core | Version: Libraries | Keywords: | Operating System: Windows Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Winsock doesn't set errno, but it is checked in `blockingReadRawBufferPtr` and `blockingWriteRawBufferPtr` (both are in `GHC.IO.FD`). I the same thing happens in the non threaded RTS too, but that's in terms of primops and I don't understand it very well. The upshot here is that every error message originating from Winsock is wrong. Nobody noticed since any error used to just crash your program (#12010). Here's some MinGW documentation http://oldwiki.mingw.org/index.php/sockets and something from MSDN https://msdn.microsoft.com/en- us/library/windows/desktop/ms740121%28v=vs.85%29.aspx -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 05:12:51 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 05:12:51 -0000 Subject: [GHC] #12013: CallStack is available from base 4.8, not 4.9 Message-ID: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> #12013: CallStack is available from base 4.8, not 4.9 -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The documentation for `CallStack` claims it's available since 4.9 (ghc 8.0), but actually it's available since 4.8 (ghc 7.10). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 07:41:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 07:41:35 -0000 Subject: [GHC] #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? In-Reply-To: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> References: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> Message-ID: <060.9749994dbf17589e2eb8e6d7aeb5f591@haskell.org> #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think it's an oversight for `oneshot`, if someone would like to fix it. Not so sure about `runRW#`. It really is a pretty internal thing; I'm ok with having to import `GHC.Magic` for it. Open to opinions. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 07:51:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 07:51:46 -0000 Subject: [GHC] #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? In-Reply-To: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> References: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> Message-ID: <060.f5d55e85f3ae9545ad0ad3815cca159d@haskell.org> #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): > I think it's an oversight for oneshot, if someone would like to fix it. Agreed, and fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 07:52:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 07:52:00 -0000 Subject: [GHC] #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? In-Reply-To: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> References: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> Message-ID: <060.10da63f8e8e456cd71452485928ae7a0@haskell.org> #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"50e70559a0be07e5b836397d4aa8facf180510f9/ghc" 50e70559/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="50e70559a0be07e5b836397d4aa8facf180510f9" Export oneShot from GHC.Exts as suggested by carter in #12011. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 08:41:19 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 08:41:19 -0000 Subject: [GHC] #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 In-Reply-To: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> References: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> Message-ID: <061.05098b4caec83d6122a204abefd40d7c@haskell.org> #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc1 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: | -------------------------------------+------------------------------------- @@ -8,2 +8,1 @@ - {{{ - + {{{#!hs @@ -33,12 +32,8 @@ - -- it is just nested loop - the first Nat is the size of loop while the - second one is the number of loops - -- As a result we ALWAYS get 0. - - type family HeavyTF (n :: Nat) (i :: Nat) :: Nat where HeavyTF n 0 = 0 - HeavyTF n i = If - (HeavyTF' n :== 0) (HeavyTF n (i - 1)) 1 - - - type family HeavyTF' (n :: Nat) :: Nat where HeavyTF' 0 = 0 - HeavyTF' n = HeavyTF' (n - 1) - + + type family HeavyTF (n :: Nat) (i :: Nat) :: Nat where + HeavyTF n 0 = 0 + HeavyTF n i = If (HeavyTF' n :== 0) (HeavyTF n (i - 1)) 1 + + type family HeavyTF' (n :: Nat) :: Nat where + HeavyTF' 0 = 0 + HeavyTF' n = HeavyTF' (n - 1) @@ -49,2 +44,2 @@ - type instance NatOf Int = 12000 - type instance NatOf String = 12000 + type instance NatOf Int = 120 + type instance NatOf String = 120 @@ -53,3 +48,5 @@ - class PerfC1 a where perfc1 :: a -> String - instance CheckOk (HeavyTF 10 (NatOf a)) => PerfC1 a where perfc1 _ = "oh" - ; {-# INLINABLE perfc1 #-} + class PerfC1 a where + perfc1 :: a -> String + instance CheckOk (HeavyTF 10 (NatOf a)) => PerfC1 a where + perfc1 _ = "oh" + {-# INLINABLE perfc1 #-} @@ -58,1 +55,1 @@ - instance CheckOk 0 + instance CheckOk 0 -- where @@ -65,1 +62,0 @@ - @@ -69,1 +65,0 @@ - @@ -73,1 +68,0 @@ - @@ -77,1 +71,0 @@ - @@ -82,2 +75,2 @@ - {-# INLINABLE perfc1' #-} - + -- {-# INLINABLE perfc1' #-} + -- {-# NOINLINE perfc1' #-} @@ -87,1 +80,0 @@ - @@ -92,1 +84,1 @@ - {{{ + {{{#!hs @@ -102,1 +94,1 @@ - {{{ + {{{#!hs @@ -112,1 +104,1 @@ - {{{ + {{{#!hs @@ -181,1 +173,1 @@ - was trying to specidy the rewrite rules manually, but GHC rejects the + was trying to specify the rewrite rules manually, but GHC rejects the New description: Hello! I've just hit a strange issue. I might missinterpret how the `SPECIALIZE` pragma works, but if I understand correctly, then there is a bug in GHC. Lets consider this simple code: module `A`: {{{#!hs {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} module A where import Prelude import GHC.TypeLits -- TF utils type family (a :: Nat) :== (b :: Nat) where a :== a = 'True a :== b = 'False type family If cond (a :: Nat) (b :: Nat) where If 'True a b = a If 'False a b = b -- Heavy TF computations type family HeavyTF (n :: Nat) (i :: Nat) :: Nat where HeavyTF n 0 = 0 HeavyTF n i = If (HeavyTF' n :== 0) (HeavyTF n (i - 1)) 1 type family HeavyTF' (n :: Nat) :: Nat where HeavyTF' 0 = 0 HeavyTF' n = HeavyTF' (n - 1) -- Params for tests (bigger numbers = longer compile times) type family NatOf a :: Nat type instance NatOf Int = 120 type instance NatOf String = 120 -- Type class to check GHC behavior class PerfC1 a where perfc1 :: a -> String instance CheckOk (HeavyTF 10 (NatOf a)) => PerfC1 a where perfc1 _ = "oh" {-# INLINABLE perfc1 #-} class CheckOk (n :: Nat) instance CheckOk 0 -- where main_cache :: IO () main_cache = do print $ perfc1 (1 :: Int) print $ perfc1 ("a" :: String) perfc1_Int :: Int -> String perfc1_Int = perfc1 perfc1_String :: String -> String perfc1_String = perfc1 {-# SPECIALIZE perfc1 :: Int -> String #-} {-# SPECIALIZE perfc1 :: String -> String #-} ----- perfc1' :: PerfC1 a => a -> String perfc1' = perfc1 -- {-# INLINABLE perfc1' #-} -- {-# NOINLINE perfc1' #-} {-# SPECIALIZE perfc1' :: Int -> String #-} {-# SPECIALIZE perfc1' :: String -> String #-} }}} module `Test1`: {{{#!hs import A main = do print $ perfc1 (1 :: Int) print $ perfc1 ("a" :: String) }}} module `Test2`: {{{#!hs import A main = do print $ perfc1' (1 :: Int) print $ perfc1' ("a" :: String) }}} module `Test3`: {{{#!hs import A main = do print $ perfc1_Int (1 :: Int) print $ perfc1_String ("a" :: String) }}} Compile with: `ghc 7.10.3` : `ghc -O2 -fenable-rewrite-rules Test.hs` `ghc 8.0-rc1` : `ghc -O2 -fenable-rewrite-rules -freduction-depth=0 Test.hs` (I've used `-fenable-rewrite-rules` explicitly just to be sure it is enabled. We can omit it because `-O2` enables it) If module `A` was already compiled the compilation times for `ghc 7.10.3` were as follow: - `Test1`: ~ 16s - `Test2`: ~ 16s - `Test3`: almost instant And for `ghc 8.0-rc1` were as follow: - `Test1`: ~ 28s - `Test2`: ~ 28s - `Test3`: almost instant Here are 2 bugs to note: 1) the compilation times are much longer with new GHC 2) the specialize pragmas do not work **EDIT** There is yet another funny issue here. If I try to compile the modules like so: `time ghc -O2 -fenable-rewrite-rules -ddump-spec B.hs` GHC prints the following lines and hangs forever eating GBs of RAM: {{{ [1 of 2] Compiling A ( A.hs, A.o ) ==================== Specialise ==================== Result size of Specialise = {terms: 60, types: 80, coercions: 3,048,032} Rec { $dShow_a20B :: Show String [LclId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}] $dShow_a20B = GHC.Show.$fShow[]_$s$fShow[]1 $dPerfC1_a1Rk :: PerfC1 Int [LclId, Arity=1, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 60}] }}} **EDIT 2** I would like to take the opportunity here to ask a related question ? I was trying to specify the rewrite rules manually, but GHC rejects the following ones (It accepts one of them, but not both, somehow thinking that `perfcx` is monomorphic). I know that the rules are fired when GHC uses CORE, so typeclasses are "just normal polymorphic objects" and "hidden inputs", but are we able to specify them somehow? {{{ {-# RULES "perfcx/Int" forall (a :: Int). perfcx (a :: Int) = perfc1_Int a "perfcx/String" forall (b :: String). perfcx (b :: String) = perfc1_String b #-} perfcx = perfc1 {-# NOINLINE perfcx #-} [...] }}} But If I'm dumping the rules generated by GHC (using `-ddump-rules`) I can see both of the rules generated, so there probably is a way to define them: {{{ "SPEC perfc1'" [ALWAYS] forall ($dPerfC1 :: PerfC1 Int). perfc1' @ Int $dPerfC1 = $sperfc3 "SPEC perfc1'" [ALWAYS] forall ($dPerfC1 :: PerfC1 String). perfc1' @ String $dPerfC1 = $sperfc1 "SPEC/A perfc1 @ Int" [ALWAYS] forall (tpl :: PerfC1 Int). perfc1 @ Int tpl = $sperfc3 "SPEC/A perfc1 @ String" [ALWAYS] forall (tpl :: PerfC1 String). perfc1 @ String tpl = $sperfc1 }}} -- Comment (by bgamari): {{{ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 09:40:43 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 09:40:43 -0000 Subject: [GHC] #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 In-Reply-To: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> References: <046.16fee1c0ad28881e1f272636dfd13b83@haskell.org> Message-ID: <061.18ffad00446cfa6524f5c8121be5bb95@haskell.org> #11443: SPECIALIZE pragma does not work + compilation times regression in GHC 8.0-rc1 -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Looking at the `verbose-core2core` output from `Test2` it seems quite clear that the specialisation rules are firing as expected: While the `dump-ds` output contains an application of `perfc1' @Int ...` as expected, this is rewritten to `A.$sperfc3 ...` in the first simplifier phase (where `$sperfc3` is indeed the expected `Int`-specialised binding). So, the question is: why are things slowing down despite this? I know that Richard did make some changes in how type families are reduced (see 3f5d1a13f112f34d992f6b74656d64d95a3f506d and 3e1b8824c849d063c7354dbdf63ae2910cf0fdfc). Perhaps the next place to look is the tc-trace output. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 11:18:53 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 11:18:53 -0000 Subject: [GHC] #11999: expressing injectivity on functional dependencies gives orphan instances warnings In-Reply-To: <049.e1a894cc5c9f0aa2059ef87b6b697a86@haskell.org> References: <049.e1a894cc5c9f0aa2059ef87b6b697a86@haskell.org> Message-ID: <064.8ba858ac74df9796966f02ea6f7fc8aa@haskell.org> #11999: expressing injectivity on functional dependencies gives orphan instances warnings -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dredozubov): This code comment was brought to my attention on IRC: [https://ghc.haskell.org/trac/ghc/ticket/11999 ] It mentions this issue, but it still feels like a broken behavior to me. I'll leave it to the people more knowledgeable that me to decide if that's can be considered a bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 11:18:58 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 11:18:58 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows In-Reply-To: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> References: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> Message-ID: <060.7461134a3c5afdef171756a8242b00ad@haskell.org> #12010: Incorrect return types for recv() and send() on Windows -----------------------------------+-------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -----------------------------------+-------------------------------------- Changes (by enolan): * status: new => patch * differential: => Phab:D2170 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 11:47:52 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 11:47:52 -0000 Subject: [GHC] #11999: expressing injectivity on functional dependencies gives orphan instances warnings In-Reply-To: <049.e1a894cc5c9f0aa2059ef87b6b697a86@haskell.org> References: <049.e1a894cc5c9f0aa2059ef87b6b697a86@haskell.org> Message-ID: <064.e758380a14db3f73c4d89e2840d3291c@haskell.org> #11999: expressing injectivity on functional dependencies gives orphan instances warnings -------------------------------------+------------------------------------- Reporter: dredozubov | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rahulmutt): > Note [When exactly is an instance decl an orphan?] > ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ > (see MkIface.instanceToIfaceInst, which implements this) > Roughly speaking, an instance is an orphan if its head (after the =>) > mentions nothing defined in this module. > > Functional dependencies complicate the situation though. Consider > > module M where { class C a b | a -> b } > > and suppose we are compiling module X: > > module X where > import M > data T = ... > instance C Int T where ... > > This instance is an orphan, because when compiling a third module Y we > might get a constraint (C Int v), and we'd want to improve v to T. So > we must make sure X's instances are loaded, even if we do not directly > use anything from X. This part of the note explains why your example would be considered an orphan instance. Otherwise you can define instances that may not be "seen" as intended. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 13:01:58 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 13:01:58 -0000 Subject: [GHC] #11959: Importing doubly exported pattern synonym and associated pattern synonym panics In-Reply-To: <046.6ec5a340ae5bc3bfa0a1a054dcc8ecc7@haskell.org> References: <046.6ec5a340ae5bc3bfa0a1a054dcc8ecc7@haskell.org> Message-ID: <061.1739ee076f2ad00a7d4a15f53180abd3@haskell.org> #11959: Importing doubly exported pattern synonym and associated pattern synonym panics -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc3 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): Phab:D2132, Wiki Page: | Phab:D2133 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"4f2afe1e674606230f2dc2f8ce040a2bd345a647/ghc" 4f2afe1/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4f2afe1e674606230f2dc2f8ce040a2bd345a647" testsuite: Add test for #11959 Test Plan: Validate, expected to fail Reviewers: goldfire, austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2132 GHC Trac Issues: #11959 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 13:01:58 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 13:01:58 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.f66e885c45a922a346e8d4abd85eb7d3@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b75d1940dd3362382c0bc94018a9045c2def82a9/ghc" b75d1940/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b75d1940dd3362382c0bc94018a9045c2def82a9" Be more aggressive when checking constraints for custom type errors. This fixes #11990. The current rule is simpler than before: if we encounter an unsolved constraint that contains any mentions of properly applied `TypeError`, then we report the type error. If there are multiple `TypeErrors`, then we just report one of them. Reviewers: simonpj, bgamari, austin Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2151 GHC Trac Issues: #11990 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 13:46:29 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 13:46:29 -0000 Subject: [GHC] #12014: Make it possible to deprecate a method instantiation of a typeclass instance Message-ID: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> #12014: Make it possible to deprecate a method instantiation of a typeclass instance -------------------------------------+------------------------------------- Reporter: niteria | Owner: Type: feature | Status: new request | 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: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider: {{{ module A where data Foo = Foo instance Eq Foo where -- {-# DEPRECATED (==) "Deprecated for no reason as well" #-} _a == _b = True {-# DEPRECATED (==.) "Deprecated for no reason" #-} (==.) :: Foo -> Foo -> Bool (==.) _a _b = True }}} Deprecating `(==.)` is possible, but it's not possible to deprecate `(==)` of the `Eq Foo` instance. I'd be useful for my use-case of finding out where `Ord Unique` is used, as these would be a potential sources of non-determinism. Currently the best I can do is to remove the instance, get a compile error, suppress it by fixing up the code and repeat for every affected file. I imagine it would also be useful if a method turned out to be a bad idea for a particular type and the library author tried to phase it out. It could be that one method is implementable, but has terrible performance. For my use-case I would be happy with instance level granularity. Related (but not quite the same): * https://ghc.haskell.org/trac/ghc/wiki/Design/DeprecationMechanisms#Classmethoddeprecation * https://ghc.haskell.org/trac/ghc/wiki/Design/DeprecationMechanisms/TypeClassMethods -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 13:46:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 13:46:48 -0000 Subject: [GHC] #12014: Make it possible to deprecate a method instantiation of a typeclass instance In-Reply-To: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> References: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> Message-ID: <061.6c39fcd2f5d271dbd8d3dc4dcf8c9911@haskell.org> #12014: Make it possible to deprecate a method instantiation of a typeclass instance -------------------------------------+------------------------------------- Reporter: niteria | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by niteria): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 17:16:33 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 17:16:33 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.e5a98abc5473d7592e8c83b9ad98976c@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"ad4392c142696d5092533480a82ed65322e9d413/ghc" ad4392c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ad4392c142696d5092533480a82ed65322e9d413" Kill non-deterministic foldUFM in TrieMap and TcAppMap Summary: foldUFM introduces unnecessary non-determinism that actually leads to different generated code as explained in Note [TrieMap determinism]. As we're switching from UniqFM to UniqDFM here you might be concerned about performance. There's nothing that ./validate detects. nofib reports no change in Compile Allocations, but Compile Time got better on some tests and worse on some, yielding this summary: -1 s.d. ----- -3.8% +1 s.d. ----- +5.4% Average ----- +0.7% This is not a fair comparison as the order of Uniques changes what GHC is actually doing. One benefit from making this deterministic is also that it will make the performance results more stable. Full nofib results: P108 Test Plan: ./validate, nofib Reviewers: goldfire, simonpj, simonmar, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2169 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 17:30:17 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 17:30:17 -0000 Subject: [GHC] #11830: Disabling idle GC leads to freeze In-Reply-To: <051.01e036a0222a29198e3a9c508112fb05@haskell.org> References: <051.01e036a0222a29198e3a9c508112fb05@haskell.org> Message-ID: <066.18eef023be96e64557cbd71dc77f226f@haskell.org> #11830: Disabling idle GC leads to freeze -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Runtime System | Version: 8.0.1-rc3 Resolution: fixed | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2129 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: The commit in comment:9 isn't quite the whole story due to lacking synchronization. This is cleaned up in the rework of the itimer subsystem in 999c464da36e925bd4ffea34c94d3a7b3ab0135c (which also addresses #11965). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 17:32:15 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 17:32:15 -0000 Subject: [GHC] #10840: Periodic alarm signals can cause a retry loop to get stuck In-Reply-To: <049.c792fb7fbab25e12997f6231b1f3472d@haskell.org> References: <049.c792fb7fbab25e12997f6231b1f3472d@haskell.org> Message-ID: <064.2949967eb636b3cf4ef4a052a83c3ba4@haskell.org> #10840: Periodic alarm signals can cause a retry loop to get stuck -------------------------------------+------------------------------------- Reporter: Rufflewind | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The hangs should now be fixed. I'll try reenabling `USE_PTHREAD_FOR_ITIMER` once I have access to the OS X test again. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 17:56:37 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 17:56:37 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.8d3f2c4279acf507e8b7f64fe2212efd@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): phab:D2159 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * status: patch => new * milestone: => 8.0.2 Comment: The previous patch didn't fix the underlying issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 18:01:24 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 18:01:24 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.59f0041b93440190b0f31327801abdc1@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * status: new => patch * differential: phab:D2159 => Phab:D2174 Comment: It actually turns out this was pretty easy to fix (assuming Phab:D2174 indeed is a fix). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 19:18:21 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 19:18:21 -0000 Subject: [GHC] #12013: CallStack is available from base 4.8, not 4.9 In-Reply-To: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> References: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> Message-ID: <059.59b61942843315cf16d7810ac9167831@haskell.org> #12013: CallStack is available from base 4.8, not 4.9 -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Does it? It looks like it claims it's been available since `base-4.8.1.0` [http://git.haskell.org/ghc.git/blob/ad4392c142696d5092533480a82ed65322e9d413:/libraries/base/GHC/Stack/Types.hs#l132 here]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 20:16:55 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 20:16:55 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.ba048d241a7a08411c2d00a453792d8b@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): * owner: => erikd -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 4 20:45:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 04 May 2016 20:45:40 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.c6a3a922d28d1c28010d199707addb18@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: erikd Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by erikd): * owner: => erikd -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 00:02:35 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 00:02:35 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.89a120c5a5b185a1a2ef1a637e0c8aed@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: erikd Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by erikd): With @bgamari's ok, I've taken ownership of this ticket. I have a fix very similar to Ben's (with an extra `ASSERT`) and a test. However the test also triggers the bug in #12009 so I need to fix that bug before I can commit the fix and test for this one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 00:03:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 00:03:19 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.1bdadf6cb4902d81b35fafbfc28f1cf6@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): The test I have for #11978 triggers this `ASSERT` as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 02:48:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 02:48:44 -0000 Subject: [GHC] #11768: Need a way to attach Haddock documentation to derived instances In-Reply-To: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> References: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> Message-ID: <061.1b8b8ecd41b84241edbb663531234868@haskell.org> #11768: Need a way to attach Haddock documentation to derived instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11767 | Differential Rev(s): Phab:D2175 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2175 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 04:00:47 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 04:00:47 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.a82baf7ba1a91f61f2639b4a9d5bf85b@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): Wow, this is interesting. Note that I am running the test program with `+RTS -hb -DS -N1` and its crashing in `processNurseryForDead` which has some code that looks like: {{{ p = bd->start; while (p < bd->free) { while (p < bd->free && !*p) p++; // skip slop if (p >= bd->free) break; }}} The line with the `skip slop` comment is the interesting one. It assumes that if the block descriptor we are currently looking at is not full, then the memory from `bd->start` to `bd-free` with be all zeros. However, this is not the case when the RTS flags include `-DS` which turns on sanity checking. One part of this sanity checking is in the function `resetNurseries` of the file `rts/sm/Storage.c` which does this: {{{ IF_DEBUG(sanity, memset(bd->start, 0xaa, BLOCK_SIZE)); }}} That is, it fills the block with `0xaa` bytes which causes the "skip slop" code in `processNurseryForDead` to incorrectly skip the slop at the start of the block. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 05:49:43 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 05:49:43 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.1c9726ba6d45a1bd39e85148a10ceb12@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): The following patch prevents the crash, but may result in in-correct heap profiling results: {{{#!diff diff --git a/rts/LdvProfile.c b/rts/LdvProfile.c index 1dfdc56..43a47aa 100644 --- a/rts/LdvProfile.c +++ b/rts/LdvProfile.c @@ -184,7 +184,14 @@ processNurseryForDead( void ) for (bd = MainCapability.r.rNursery->blocks; bd != NULL; bd = bd->link) { p = bd->start; while (p < bd->free) { + // The start of the block may be zero filled which we need to skip + // over. while (p < bd->free && !*p) p++; // skip slop + + // In debug mode, with sanity checking enabled, start of the block + // may be filled with `0xaa` so if we find it, we just break. + IF_DEBUG(sanity, if (*((StgWord32*)p) == 0xaaaaaaaa) break;); + if (p >= bd->free) break; p += processHeapClosureForDead((StgClosure *)p); } }}} Maybe we could print a warning about inaccuracey if debug sanity checking is on in profiling mode. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 07:46:41 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 07:46:41 -0000 Subject: [GHC] #11768: Need a way to attach Haddock documentation to derived instances In-Reply-To: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> References: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> Message-ID: <061.6fda163dd57b3b25d964ffb15da59ec6@haskell.org> #11768: Need a way to attach Haddock documentation to derived instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11767 | Differential Rev(s): Phab:D2175 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): See [[https://github.com/haskell/haddock/pull/499/files|Haddock #499]] for the Haddock piece of this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 10:54:15 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 10:54:15 -0000 Subject: [GHC] #12014: Make it possible to deprecate a method instantiation of a typeclass instance In-Reply-To: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> References: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> Message-ID: <061.80b8dd2b1f12d8610356c709d81b71c7@haskell.org> #12014: Make it possible to deprecate a method instantiation of a typeclass instance -------------------------------------+------------------------------------- Reporter: niteria | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Good idea in principle -- but fragile. E.g. {{{ f :: Eq a => a -> a -> Bool f x y = not (x == y) blah = f Foo Foo }}} At the call of `f` GHC can't see that you are ultimately going to use the `(==)` method of the `Eq` dictionary passed to `f`. So would you expect to get a deprecation message here? If you think about what it translates to, it's a bit like {{{ blah = f (eqFoo, neqFoo) Foo Foo }}} where the tuple argument is the dictionary. If you wrote it like that you'd get deprecations for both `eqFoo` and `newFoo` even though only one of them is ultimately actually called. I don't think I see a useful, robust path here, yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 11:16:48 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 11:16:48 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.f539cb253defbaee66fe0dca3fffdfed@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): I've ran into this two times, both regressions since GHC rc3. The two cases are: * https://github.com/ndmitchell/hlint/blob/master/src/HSE/Bracket.hs needBracket (currently at a438ba0e45697e65bbcd9fb996d350b07394a45f) * https://github.com/ndmitchell/derive/blob/master/src/Language/Haskell/TH/Peephole.hs peep (currently at 6a703a9f71986232bbb1e54853a548af2b53b706) Is there any recommendation on how I can avoid this warning without CPP in a way that works on older versions of GHC? In contrast to the original reporter, I do not welcome that GHC emits this warning. It seems a warning about GHC, not my code, and not something that I can do much about, other than turn off warnings, which seems a little sad. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 12:21:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 12:21:29 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.bc25eedfda729c244c44dd8ababe4640@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => gkaracha Comment: George, this seems odd. First, there's nothing complicated about the example, so why is it hard. Second, why has it regressed since 8.0? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 12:27:32 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 12:27:32 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.2ab11981d7d2cce50637d94b3aac7147@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Replying to [comment:4 simonpj]: > why has it regressed since 8.0? Herbert made the following change recently, in Phab:D2095: {{{#!diff - maxPmCheckIterations = 10000000, + maxPmCheckIterations = 2000000, }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 12:56:24 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 12:56:24 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.d1cba28ee6ff530f205b4a1480e1e4d2@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): I observe there are 5 instances in the GHC compiler where the revised limit was insufficient. That seems quite a high false-positive rate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 13:13:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 13:13:44 -0000 Subject: [GHC] #12002: Pragmas after a module declaration are ignored without warning. In-Reply-To: <050.a06dfff8e83390aaf98ce91845f96e30@haskell.org> References: <050.a06dfff8e83390aaf98ce91845f96e30@haskell.org> Message-ID: <065.c59c043a59be686eb49a7a1b60f0922d@haskell.org> #12002: Pragmas after a module declaration are ignored without warning. -------------------------------------+------------------------------------- Reporter: seanparsons | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > this would be incredibly baffling (it was for me), it would be nice to see a warning for this at the least I agree! Anyone want to offer a patch? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 13:15:47 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 13:15:47 -0000 Subject: [GHC] #9696: readRawBufferPtr and writeRawBufferPtr allocate memory In-Reply-To: <052.b427ad2427779cbbeba69c4df93a91d2@haskell.org> References: <052.b427ad2427779cbbeba69c4df93a91d2@haskell.org> Message-ID: <067.e9d171b2cdb2bf912d2bd461599dc4f7@haskell.org> #9696: readRawBufferPtr and writeRawBufferPtr allocate memory -------------------------------------+------------------------------------- Reporter: mergeconflict | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.8.3 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 thomie): * keywords: newcomer => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 13:21:04 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 13:21:04 -0000 Subject: [GHC] #8990: Performance tests behave differently depending on presence of .hi file (even with -fforce-recomp) In-Reply-To: <045.abd2027873a2b9d9a2bc9aa2b4b749ea@haskell.org> References: <045.abd2027873a2b9d9a2bc9aa2b4b749ea@haskell.org> Message-ID: <060.dcc777577c61b02d6a782df4302f63af@haskell.org> #8990: Performance tests behave differently depending on presence of .hi file (even with -fforce-recomp) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.9 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:D1187 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: newcomer => * owner: => thomie * differential: => Phab:D1187 Comment: I think Phab:D1187 will fix this one as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 16:28:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 16:28:03 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.66fe30df4f164050447c674ebc0609c8@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I have learned a bit more. * Here is a smaller test case {{{ pattern A a1 = a1 pattern B a1 = A a1 }}} * The bug is that `kindRep` falls over. I'm pretty sure it's the call from `typePrimRep`. * The code spat out by `CorePrep` is absolutely fine. * The crash comes when the bytecode codegen gets hold of it. I wish I knew ''which'' call to `typePrimRep` in the bytecode generator was causing the crash. Maybe someone can try stack-tracing (with our new lightweight `CallStack` stuff) to narrow it down? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 16:34:51 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 16:34:51 -0000 Subject: [GHC] #12014: Make it possible to deprecate a method instantiation of a typeclass instance In-Reply-To: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> References: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> Message-ID: <061.73e47f93eb9fc86cafefd993ee0cd6a7@haskell.org> #12014: Make it possible to deprecate a method instantiation of a typeclass instance -------------------------------------+------------------------------------- Reporter: niteria | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Deprecating the whole instance should be possible though, right? We could emit the deprecation message whenever the typechecker uses the instance. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 17:13:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 17:13:33 -0000 Subject: [GHC] #12015: Add conditional CallStack constraints to common partial utility functions Message-ID: <046.b74d0515b345cdd045765b55c27f0b21@haskell.org> #12015: Add conditional CallStack constraints to common partial utility functions -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- There are a variety of common utility functions used throughout GHC which are partial (e.g. many of the helpers in `Type`, for instance, `kindPrimRep`). It would be great if [ImplicitCallStacks] would identify their callers. However, we likely don't want to pay the cost of passing around `CallStacks` during normal compilation so I propose we make them conditional on `DEBUG`. That is, define {{{#!hs #if DEBUG type DebugCallStack = CallStack #else type DebugCallStack = (() :: Constraint) #endif }}} Now we can sprinkle `DebugCallStack` constraints about GHC and get the best of both worlds! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 17:25:48 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 17:25:48 -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.0c562d2a5e61d91a02273ddbfa65286c@haskell.org> #3427: control what sort of entity a deprecated pragma applies to -------------------------------------+------------------------------------- Reporter: igloo | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 6.10.4 Resolution: | Keywords: deprecate | warning Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => deprecate warning * priority: low => normal -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 18:06:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 18:06:23 -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.3840690eece492f7a0283c2f3dd974c9@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: 8.2.1 Component: Compiler | Version: 6.10.4 Resolution: | Keywords: deprecate | warning 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 thoughtpolice): * owner: => thoughtpolice * milestone: => 8.2.1 Comment: By popular demand (read: me), I'm probably going to fix this, because it is super, super annoying in my `ed25519` library, where I want to deprecate some constructors, *not* types, but the types and constructors have the same name. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 18:21:30 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 18:21:30 -0000 Subject: [GHC] #12016: Allow wildcards in type synonyms and data declarations Message-ID: <051.25982c21d04ab8006e28de59d7da7e1e@haskell.org> #12016: Allow wildcards in type synonyms and data declarations -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: lowest | Milestone: Component: Compiler | Version: (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs data Konst a _ = Konst a type Const a _ = a type Tagged _ b = b type Forget m a _ = a -> m }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 18:49:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 18:49:27 -0000 Subject: [GHC] #12014: Make it possible to deprecate a method instantiation of a typeclass instance In-Reply-To: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> References: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> Message-ID: <061.eb6aaf59320c72d258e76caaf0da1c15@haskell.org> #12014: Make it possible to deprecate a method instantiation of a typeclass instance -------------------------------------+------------------------------------- Reporter: niteria | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:3 simonmar]: > Deprecating the whole instance should be possible though, right? We could emit the deprecation message whenever the typechecker uses the instance. That would be quite possible, yes, and more robust. The challenge then is the user interface. Possibly {{{ instance Eq Foo where {-# DEPRECATED "Don't use the Eq instance of Foo" #-} }}} This would be fantastic if you want to remove the Eq instance. Not to hard to do if someone wants to try. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 18:53:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 18:53:18 -0000 Subject: [GHC] #12015: Add conditional CallStack constraints to common partial utility functions In-Reply-To: <046.b74d0515b345cdd045765b55c27f0b21@haskell.org> References: <046.b74d0515b345cdd045765b55c27f0b21@haskell.org> Message-ID: <061.505f116d5006bcccc5224f2b4bd04745@haskell.org> #12015: Add conditional CallStack constraints to common partial utility functions -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm all for it! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 19:08:55 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 19:08:55 -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.d8c93158b154ed886f71c2de235abfe9@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: 8.2.1 Component: Compiler | Version: 6.10.4 Resolution: | Keywords: deprecate | warning Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Good! Use the same syntax as the disambiguation in export lists though! Also `pattern`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 19:44:02 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 19:44:02 -0000 Subject: =?utf-8?q?=5BGHC=5D_=2312017=3A_GHC_panics_on_pattern_synonym_?= =?utf-8?b?4oCYa2luZFByaW1SZXDigJk=?= Message-ID: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> #12017: GHC panics on pattern synonym ?kindPrimRep? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language PatternSynonyms, GADTs #-} data Ty a where B :: Ty Bool class (Eq a, Ord a, Show a) => GetTy a where getTy :: Ty a instance GetTy Bool where getTy = B data Exp a where Constant :: GetTy a => Ty a -> a -> Exp a pattern MkBool :: () => (GetTy t, Bool ~ t) => t -> Exp t pattern MkBool bool = Constant B bool pattern Tru :: () => Bool ~ t => Exp t pattern Tru = MkBool True }}} with head: {{{ $ ghci -ignore-dot-ghci /tmp/tywM.hs GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tywM.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20160503 for x86_64-unknown-linux): kindPrimRep.go rep_a2tC Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} {{{#!hs pattern Tru :: () => Bool ~ t => Exp t pattern Tru = Constant B True }}} works fine -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 19:49:43 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 19:49:43 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312017=3A_GHC_panics_on_pattern_syno?= =?utf-8?b?bnltIOKAmGtpbmRQcmltUmVw4oCZ?= In-Reply-To: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> References: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> Message-ID: <066.4d256f729258d70faa1780316664bc3e@haskell.org> #12017: GHC panics on pattern synonym ?kindPrimRep? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Simplied {{{#!hs {-# Language PatternSynonyms, GADTs #-} data Exp a where Constant :: a -> Exp a pattern MkBool :: Bool -> Exp Bool pattern MkBool bool = Constant bool pattern Tru :: Exp Bool pattern Tru = MkBool True }}} this breaks my stuff, but it's easy to work around. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 19:52:56 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 19:52:56 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312017=3A_GHC_panics_on_pattern_syno?= =?utf-8?b?bnltIOKAmGtpbmRQcmltUmVw4oCZ?= In-Reply-To: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> References: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> Message-ID: <066.fb3bb948308253fe225762e68655b170@haskell.org> #12017: GHC panics on pattern synonym ?kindPrimRep? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: duplicate | 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 simonpj): * status: new => closed * resolution: => duplicate Comment: Always worth searching to see if someone has already reported! Dup of #12007 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 5 20:05:02 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 05 May 2016 20:05:02 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312017=3A_GHC_panics_on_pattern_syno?= =?utf-8?b?bnltIOKAmGtpbmRQcmltUmVw4oCZ?= In-Reply-To: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> References: <051.31f2b549405e2b57184a9c30d79d4112@haskell.org> Message-ID: <066.322e129663b9b6b771bd9bab05cb42f4@haskell.org> #12017: GHC panics on pattern synonym ?kindPrimRep? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: duplicate | 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): How embarrassing, I even commented on that ticket so there is no excuse :) thanks Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 00:23:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 00:23:26 -0000 Subject: [GHC] #11970: Simplify Parent for patten synonyms In-Reply-To: <046.99b58fbbe4691b1cc88a00dd47c4a70f@haskell.org> References: <046.99b58fbbe4691b1cc88a00dd47c4a70f@haskell.org> Message-ID: <061.e3cc7b0dd39b874eacbe1f151392eb42@haskell.org> #11970: Simplify Parent for patten synonyms -------------------------------------+------------------------------------- Reporter: simonpj | Owner: mpickering Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I have finally finished this small refactoring. The overloaded record stuff complicated quite a bit and makes the implementation very ugly. I will put a diff up tomorrow once I have validated locally. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 01:42:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 01:42:11 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.f400a4e82def7f9c2ca2f333a73771cc@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: erikd Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by erikd): Even with the `MSG_THROWTO` issue with `overwritingClosure()` fixed, I'm still getting a failure for the assertion I added. The back trace looks like: {{{ T11978b: internal error: ASSERTION FAILED: file includes/rts/storage/ClosureMacros.h, line 551 (GHC version 8.1.20160504 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Program received signal SIGABRT, Aborted. [Switching to Thread 0x7fffcaffd700 (LWP 30814)] 0x00007ffff6ec0478 in __GI_raise (sig=sig at entry=6) at ../sysdeps/unix/sysv/linux/raise.c:55 55 ../sysdeps/unix/sysv/linux/raise.c: No such file or directory. (gdb) bt #0 0x00007ffff6ec0478 in __GI_raise (sig=sig at entry=6) at ../sysdeps/unix/sysv/linux/raise.c:55 #1 0x00007ffff6ec18fa in __GI_abort () at abort.c:89 #2 0x00000000004dc8bc in rtsFatalInternalErrorFn (s=0x550808 "ASSERTION FAILED: file %s, line %u\n", ap=0x7fffcaff8cb8) at rts/RtsMessages.c:182 #3 0x00000000004dc4ee in barf (s=0x550808 "ASSERTION FAILED: file %s, line %u\n") at rts/RtsMessages.c:46 #4 0x00000000004dc551 in _assertFail (filename=0x54c3c0 "includes/rts/storage/ClosureMacros.h", linenum=551) at rts/RtsMessages.c:61 #5 0x00000000004c7127 in overwritingClosure (p=0x200180748) at includes/rts/storage/ClosureMacros.h:551 #6 0x00000000004e031d in threadPaused (cap=0x7b6340, tso=0x200087c00) at rts/ThreadPaused.c:310 #7 0x00000000004f7d51 in stg_returnToSched () #8 0x0000000000000000 in ?? () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 01:43:28 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 01:43:28 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) Message-ID: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.3 (Type checker) | Keywords: GADTs, | Operating System: Unknown/Multiple ScopedTypeVariables | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs data Exp a where Tru :: Ty Bool eval :: Exp a -> a eval Tru = True }}} Works fine, as does {{{#!hs eval :: Exp a -> a eval (Tru :: Exp _) = True }}} But {{{#!hs eval :: Exp a -> a eval (Tru :: Exp Bool) = True }}} doesn't, is this an intended design of GADTs/ScopedTypeVariables that the type equality constraint isn't in scope in the type signature of the pattern match, I would like to match on an existential type in my own code: {{{#!hs compile (ArrIx arr index :: Exp (Sca elt)) = do ... }}} It can be worked around by writing: {{{#!hs eval a at Tru = case a :: Exp Bool of }}} but for my own code it seems I must write {{{#!hs compile uuu@(ArrIx arr index :: Exp a) = do case uuu :: (a ~ Sca elt) => Exp (Sca elt) of }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 01:50:38 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 01:50:38 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.b29a343a6128af65bac6f70b0981625c@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Hm, the type variable `elt` doesn't get brought into scope. Maybe because it's existential -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 01:54:35 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 01:54:35 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.bb87fbd07b64d4391ed9bc861134dc8a@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I think this would largely be solved by #11350, {{{#!hs eval (ArrIx @_ @elt arr index) = do ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 02:43:35 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 02:43:35 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.fe3f0bc428ac4fbfb79e494d7c51ac05@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): The fix is insufficient. I am still getting intermittent assertion failures on {{{#!C ASSERT(((LDVW(c) & LDV_CREATE_MASK) >> LDV_SHIFT) > 0); }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 03:44:33 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 03:44:33 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.ca11fa3ce72e3ee4f0185147b9a72d23@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): * cc: carter (added) Comment: Oh wow, just realised that the profiling code is not thread safe!!!!! The function `LDV_recordDead` mutates global variable `censuses` which does not have any locking around it. Only figured this out because the following assert (in `LDV_recordDead`) was being triggered. {{{ ASSERT(censuses[t].void_total < censuses[t].not_used); }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 03:50:36 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 03:50:36 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.407bb0755a36b34ae4a5cd53f8e7f891@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 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 erikd): Wow, that assert is even triggered when the test program is run as `./T11978b +RTS -hb -N1`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 04:55:28 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 04:55:28 -0000 Subject: [GHC] #12019: Profiling option -hb is not thread safe Message-ID: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> #12019: Profiling option -hb is not thread safe -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Runtime | Version: 8.1 System | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11978, #12009 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This ticket is a continuation of #11978 and #12009. After fixing a couple of issues in those two tickets I found that the profiling run time is not thread safe. Have a trivial test program (written as one of the tests for #11978): {{{ import Control.Concurrent import Control.Concurrent.MVar import Control.Exception import Control.Monad main :: IO () main = do putStrLn "Start ..." mvar <- newMVar (0 :: Int) let count = 50 forM_ [ 1 .. count ] $ const $ forkIO $ do threadDelay 100 i <- takeMVar mvar putMVar mvar $! i + 1 threadDelay 1000000 end <- takeMVar mvar putStrLn $ "Final result " ++ show end assert (end == count) $ return () }}} Compiling that with a compiler that has bug fixes arising from #11978 and #12009 as: {{{ inplace/bin/ghc-stage2 testsuite/tests/profiling/should_run/T11978b.hs \ -fforce-recomp -rtsopts -fno-warn-tabs -O -prof -static -auto-all \ -threaded -debug -o T11978b }}} and run as: {{{ ./T11978b +RTS -p -hb -N10 }}} crashes in a number of different ways. I've seen at least 3 different assertion failures and numerous segfaults (in different `stg_ap_*` functions). Replace `-hb` with other profiling options like `-hr` etc do not seem to crash. Looking at code, one example of lack of thread safetly is the function `LDV_recordDead` which mutates global variable `censuses` which does not have any locking around it. Only figured this out because the following assert (in `LDV_recordDead`) was being triggered occasionally. {{{ ASSERT(censuses[t].void_total < censuses[t].not_used); }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 08:02:20 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 08:02:20 -0000 Subject: [GHC] #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 In-Reply-To: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> References: <044.8b529ad387ef448a4192c65c3e5cac8e@haskell.org> Message-ID: <059.24e3608e247b22f0186a834b5254032b@haskell.org> #12009: ASSERTION FAILED: file rts/LdvProfile.c, line 48 -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 Resolution: duplicate | 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 erikd): * status: new => closed * resolution: => duplicate Comment: This bug is actually caused by the fact that the `-hb` profiling mode is not thread safe. Closing this in favour of #12019 which gives a much better explanation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 08:29:38 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 08:29:38 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.e9e60e6b3e3aeebee3744b78727c25a5@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: erikd Type: bug | Status: patch Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by erikd): The `overwritingClosure` issue can only be triggered in the `-hb` profiling mode and I finally figure our that the `-hb` profiling mode was not thread safe (see #12019). Leaving this ticket open as a place holder for adding tests for the other profiling modes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 08:40:30 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 08:40:30 -0000 Subject: [GHC] #11502: Scrutinize use of 'long' in rts/ In-Reply-To: <045.a2d5adf2c113bf5cbc484973798f0d81@haskell.org> References: <045.a2d5adf2c113bf5cbc484973798f0d81@haskell.org> Message-ID: <060.9548b074294f39da470be8c875e779d2@haskell.org> #11502: Scrutinize use of 'long' in rts/ -------------------------------------+------------------------------------- Reporter: thomie | Owner: MarcelineVQ Type: task | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): Given we're slowly moving to C99-izing the code (se e.g. db9de7eb3e91820024f673bfdb6fb8064cfed20d), it may make sense to take this opportunity to use ``-typedefs instead, e.g. - `int64_t` instead of `StgInt64` - `uint64_t` instead of `StgWord64` - `intptr_t` instead of `StgInt` - `uintptr_t` instead of `StgWord` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 08:52:33 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 08:52:33 -0000 Subject: [GHC] #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) In-Reply-To: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> References: <051.6f4adb265ab208b75b739851f1fb480c@haskell.org> Message-ID: <066.323051f19187e2ba87ea6686f7cb420f@haskell.org> #12018: Equality constraint not available in pattern type signature (GADTs/ScopedTypeVariables) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: GADTs, Resolution: | ScopedTypeVariables Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > Is this an intended design of GADTs/ScopedTypeVariables that the type equality constraint isn't in scope in the type signature of the pattern match Yes, it is. The type equalities are available only "after" the match. For your second point I need a more complete example. To bind an existential you need a pattern type sig. Eg {{{ data T where MkT :: a -> ([a]->Int) -> T f (MkT (x :: a) f) = f ([x,x] :: [a]) }}} The pattern signature `(x :: a)` binds `a`. Currently that's the only way to bind an existential type variable. #11350 would be a good alternative. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 08:56:25 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 08:56:25 -0000 Subject: [GHC] #11502: Scrutinize use of 'long' in rts/ In-Reply-To: <045.a2d5adf2c113bf5cbc484973798f0d81@haskell.org> References: <045.a2d5adf2c113bf5cbc484973798f0d81@haskell.org> Message-ID: <060.89353cb98bbe81dcc80d8be40fd5bbca@haskell.org> #11502: Scrutinize use of 'long' in rts/ -------------------------------------+------------------------------------- Reporter: thomie | Owner: MarcelineVQ Type: task | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by erikd): * cc: erikd (added) Comment: Replying to [comment:4 hvr]: > Given we're slowly moving to C99-izing the code (se e.g. db9de7eb3e91820024f673bfdb6fb8064cfed20d), it may make sense to take this opportunity to use ``-typedefs instead, e.g. > > - `int64_t` instead of `StgInt64` > - `uint64_t` instead of `StgWord64` > - `intptr_t` instead of `StgInt` > - `uintptr_t` instead of `StgWord` I'm no actually sure that just applying this change blindly across the code base is a good idea. There are almost certainly places where `StgWord` is used as a "machine word sized unsigned value" and has no notion of pointer-ness at all. In that case. `size_t` might be a better choice. Similarly, for `StgInt`, there are probably places where `ssize_t` (the signed version of `size_t`) is a better choice. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 09:28:46 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 09:28:46 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.f22e2bcb74cbdc9791effe38c56b4092@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gkaracha): Apologies for the late (and long) response. You can find below some explanation about the behavior of the checker, which I hope to clear things out a bit. == Why does this example exceed the limit == In principle, the match of `sameAttribute` gives rise to 161*161 = 25,921 cases. Also, the counter takes into account the arguments too and most constructors have at least one. Yet, the most important reason that the match iterates >2000000 times is that **all** unmatched cases from the first clause are checked with the second, and the resulting ones are checked with the third, etc. {{{#!hs data T = A | B | C f :: T -> () f A = () f B = () -- (*) f C = () }}} That being said, for `f` above, the second clause will be checked against missing cases `B` and `C`. This is a pretty small example, but in general this gives rise to (something like) a quadratic number of checks. That's why the iteration counter goes over the roof. == General Comments on Performance == About the general performance of the algorithm, there are some things worth mentioning: 1. In principle, the new checker is slower than the previous one on average. This makes sense because we check term and type constraints, that the previous checker didn't, so we have to pay something for that. Nevertheless, the main reason that it's slower on average is that the new checker checks uncovered matches eagerly, while the past checker did it lazily (whether the specific match has GADTs or not, the new checking function is in `TcM` also, to be able to call the type-checker). 2. Neither I or Simon were happy about the above, but (that's why we opened #11528 but it still needs a lot of work to figure out how to change) the constraint-based approach grew really fast, unless we performed constraint solving as soon as possible, to remove useless cases (as I said above, what is generated from one clause is passed to the next one so this was devastating). 3. The takeaway is that, in order to avoid extreme cases (like #11195 which is really difficult for the checker), we chose to have predictable behavior for all (with/without guards or GADTs) but a bit slower. The other result is that since the checker is now strict, it had to be bounded, to avoid memory-issues. I dislike the exceeded-iterations-warning too, but I know no better solution at the moment. My original limit was 10000000, which even worked on #11195 and gave no such warning. However, as Herbert said, memory consumption can be too high, if we let it. The best solution, the way I see it would be to collect statistics (like the examples from Neil or this whole bug report) and fine-tune it. Maybe 10000000 was too high but 2000000 seems to be too low. I do not have anything better to offer at the moment, but I am open to suggestions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 09:40:21 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 09:40:21 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.156e32dd5533587c53507c9397986e37@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): Perhaps make it a warning that is off by default? That solves the immediate problem and lets people who do care about the new pattern match checker opt in to issues where their patterns are too complex to be properly matched. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 09:46:05 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 09:46:05 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.a61058d56a39b424de066d0217865b64@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gkaracha): But if we do this silently, we may get no warning at all for non- exhaustive matches, even with `-Wall` on. Don't you think that this is much worse in terms of safety? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 10:24:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 10:24:43 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.d90f204aa1f810f192a685ed522889af@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): There are some warnings that are on by default, and some that are only on with {{-Wall}}. Making this a warning that was not triggered by default but was by {{-Wall}} would give you what you want. As to my personal opinion, I want my code to compile without warnings. If you can give me a warning that I have an undesirable problem, and I can reasonably mitigate it, I'm happy. If you give me a vague sense of unease about limitations in your checker, and I can't do anything with it other than disable warnings, I'm sad. The warning above doesn't relate to whether there are inexhaustive patterns or not, it's all about whether your checker can prove that, which is a different thing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 11:15:37 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 11:15:37 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.e377affcfeabacd2b3b043490e0a8589@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | https://github.com/TobyGoodwin/odd- | ghc-pattern-bug Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Can you explain how to reproduce, preferably without installing all of Yesod? (eg can you cut it down somehow?) The readme on the odd-ghc-pattern-bug github doesn't give repro instructions. Thanks Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 12:27:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 12:27:43 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.ec8fe67ae703b3317a3063f431f5ba5d@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | https://github.com/TobyGoodwin/odd- | ghc-pattern-bug Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by TobyGoodwin): Commands to run are in RUNME (I just updated README to make this clearer). I whittled it down as far as I could in the time I had: it's not quite ''all'' of yesod... just persistent :) My hunch is that TH is implicated. When I get the chance, I'll see if I can build up a test case from nothing that mimics the way persistent defines the types. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 12:48:50 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 12:48:50 -0000 Subject: [GHC] #12020: Error message on use of != should suggest use of /= Message-ID: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> #12020: Error message on use of != should suggest use of /= -------------------------------------+------------------------------------- Reporter: mhoermann | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently when one uses != instead of /= it comes up with this error message {{{ Not in scope: ?!=? Perhaps you meant one of these: ?Map.!? (imported from Data.Map), ?>=? (imported from Prelude), ?==? (imported from Prelude) }}} Considering != is very common for unequal in other languages there should be a more helpful hint to use /= instead of or in addition to the current generic symbol error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 13:14:44 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 13:14:44 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.26c8787a0c3ec800e41f8cb81be6339d@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): I guess one question I have here is whether we can improve the approximation here to have better bounds in the non gadt case? I do like having informative coverage warnings rather than silent anything or resource blowups on my lap top (though 8.0 does claim 1tb of virtual memory either way :)) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 13:30:10 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 13:30:10 -0000 Subject: [GHC] #12016: Allow wildcards in type synonyms and data declarations In-Reply-To: <051.25982c21d04ab8006e28de59d7da7e1e@haskell.org> References: <051.25982c21d04ab8006e28de59d7da7e1e@haskell.org> Message-ID: <066.292dcc6f6e2e89dbbf8c9e89e9c25d46@haskell.org> #12016: Allow wildcards in type synonyms and data declarations -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think it's probably rare for this to be useful, but I certainly don't object. I'm surprised we don't have a ticket for this already. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 13:34:46 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 13:34:46 -0000 Subject: [GHC] #12020: Error message on use of != should suggest use of /= In-Reply-To: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> References: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> Message-ID: <063.fdeb6394af0e1db16ecdf2249921bf30@haskell.org> #12020: Error message on use of != should suggest use of /= -------------------------------------+------------------------------------- Reporter: mhoermann | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): This is a good idea, but it immediately leads towards implementing a more general concept, where with any name you can list ?common misspellings? that are in scope with the original name, and are consulted if something is not in scope. How would that be implemented. How about a pragma like this? {{{ `(!=)` :: a -> a -> Bool {-# MISSPELLINGS (!=), (<>) #-} }}} Naturally, if such a symbol is properly in scope, then the misspelling should be ignored. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 14:18:23 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 14:18:23 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.54697e6644468955b83f81e62f3959bc@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by magesh.b): * Attachment "MutiCE.hs" added. MultipleCustomErrors -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 14:19:27 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 14:19:27 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.b0086489e599fb8f73ef0b058e0fe04a@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by magesh.b): > If there are multiple `TypeErrors`, then we just report one of them. Consider the following class, whose instance has a contrived TypeError {{{ class ShowHL (xs :: [*]) where showHL :: HList xs -> String instance (Show x, ShowHL xs, TypeError (ShowType x)) => ShowHL (x ': xs) where showHL (x :& xs) = show x ++ showHL xs }}} The error message emitted when this type class method is called with **showHL ('a' :& True :& Nil)** contains all the errors in one shot. This behavior is very useful and would this be retained after this fix? {{{ MutiCE.hs:26:8: error: ? Bool ? In the expression: showHL testRec In an equation for ?test?: test = showHL testRec MutiCE.hs:26:8: error: ? Char ? In the expression: showHL testRec In an equation for ?test?: test = showHL testRec Failed, modules loaded: none. }}} I have attached the full source code which contains the test case for this behaviour -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 15:29:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 15:29:42 -0000 Subject: [GHC] #11502: Scrutinize use of 'long' in rts/ In-Reply-To: <045.a2d5adf2c113bf5cbc484973798f0d81@haskell.org> References: <045.a2d5adf2c113bf5cbc484973798f0d81@haskell.org> Message-ID: <060.1832dfbb822789228134ce9ee9e8fdcf@haskell.org> #11502: Scrutinize use of 'long' in rts/ -------------------------------------+------------------------------------- Reporter: thomie | Owner: MarcelineVQ Type: task | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): `StgWord` is a pretty fundamental notion across the whole of the GHC backend and runtime system: it's the unit of allocation on the heap and stack. So I think for the storage manager we should keep `StgWord` as it is. Places where we're using `StgWord` as just a "machine word sized unsigned value" as @erikd says, we should use something more appropriate. I'd be fine with getting rid of the explicitly sized Stg types in favour of the standard ones. When we originally built this, the standard ones weren't standard enough. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 15:44:31 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 15:44:31 -0000 Subject: [GHC] #5642: Deriving Generic of a big type takes a long time and lots of space In-Reply-To: <049.904645e363a227f735eb4cfb7fbae513@haskell.org> References: <049.904645e363a227f735eb4cfb7fbae513@haskell.org> Message-ID: <064.3a80b5366ab159af47dda493834668d9@haskell.org> #5642: Deriving Generic of a big type takes a long time and lots of space -------------------------------------+------------------------------------- Reporter: basvandijk | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.3 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: T5642 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 15:44:52 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 15:44:52 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.318d8e25166702ee92bc7be1df8a899f@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 16:22:01 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 16:22:01 -0000 Subject: [GHC] #11970: Simplify Parent for patten synonyms In-Reply-To: <046.99b58fbbe4691b1cc88a00dd47c4a70f@haskell.org> References: <046.99b58fbbe4691b1cc88a00dd47c4a70f@haskell.org> Message-ID: <061.2648c0391e95e60ac9525a9365e8bca3@haskell.org> #11970: Simplify Parent for patten synonyms -------------------------------------+------------------------------------- Reporter: simonpj | Owner: mpickering Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2179 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * differential: => Phab:D2179 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 16:37:07 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 16:37:07 -0000 Subject: [GHC] #10775: Enable PolyKinds in GHC.Generics In-Reply-To: <050.1fb49e8a4f9e9ff5b73b6dbae85f944e@haskell.org> References: <050.1fb49e8a4f9e9ff5b73b6dbae85f944e@haskell.org> Message-ID: <065.e1a2dd17f3240590ea724011246d34ee@haskell.org> #10775: Enable PolyKinds in GHC.Generics -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: feature request | Status: closed Priority: normal | Milestone: 8.0.1 Component: libraries/base | Version: 7.10.2 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10604 | Differential Rev(s): Phab:D1166 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #10604 Comment: See also #10604, which concerns making the definition of `Generic1` itself leverage `PolyKinds`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 16:37:10 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 16:37:10 -0000 Subject: [GHC] #12021: Type variable escapes its scope Message-ID: <046.130748221ef7180f1063edfb1f33f5e9@haskell.org> #12021: Type variable escapes its scope -------------------------------------+------------------------------------- Reporter: ttuegel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Keywords: | 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: -------------------------------------+------------------------------------- In the following example, I believe a type variable is incorrectly escaping its scope. The example produces the error: {{{ Bug.hs:20:20: error: ? Expected kind ?Cat k?, but ?(:-)? has kind ?Constraint -> Constraint -> *? ? In the first argument of ?Iso?, namely ?(:-)? In the type signature: functor :: forall a b. Iso (:-) (:-) (Ob (Dom f) a) (Ob (Dom f) b) (Ob (Cod f) (f a)) (Ob (Cod f) (f b)) In the class declaration for ?Functor? }}} If the definition of `Iso` is changed from {{{#!hs type Iso (c :: Cat k) (d :: Cat k) s t a b = forall p. (Cod p ~ Nat d (->)) => p a b -> p s t }}} to {{{#!hs type Iso (c :: Cat k) (d :: Cat k) s t a b = forall p. p a b -> p s t }}} then this error does not occur. (The example still will not compile because I have omitted almost the entire implementation, but it should not fail here.) I am not certain what is really happening here, but it seems to me that when the RHS of `Iso` is constrained, then the type variable `k` introduced on the LHS of `Iso` is being unified incorrectly with the type variable `k` introduced in the definition of the `Functor` class. When the constraint is removed, GHC seems to recognize (correctly!) that the type variables are distinct. (This bug actually occurs with GHC 8.0.1-rc4, but the "Version" menu doesn't give me that option.) {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} import GHC.Base ( Constraint, Type ) type Cat k = k -> k -> Type class Category (p :: Cat k) where type Ob p :: k -> Constraint class (Category (Dom f), Category (Cod f)) => Functor (f :: j -> k) where type Dom f :: Cat j type Cod f :: Cat k functor :: forall a b. Iso (:-) (:-) (Ob (Dom f) a) (Ob (Dom f) b) (Ob (Cod f) (f a)) (Ob (Cod f) (f b)) class (Functor f , Dom f ~ p, Cod f ~ q) => Fun (p :: Cat j) (q :: Cat k) (f :: j -> k) | f -> p q instance (Functor f , Dom f ~ p, Cod f ~ q) => Fun (p :: Cat j) (q :: Cat k) (f :: j -> k) data Nat (p :: Cat j) (q :: Cat k) (f :: j -> k) (g :: j -> k) type Iso (c :: Cat k) (d :: Cat k) s t a b = forall p. (Cod p ~ Nat d (->)) => p a b -> p s t data (p :: Constraint) :- (q :: Constraint) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 17:53:34 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 17:53:34 -0000 Subject: [GHC] #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE Message-ID: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE -------------------------------------+------------------------------------- Reporter: Rufflewind | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 7.10.3 libraries/base | Keywords: performance, | Operating System: Unknown/Multiple inline, bits | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given that they are fairly essential operations in core libraries such as containers, I think it would be useful to have them marked as INLINE (or INLINABLE at the very least). See also: https://github.com/haskell/containers/pull/216 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 18:06:51 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 18:06:51 -0000 Subject: [GHC] #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE In-Reply-To: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> References: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> Message-ID: <064.cf9f9292adf34335b34ab7d4067bb143@haskell.org> #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE -------------------------------------+------------------------------------- Reporter: Rufflewind | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: performance, | inline, bits Operating System: 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 think `INLINABLE` would help this at all. I would lean toward either `INLINE` or `INLINE CONLIKE`. I don't have an example, but I think I saw GHC allocate when just `INLINE` for a copy of one of these. -- Ticket URL: GHC The Glasgow Haskell Compiler From matthew at wellquite.org Fri May 6 19:08:01 2016 From: matthew at wellquite.org (matthew at wellquite.org) Date: Fri, 6 May 2016 22:08:01 +0300 Subject: Fw: new message Message-ID: <0000a71586ee$a5e18d42$5ce0795c$@wellquite.org> Hello! You have a new message, please read matthew at wellquite.org -------------- next part -------------- An HTML attachment was scrubbed... URL: From ghc-devs at haskell.org Fri May 6 20:40:03 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 20:40:03 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.2eb96b907d89e3e6cc0b2702801a8fc4@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: merge => new -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 20:40:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 20:40:43 -0000 Subject: [GHC] #11990: Custom Type Error not getting triggered in the nested Type function call In-Reply-To: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> References: <047.cd64e02ac6207e6c5247bec38dfaa3ba@haskell.org> Message-ID: <062.2335fa665f2e17222e89ff0599bf2047@haskell.org> #11990: Custom Type Error not getting triggered in the nested Type function call -------------------------------------+------------------------------------- Reporter: magesh.b | Owner: diatchki Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => diatchki -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 23:41:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 23:41:43 -0000 Subject: [GHC] #12020: Error message on use of != should suggest use of /= In-Reply-To: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> References: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> Message-ID: <063.9bf2a089ce8cd5a04bf1a320e0c2674e@haskell.org> #12020: Error message on use of != should suggest use of /= -------------------------------------+------------------------------------- Reporter: mhoermann | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:1 nomeata]: I like it, comments: Do you have more motivational examples, I have a feeling this would mostly be used for operators. Would it appear in `:info (/=)` output? What about `:info (!=)` whether or not it's defined. Would it be attached to the definition or definable in a separate module? Adding a custom error message. I take it that the first definition was supposed to be `(/=) :: a -> a -> Bool`: {{{#!hs class Eq a where (==) :: a -> a -> Bool (/=) :: a -> a -> Bool {-# MISSPELLINGS (/=) AS (!=) "?Not equal to? is (/=), syntactically emulating the the math symbol ?" #-} class Eq a => Bits a where (.&.) :: a -> a -> a {-# MISSPELLINGS (.&.) AS (&) "Bitwise and is (.&.)." #-} (.|.) :: a -> a -> a {-# MISSPELLINGS (.|.) AS (|) "Bitwise or is (.|.)." #-} ... shiftL :: a -> Int -> a {-# MISSPELLINGS shiftL AS (<<) "Left shift" #-} }}} `(|)` doesn't parse but oh well {{{ ghci> 4 != 10 _--_ It looks like you're trying ? ? ,- to code. ?Not equal to? is (/=), syntactically || | ' emulating the the math symbol ?. Try writing |\_|/ ?4 /= 10? instead. \_/ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 6 23:51:12 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 06 May 2016 23:51:12 -0000 Subject: [GHC] #12020: Error message on use of != should suggest use of /= In-Reply-To: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> References: <048.7e4196f37cf20a151fb045706d077aa8@haskell.org> Message-ID: <063.a110523c7bd4592cd5d50b4e5bf2a15c@haskell.org> #12020: Error message on use of != should suggest use of /= -------------------------------------+------------------------------------- Reporter: mhoermann | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): This isn't a misspelling, so maybe it could suggest any alternate name: {{{#!hs and :: Foldable t => t Bool -> Bool {-# MISSPELLINGS and AS every "Determines whether every element of the structure is True." #-} or :: Foldable t => t Bool -> Bool {-# MISSPELLINGS or AS some "Determines whether some element of the structure is True." #-} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 00:43:22 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 00:43:22 -0000 Subject: [GHC] #12023: Problems getting information and kind from GHC.Prim ~#, ~R#, ... Message-ID: <051.e18556256e79a3a1dab6064a1d75c6d2@haskell.org> #12023: Problems getting information and kind from GHC.Prim ~#, ~R#, ... -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ >>> import GHC.Prim >>> :bro GHC.Prim [...] type role (~#) nominal nominal data (~#) (t3 :: a) (t4 :: b) type role ~P# phantom phantom data ~P# (t3 :: a) (t4 :: b) type role (~R#) representational representational data (~R#) (t3 :: a) (t4 :: b) }}} getting the kind of `~`, `~#`, `~~` works fine: {{{ >>> import GHC.Prim >>> import GHC.Types >>> :kind (~) (~) :: k -> k -> Constraint >>> :kind (~#) (~#) :: a -> b -> TYPE 'VoidRep >>> :kind (~~) (~~) :: j -> k -> Constraint }}} but `#` gets incorrectly treated as an operator in `~R#` and `~P#`: {{{ >>> :kind (~R#) :1:3: error: Illegal operator ?#? in type ?~R #? Use TypeOperators to allow operators in types :1:3: error: Operator applied to too few arguments: ~R # :1:4: error: Not in scope: type constructor or class ?R? }}} Furthermore while running `:info` on `~~` and `~#` works fine {{{ >>> :info (~~) class a ~# b => (~~) (a :: j) (b :: k) -- Defined in ?GHC.Types? >>> :info (~#) type role (~#) nominal nominal data (~#) (t3 :: a) (t4 :: b) -- Defined in ?GHC.Prim? }}} the others don't parse {{{ >>> :info (~) :1:2: error: parse error on input ?~? >>> :info (~R#) :1:2: error: parse error on input ?~? >>> :info (~P#) :1:2: error: parse error on input ?~? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 00:53:20 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 00:53:20 -0000 Subject: [GHC] #12024: GHC leaks GHC.Prim.~# into type Message-ID: <051.7eb6150e403ea080535783c5107e00b5@haskell.org> #12024: GHC leaks GHC.Prim.~# into type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs data A a where X :: A [xxx] pattern X' = X }}} the inferred type of which is {{{ >>> :info X' pattern X' :: () => t GHC.Prim.~# [xxx] => A t }}} Casts use unlifted equality as I understand it, but lifted would present a nicer UI: {{{#!hs pattern X' :: () => t ~> [xxx] => A t pattern X' = X }}} In my own code this means I get the following monster {{{#!hs pattern MkArr :: () => (GetTy a, GetTy b, GetTy t, a GHC.Prim.~# 'Sca ('Number 'I32), b GHC.Prim.~# 'Sca a1, t GHC.Prim.~# 'Arr a1, GetSca a1) => Exp a -> Id -> Exp b -> Exp t }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 01:00:03 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 01:00:03 -0000 Subject: [GHC] #12024: GHC leaks GHC.Prim.~# into type In-Reply-To: <051.7eb6150e403ea080535783c5107e00b5@haskell.org> References: <051.7eb6150e403ea080535783c5107e00b5@haskell.org> Message-ID: <066.7f343cbfea76693d6c8b79b0d5fe1422@haskell.org> #12024: GHC leaks GHC.Prim.~# into type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: 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 Iceland_jack): * cc: mpickering (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 01:00:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 01:00:31 -0000 Subject: [GHC] #12024: GHC leaks GHC.Prim.~# into type In-Reply-To: <051.7eb6150e403ea080535783c5107e00b5@haskell.org> References: <051.7eb6150e403ea080535783c5107e00b5@haskell.org> Message-ID: <066.0fc820d3a59de5f49cb6bd7a3607f33f@haskell.org> #12024: GHC leaks GHC.Prim.~# into type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.3 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * keywords: => PatternSynonyms -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 01:39:33 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 01:39:33 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) Message-ID: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple TypeApplications PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: 11513, 10928 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Ever since `TypeApplications` the order of quantification matters. It seems there are some places where the user has no control over the order: {{{#!hs data A a where X :: A [xxx] pattern X' :: forall t. () => forall xxx. t ~ [xxx] => A t pattern X' = X }}} This quantifies the universal `t` and the existential `xxx`.. but in this case `t` is constrained to equal `[xxx]` so when we supply our first type (the universal `t`) it is forced to be of the form `[a]`. Then the existential is forced to equal `a` (there is currently no way to express this without a type annotation `X' @[t] @t :: A [t]`, see ticket #11385 to allow `X' @[_t] @_t`, for this ticket the equality is inherent in `X` so it's no big deal). This means that the first argument really doesn't give any further information but it seems impossible to reorder the existential type before the universal. This either forces the user to supply a dummy type: {{{#!hs X' @_ @ActualType }}} or to write `[ActualType]` explicitly {{{#!hs X' @[ActualType] X' @[ActualType] @ActualType X' @[_] @ActualType }}} This may be a bigger inconvenience than it may seem: the return type can be more complicated `A (B (C a))` and it requires the user to look it up. `X' @_ @ActualType` feels like bad library design, especially as the number of existential variables grows and the user has to remember how many underscores to provide. See also ticket:10928#comment:5 Keep in mind that this usage will be common, since the more obvious (see ticket:10928#comment:16) {{{#!hs pattern X'' :: forall xxx. A [xxx] pattern X'' = X }}} cannot match against a type `A a` {{{#!hs -- Works foo :: A a -> ... foo X' = ... -- Doesn't bar :: A a -> ... bar X'' = ... }}} Thoughts? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 01:41:41 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 01:41:41 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.7da6869d0ff01e9d5a1b436a98cfe03c@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -18,3 +18,3 @@ - this without a type annotation `X' @[t] @t :: A [t]`, see ticket #11385 to - allow `X' @[_t] @_t`, for this ticket the equality is inherent in `X` so - it's no big deal). + this without quantification + annotation `X' @[t] @t :: forall t. A [t]`, + see ticket #11385 to allow `X' @[_t] @_t`, for this ticket the equality is + inherent in `X` so it doesn't matter). New description: Ever since `TypeApplications` the order of quantification matters. It seems there are some places where the user has no control over the order: {{{#!hs data A a where X :: A [xxx] pattern X' :: forall t. () => forall xxx. t ~ [xxx] => A t pattern X' = X }}} This quantifies the universal `t` and the existential `xxx`.. but in this case `t` is constrained to equal `[xxx]` so when we supply our first type (the universal `t`) it is forced to be of the form `[a]`. Then the existential is forced to equal `a` (there is currently no way to express this without quantification + annotation `X' @[t] @t :: forall t. A [t]`, see ticket #11385 to allow `X' @[_t] @_t`, for this ticket the equality is inherent in `X` so it doesn't matter). This means that the first argument really doesn't give any further information but it seems impossible to reorder the existential type before the universal. This either forces the user to supply a dummy type: {{{#!hs X' @_ @ActualType }}} or to write `[ActualType]` explicitly {{{#!hs X' @[ActualType] X' @[ActualType] @ActualType X' @[_] @ActualType }}} This may be a bigger inconvenience than it may seem: the return type can be more complicated `A (B (C a))` and it requires the user to look it up. `X' @_ @ActualType` feels like bad library design, especially as the number of existential variables grows and the user has to remember how many underscores to provide. See also ticket:10928#comment:5 Keep in mind that this usage will be common, since the more obvious (see ticket:10928#comment:16) {{{#!hs pattern X'' :: forall xxx. A [xxx] pattern X'' = X }}} cannot match against a type `A a` {{{#!hs -- Works foo :: A a -> ... foo X' = ... -- Doesn't bar :: A a -> ... bar X'' = ... }}} Thoughts? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 01:52:56 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 01:52:56 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.9eb45a08894c5e8da8faa3795b0b4adc@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Another place I've discovered this is in type classes (I want to hear about other cases), let's say that for what ever reason want to supply the type `a` first but we can't (by design) {{{#!hs class P p where q_ :: forall a. p a -> Int instance P Maybe where q_ :: forall a. Maybe a -> Int q_ = length }}} Unlike the pattern synonym case this can be remedied by new function {{{#!hs q :: forall a p. P p => p a -> Int q = q_ }}} Users will have to define a different method than they use, it's inelegant but it works. This isn't a problem if we allow signatures with explicit quantification for type classes #11620 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 01:57:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 01:57:17 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.deaaa5c204ffc77c696790263eebfe3f@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): My gut tells me that this is less of an issue for type classes since quite often you want to supply the named/instance type first. Still I need this every once in a while -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 02:00:23 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 02:00:23 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs Message-ID: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When compiling dimensional-1.0.1.1 after patching numtype-dk with the patch at https://github.com/bjornbm/numtype-dk/issues/12 GHC does the "impossible": [ 3 of 16] Compiling Numeric.Units.Dimensional.Dimensions.TypeLevel ( src/Numeric/Units/Dimensional/Dimensions/TypeLevel.hs, dist/dist-sandbox- 68389a1a/build/Numeric/Units/Dimensional/Dimensions/TypeLevel.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-unknown-linux): Pattern match failure in do expression at compiler/rename/RnNames.hs:902:12-50 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 02:52:16 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 02:52:16 -0000 Subject: [GHC] #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors Message-ID: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I was getting around to testing some of my maths code with ghc 8.0 and i noticed that whereas in ghc 7.10 and earlier i could have an INLINE pragma for a method of a type class method that has a default implementation (whether this did anything or not is another question), in ghc 8.0 this now gives an ERROR (with not even a warning in ghc 7.10) is this a deliberate design change or an accident? I dont see it in the release notes! heres a small program that illustrates the differences (builds fine with no mention of the INLINE pragma matter under -Wall for 7.10, errors during build in 8.0) {{{ {-# LANGUAGE NoImplicitPrelude #-} module Main where import Prelude (putStrLn) import qualified Data.Functor as Fun import qualified Data.Foldable as F import Prelude hiding (map,foldl,foldr,init,scanl,scanr,scanl1,scanr1,foldl1,foldr1) newtype ListWrap a = ListWrap { unListWrap :: [a] } deriving (Eq, Show) instance Foldable ListWrap where {-# INLINE foldMap #-} {-# INLINE foldr #-} foldMap f (ListWrap ls)= (F.foldMap f ls ) main = putStrLn "hello" }}} this may be a *valid* design change, but i've not seen it documented anywhere, such as the release notes in the RC or in https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0 ... so i'm assuming its a regression pending dicussion ;) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 02:53:34 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 02:53:34 -0000 Subject: [GHC] #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors In-Reply-To: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> References: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> Message-ID: <060.b5f52cb28c5348e1efe53e5f4a46f6a1@haskell.org> #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): oh just to clarify, the error in ghc 8.0 is {{{ Shape.hs:15:14: error: The INLINE pragma for ?foldr? lacks an accompanying binding (The INLINE pragma must be given where ?foldr? is declared) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 02:57:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 02:57:37 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.7cb8d2dcab411b4020e7e15661a47f67@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by davean): For simplicity I've provided the patched numtype-dk repo at http://code.xkrd.net/davean/numtype-dk.git Additionally, this compiles clean on 7.10.3 (including with the patched numtype-dk). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 03:39:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 03:39:45 -0000 Subject: [GHC] #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) Message-ID: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- See the attached somewhat reduced version of the main (manually unrolled) portion of an MD5 implementation taken from PureMD5. It used to compile in about 200ms, which is already bad enough, but now takes 1200 ms (ghc 6.12.3 to ghc 7.10.3 using -O2). I'd like to note that in my light testing the UNPACK pragma accounts for 400ms of this delta. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 03:40:22 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 03:40:22 -0000 Subject: [GHC] #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) In-Reply-To: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> References: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> Message-ID: <059.f756a1fff37f6431a199ba1791a03910@haskell.org> #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by tommd): * Attachment "regression-md5.hs" added. A slice of pureMD5 that shows performance issues in GHC -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 03:59:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 03:59:46 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.f4f20d1d2836b34c4b4d48411bb7a474@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: closed => new * owner: osa1 => * resolution: fixed => Comment: I think we should improve this a bit more. For one, this is not on by default, right? Any reason it shouldn't be? And if it's not on by default, GHC should at least mention that you can pass `-fprint-expanded-synonyms` to see the expansion of the type synonyms. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 04:20:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 04:20:29 -0000 Subject: [GHC] #11011: Add type-indexed type representations (`TypeRep a`) In-Reply-To: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> References: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> Message-ID: <062.e2f8e3959ae2bc904016393cb90756fe@haskell.org> #11011: Add type-indexed type representations (`TypeRep a`) -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2010 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Bikeshedding. Base already has the existentials `SomeSymbol` and `SomeNat` so one wonders if `SomeTypeRep` is a more consistent name for `TypeRepX`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 06:08:24 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 06:08:24 -0000 Subject: [GHC] #12029: Notify user to import * from Data.Kind with TypeInType on Message-ID: <051.cab193afa0e611bf75b1dd6c73bcab4d@haskell.org> #12029: Notify user to import * from Data.Kind with TypeInType on -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: lowest | Milestone: Component: GHCi | Version: 8.1 Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With `TypeInType` asking for the kind of `*` gives the user a warning to import it {{{ ghci> :set -XTypeInType ghci> :k * :1:1: error: Not in scope: type constructor or class ?*? NB: With TypeInType, you must import * from Data.Kind :1:1: error: Illegal operator ?*? in type ?*? Use TypeOperators to allow operators in types :1:1: error: Operator applied to too few arguments: * }}} Should a similar warning be issued when she asks for information on it {{{ ghci> :i * class Num a where ... (*) :: a -> a -> a ... -- Defined in ?GHC.Num? infixl 7 * }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 06:15:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 06:15:15 -0000 Subject: [GHC] #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors In-Reply-To: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> References: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> Message-ID: <060.ac7366e4fb609770b8ec03dc80a30ade@haskell.org> #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 8.0.1 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 bgamari): * status: new => closed * resolution: => invalid Comment: Right, because, just as the error says, that INLINE doesn't correspond to any particular in-scope binding. However, you should not need an INLINE here; instead just place one on the default definition. You can test this yourself with the following, {{{#!hs module Class where class AClass a where aList :: a -> [Int] aList _ = [1,2,3] {-# INLINE aList #-} }}} {{{#!hs module Instance where import Class instance AClass Int where }}} {{{#!hs module Use where import Class import Instance n :: Int n = 42 main :: IO () main = print (aList n) }}} If you build `Use` with `-O -ddump-simpl` you will see that the RHS of `aList` has been inlined. I suspect the real bug here is the fact that this wasn't warned about previously. I'll try to draw attention to this change in the release notes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 07:24:27 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 07:24:27 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.b8f3979a2a65a0002ec0f2ab91fd64f1@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by hvr: @@ -5,0 +5,1 @@ + {{{ @@ -12,0 +13,1 @@ + }}} New description: When compiling dimensional-1.0.1.1 after patching numtype-dk with the patch at https://github.com/bjornbm/numtype-dk/issues/12 GHC does the "impossible": {{{ [ 3 of 16] Compiling Numeric.Units.Dimensional.Dimensions.TypeLevel ( src/Numeric/Units/Dimensional/Dimensions/TypeLevel.hs, dist/dist-sandbox- 68389a1a/build/Numeric/Units/Dimensional/Dimensions/TypeLevel.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-unknown-linux): Pattern match failure in do expression at compiler/rename/RnNames.hs:902:12-50 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 07:59:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 07:59:15 -0000 Subject: [GHC] #12030: GHCi Proposal: Display (Data.Kind.)Type instead of * Message-ID: <051.b7378bd56fec6afa8a8403e249c2a583@haskell.org> #12030: GHCi Proposal: Display (Data.Kind.)Type instead of * -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: GHCi | Version: 8.1 Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is premature but what the darn, {{{ >>> :kind Maybe Maybe :: Type -> Type >>> :kind StateT StateT :: Type -> (Type -> Type) -> Type -> Type >>> :kind Eq Eq :: Type -> Constraint >>> :info Functor class Functor (f :: Type -> Type) where ... }}} `*` throws students off and makes it seem scarier than it is. Symbols are harder to search for in general and to understand without documentation, `Type` on the other hand is descriptive. There are valid arguments against displaying `Type`: 1. It's a recent feature subject to change. 2. Although symbols are more difficult to search for, `*` is established in educational materials, logs, blogs and questions. 3. By default `Type` is not in scope so a user cannot ask for information in GHCi. `*` is established and searching for ?Haskell asterisk? yields a lot resources but [https://support.google.com/websearch/answer/2466433?hl=en ?*? is also a wildcard] in Google and ignored by GitHub. With time `Type` would be a good search term but currently it's chicken-and-the-egg. Previous versions of GHCi error on `:kind *` and `:info *` only shows multiplication so that wouldn't be a huge difference but we can qualify by default: {{{ >>> :kind Maybe Maybe :: Data.Kind.Type -> Data.Kind.Type >>> :kind StateT StateT :: Data.Kind.Type -> (Data.Kind.Type -> Data.Kind.Type) -> Data.Kind.Type -> Data.Kind.Type >>> :kind Eq Eq :: Data.Kind.Type -> Constraint >>> :info Functor class Functor (f :: Data.Kind.Type -> Data.Kind.Type) where ... }}} or display `*` normally and only when `TypeInType` is set do we display `Type`. I don't love it (and love `GHC.Types.Type` slightly less) but there is a precedent for unqualified names, browsing the Prelude for example: {{{#!hs ($) :: forall (r :: GHC.Types.RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b undefined :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). GHC.Stack.Types.HasCallStack => a }}} __If__ the consensus is that this will happen sometime down the line consider that each passing release means many more books and blog posts get written using `*`. I wasn't planning on resulting to scare tactics but [https://www.peoria.com/spaw/spawimages/members/member60763/shoot_this_dog.jpg here we are]... ---- If needed a migration plan can be drafted like the Semigroup/FTP/AMP/BBP/MonadFail/expanding Float/... proposals, possibly culminating in `Type` fully replacing `*` and being imported by default. I'm sure there are some further reaching consequences to this and better arguments against. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 09:39:55 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 09:39:55 -0000 Subject: [GHC] #12019: Profiling option -hb is not thread safe In-Reply-To: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> References: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> Message-ID: <059.caaf4ebb960ed29cb5275e8080319903@haskell.org> #12019: Profiling option -hb is not thread safe -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Runtime System | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11978, #12009 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Yes, when I made the rest of profiling thread-safe I didn't look at +RTS -hb. Perhaps we should disable it except at `-N1`, unless you want to have a go at fixing it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 09:52:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 09:52:37 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.0ea01d82de1c3a87ef5eeb69fa1b287d@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: high => highest Comment: Here is a small reproducer: T12026.hs: {{{#!hs module T12026 where import Prelude (map ()) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 10:18:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 10:18:10 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.4d0b677ef3f521f6b693b6fe64aa07e6@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: mpickering Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * owner: => mpickering -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 11:26:23 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 11:26:23 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.7061bc899289ce4ee39081d7a4d9f64e@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjcjoosten): * Attachment "TestTypeSynonyms.hs" added. Test file in which it takes really long to expand type synonyms (in ghc-8.0.1-rc4) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 11:33:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 11:33:13 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.a97004b0925a1bfef50697b27185d1f0@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016 Wiki Page: | -------------------------------------+------------------------------------- Comment (by sjcjoosten): Attached script is a reason to not have it on by default. The example code takes long enough to notice a delay but still see a result; changing the T12 and S12 into something like T15 S15 makes it take 'forever'. I don't know if this will occur in practice ? it's hard to measure since all of hackage seems to type-check, but it's a reason to keep the switch off by default (as it is in rc-4). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 12:11:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 12:11:32 -0000 Subject: [GHC] #12019: Profiling option -hb is not thread safe In-Reply-To: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> References: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> Message-ID: <059.33e4717e96cb91b2bda2cc52f1b200c4@haskell.org> #12019: Profiling option -hb is not thread safe -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Runtime System | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11978, #12009 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Yes, I'm going to try to fix it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 13:01:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 13:01:46 -0000 Subject: [GHC] #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors In-Reply-To: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> References: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> Message-ID: <060.3e1576b87b3543d5af337fde3dc0606f@haskell.org> #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by carter): I think I definitely would get a warning previously somehow for ordinary things. But foldable was sneaking off and getting away with stuff -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 13:55:23 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 13:55:23 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.5d656bd9ca6183a88a940bd918fb2456@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: mpickering Type: bug | Status: patch Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2181 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2181 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 16:21:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 16:21:02 -0000 Subject: [GHC] #12031: GHCi segfaults on Windows when compiling C code using extern-declared variable Message-ID: <050.daa1dfd7fb3e8ebf751c2100561e30c6@haskell.org> #12031: GHCi segfaults on Windows when compiling C code using extern-declared variable ----------------------------------------+------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: GHCi crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+------------------------------- Phyx- and I [https://phabricator.haskell.org/D1805#59850 noticed] that `bindings-GLFW` unpredictably segfaults when running this simple program in interpreted code: {{{#!hs module Main where import qualified Graphics.UI.GLFW as G main :: IO () main = do successfulInit <- G.init return () }}} Phyx- [https://phabricator.haskell.org/D1805#60275 suspected] that it had something to do with the `extern`-declared variables used in the GLFW library itself. To avoid requiring a dependency on GLFW, I boiled the issue down to a small, reproducible example with no dependencies, located at https://github.com/RyanGlScott/extern-bug. I will reproduce the code below: {{{#!c // foo.h #ifndef FOO_H #define FOO_H extern int foo; void bar(void); void baz(void); #endif }}} {{{#!c // bar.c #include "foo.h" int foo = 0; void bar(void) { foo = 1; baz(); } }}} {{{#!c // baz.c #include "foo.h" #include void baz(void) { printf("The value of foo is %d\n", foo); // Segfaults on this line fflush(stdout); } }}} {{{#!hs -- ExternBug.hs {-# LANGUAGE ForeignFunctionInterface #-} module ExternBug (bar) where {-# INCLUDE foo.h #-} foreign import ccall "bar" bar :: IO () }}} While I've managed to reproduce this bug sporadically with GHC 7.10.3, it happens far more reliably with GHC 8.0. Here is what I did to trigger the segfault: 1. Run `ghc bar.c baz.c ExternBug.hs` 2. Run `ghci bar.o baz.o ExternBug.hs` 3. Invoke `bar` I'm not sure what's happening, but there seem to be four important ingredients here: 1. This needs to be run in interpreted code. Compiled code does not have this issue. 2. The C sources need to be compiled to object code using GHC. (For example, if you link the MSYS2-provided `mingw-w64-x86_64-glfw` DLL, it will work correctly.) 3. There needs to be an `extern`-declared variable. (For example, uncommenting the lines mentioning the `foo` variable will make the issue go away.) 4. There needs to be at least two `.c` files. One file needs to assign a value to the `extern`-declared variable, and the other file needs to use the value. (For example, if you put the definitions of `bar` and `baz` in the same file, the bug doesn't occur.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 19:50:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 19:50:05 -0000 Subject: [GHC] #12032: Performance regression with large numbers of equation-style decls Message-ID: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> #12032: Performance regression with large numbers of equation-style decls -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- See the attached for a slice of code taken from Crypto-API that demonstrates a 2x regression in GHC compile times using -O2 (from 6.12.x to 7.10.x). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 19:50:38 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 19:50:38 -0000 Subject: [GHC] #12032: Performance regression with large numbers of equation-style decls In-Reply-To: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> References: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> Message-ID: <059.a884a62d911cb92a2e58775a623c4a0d@haskell.org> #12032: Performance regression with large numbers of equation-style decls -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by tommd): * Attachment "regression-cpoly.hs" added. A slice of crypto-api that shows performance regression in GHC -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 19:55:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 19:55:11 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.6bd3cb12d4ebc1991fa935400f566e8f@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This ordering problem is very apparent in GADT definitions. If you say {{{#!hs data X b where MkX :: forall a b. a -> b -> X b }}} you get `MkX :: forall b a. a -> b -> X b`. See the last bullet [https://downloads.haskell.org/~ghc/8.0.1-rc4/docs/html/users_guide/glasgow_exts.html #visible-type-application in the manual]. It would be straightforward, syntactically, to fix this for GADTs. The implementation is a bit more involved, because GHC assumes that universals come before existentials. This is surmountable with some engineering. We should consider this problem in concert with allowing visible type patterns (#11350), because we want patterns to be able to match existentials but not universals. It's very unclear how to do this in a way that will be sane to users. I don't have a good idea for a new syntax for dealing with this in pattern synonyms. As for classes, I'm not as bothered. The workaround is straightforward. Furthermore, we don't currently give full type signatures for class methods, always leaving off the class constraint. (I don't see how #11620 relates to this.) If we are going to be bothered about classes, we should also be bothered about record seleectors. But I vote not to be bothered about anything except data constructors and pattern synonyms. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 20:57:44 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 20:57:44 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311632=3A_Data=2EChar_repeated_readL?= =?utf-8?q?itChar_barfs_on_output_from_show_=22=C3=B31=22?= In-Reply-To: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> References: <049.9bf2436e7fb9c211d83d1b0ba3c6ee23@haskell.org> Message-ID: <064.8c3eb270eaaa8afc42b20c834e3a197a@haskell.org> #11632: Data.Char repeated readLitChar barfs on output from show "?1" -------------------------------------+------------------------------------- Reporter: inversemot | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer Comment: inversemot: what should `lexLitChar "\\243\\&1"` return in your opinion: 1. unchanged `[("\\243","\\&1")]` 2. consume the `\\&1` `[("\\243","")]` 3. consume and include the `\\&1` `[("\\243\\&1","")]` I suppose option 2. For a newcomer: I think you'll want to either change the function `lexChar` in the file `libraries/base/Text/Read/Lex.hs`, and/or the functions `lexLitChar` and `readLitChar` in `libraries/base/GHC/Read.hs`. * Why not change the function `lexCharE`? Because it is used by the function `lexLitChar`, which lexes a character surrounded by single quotes, but `'x\&'` isn't a valid character (maybe it should be? It would simplify things.). Also note that the function `lexString` handles `\&` by itself in `lexEmpty`. Don't forget a [wiki:Building/RunningTests/Adding test] and [wiki:WorkingConventions/FixingBugs submit] your patch to Phabricator. For reference, the [https://www.haskell.org/onlinereport/haskell2010/haskellch2.html#x7-200002.6 Haskell 2010 report] has this to say: > The escape character \& is provided as a ?null character? to allow strings such as "\137\&9" and "\SO\&H" to be constructed (both of length two). Thus "\&" is equivalent to "" and the character '\&' is disallowed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 21:05:01 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 21:05:01 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.27278404a7c23f120e5cbb64a1b3722f@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Thanks for the nice example. osa1, can you tell why it is slow in this case? Would it be easy to fix? If testing if there is an interesting expansion is slow, then it won't be possible to mention `-fprint-expanded-synonyms` since we won't be able to tell if there is an expansion or not (we could mention it unconditionally but that feels like bad UX.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 21:13:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 21:13:45 -0000 Subject: [GHC] #11640: Panic because of "updateRole" In-Reply-To: <051.a2aa2f07407d8fdc661bf953d330894a@haskell.org> References: <051.a2aa2f07407d8fdc661bf953d330894a@haskell.org> Message-ID: <066.b84a5ca7e45b962151177ad5409d2f51@haskell.org> #11640: Panic because of "updateRole" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Compiler (Type checker) Comment: This bug must have been fixed at some point. Can no longer reproduce this with HEAD. Perhaps the test should be added to the testsuite. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 21:27:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 21:27:36 -0000 Subject: [GHC] #11641: Allow wildcards for parameters functionally determined (also type synonyms) In-Reply-To: <051.4197dd5726816208c81417014cf4fc04@haskell.org> References: <051.4197dd5726816208c81417014cf4fc04@haskell.org> Message-ID: <066.97205fb69fda0f74a27e22b984840a1f@haskell.org> #11641: Allow wildcards for parameters functionally determined (also type synonyms) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | PartialTypeSignatures | FunctionalDependencies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: PartialTypeSignatures => PartialTypeSignatures FunctionalDependencies * cc: thomasw (added) * component: Compiler => Compiler (Type checker) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 21:35:19 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 21:35:19 -0000 Subject: [GHC] #11646: Make pattern synonym export type mismatch a warning In-Reply-To: <045.9eb8b2d1f35f468ff5981bb2e5b0840b@haskell.org> References: <045.9eb8b2d1f35f468ff5981bb2e5b0840b@haskell.org> Message-ID: <060.295dbe5efe9b862da4c975c2911ec53a@haskell.org> #11646: Make pattern synonym export type mismatch a warning -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Keywords: Resolution: wontfix | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | PatternSynonyms/AssociatingSynonyms| -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => wontfix Comment: No response from submitter. Unclear which problem this feature would solve. Please reopen if you disagree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 21:59:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 21:59:46 -0000 Subject: [GHC] #11655: Ambiguous types in pattern synonym not determined by functional dependencies In-Reply-To: <051.594ea8df445a741b9cbfd97613b98e7e@haskell.org> References: <051.594ea8df445a741b9cbfd97613b98e7e@haskell.org> Message-ID: <066.b6b246af004693a464463bd564088a14@haskell.org> #11655: Ambiguous types in pattern synonym not determined by functional dependencies -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | PatternSynonyms, | FunctionalDependencies, GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => PatternSynonyms, FunctionalDependencies, GADTs * cc: mpickering (added) * component: Compiler => Compiler (Type checker) Comment: Inferred type is still rejected in 8.1.20160503. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 22:41:54 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 22:41:54 -0000 Subject: [GHC] #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" In-Reply-To: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> References: <051.ef9fc6a373cf8eba53b7bf79d29ca288@haskell.org> Message-ID: <066.845d84413326d76b78be3faf551564a8@haskell.org> #11669: Incorrectly suggests RankNTypes for ill-formed type "forall a. Eq a. Int" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Parser) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #3155 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer * failure: None/Unknown => Incorrect warning at compile-time * component: Compiler => Compiler (Parser) * related: => #3155 Comment: This could be easy to fix: * Suggest `ExplicitForAll` instead of `RankNTypes`. * Only suggest `ExplicitForAll` if `ExplicitForAll` isn't set yet. For a newcomer: the code is `compiler/parser/Parser.y`. Search for `RankNTypes`, and see the function `hintExplicitForall` for inspiration. Don't forget a test! The last real change to this code was in 6c06fdc7ad20682f0f52b5a78e5e3487a2ed047b (#3155). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 23:03:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 23:03:05 -0000 Subject: [GHC] #11692: Suggest default definition of Applicative In-Reply-To: <051.d49ddb0a05fa30783e0a6deba6437f12@haskell.org> References: <051.d49ddb0a05fa30783e0a6deba6437f12@haskell.org> Message-ID: <066.f08d7df00428d0a64dff6f4131cc307a@haskell.org> #11692: Suggest default definition of Applicative -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => wontfix Comment: Replying to [comment:1 hvr]: > Your suggested warning enhancement is in contradiction to the recommendation expressed in several places (migration guide, AMP wiki page etc, `-Wnoncanonical-monad-instances`) to define `return` in terms of `pure` rather than the other way round. Wontfix it is. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 23:11:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 23:11:17 -0000 Subject: [GHC] #11695: On GHCi prompt the arrow (movement) keys create strange character sequences In-Reply-To: <048.2c7ac4aadebf684928a9b23225097ed9@haskell.org> References: <048.2c7ac4aadebf684928a9b23225097ed9@haskell.org> Message-ID: <063.1ff4b5b5950682bc6f8aef91fa05fac5@haskell.org> #11695: On GHCi prompt the arrow (movement) keys create strange character sequences ---------------------------------+-------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: GHCi | Version: 8.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: ping @heisenbug. See comment:9. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 7 23:21:14 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 07 May 2016 23:21:14 -0000 Subject: [GHC] #11802: Make a Win32 release In-Reply-To: <046.f5b09c91b5d426ec652c2f35da0c43b5@haskell.org> References: <046.f5b09c91b5d426ec652c2f35da0c43b5@haskell.org> Message-ID: <061.ac9eecfa4900747618909b25741f16ca@haskell.org> #11802: Make a Win32 release -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: upstream => closed * resolution: => fixed Comment: It happened. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 8 00:12:19 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 08 May 2016 00:12:19 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.bd040c5514b49329c461579551b8316a@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | https://github.com/TobyGoodwin/odd- | ghc-pattern-bug Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Here is a reproducer: {{{#!hs {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE TypeFamilies #-} -- Remove this line and the code compiles. module T11700 where data Muse data Message data Folder class PersistEntity record data Entity record = PersistEntity record => Entity record fn1 :: (Entity Muse, Entity Message, Entity Folder) -> (Message, Folder) fn1 cluster = let (Entity muse, Entity msg, Entity fldr) = cluster in (msg, fldr) }}} {{{ [1 of 1] Compiling T11700 ( T11700.hs, /tmp/T11700.o ) T11700.hs:17:12: error: ? Couldn't match expected type ?Folder? with actual type ?Folder? ? In the expression: fldr In the expression: (msg, fldr) In the expression: let (Entity muse, Entity msg, Entity fldr) = cluster in (msg, fldr) T11700.hs:17:7: error: ? Couldn't match expected type ?Message? with actual type ?Message? ? In the expression: msg In the expression: (msg, fldr) In the expression: let (Entity muse, Entity msg, Entity fldr) = cluster in (msg, fldr) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 8 16:49:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 08 May 2016 16:49:02 -0000 Subject: [GHC] #11816: Refactor SymbolInfo out of Linker.c In-Reply-To: <044.2e959aba1a89ef8ffe1336bae5217af4@haskell.org> References: <044.2e959aba1a89ef8ffe1336bae5217af4@haskell.org> Message-ID: <059.653edbb1ea7bc4e7498ca328c9ca44c1@haskell.org> #11816: Refactor SymbolInfo out of Linker.c -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: patch Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11223 | Differential Rev(s): Phab:D2184 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * differential: => Phab:D2184 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 8 17:01:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 08 May 2016 17:01:28 -0000 Subject: [GHC] #12031: GHCi segfaults on Windows when compiling C code using extern-declared variable In-Reply-To: <050.daa1dfd7fb3e8ebf751c2100561e30c6@haskell.org> References: <050.daa1dfd7fb3e8ebf751c2100561e30c6@haskell.org> Message-ID: <065.13ce5675fb91f41a037e95fd5e02636e@haskell.org> #12031: GHCi segfaults on Windows when compiling C code using extern-declared variable --------------------------------+---------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | --------------------------------+---------------------------------------- Comment (by RyanGlScott): I can't reproduce this issue with GHC 7.8.4 or 7.10.2, so it looks like the problem surfaced in GHC 7.10.3. Perhaps [https://ghc.haskell.org/trac/ghc/ticket/10726 upgrading the MinGW-w64 toolchain] has something to do with this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 8 19:28:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 08 May 2016 19:28:43 -0000 Subject: [GHC] #11974: `default` declaration doesn't allow higher-kinded types In-Reply-To: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> References: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> Message-ID: <062.54e662655beac8dcb91f2d1fa4b02402@haskell.org> #11974: `default` declaration doesn't allow higher-kinded types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2136 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Can this also let users default promoted datatypes? It would be very useful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 8 23:36:03 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 08 May 2016 23:36:03 -0000 Subject: [GHC] #10681: Teach GHC to interpret all hs files as two levels of hs-boot files (abstract types only/full types + values) In-Reply-To: <045.0dac7803547af5ada3f670c588d36854@haskell.org> References: <045.0dac7803547af5ada3f670c588d36854@haskell.org> Message-ID: <060.f4f4b25df1d4237c7d3028e19889a16a@haskell.org> #10681: Teach GHC to interpret all hs files as two levels of hs-boot files (abstract types only/full types + values) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 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 ezyang): * keywords: => backpack -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 01:22:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 01:22:42 -0000 Subject: [GHC] #11974: `default` declaration doesn't allow higher-kinded types In-Reply-To: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> References: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> Message-ID: <062.f78290a0977281ba7eb5d1352397c479@haskell.org> #11974: `default` declaration doesn't allow higher-kinded types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2136 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I have no idea what you mean here -- sorry. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 02:11:44 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 02:11:44 -0000 Subject: [GHC] #11743: Add unicode support for TH quotes (`[| |]`) In-Reply-To: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> References: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> Message-ID: <066.c21a8a86700c7d246807fec39e8d0bab@haskell.org> #11743: Add unicode support for TH quotes (`[| |]`) -------------------------------------+------------------------------------- Reporter: JoshPrice247 | Owner: JoshPrice247 Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.3 (Parser) | Keywords: unicode, Resolution: | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 2878, 10162 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by JoshPrice247: @@ -14,2 +14,1 @@ - in #10162 and implemented in Phab:D2012 (which has been accepted, but has - not yet landed), leaving TH quotes. + in #10162 and implemented in Phab:D2012, leaving TH quotes. New description: This has been mentioned before but didn't have it's own ticket. The following where mentioned in #2978, but the respective patch did not include them: * For TemplateHaskell: `? ?` (MATHEMATICAL _ WHITE SQUARE BRACKET) can be used instead of `[| |]` * For Generics: `? ?` (_ WHITE CURLY BRACKET) can be used instead of `{| |}` * For Arrows: `? ?` (Z NOTATION _ IMAGE BRACKET) can be used instead of `(| |)` Generic classes have since been removed and banana brackets were suggested in #10162 and implemented in Phab:D2012, leaving TH quotes. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 04:05:24 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 04:05:24 -0000 Subject: [GHC] #11743: Add unicode support for TH quotes (`[| |]`) In-Reply-To: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> References: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> Message-ID: <066.c2776a06b6ceee5d00d03fbcc2d3e078@haskell.org> #11743: Add unicode support for TH quotes (`[| |]`) -------------------------------------+------------------------------------- Reporter: JoshPrice247 | Owner: JoshPrice247 Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.3 (Parser) | Keywords: unicode, Resolution: | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 2878, 10162 | Differential Rev(s): Phab:D2185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by JoshPrice247): * differential: => Phab:D2185 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 04:40:20 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 04:40:20 -0000 Subject: [GHC] #12033: [TypeApplications] GHC internal error Message-ID: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> #12033: [TypeApplications] GHC internal error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Toying around, got {{{ GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/CatFail.hs, interpreted ) /tmp/CatFail.hs:55:26: error: ? GHC internal error: ?a? is not in scope during type checking, but it passed the renamer tcl_env of environment: [a1Ej :-> Type variable ?i? = i, a1Ek :-> Type variable ?p? = p, a1Et :-> Type variable ?a? = a, a1Eu :-> Type variable ?b? = b] ? In the first argument of ?Vacuous?, namely ?a? In the type ?Vacuous a? In the expression: Dict @(Vacuous a) /tmp/CatFail.hs:66:10: error: ? Couldn't match type ?Fun p q? with ?Vacuous? arising from a use of ?Main.$dmsrc? ? In the expression: Main.$dmsrc In an equation for ?src?: src = Main.$dmsrc In the instance declaration for ?Category (Nat p q)? ? Relevant bindings include src :: Nat p q a b -> Dict (Ob (Nat p q) a) (bound at /tmp/CatFail.hs:66:10) Failed, modules loaded: none. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 04:40:31 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 04:40:31 -0000 Subject: [GHC] #12033: [TypeApplications] GHC internal error In-Reply-To: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> References: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> Message-ID: <066.dd162388bf0fb485cc2ec3f7b0476e1f@haskell.org> #12033: [TypeApplications] GHC internal error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * Attachment "CatFail.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 07:32:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 07:32:42 -0000 Subject: [GHC] #11974: `default` declaration doesn't allow higher-kinded types In-Reply-To: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> References: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> Message-ID: <062.cd264d713e7a865b5daeb96324067040@haskell.org> #11974: `default` declaration doesn't allow higher-kinded types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2136 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Let's say you have {{{#!hs type Type? = Type type Num? = Num data Exp? (ty :: Type?) where N? :: Num? n => Exp? n deriving instance Show (Exp? ty) }}} {{{ ghci> :set -fwarn-type-defaults ghci> N? ... warning: [-Wtype-defaults] ? Defaulting the following constraint to type ?Integer? Num n0 arising from a use of ?it? ... N? }}} and you avoid writing `N? :: Exp? Integer` because of defaulting. If however one indexes it with a promoted data type {{{#!hs data Type? = Integer? | Int32? | Bool? class Num? (a :: Type?) instance Num? 'Integer? instance Num? 'Int32? data Exp? (ty :: Type?) where N? :: Num? n => Exp? n deriving instance Show (Exp? ty) }}} but showing it errors {{{ ghci> N? :3:1: error: ? Ambiguous type variable ?n0? arising from a use of ?it? prevents the constraint ?(Num? n0)? from being solved. Probable fix: use a type annotation to specify what ?n0? should be. These potential instances exist: instance Num? 'Int32? -- Defined at /tmp/tyGL.hs:11:10 instance Num? 'Integer? -- Defined at /tmp/tyGL.hs:10:10 ? In the first argument of ?print?, namely ?it? In a stmt of an interactive GHCi command: print it ghci> }}} I needed this and remembered this ticket. I want to write something like {{{#!hs default ('Integer?) -- Using https://prime.haskell.org/wiki/Defaulting#Proposal1-nametheclass default Num? ('Integer?) }}} Comment got to long, may split it -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 07:45:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 07:45:42 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.1fcac80ec4ecf82d1204dd7123a6710a@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): One possibility would be to use the same rules for pattern synonyms as for GADTs. When you write a GADT {{{ data A a where X :: A [xxx] }}} you mean {{{ X :: forall t. forall xxx. (t~[xxx]) => A t }}} so that it matches against a value of type `A ty` for any `ty`. We could do the same for pattern synonyms, so that {{{ pattern X' :: () => forall xxx. A [xxx] }}} means precisely {{{ pattern X' :: forall t. () => forall xxx. (t ~ [xxx]) => A t }}} Perhaps we could do without the leading `() =>`; I'm not sure. This doesn't deal with the whole issue (as Richard points out, GADTs themselves have a smaller problem), but it ameliorates it and makes it the same as GADTs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 07:46:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 07:46:58 -0000 Subject: [GHC] #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) In-Reply-To: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> References: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> Message-ID: <059.d463544b50494d7ba16cd4fe032c9366@haskell.org> #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * failure: None/Unknown => Compile-time performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 07:53:51 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 07:53:51 -0000 Subject: [GHC] #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors In-Reply-To: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> References: <045.16fbc969ee37854242b852c0f4001eba@haskell.org> Message-ID: <060.38ca06ea62c8c42a02e303fee08d26e1@haskell.org> #12027: ghc 8.0rc4 treats INLINE pragmas for methods with default (implicit) definitions as errors -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by simonpj): I suppose it's conceivable that in some instances you want to inline the default method, and not in others. So we could make it so that a pragma for the (invisible) default-method binding in the instance overrides the one from the class decl. Possible, if there are compelling use-cases. But it's one more thing to specify, explain, implement, and maintain. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 08:05:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 08:05:29 -0000 Subject: [GHC] #12032: Performance regression with large numbers of equation-style decls In-Reply-To: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> References: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> Message-ID: <059.f6bddd9ce263a14d614d800c62ebf3d7@haskell.org> #12032: Performance regression with large numbers of equation-style decls -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * failure: None/Unknown => Compile-time performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 08:11:59 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 08:11:59 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.3e2421a0e155470bf3a92b5add1e8e8c@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | https://github.com/TobyGoodwin/odd- | ghc-pattern-bug Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thomie, thanks. But when you say "here is a reproducer" you are assuming that I've installed some package defining "Muse" etc. Which ones, precisely? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 08:53:06 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 08:53:06 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.d426927d736e94eccb88140c13ccf25d@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | https://github.com/TobyGoodwin/odd- | ghc-pattern-bug Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by TobyGoodwin): Fantastic work thomie! Thanks so much for this. That appears to be standalone to me, no extra packages needed. Copy and paste that code into `T11700.hs`, run `ghc T11700.hs` and you get the bogus error. Works for me with ghc-7.10.3 and no `~/.ghc` or `~/.cabal`. And as thomie says, removing the `TypeFamilies` extension makes the problem go away. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 10:28:31 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 10:28:31 -0000 Subject: [GHC] #11629: reify returns Dec that use ConT instead of PromotedT In-Reply-To: <045.3a9e8f83fc23a014023064d2c545236e@haskell.org> References: <045.3a9e8f83fc23a014023064d2c545236e@haskell.org> Message-ID: <060.49ded89d494413a7f5740b194645f0a7@haskell.org> #11629: reify returns Dec that use ConT instead of PromotedT -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bollmann): Also with promoted tuples quotation with quotation brackets `[t| .. |]` yields a different promoted type than the type obtained by reify. Consider: {{{ {-# LANGUAGE FlexibleInstances, KindSignatures, TemplateHaskell, DataKinds #-} module MoreBugs where import Language.Haskell.TH class D (a :: (Bool, Bool)) instance D '(True, False) $(return []) main = do putStrLn $ $([t| D '(True, False) |] >>= stringE . show) putStrLn "vs." putStrLn $ $(do ClassI _ [InstanceD _ ty _] <- reify ''D stringE (show ty)) }}} On a recent GHC snapshot this gives: {{{ AppT (ConT MoreBugs.D) (AppT (AppT (PromotedTupleT 2) (PromotedT GHC.Types.True)) (PromotedT GHC.Types.False)) vs. AppT (ConT MoreBugs.D) (SigT (AppT (AppT (ConT GHC.Tuple.(,)) (ConT GHC.Types.True)) (ConT GHC.Types.False)) (AppT (AppT (TupleT 2) (ConT GHC.Types.Bool)) (ConT GHC.Types.Bool))) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 11:55:15 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 11:55:15 -0000 Subject: [GHC] #11974: `default` declaration doesn't allow higher-kinded types In-Reply-To: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> References: <047.2c4be3a4c34290389efa6f45ff0342fe@haskell.org> Message-ID: <062.06531fc625f9e10501a10b69c3d8856a@haskell.org> #11974: `default` declaration doesn't allow higher-kinded types -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2136 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): You're proposing a wholesale extension of the defaulting mechanism. Defaulting happens as per the Haskell Report or with a [https://downloads.haskell.org/~ghc/8.0.1-rc4/docs/html/users_guide/ghci.html #type-defaulting-in-ghci small extension]. In either case, the set of defaultable classes is fixed. You're proposing changing this, which is quite different than the purpose of this ticket. (This ticket is about letting `default` declarations include types that are already defaultable.) If you want this new behavior, I encourage you to write a specification of it (on a wiki page) and then submit a feature request. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 14:00:09 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 14:00:09 -0000 Subject: [GHC] #8761: Make pattern synonyms work with Template Haskell In-Reply-To: <047.c5d8ed063e9e82c354c50c5724ebe787@haskell.org> References: <047.c5d8ed063e9e82c354c50c5724ebe787@haskell.org> Message-ID: <062.fa574e656764c2abb813ece09833b6c0@haskell.org> #8761: Make pattern synonyms work with Template Haskell -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bollmann Type: feature request | Status: patch Priority: normal | Milestone: Component: Template Haskell | 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): Phab:D1940 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bollmann): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 14:17:45 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 14:17:45 -0000 Subject: [GHC] #11954: Associated pattern synonyms not included in haddock In-Reply-To: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> References: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> Message-ID: <061.72dfc07cd53987ac08b546c844efa772@haskell.org> #11954: Associated pattern synonyms not included in haddock -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by darchon): * Attachment "haddock_bundled_pat_to_con.patch" added. Cleaned up version of earlier patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 14:32:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 14:32:02 -0000 Subject: [GHC] #11954: Associated pattern synonyms not included in haddock In-Reply-To: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> References: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> Message-ID: <061.89dd31fcfa45470d66756e67e6482639@haskell.org> #11954: Associated pattern synonyms not included in haddock -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by darchon): * Attachment "0001-Display-bundled-pattern-synonyms-as-GADT- constructor.patch" added. Now in git format-patch style -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 16:36:00 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 16:36:00 -0000 Subject: [GHC] #9630: compile-time performance regression (probably due to Generics) In-Reply-To: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> References: <042.a529e5f70870528e7f8796a28ce82a84@haskell.org> Message-ID: <057.537031feff8a9fbbd8cffd45811250a7@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: deriving- | perf, Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thoughtpolice): Just as an aside, I also applied the trick from comment:23 to cereal, and the results were almost unbelievable. The example given (comment:22) actually completely exhausts the simplifier tickets, so it essentially turns a non-compiling program into a compiling one that works in less than a second. https://github.com/GaloisInc/cereal/commit/94c87592d010fdb381c6a2dc963bbfcef99c3a27 The result on the `binary-serialise-cbor` suite with this change is incredible. Just another data point - it would be useful to minimize `cereal` akin to `binary` in comment:22 and see the difference. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 18:59:15 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 18:59:15 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.22f94db41dc74f4eb71e883f8d9a6fcb@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Thanks for your responses. Replying to [comment:5 simonpj]: > We could do the same for pattern synonyms, so that > {{{ > pattern X' :: () => forall xxx. A [xxx] > }}} > means precisely > {{{ > pattern X' :: forall t. () => forall xxx. (t ~ [xxx]) => A t > }}} That sounds like a step in the right direction Simon but would this make the current meaning of {{{#!hs pattern X' :: () => forall xxx. A [xxx] }}} inexpressible (a pattern that only matches `A [xxx]`)? I want to be aware of the trade-offs, I don't have use for it personally -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 19:36:07 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 19:36:07 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.b0e8ba2c15ddd85533f8d8ad0f78f3be@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): 8.1.20160503 {{{ ghci> class P (p :: Type -> Type) where pee :: p a -> Int ghci> :set -fprint-explicit-foralls ghci> :t pee pee :: forall {a} {p :: Type -> Type}. P p => p a -> Int }}} `a` appears before `p`, but does not apply in that order? This is surprising behaviour to me: {{{ ghci> instance P Maybe where pee = length ghci> :t pee @Maybe pee @Maybe :: forall {a}. Maybe a -> Int ghci> :t pee @Maybe @() pee @Maybe @() :: Maybe () -> Int }}} ---- Replying to [comment:4 goldfire]: > As for classes, I'm not as bothered. The workaround is straightforward. I wonder if you could just mention the variable before the instance but that is disallowed in `class` declarations. Something silly `class a ~ a => P p where pee :: p a -> Int`. By accident I saw the ticket #6081 which quantifies in the instance signature: {{{#!hs instance forall (a :: k). KindClass (KP :: KProxy [k]) }}} I had no idea this was allowed, it seems to only refer to variables in the instance head, when I try to use it: {{{#!hs -- error: -- ? Couldn't match type ?a1? with ?a? instance forall a. P Maybe where pee :: Maybe a -> Int pee = length }}} Currently disallowed in class declarations, but what if {{{#!hs class forall a. P (p :: Type -> Type) where pee :: p a -> Int }}} meant that `a` appears before `p` in methods? The downside is that this would apply to every method across the board leaving no way to write siblings with a different order {{{#!hs class Q q where cue_1 :: q a -> Int cue_2 :: q a -> Int -- cue_1 :: forall q a. Q q => q a -> Int -- cue_1 :: forall a q. Q q => q a -> Int }}} This may just be inherent in the way type classes are structured, reminds me of Idris' [http://docs.idris-lang.org/en/latest/tutorial/typesfuns.html #using-notation ?using? notation]. In broken Idris: {{{#!hs using (q:Type -> Type) using (a:Type) cue_1 : q a -> Int cue_2 : q a -> Int using (a:Type) using (q:Type -> Type) cue_1 : q a -> Int cue_2 : q a -> Int }}} It isn't a show-stopper for type classes as Richard says, just nice to have. I hadn't even thought of record selectors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 19:40:52 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 19:40:52 -0000 Subject: [GHC] #7100: Loosen requirement for free variables in constraint in class declaration In-Reply-To: <047.d6cecb0b4fa4ed28c6ded84e8fff3141@haskell.org> References: <047.d6cecb0b4fa4ed28c6ded84e8fff3141@haskell.org> Message-ID: <062.4903b09872716bc9f474d0d57425a23a@haskell.org> #7100: Loosen requirement for free variables in constraint in class declaration -------------------------------------+------------------------------------- Reporter: selinger | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 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 Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 19:44:41 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 19:44:41 -0000 Subject: [GHC] #12025: Order of constraints forced (in pattern synonyms, type classes in comments) In-Reply-To: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> References: <051.f7825cd1538f4e1bd703526f61b3a749@haskell.org> Message-ID: <066.d579aed20123b141c9d6ead91b358ee4@haskell.org> #12025: Order of constraints forced (in pattern synonyms, type classes in comments) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: Resolution: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11513, 10928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Semirelated: #7100 ticket allowing variables in `class` declaration that don't appear as class parameters, this would be handy -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 9 20:04:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 09 May 2016 20:04:16 -0000 Subject: [GHC] #6118: Kind variable falls out of scope in instance declaration In-Reply-To: <047.beaad97b513c5786b53ced9432d2cba5@haskell.org> References: <047.beaad97b513c5786b53ced9432d2cba5@haskell.org> Message-ID: <062.2624042982b756438d936c10178b1978@haskell.org> #6118: Kind variable falls out of scope in instance declaration -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.5 Resolution: fixed | Keywords: PolyKinds Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | polykinds/T6118 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): 8.1.20160503: {{{#!hs -- twgv.hs:32:3-43: error: ? -- The RHS of an associated type declaration mentions ?k? -- All such variables must be bound on the LHS -- Compilation failed. instance SingE (a :: Maybe k) where type Demote a = Maybe (Demote (Any :: k)) }}} Still fails, kind annotation needed: {{{#!hs instance SingE (a :: Maybe k) where type Demote (a ::Maybe k) = Maybe (Demote (Any :: k)) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 00:26:38 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 00:26:38 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.e5690386560490e9ad641999ba4f50fb@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * owner: => akio -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 03:54:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 03:54:30 -0000 Subject: [GHC] #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer Message-ID: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.0.1-rc2 (Type checker) | Keywords: backpack | 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 don't think this is a very harmful bug but it definitely is a bug. Consider: {{{ -- A.hs-boot module A where data T -- B.hs module B (module A) where import {-# SOURCE #-} A -- A.hs {-# LANGUAGE TemplateHaskell #-} module A where import qualified B import Language.Haskell.TH f :: B.T -> B.T f x = x $( return [] ) data T = T B.T }}} The point of the splice is to convince GHC to typecheck `f :: B.T -> B.T` before it typechecks the type declaration. But this is not going to work, because `tcLookupGlobal` is going to bail if (1) T is not in the `tcg_type_env` and (2) T comes from this module. It would be a simple matter to improve the error message but from a user's perspective, there is no good reason for this to not typecheck. On the implementation side, I am sympathetic to not letting this typecheck: if it does typecheck, then some `TyCon`s will incorrectly refer to the definition from the hs-boot file, rather than our local definition. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 05:18:36 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 05:18:36 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.c214f52b240a031dc6a05a9639b957e1@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * keywords: => hs-boot Comment: Here is an interesting phenomenon in the test case in this bug: it does not infinite loop if you use `--make`. If we look carefully at the inlining log we can see why (I added an extra trace for when there is no unfolding): {{{ Inlining done: T10083.eqRSR \ (ds_d1H8 [Occ=Once!] :: T10083.RSR) (ds_d1H9 [Occ=Once!] :: T10083.RSR) -> case ds_d1H8 of { T10083.MkRSR s1 [Occ=Once] -> case ds_d1H9 of { T10083.MkRSR s2 [Occ=Once] -> T10083a.eqSR s1 s2 } } Inlining done: T10083a.eqSR \ (ds [Occ=Once!] :: T10083a.SR) (ds1 [Occ=Once!] :: T10083a.SR) -> case ds of { T10083a.MkSR r1 [Occ=Once] -> case ds1 of { T10083a.MkSR r2 [Occ=Once] -> T10083.eqRSR r1 r2 } } no unfolding eqRSR }}} Notice that once we unfold `eqSR`, there is NO INLINING on `eqRSR`! Coincidence? Absolutely not: when we compiled `B.hs` we added an `Id` to the HPT which has an unfolding referring to the `eqRSR` from the hs-boot file, which obviously doesn't have an inlining. And clearly we don't flush the HPT prior to typechecking `A.hs`. So we will stop inlining once we hit this hs-boot `Id`. The situation with one-shot is different, however: we haven't loaded the interface, and by the time we try to load the `Id` for `eqRSR` when loading the unfolding for `eqSR`, it's already in the environment and so we give it the right unfolding... disaster! There is something pesky going on with the interface loading business but that's for another bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 06:15:53 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 06:15:53 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.5812322965ff70ee42bdb5d22f922623@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Another observation: `ghc --make -fforce-recomp -ddump-if-trace` hangs infinitely. That's a bug in its own right; one that I've seen before but never for such a nice test-case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 08:31:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 08:31:11 -0000 Subject: [GHC] #9478: Partial type signatures In-Reply-To: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> References: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> Message-ID: <061.c2beec9a3bd87124659fcb8d24eb196c@haskell.org> #9478: Partial type signatures -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/PatBind2 | partial- | sigs/should_compile/EqualityConstraint Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D168 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"e1ff2b4950a02bc26b9ab36c9c589a8156e324bd/ghc" e1ff2b49/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e1ff2b4950a02bc26b9ab36c9c589a8156e324bd" Fix partial sigs and pattern bindings interaction It turns out that GHC 8.0 would accept entirely bogus programs like f2 :: (True, _) -> Char Just f2 = Just (\x->x) (which is now partial-sigs/should_fail/PatBind3) This also fixes Trac #9478, test `PatBind2`. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:08:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:08:50 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.9b54ccbffdf9a90118b3a0f883135f4e@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Simon, re the performance problem, I'm no inliner expert but I think the problem is that you're always giving declarations which occur in the hs- boot file "never inline", even when it's totally inappropriate. For example, rewrite `eqRSR` to unconditionally return `True` and you'll still get: {{{ -- RHS size: {terms: 9, types: 6, coercions: 0} eqRSR [InlPrag=[NEVER]] :: RSR -> RSR -> Bool [GblId, Arity=2, Caf=NoCafRefs, Str=] eqRSR = \ (ds_d1H9 :: RSR) (ds1_d1Ha :: RSR) -> case ds_d1H9 of { MkRSR s1_aKA -> case ds1_d1Ha of { MkRSR s2_aKB -> GHC.Types.True } } }}} I bet it's failure to inline for clients of RSR.hs which is causing the performance degradation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:29:39 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:29:39 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.86d3f093f8464d966f8324e06202c5ca@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > I bet the inability to inline eqRSR even if you don't depend on the boot file is causing the performance degradation. Yes, that's what I speculated in comment:18, final para. But I still don't know what to do about it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:31:29 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:31:29 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.ce882877a6559aab673b3e0fd2a6f28f@haskell.org> #10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:751 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): It seems unlikely that bullet (2) is the way to go: `idArity` is ostensibly saying something about the Core program it points to. Which causes the invariant to be violated first: the simplifier or demand analysis? I think that's the one that should be responsible for fixing the invariant. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:36:20 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:36:20 -0000 Subject: [GHC] #11961: PatBind test suite failure with `-DDEBUG` In-Reply-To: <046.8458f776be5ba55c048624dcb46a7891@haskell.org> References: <046.8458f776be5ba55c048624dcb46a7891@haskell.org> Message-ID: <061.6dc0381785128550a4a4cb3c6f4f9278@haskell.org> #11961: PatBind test suite failure with `-DDEBUG` -------------------------------------+------------------------------------- Reporter: nomeata | Owner: simonpj Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Fixed by one of my recent commits: {{{ commit 9dbf5f5c63f6ffde86c2faab60c97e97c77a27c3 Tidy up partial-sig quantification commit e1ff2b4950a02bc26b9ab36c9c589a8156e324bd Fix partial sigs and pattern bindings interaction commit 76d9156f6446d87e0f859a44959d63c2067fc805 Emit wild-card constraints in the right place }}} I forget which one -- but fixing this bug is what started me down the road! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:47:18 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:47:18 -0000 Subject: [GHC] #12035: hs-boot knot tying insufficient for ghc --make Message-ID: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> #12035: hs-boot knot tying insufficient for ghc --make -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: hs-boot | Operating System: Unknown/Multiple backpack | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC in one-shot mode goes through great pains to make sure that if we are typechecking A.hs with an A.hs-boot, any references to A in the interfaces we load in should point to the `TyThing`s from our LOCAL `tcg_type_env` (`_var`), not the declarations from the `hs-boot`. Indeed, it is never right to load the hi-boot file into the EPS (#10182, #10336). Because in one-shot compilation we are loading things into the EPS anew, there is not much risk of having stale `TyThing`s lying around which still refer to the old `hs-boot` ModDetails. `ghc --make` does not do a sufficient job as knot tying. Specifically, any `Id`s/`TyThing`s from the HPT which were built against the `hs-boot` ModDetails will have out-of-date information. We do manage to tie the knot if we use `tcLookupGlobal` directly, which does look in the local type environment (e.g., #12034 affects both `-c` and `--make`), but if we get our hands on a `TyThing` indirectly, we're in trouble. The case where this is most obvious is unfoldings; see #10083 for an example of GHC behaving differently between `-c` and `--make` (although, ironically, `--make`s bad behavior masks the bug). It's not entirely clear how to fix this problem. In analogy to what happens in `-c`, we should clear the stale `TyThing`s from our HPT and retypecheck them after we have setup the type environment for our `hs` file. But presently in `--make` we don't lazily load types from our home package. Maybe we should! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:58:59 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:58:59 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.04a859a84e5fa659e4d1f8da9ac63105@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: mpickering Type: bug | Status: patch Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2181 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"53f26f5a45f146e1cc988bbcf76a362c877beaa2/ghc" 53f26f5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="53f26f5a45f146e1cc988bbcf76a362c877beaa2" Forbid variables to be parents in import lists. In the long discussion on #11432, it was decided that when a type constructor is parsed as a variable ((--.->) is one example) then in order to export the type constructor then the user should be required to use the ExplicitNamespaces keyword. This was implemented in quite an indirect manner in the renamer. It is much more direct to enforce this in the parser at the expense of slighty worse error messages. Further to this, the check in the renamer was actually slightly wrong. If the variable was in scope then no error was raised, this was causing panics, see #12026 for an example. Reviewers: austin, bgamari Subscribers: davean, skvadrik, thomie Differential Revision: https://phabricator.haskell.org/D2181 GHC Trac Issues: #12026 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 09:58:59 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 09:58:59 -0000 Subject: [GHC] #11432: Cannot export operator newtype In-Reply-To: <045.9a7fdda2cb353078e033f239a1207022@haskell.org> References: <045.9a7fdda2cb353078e033f239a1207022@haskell.org> Message-ID: <060.5033a569846f480bdfe31abb81882665@haskell.org> #11432: Cannot export operator newtype -------------------------------------+------------------------------------- Reporter: phadej | Owner: skvadrik Type: bug | Status: closed Priority: highest | Milestone: 8.0.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): Phab:D1902 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"53f26f5a45f146e1cc988bbcf76a362c877beaa2/ghc" 53f26f5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="53f26f5a45f146e1cc988bbcf76a362c877beaa2" Forbid variables to be parents in import lists. In the long discussion on #11432, it was decided that when a type constructor is parsed as a variable ((--.->) is one example) then in order to export the type constructor then the user should be required to use the ExplicitNamespaces keyword. This was implemented in quite an indirect manner in the renamer. It is much more direct to enforce this in the parser at the expense of slighty worse error messages. Further to this, the check in the renamer was actually slightly wrong. If the variable was in scope then no error was raised, this was causing panics, see #12026 for an example. Reviewers: austin, bgamari Subscribers: davean, skvadrik, thomie Differential Revision: https://phabricator.haskell.org/D2181 GHC Trac Issues: #12026 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 10:00:16 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 10:00:16 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.5a117f0900b56295904dd254589733b4@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Ah, I misparsed comment:18. How about call-site loop breakers? Put something in `IdDetails` saying that you should never inline this variable, and then always annotate any direct references to an `hs-boot` file with this marker. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 10:57:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 10:57:41 -0000 Subject: [GHC] #11629: reify returns Dec that use ConT instead of PromotedT In-Reply-To: <045.3a9e8f83fc23a014023064d2c545236e@haskell.org> References: <045.3a9e8f83fc23a014023064d2c545236e@haskell.org> Message-ID: <060.45cce947b3989b6f95fb4f5e734706d9@haskell.org> #11629: reify returns Dec that use ConT instead of PromotedT -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Template Haskell | 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:D2188 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bollmann): * status: new => patch * differential: => Phab:D2188 Comment: I've submitted a preliminary patch fixing the bug mentioned by @aavogt's . However, the inconsistencies wrt promoted tuples remain. See the phabricator diff for the remaining problems. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 11:31:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 11:31:58 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.4e7d538eb40cb2975560927b35a1cfe5@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't understand how that would differ from marking it NOINLINE. Can you be more specific? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 11:40:14 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 11:40:14 -0000 Subject: [GHC] #12019: Profiling option -hb is not thread safe In-Reply-To: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> References: <044.c916057b5b621f461c24cd1e505f507d@haskell.org> Message-ID: <059.768a180681ed2bc085c52fe74705a186@haskell.org> #12019: Profiling option -hb is not thread safe -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Runtime System | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11978, #12009 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Fixing this is definitely not trivial. I've placed locks around some of the shared mutable data structures, but I still get the same assertion (in function `processHeapClosureForDead`) failing: {{{ ASSERT(((LDVW(c) & LDV_CREATE_MASK) >> LDV_SHIFT) > 0); }}} because the `overwritingClosure` has already been called on it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:09:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:09:13 -0000 Subject: [GHC] #12038: Shutdown interacts badly with requestSync() Message-ID: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> #12038: Shutdown interacts badly with requestSync() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Runtime | Version: 7.10.3 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: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:09:33 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:09:33 -0000 Subject: [GHC] #12038: Shutdown interacts badly with requestSync() In-Reply-To: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> References: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> Message-ID: <062.5f40cc43cd3de837e4a224c81dc4b878@haskell.org> #12038: Shutdown interacts badly with requestSync() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonmar: @@ -0,0 +1,3 @@ + I've been investigating #10860, and the problem goes pretty deep, + so I'm going to record what I know here and come back to fix it + properly later. @@ -2,0 +5,19 @@ + We have this mechanism `requestSync()` for operations that need + to seize control of the whole runtime to do something. It is used by + + * `scheduleDoGC()` + * `setNumCapabilities()` + * `forkProcess()` + + `requestSync()` ensures that only one of these operations wins, + the others will `yieldCapability()` to the winner, before + continuing with their own sync. + + The problem is that this interacts badly with shutdown. Shutdown + might start at any time (initiated by `exitScheduler()`). If it + starts during a sync, then a deadlock is likely: some + capabilities will be already shut down, and cannot be acquired by + `acquireAllCapabilities()`. This happens in #10860. + + Really, shutdown should play the `requestSync()` game too, but + that requires a lot of thought. New description: I've been investigating #10860, and the problem goes pretty deep, so I'm going to record what I know here and come back to fix it properly later. We have this mechanism `requestSync()` for operations that need to seize control of the whole runtime to do something. It is used by * `scheduleDoGC()` * `setNumCapabilities()` * `forkProcess()` `requestSync()` ensures that only one of these operations wins, the others will `yieldCapability()` to the winner, before continuing with their own sync. The problem is that this interacts badly with shutdown. Shutdown might start at any time (initiated by `exitScheduler()`). If it starts during a sync, then a deadlock is likely: some capabilities will be already shut down, and cannot be acquired by `acquireAllCapabilities()`. This happens in #10860. Really, shutdown should play the `requestSync()` game too, but that requires a lot of thought. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:10:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:10:13 -0000 Subject: [GHC] #10860: setnumcapabilities001: internal error: ASSERTION FAILED: file rts/Schedule.c, line 400 In-Reply-To: <045.1b9d7e0fabda0a4b3797cc5dc85f2044@haskell.org> References: <045.1b9d7e0fabda0a4b3797cc5dc85f2044@haskell.org> Message-ID: <060.34777c5d7ae7d6b6e30c6005d35aaf4c@haskell.org> #10860: setnumcapabilities001: internal error: ASSERTION FAILED: file rts/Schedule.c, line 400 -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 12038 | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * blockedby: => 12038 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:26:43 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:26:43 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.5239e752f6b74844b4826b97abba02f2@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"4ac0e815739f6362c2815dd3ae531055a095d6a9/ghc" 4ac0e81/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4ac0e815739f6362c2815dd3ae531055a095d6a9" Kill unnecessary cmpType in lhs_cmp_type This is the only call site of `lhs_cmp_type` and we only care about equality. `cmpType` is nondeterministic (because `TyCon`s are compared with Uniques in `cmpTc`), so if we don't have to use it, it's better not to. Test Plan: ./validate Reviewers: simonmar, goldfire, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2172 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:31:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:31:11 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.0d617e2452aebd73e5b1168dcfafb2ce@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"b58b0e18a568bbf6381a85eea7adc72679355671/ghc" b58b0e1/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b58b0e18a568bbf6381a85eea7adc72679355671" Make simplifyInstanceContexts deterministic simplifyInstanceContexts used cmpType which is nondeterministic for canonicalising typeclass constraints in derived instances. Following changes make it deterministic as explained by the Note [Deterministic simplifyInstanceContexts]. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2173 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:37:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:37:06 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.880a89b91664066d7919d7cc76e4d55b@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * differential: => Phab:D2189 Comment: Replying to [comment:14 ezyang]: > If it's a regression from per-generation weak pointer lists, we can just revert that commit, right? Since per-generation weak pointer lists are in since GHC 7.8, reverting it would mean creating another regression. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 12:46:19 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 12:46:19 -0000 Subject: [GHC] #12039: Panic with partial class definition Message-ID: <043.594973634c4616bf2544fe97c427a9c7@haskell.org> #12039: Panic with partial class definition -------------------------------------+------------------------------------- Reporter: maud | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Compiling a class with partial definition fails: {{{#!hs class A _ => B a }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-apple-darwin): rnHsTyKi HsWildcardTy }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 13:21:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 13:21:55 -0000 Subject: [GHC] #9478: Partial type signatures In-Reply-To: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> References: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> Message-ID: <061.d12a246fd65b2bd4167599b96aa517cf@haskell.org> #9478: Partial type signatures -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/PatBind2 | partial- | sigs/should_compile/EqualityConstraint Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D168 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"e24b50c3a70a247a4695a80aceba0cf351eb1e9e/ghc" e24b50c3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e24b50c3a70a247a4695a80aceba0cf351eb1e9e" Use partial-sig constraints as givens In TcSimplify.simplifyInfer, use the context of a partial type signature as 'givens' when simplifying the inferred constraints of the group. This way we get maximum benefit from them. See Note [Add signature contexts as givens]. This (finally) fixes test EqualityConstraints in Trac #9478. And it's a nice tidy-up. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 13:34:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 13:34:40 -0000 Subject: [GHC] #9478: Partial type signatures In-Reply-To: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> References: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> Message-ID: <061.40a4ce29c1e8e88618009ebc6d50d384@haskell.org> #9478: Partial type signatures -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/PatBind2 | partial- | sigs/should_compile/EqualityConstraint Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D168 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"1a43783edd3bda2b934aaedf2f68b4d0e0c5eb02/ghc" 1a43783e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1a43783edd3bda2b934aaedf2f68b4d0e0c5eb02" Record that EqualityConstraint now works Fixing Trac #9478 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 13:35:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 13:35:41 -0000 Subject: [GHC] #9478: Partial type signatures In-Reply-To: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> References: <046.53a47ac5f73cf1b7df317af2585f061e@haskell.org> Message-ID: <061.a8ec15d0c958008ccf3cbfe8447cfac9@haskell.org> #9478: Partial type signatures -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_compile/PatBind2 | partial- | sigs/should_compile/EqualityConstraint Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D168 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: This last patch finally fixes the `EqualityConstraint` test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 14:11:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 14:11:06 -0000 Subject: [GHC] #11640: Panic because of "updateRole" In-Reply-To: <051.a2aa2f07407d8fdc661bf953d330894a@haskell.org> References: <051.a2aa2f07407d8fdc661bf953d330894a@haskell.org> Message-ID: <066.9b10f151674cceb7095ff1017c993b3c@haskell.org> #11640: Panic because of "updateRole" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"f6e58be297f97e8871396f80a81fe3a9984d77b9/ghc" f6e58be/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f6e58be297f97e8871396f80a81fe3a9984d77b9" Test Trac #11640 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 14:11:32 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 14:11:32 -0000 Subject: [GHC] #11959: Importing doubly exported pattern synonym and associated pattern synonym panics In-Reply-To: <046.6ec5a340ae5bc3bfa0a1a054dcc8ecc7@haskell.org> References: <046.6ec5a340ae5bc3bfa0a1a054dcc8ecc7@haskell.org> Message-ID: <061.6926effe039f28e2d585ec82bae9c03b@haskell.org> #11959: Importing doubly exported pattern synonym and associated pattern synonym panics -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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): Phab:D2132, Wiki Page: | Phab:D2133 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.0.1 => 8.0.2 Comment: We're going to bump this off to 8.0.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 14:14:44 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 14:14:44 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.ccf65b7671cd47f722acfdcf1dd605c0@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"7e28e47ca36e849ed104f5a13e0c08253b135fae/ghc" 7e28e47/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7e28e47ca36e849ed104f5a13e0c08253b135fae" Get rid of Traversable UniqFM and Foldable UniqFM Both Traversable and Foldable can introduce non-determinism and because of typeclass overloading it's implicit and not obvious at the call site. This removes the instances, so that they can't accidentally be used. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2190 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 16:27:54 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 16:27:54 -0000 Subject: [GHC] #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 Message-ID: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- (I am not sure if this is an issue with the release candidate or with my code. I'm sorry, I've tried hard to investigate that but not come to a firm conclusion. I'm reporting it on the chance that it might be an issue with the release candidate.) The code at https://github.com/bjornbm/dimensional/tree/c5b41bbcecb710d566f8af6e561dcafd93ea4e20 builds and passes tests on 7.8.4 and 7.10.3. The same code fails under 8.0.1-rc4 with the following message: {{{ src/Numeric/Units/Dimensional/Dynamic.hs:79:10: error: ? The constraint ?KnownDimension d? is no smaller than the instance head (Use UndecidableInstances to permit this) ? In the instance declaration for ?Demotable (Quantity d)? }}} I'm not sure if the relationship here between `Demotable`, `KnownDimension`, `HasDimension`, and `HasDynamicDimension` in fact requires undecidable instances (in which case 7.8.4 and 7.10.3 are either allowing it in error? or helpfully allowing it even though they aren't obligated to?) or if it does not in fact require undecidable instances (in which case 8.0.1-rc4 is disallowing it in error). Making things even more interesting, a new feature branch of the same project doesn't appear to change any of the things that should be relevant to this error message, but compiles and tests without the error on 8.0.1-rc4 as well as the earlier compiler versions. That one's at https://github.com/dmcclean/dimensional/tree/9f3b0a207258851964defd90ce497e75edb4fe2a. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 16:33:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 16:33:13 -0000 Subject: [GHC] #11954: Associated pattern synonyms not included in haddock In-Reply-To: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> References: <046.dee795066f70760dedef2b550cf6d5e0@haskell.org> Message-ID: <061.6b46808bb6e7583ab6072d864ebab39b@haskell.org> #11954: Associated pattern synonyms not included in haddock -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.0.1 => 8.0.2 Comment: Sadly this will need to be bumped to 8.0.2 as the current patch is still a bit rough around the edges. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 16:33:54 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 16:33:54 -0000 Subject: [GHC] #11955: Haddock documentation for pattern synonyms printed with explicit forall quantifiers In-Reply-To: <046.a6a2b187c86fbb5c93bbd55a34566418@haskell.org> References: <046.a6a2b187c86fbb5c93bbd55a34566418@haskell.org> Message-ID: <061.e866becfe185523cb985034c731ea7d8@haskell.org> #11955: Haddock documentation for pattern synonyms printed with explicit forall quantifiers -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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 bgamari): * milestone: 8.0.1 => 8.0.2 Comment: I'm afraid this won't be fixed for 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 16:41:48 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 16:41:48 -0000 Subject: [GHC] #4806: Make error message more user friendly when module is not found because package is unusable In-Reply-To: <044.33251b8e69d1b6796ddff38b98a4991e@haskell.org> References: <044.33251b8e69d1b6796ddff38b98a4991e@haskell.org> Message-ID: <059.f40ebf06f614f3b85fa23a3c79b7eb15@haskell.org> #4806: Make error message more user friendly when module is not found because package is unusable -------------------------------------+------------------------------------- Reporter: mitar | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.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 mpickering): * owner: lstrano => Comment: Please reassign if you still plan to work on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 16:44:20 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 16:44:20 -0000 Subject: [GHC] #10600: -fwarn-incomplete-patterns doesn't work with -fno-code In-Reply-To: <043.972d3170891da80a4e96bca7b675a836@haskell.org> References: <043.972d3170891da80a4e96bca7b675a836@haskell.org> Message-ID: <058.dff0f388064f62122071e03de649671a@haskell.org> #10600: -fwarn-incomplete-patterns doesn't work with -fno-code -------------------------------------+------------------------------------- Reporter: akio | Owner: ezyang Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: driver/T8101b Blocked By: | Blocking: Related Tickets: #8101 | Differential Rev(s): Phab:D1278 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: newcomer => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 18:57:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 18:57:27 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" Message-ID: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language PolyKinds, TypeFamilies #-} import Data.Kind class Category (p :: i -> i -> Type) where type Ob p :: i -> Constraint data I a b instance Category I where type Ob I = (~) Int }}} fails with {{{ $ ghci -ignore-dot-ghci /tmp/Error.hs GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/Error.hs, interpreted ) /tmp/Error.hs:10:15: error:ghc: panic! (the 'impossible' happened) (GHC version 8.1.20160503 for x86_64-unknown-linux): print_equality ~ Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 20:26:32 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 20:26:32 -0000 Subject: [GHC] #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. In-Reply-To: <049.7ed7d5ba2f5e5e856922764e36628b22@haskell.org> References: <049.7ed7d5ba2f5e5e856922764e36628b22@haskell.org> Message-ID: <064.ff0a7ebb13f639f9268cb509ea679877@haskell.org> #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. -------------------------------------+------------------------------------- Reporter: jpbernardy | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Resolution: | Keywords: deriving, | newcomer 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:D978 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * owner: osa1 => @@ -1,10 +1,34 @@ - On a "phantom datatype" D, one gets the message: - {{{ - Can't make a derived instance of `Eq D': - `D' must have at least one data constructor - }}} - However there is a trivial, correct instance of Eq D: - {{{ - instance Eq D where - (==) = undefined - }}} + mpickering reminded me this ticket so before I leave the ownership of this + ticket let me write down the current status: + + Basically there are a couple of things we can do and we just need someone + to + decide which one. + + 1. Implement {{{==}}} as {{{_ == _ = True}}}. Pro: this is consistent with + {{{Void}}}'s {{{Eq}}} instance. Con: I think this lets some bugs to sneak + in. I think it doesn't make sense to compute things based on equality of + empty types, so at this point you've probably made a mistake and it's + better to just bail out. + + 2. Implement {{{==}}} as `x == y = case x of {}`. Pro: it fixes the + problem with (1) and in a good way - you've probably used something like + {{{error "..."}}} for the empty type terms, so you get your error message. + Con: this inconsistent with {{{Void}}}. + + 3. Leave this as is - no {{{deriving (Eq)}}}. This way we make the user + decide which behaviour to have. Pro: You can have whatever you want. Con: + Inconvenient. + + These were also discussed at some point but IIRC most people agree that + these + are bad ideas: + + 4. {{{x == y = error "(==) on empty type"}}}: If it's going to fail it's + better to fail like (2). + + 5. {{{_ == _ = False}}}: Denotationally / type-theoretically bottoms are + equal or something like that? So it's better to implement (1) instead. + + 6. Implement (2), change {{{Void}}}s instance too: Can potentially break + code. New description: mpickering reminded me this ticket so before I leave the ownership of this ticket let me write down the current status: Basically there are a couple of things we can do and we just need someone to decide which one. 1. Implement {{{==}}} as {{{_ == _ = True}}}. Pro: this is consistent with {{{Void}}}'s {{{Eq}}} instance. Con: I think this lets some bugs to sneak in. I think it doesn't make sense to compute things based on equality of empty types, so at this point you've probably made a mistake and it's better to just bail out. 2. Implement {{{==}}} as `x == y = case x of {}`. Pro: it fixes the problem with (1) and in a good way - you've probably used something like {{{error "..."}}} for the empty type terms, so you get your error message. Con: this inconsistent with {{{Void}}}. 3. Leave this as is - no {{{deriving (Eq)}}}. This way we make the user decide which behaviour to have. Pro: You can have whatever you want. Con: Inconvenient. These were also discussed at some point but IIRC most people agree that these are bad ideas: 4. {{{x == y = error "(==) on empty type"}}}: If it's going to fail it's better to fail like (2). 5. {{{_ == _ = False}}}: Denotationally / type-theoretically bottoms are equal or something like that? So it's better to implement (1) instead. 6. Implement (2), change {{{Void}}}s instance too: Can potentially break code. -- Comment: mpickering reminded me this ticket so before I leave the ownership of this ticket let me write down the current status: Basically there are a couple of things we can do and we just need someone to decide which one. 1. Implement {{{==}}} as {{{_ == _ = True}}}. Pro: this is consistent with {{{Void}}}'s {{{Eq}}} instance. Con: I think this lets some bugs to sneak in. I think it doesn't make sense to compute things based on equality of empty types, so at this point you've probably made a mistake and it's better to just bail out. 2. Implement {{{==}}} as {{{x == y = case x of {}}}}. Pro: it fixes the problem with (1) and in a good way - you've probably used something like {{{error "..."}}} for the empty type terms, so you get your error message. Con: this inconsistent with {{{Void}}}. 3. Leave this as is - no {{{deriving (Eq)}}}. This way we make the user decide which behaviour to have. Pro: You can have whatever you want. Con: Inconvenient. These were also discussed at some point but IIRC most people agree that these are bad ideas: 4. {{{x == y = error "(==) on empty type"}}}: If it's going to fail it's better to fail like (2). 5. {{{_ == _ = False}}}: Denotationally / type-theoretically bottoms are equal or something like that? So it's better to implement (1) instead. 6. Implement (2), change {{{Void}}}s instance too: Can potentially break code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 20:41:56 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 20:41:56 -0000 Subject: [GHC] #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm In-Reply-To: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> References: <044.ad3f32463aae7c699d4d4bd8ae6b6c27@haskell.org> Message-ID: <059.2d3b68424da6f52c0f99e302a35feb85@haskell.org> #11981: unknown symbol `__udivti3' when BuildFlavour = perf-llvm -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Further examination shows that this only happens when `DYNAMIC_GHC_PROGRAMS = NO` in `mk/build/mk`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 20:43:08 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 20:43:08 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" In-Reply-To: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> References: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> Message-ID: <066.332482ce9e6e5a791a3696f2239dc6d0@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Doesn't happen if {{{#!hs data I (a :: Type) (b :: k) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 20:48:19 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 20:48:19 -0000 Subject: [GHC] #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. In-Reply-To: <049.7ed7d5ba2f5e5e856922764e36628b22@haskell.org> References: <049.7ed7d5ba2f5e5e856922764e36628b22@haskell.org> Message-ID: <064.42f6b88dc797568ba3599446fde7a477@haskell.org> #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. -------------------------------------+------------------------------------- Reporter: jpbernardy | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Resolution: | Keywords: deriving, | newcomer 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:D978 Wiki Page: | -------------------------------------+------------------------------------- Description changed by osa1: @@ -1,34 +1,10 @@ - mpickering reminded me this ticket so before I leave the ownership of this - ticket let me write down the current status: - - Basically there are a couple of things we can do and we just need someone - to - decide which one. - - 1. Implement {{{==}}} as {{{_ == _ = True}}}. Pro: this is consistent with - {{{Void}}}'s {{{Eq}}} instance. Con: I think this lets some bugs to sneak - in. I think it doesn't make sense to compute things based on equality of - empty types, so at this point you've probably made a mistake and it's - better to just bail out. - - 2. Implement {{{==}}} as `x == y = case x of {}`. Pro: it fixes the - problem with (1) and in a good way - you've probably used something like - {{{error "..."}}} for the empty type terms, so you get your error message. - Con: this inconsistent with {{{Void}}}. - - 3. Leave this as is - no {{{deriving (Eq)}}}. This way we make the user - decide which behaviour to have. Pro: You can have whatever you want. Con: - Inconvenient. - - These were also discussed at some point but IIRC most people agree that - these - are bad ideas: - - 4. {{{x == y = error "(==) on empty type"}}}: If it's going to fail it's - better to fail like (2). - - 5. {{{_ == _ = False}}}: Denotationally / type-theoretically bottoms are - equal or something like that? So it's better to implement (1) instead. - - 6. Implement (2), change {{{Void}}}s instance too: Can potentially break - code. + On a "phantom datatype" D, one gets the message: + {{{ + Can't make a derived instance of `Eq D': + `D' must have at least one data constructor + }}} + However there is a trivial, correct instance of Eq D: + {{{ + instance Eq D where + (==) = undefined + }}} New description: On a "phantom datatype" D, one gets the message: {{{ Can't make a derived instance of `Eq D': `D' must have at least one data constructor }}} However there is a trivial, correct instance of Eq D: {{{ instance Eq D where (==) = undefined }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 10 23:23:29 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 10 May 2016 23:23:29 -0000 Subject: [GHC] #11062: Type families + hs-boot files = panic In-Reply-To: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> References: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> Message-ID: <062.d4f027ba61ebe106bd94b49b53743f9d@haskell.org> #11062: Type families + hs-boot files = panic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Another example of this is T6018, when built in one-shot mode. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 04:07:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 04:07:22 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.f6d65d7a284655ba050be0133d8e77ed@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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 akio): * cc: akio (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 04:59:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 04:59:14 -0000 Subject: [GHC] #12042: Infinite loop with type synonyms and hs-boot Message-ID: <045.2af2d998455883876e6ff4ff050c9c9d@haskell.org> #12042: Infinite loop with type synonyms and hs-boot -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: hs-boot | Operating System: Unknown/Multiple backpack | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is a "known" bug, but the source code comment which mentioned this could happen didn't give a test case so I thought I'd supply one. {{{ -- A.hs-boot module A where data S type R = S -- B.hs module B (module A, module B) where import {-# SOURCE #-} A type U = S -- A.hs module A where import qualified B type S = B.R type R = B.U }}} When I try to build `A.hs` in one-shot I infinite loop: {{{ ezyang at sabre:~$ ghc-8.0 --make A.hs -fforce-recomp [1 of 3] Compiling A[boot] ( A.hs-boot, A.o-boot ) [2 of 3] Compiling B ( B.hs, B.o ) [3 of 3] Compiling A ( A.hs, A.o ) A.hs-boot:2:1: error: Type constructor ?S? has conflicting definitions in the module and its hs-boot file Main module: type S = R Boot file: abstract S ezyang at sabre:~$ ghc-8.0 -c A.hs -fforce-recomp ^C }}} The problem is that `-c` properly knot ties `data S` in the boot file to the local type synonym (`--make` is unaffected due to #12035), and then we have a type synonym loop which GHC doesn't catch early enough. `TcTyDecls.hs` has a nice comment which suggests that this is a known bug: {{{ Checking for class-decl loops is easy, because we don't allow class decls in interface files. We allow type synonyms in hi-boot files, but we *trust* hi-boot files, so we don't check for loops that involve them. So we only look for synonym loops in the module being compiled. We check for type synonym and class cycles on the *source* code. Main reasons: a) Otherwise we'd need a special function to extract type-synonym tycons from a type, whereas we already have the free vars pinned on the decl b) If we checked for type synonym loops after building the TyCon, we can't do a hoistForAllTys on the type synonym rhs, (else we fall into a black hole) which seems unclean. Apart from anything else, it'd mean that a type-synonym rhs could have for-alls to the right of an arrow, which means adding new cases to the validity checker Indeed, in general, checking for cycles beforehand means we need to be less careful about black holes through synonym cycles. The main disadvantage is that a cycle that goes via a type synonym in an .hi-boot file can lead the compiler into a loop, because it assumes that cycles only occur entirely within the source code of the module being compiled. But hi-boot files are trusted anyway, so this isn't much worse than (say) a kind error. }}} although the circumstances in this example are a little different. I take this bug as evidence that we should NOT attempt to knot-tie in this situation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 07:57:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 07:57:57 -0000 Subject: [GHC] #12043: internal error: evacuate: strange closure type Message-ID: <047.629114b05785e472aaf473c1aa71fdb1@haskell.org> #12043: internal error: evacuate: strange closure type -------------------------------------+------------------------------------- Reporter: mattchan | Owner: Type: bug | Status: new Priority: normal | Milestone: Research needed Component: Compiler | Version: 7.10.3 Keywords: internal | Operating System: Unknown/Multiple error, strange closuren | Architecture: ia64 | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Scary error while building Liquid Haskell from source: {{{ $ stack install [truncated] text-1.2.2.1: copy/register Progress: 40/61 -- While building package Cabal-1.22.8.0 using: /Users/matt/.stack/setup-exe-cache/x86_64-osx/setup-Simple- Cabal-1.22.5.0-ghc-7.10.3 --builddir=.stack- work/dist/x86_64-osx/Cabal-1.22.5.0 build --ghc-options " -ddump-hi -ddump-to-file" Process exited with code: ExitFailure (-6) Logs have been written to: /Users/matt/liquid/liquidhaskell/.stack- work/logs/Cabal-1.22.8.0.log Configuring Cabal-1.22.8.0... Building Cabal-1.22.8.0... Preprocessing library Cabal-1.22.8.0... [ 1 of 81] Compiling Paths_Cabal ( .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/autogen/Paths_Cabal.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Paths_Cabal.o ) [ 2 of 81] Compiling Distribution.TestSuite ( Distribution/TestSuite.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/TestSuite.o ) [ 3 of 81] Compiling Distribution.Simple.PreProcess.Unlit ( Distribution/Simple/PreProcess/Unlit.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Simple/PreProcess/Unlit.o ) [ 4 of 81] Compiling Distribution.GetOpt ( Distribution/GetOpt.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/GetOpt.o ) [ 5 of 81] Compiling Distribution.PackageDescription.Utils ( Distribution/PackageDescription/Utils.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/PackageDescription/Utils.o ) [ 6 of 81] Compiling Distribution.Simple.CCompiler ( Distribution/Simple/CCompiler.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Simple/CCompiler.o ) [ 7 of 81] Compiling Distribution.Compat.Binary ( Distribution/Compat/Binary.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Compat/Binary.o ) [ 8 of 81] Compiling Distribution.Compat.ReadP ( Distribution/Compat/ReadP.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Compat/ReadP.o ) [ 9 of 81] Compiling Distribution.Text ( Distribution/Text.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Text.o ) [10 of 81] Compiling Distribution.Version ( Distribution/Version.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Version.o ) [11 of 81] Compiling Language.Haskell.Extension ( Language/Haskell/Extension.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Language/Haskell/Extension.o ) [12 of 81] Compiling Distribution.Compiler ( Distribution/Compiler.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Compiler.o ) [13 of 81] Compiling Distribution.Simple.Compiler ( Distribution/Simple/Compiler.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Simple/Compiler.o ) [14 of 81] Compiling Distribution.Simple.GHC.ImplInfo ( Distribution/Simple/GHC/ImplInfo.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Simple/GHC/ImplInfo.o ) [15 of 81] Compiling Distribution.License ( Distribution/License.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/License.o ) [16 of 81] Compiling Distribution.ModuleName ( Distribution/ModuleName.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/ModuleName.o ) [17 of 81] Compiling Distribution.Package ( Distribution/Package.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/Package.o ) [18 of 81] Compiling Distribution.System ( Distribution/System.hs, .stack-work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/System.o ) [19 of 81] Compiling Distribution.PackageDescription ( Distribution/PackageDescription.hs, .stack- work/dist/x86_64-osx/Cabal-1.22.5.0/build/Distribution/PackageDescription.o ) ghc: internal error: evacuate: strange closure type 41832616 (GHC version 7.10.3 for x86_64_apple_darwin) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} [[Image(http://i.imgur.com/T44UPg0.png)]] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 08:00:55 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 08:00:55 -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.60b8063f99af2954f935738552a2b568@haskell.org> #12043: internal error: evacuate: strange closure type -------------------------------------+------------------------------------- Reporter: mattchan | Owner: Type: bug | Status: new Priority: normal | Milestone: Research | needed Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: ia64 Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mattchan): * keywords: internal error, strange closuren => * failure: None/Unknown => Runtime crash -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 08:02:07 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 08:02:07 -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.9afd0d49c6142449c07f3144abb37898@haskell.org> #12043: internal error: evacuate: strange closure type ----------------------------------+--------------------------------------- Reporter: mattchan | Owner: Type: bug | Status: new Priority: normal | Milestone: Research needed 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 mattchan): * os: Unknown/Multiple => MacOS X -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 10:05:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 10:05:35 -0000 Subject: [GHC] #12044: Remove sortWith in favor of sortOn Message-ID: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> #12044: Remove sortWith in favor of sortOn -------------------------------------+------------------------------------- Reporter: cblp | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 7.10.3 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: 2659 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- There is Data.List.sortOn that does the same as GHC.Exts.sortWith, and even seems to be more effective. GHC.Exts.sortWith should be deprecated or removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 10:38:28 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 10:38:28 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.9543a0249414fc0ee8c4ba33c8b104b6@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"8669c48d06ca260c13740e0bda97beea52d332fb/ghc" 8669c48/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8669c48d06ca260c13740e0bda97beea52d332fb" Document why closeOverKind is OK for determinism There's no point in converting the existing call sites to use deterministic closeOverKinds if they never linearize the set. Test Plan: it compiles, this is basically just documentation Reviewers: simonpj, goldfire, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2191 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 13:18:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 13:18:48 -0000 Subject: [GHC] #11746: I encountered an: internal error: evacuate: strange closure type 803645000 In-Reply-To: <044.aa2d5c70936d934e77a4152edf0034bf@haskell.org> References: <044.aa2d5c70936d934e77a4152edf0034bf@haskell.org> Message-ID: <059.2e4bc583832bed657beb7c7016b0db7b@haskell.org> #11746: I encountered an: internal error: evacuate: strange closure type 803645000 -------------------------------+-------------------------------------- Reporter: hkBst | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #11108 | Differential Rev(s): Wiki Page: | -------------------------------+-------------------------------------- Comment (by Ben Gamari ): In [changeset:"9363f04d0ff22f3d898af35bb5432c4287e6dc9a/ghc" 9363f04/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9363f04d0ff22f3d898af35bb5432c4287e6dc9a" Handle promotion failures when scavenging a WEAK (#11108) Previously, we ignored promotion failures when evacuating fields of a WEAK object. When a failure happens, this resulted in an WEAK object pointing to another object in a younger generation, causing crashes. I used the test case from #11746 to check that the fix is working. However I haven't managed to produce a test case that quickly reproduces the issue. Test Plan: ./validate Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2189 GHC Trac Issues: #11108 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 13:18:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 13:18:48 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.f5b9aa721fcf7633460e19f6592955a2@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9363f04d0ff22f3d898af35bb5432c4287e6dc9a/ghc" 9363f04/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9363f04d0ff22f3d898af35bb5432c4287e6dc9a" Handle promotion failures when scavenging a WEAK (#11108) Previously, we ignored promotion failures when evacuating fields of a WEAK object. When a failure happens, this resulted in an WEAK object pointing to another object in a younger generation, causing crashes. I used the test case from #11746 to check that the fix is working. However I haven't managed to produce a test case that quickly reproduces the issue. Test Plan: ./validate Reviewers: austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2189 GHC Trac Issues: #11108 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 13:40:15 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 13:40:15 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.8a7560210440ca88ff0f660227bf2e88@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * milestone: 8.2.1 => 8.0.1 Comment: This was merged to `ghc-8.0` as 0e12124320f0e09a56813fe6361e61043667db53. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 14:51:38 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 14:51:38 -0000 Subject: [GHC] #12035: hs-boot knot tying insufficient for ghc --make In-Reply-To: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> References: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> Message-ID: <060.042e1b98b0fa420f985e44dde3f13633@haskell.org> #12035: hs-boot knot tying insufficient for ghc --make -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: hs-boot Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't understand. In `--make` mode, doesn't `GhcMake.typecheckLoop` re- typecheck all the modules that depended on the `hs-boot` file? Isn't that precisely what `typecheckLoop` is for? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 15:17:15 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 15:17:15 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.17b6f68e97fe0d5081f56a31263d4a83@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryantrinkle): Here's a patch to add this test: https://phabricator.haskell.org/D2196 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 15:20:01 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 15:20:01 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.43942bc46bf6cd539f990dcb002cab26@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"3edbd091341ab0ab60862ba18d3107f34c7fc876/ghc" 3edbd09/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3edbd091341ab0ab60862ba18d3107f34c7fc876" Document SCC determinism I've documented the guarantees that stronglyConnCompFromEdgedVertices provides and commented on the call sites to explain why they are OK from determinism standpoint. I've changed the functions to nonDetUFM versions, so that it's explicit they could introduce nondeterminism. I haven't defined container (VarSet, NameSet) specific versions, so that we have less functions to worry about. Test Plan: this is mostly just documentation, it should have no runtime effect Reviewers: bgamari, simonmar, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2194 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 15:20:01 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 15:20:01 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.c2d57dfa49bb0652c72b400fc9f13003@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"0e719885f53e20f2e14a94b32d858b47b516a8fc/ghc" 0e719885/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0e719885f53e20f2e14a94b32d858b47b516a8fc" Remove some varSetElems in dsCmdStmt varSetElems introduces unnecessary determinism and it's easy to preserve determinism here. Test Plan: ./validate Reviewers: goldfire, simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2195 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 15:20:03 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 15:20:03 -0000 Subject: [GHC] #12045: Visible kind application Message-ID: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> #12045: Visible kind application -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple TypeApplications TypeInType | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I've wanted this for a while {{{ ghci> :kind (:~:) (:~:) :: k -> k -> Type }}} {{{ ghci> :kind (:~:) @(Type -> Type) (:~:) @(Type -> Type) :: (Type -> Type) -> (Type -> Type) -> Type ghci> :kind (:~:) @(Type -> Type) [] (:~:) @(Type -> Type) [] :: (Type -> Type) -> Type ghci> :kind (:~:) @(Type -> Type) [] Maybe (:~:) @(Type -> Type) [] Maybe :: Type }}} Working like {{{ ghci> type Same k (a::k) (b::k) = a :~: b ghci> :kind Same Same :: forall k -> k -> k -> * }}} {{{ ghci> :kind Same (Type -> Type) Same (Type -> Type) :: (Type -> Type) -> (Type -> Type) -> * ghci> :kind Same (Type -> Type) [] Same (Type -> Type) [] :: (Type -> Type) -> * ghci> :kind Same (Type -> Type) [] Maybe Same (Type -> Type) [] Maybe :: * }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 15:24:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 15:24:14 -0000 Subject: [GHC] #12045: Visible kind application In-Reply-To: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> References: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> Message-ID: <066.2f687fb91396885c92d1a8e667586beb@haskell.org> #12045: Visible kind application -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I had better motivating examples in mind way back when. I believe this should be fine wrt parsing `@` at the type level: {{{#!haskell k :: Const @Bool Int 'False -- ' k = Const 42 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 15:46:59 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 15:46:59 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.09645d3641c5a679dbca0215d8efc353@haskell.org> #10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:751 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The real culprit here is the eta-reduction of {{{ t = \x -> t x }}} In general `CoreUtils.tryEtaReduce` eta-reduces `\x t x` to `t` if `t` is a head-normal form, definitely not bottom. However, here `t` cheerfully says that its arity is 1, and so the eta-reduction goes ahead. But now its arity isn't 1 any more! And the eta-reduction is unsound, because {{{t `seq` True}}} will behave differently than before. One simple solution would be this: * Never eta-reduce a let right-hand side. See `SimplUtils.mkLam`, which refrains from eta-expansion of let right-hand sides. This a bit drastic because it doesn't eta-reduce the non-recursive {{{ myMap = \f x -> map f x }}} When we eta-reduce we get a trivial binding, so we can substitute, and win all round. So a better strategy would be * Never eta-reduce a let right-hand side of a recursive group. To do this, we'd have to augment `RhsCtxt` (the data constructor of `CoreUnfold.CallCtxt`) with a `RecFlag`. My bet is that this more conservative story would do little harm. More ambitiously, we should look at at recursive group of bindings as a whole. We already have special treatment for eta ''expansion'' for let(rec) rhss; see `SimplUtils.tryEtaExpandRhs`. But it is still one- binding-at-a-time, which isn't as good as it could be; see `Note [Arity analysis]` in `CoreArity`. We could instead do eta expansion and reduction for let(rec) RHSs for a group as a whole. This latter seems like the Right Thing to do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 16:01:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 16:01:56 -0000 Subject: [GHC] #12038: Shutdown interacts badly with requestSync() In-Reply-To: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> References: <047.55986d4d6d0cb4f4e54545fae8ff67a3@haskell.org> Message-ID: <062.68ba68a38788b004adc0c56935d84924@haskell.org> #12038: Shutdown interacts badly with requestSync() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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: 10860 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"cfc5df43a7789832a2789e517d8270650cc31b7f/ghc" cfc5df4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cfc5df43a7789832a2789e517d8270650cc31b7f" Fix ASSERT failure and re-enable setnumcapabilities001 The assertion failure was fairly benign, I think, but this fixes it. I've been running the test repeatedly for the last 30 mins and it hasn't triggered. There are other problems exposed by this test (see #12038), but I've worked around those in the test itself for now. I also copied the relevant bits of the parallel library here so that we don't need parallel for the test to run. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 16:59:23 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 16:59:23 -0000 Subject: [GHC] #12035: hs-boot knot tying insufficient for ghc --make In-Reply-To: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> References: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> Message-ID: <060.61c63ab9a99eeb95ad4bb3e6ec03045e@haskell.org> #12035: hs-boot knot tying insufficient for ghc --make -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: hs-boot Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by ezyang): This PDF gives the full story, http://web.mit.edu/~ezyang/Public/backpack- symbol-tables.pdf but the short answer is that there are two ways we loop tie hs-boot. The first, which is correctly implemented for `--make`, is retypechecking all the modules that depended on the `hs-boot` file. The second is tying the loop ''at the same time'' we are typechecking the `hs` module which implements the `hs-boot` file; i.e., it's what `tcg_type_env_var` is for. If we have: {{{ -- A.hs-boot module A where x :: Bool -- B.hs module B where import {-# SOURCE #-} A y = not x -- A.hs module A where import B x = True z = not y }}} When we typecheck `A.hs`, does the unfolding for `y` have an up-to-date unfolding for `x`? In one-shot mode the answer is yes (and thus we see the behavior of #10083), but in make mode the answer is no. The retypecheck loop has nothing to do with it, since it happens AFTER we finish building the hs file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 18:18:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 18:18:30 -0000 Subject: [GHC] #4239: -ddump-minimal-imports vs. type operators In-Reply-To: <046.6d817d321031413c0ab6d8874d8ae7ab@haskell.org> References: <046.6d817d321031413c0ab6d8874d8ae7ab@haskell.org> Message-ID: <061.b5faf876a82b69286e6df368830f0c6c@haskell.org> #4239: -ddump-minimal-imports vs. type operators -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T4239 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dsf): * status: closed => new * version: 6.12.1 => 7.10.3 * resolution: fixed => * milestone: 7.4.1 => Comment: There is still at least one case where this is still happening - the operator ? (char 183) comes out without parens: {{{#!hs module Test ((?), (?)) where (?) = undefined (?) = undefined }}} {{{#!hs module Test2 ((?), (?)) where import Test ((?), (?)) }}} -ddump-minimal-imports outputs this for Test2: {{{#!hs import Test ( ?, (?) ) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 18:40:37 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 18:40:37 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.ab57cba89947df2841908fd3a9bf59be@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I found the problem and I'm current working on a fix... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 19:24:04 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 19:24:04 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.187e2482ddd7fc67aab9fee6ebc55e14@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Changes (by osa1): * differential: Phab:D1016 => Phab:D1016, Phab:D2198 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 19:32:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 19:32:48 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.a1de299d27bbb5c75c3c4f32b544621a@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Comment (by osa1): OK, this should be fixed now. I'm currently validating the patch locally. As for why not enable this by default: The algorithm is looking through all expansions, so if the first type can be expanded `n` and second type `m` times, it takes `O(n * m)` steps to find a version of the error message that has minimum amount of expansions. When fixing this bug I realized that type synonym expansion is probably fast enough, and in practice `n` and `m` will not be too big, so maybe it's OK to enable this by default. We should probably just generate some pathological cases and look at compile times with and without `-fprint-expanded-synonyms`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 20:07:25 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 20:07:25 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.de031ad3068cb2bc86fc4851c7945ef1@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Comment (by ezyang): Under Simon's algorithm, I don't see why you should have an `O(n * m)` asymptotic behavior. I guess you are trying to handle this case? {{{ type T = Int type S = T type S1 = S type S2 = S -- error message comparing S1 and S2 -- AKA S and S (not Int and Int) }}} Then the problem resolves to this: given two (singly) linked lists which share a common tail, determine the head of the tail. This is a popular coding interview question and you can do better than `O(n * m)`; e.g. by method 3 here http://www.geeksforgeeks.org/write-a-function-to-get-the- intersection-point-of-two-linked-lists/ -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 11 22:34:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 11 May 2016 22:34:41 -0000 Subject: [GHC] #4239: -ddump-minimal-imports vs. type operators In-Reply-To: <046.6d817d321031413c0ab6d8874d8ae7ab@haskell.org> References: <046.6d817d321031413c0ab6d8874d8ae7ab@haskell.org> Message-ID: <061.79e176657b4987880d5263c9dfd3e140@haskell.org> #4239: -ddump-minimal-imports vs. type operators -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T4239 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 May 12 05:13:32 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 05:13:32 -0000 Subject: [GHC] #12046: AllowAmbiguousTypes doesn't work with UndecidableSuperClasses Message-ID: <050.acd80f71b0a88c07742de9edc6ba0919@haskell.org> #12046: AllowAmbiguousTypes doesn't work with UndecidableSuperClasses -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Given the code below, `test1` and `test2` are the same except the former has an ambiguous type and the latter does not. The compiler rejects the former and accepts the latter. {{{ {-# LANGUAGE UndecidableSuperClasses #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE TypeFamilies #-} class A (T a) => A a where type T a test1 :: forall a. A a => () test1 = () test2 :: A a => proxy a -> () test2 _ = () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 05:49:10 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 05:49:10 -0000 Subject: [GHC] #10803: New SignatureSections extension In-Reply-To: <042.499b2af8de1376e7739ef3516bd5a45e@haskell.org> References: <042.499b2af8de1376e7739ef3516bd5a45e@haskell.org> Message-ID: <057.b07df087e149a6de7ca7255aa6b502ed@haskell.org> #10803: New SignatureSections extension -------------------------------------+------------------------------------- Reporter: hvr | Owner: hvr Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 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:D1185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 05:50:14 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 05:50:14 -0000 Subject: [GHC] #12046: AllowAmbiguousTypes doesn't work with UndecidableSuperClasses In-Reply-To: <050.acd80f71b0a88c07742de9edc6ba0919@haskell.org> References: <050.acd80f71b0a88c07742de9edc6ba0919@haskell.org> Message-ID: <065.25dba21a9363c94aeeebeeef686096a8@haskell.org> #12046: AllowAmbiguousTypes doesn't work with UndecidableSuperClasses -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc3 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 Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 06:00:53 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 06:00:53 -0000 Subject: [GHC] #12047: Users Guide: Message-ID: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> #12047: Users Guide: -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- In [http://downloads.haskell.org/~ghc/8.0.1-rc4/docs/html/users_guide/glasgow_exts.html #generalising-the-deriving-clause 9.6.9.1. Generalising the deriving clause] > Notionally, the compiler derives an instance declaration of the form > > {{{#!hs > instance Num Int => Num Dollars > }}} > > which just adds or removes the newtype constructor according to the type. which I find weird, I so I decided to check the actual derived instance {{{ $ ghci -ignore-dot-ghci GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help Prelude> :set -ddump-deriv Prelude> :set -XGeneralizedNewtypeDeriving Prelude> newtype Dollar = Dollar Int deriving Num ==================== Derived instances ==================== Derived instances: instance GHC.Num.Num Ghci1.Dollar where [...] }}} and neither found it there nor in the `:info` {{{ Prelude> :info Num class Num a where [...] instance [safe] Num Dollar -- Defined at :3:38 }}} and while actually defining `instance Num Int => Num Dollar` gives you this awkward encounter {{{ $ ghci -ignore-dot-ghci GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help Prelude> data Dollar Prelude> instance Num Int => Num Dollar :2:10: error: ? Non type-variable argument in the constraint: Num Int (Use FlexibleContexts to permit this) ? In the context: Num Int While checking an instance declaration In the instance declaration for ?Num Dollar? Prelude> :set -XFlexibleContexts Prelude> instance Num Int => Num Dollar :4:10: error: ? The constraint ?Num Int? is no smaller than the instance head (Use UndecidableInstances to permit this) ? In the instance declaration for ?Num Dollar? Prelude> :set -XUndecidableInstances Prelude> instance NumPrelude Int => Num Dollar :6:10: warning: [-Wsimplifiable-class-constraints] The constraint ?Num Int? matches an instance declaration instance Num Int -- Defined in ?GHC.Num? This makes type inference very fragile; try simplifying it using the instance :6:10: warning: [-Wmissing-methods] ? No explicit implementation for ?+?, ?*?, ?abs?, ?signum?, ?fromInteger?, and (either ?negate? or ?-?) ? In the instance declaration for ?Num Dollar? }}} {{{ Prelude> :info Dollar data Dollar -- Defined at :1:1 instance [safe] Num Int => Num Dollar -- Defined at :6:10 }}} Note that it appears with the context in `:info` so I wonder in what way that type signature is correct -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 06:01:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 06:01:25 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?b?PiBOdW0gRG9sbGFyc+KAnSAod2FzOiBVc2VycyBHdWlkZTop?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.85a91e7d3c8d4819dee9ae7e3bb58381@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 06:02:39 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 06:02:39 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?q?=3E_Num_Dollars=E2=80=9D?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.311af3c02fc969f7d2b7364e1ab2e604@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -54,0 +54,2 @@ + }}} + {{{ @@ -61,0 +63,2 @@ + }}} + {{{ @@ -86,1 +90,1 @@ - that type signature is correct + that instance declaration is correct New description: In [http://downloads.haskell.org/~ghc/8.0.1-rc4/docs/html/users_guide/glasgow_exts.html #generalising-the-deriving-clause 9.6.9.1. Generalising the deriving clause] > Notionally, the compiler derives an instance declaration of the form > > {{{#!hs > instance Num Int => Num Dollars > }}} > > which just adds or removes the newtype constructor according to the type. which I find weird, I so I decided to check the actual derived instance {{{ $ ghci -ignore-dot-ghci GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help Prelude> :set -ddump-deriv Prelude> :set -XGeneralizedNewtypeDeriving Prelude> newtype Dollar = Dollar Int deriving Num ==================== Derived instances ==================== Derived instances: instance GHC.Num.Num Ghci1.Dollar where [...] }}} and neither found it there nor in the `:info` {{{ Prelude> :info Num class Num a where [...] instance [safe] Num Dollar -- Defined at :3:38 }}} and while actually defining `instance Num Int => Num Dollar` gives you this awkward encounter {{{ $ ghci -ignore-dot-ghci GHCi, version 8.1.20160503: http://www.haskell.org/ghc/ :? for help Prelude> data Dollar Prelude> instance Num Int => Num Dollar :2:10: error: ? Non type-variable argument in the constraint: Num Int (Use FlexibleContexts to permit this) ? In the context: Num Int While checking an instance declaration In the instance declaration for ?Num Dollar? }}} {{{ Prelude> :set -XFlexibleContexts Prelude> instance Num Int => Num Dollar :4:10: error: ? The constraint ?Num Int? is no smaller than the instance head (Use UndecidableInstances to permit this) ? In the instance declaration for ?Num Dollar? }}} {{{ Prelude> :set -XUndecidableInstances Prelude> instance NumPrelude Int => Num Dollar :6:10: warning: [-Wsimplifiable-class-constraints] The constraint ?Num Int? matches an instance declaration instance Num Int -- Defined in ?GHC.Num? This makes type inference very fragile; try simplifying it using the instance :6:10: warning: [-Wmissing-methods] ? No explicit implementation for ?+?, ?*?, ?abs?, ?signum?, ?fromInteger?, and (either ?negate? or ?-?) ? In the instance declaration for ?Num Dollar? }}} {{{ Prelude> :info Dollar data Dollar -- Defined at :1:1 instance [safe] Num Int => Num Dollar -- Defined at :6:10 }}} Note that it appears with the context in `:info` so I wonder in what way that instance declaration is correct -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 06:47:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 06:47:23 -0000 Subject: [GHC] #11099: Incorrect warning about redundant constraints In-Reply-To: <047.537aacca9c06ec47d57c61fce1d68f6c@haskell.org> References: <047.537aacca9c06ec47d57c61fce1d68f6c@haskell.org> Message-ID: <062.c288462e7394ba3e5fc0addad629b03e@haskell.org> #11099: Incorrect warning about redundant constraints -------------------------------------+------------------------------------- Reporter: diatchki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * keywords: => CustomTypeErrors -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 06:53:59 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 06:53:59 -0000 Subject: [GHC] #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 In-Reply-To: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> References: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> Message-ID: <062.d2fdb086ac3678b9322bd36d9f11b632@haskell.org> #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bjornbm): * cc: bjorn.buckwalter@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 07:00:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 07:00:05 -0000 Subject: [GHC] #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) Message-ID: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: -------------------------------------+------------------------------------- I didn't find a ticket with this, but with wiki:CustomTypeErrors you can't define a type synonym without it erroring: {{{#!hs -- error: ? -- ? onetwothree -- ? In the type synonym declaration for ?ERROR? -- Compilation failed. type ERROR = TypeError (Text "onetwothree") }}} but I often want to abstract over error messages since they are clunky to write at the type level and I often use a similar message in many different type families, especially when they can be determined by a type family. Here's a hypothetical example: {{{#!hs type family Whoami (ty :: Type) :: Symbol where Whoami Int = "a number" Whoami Float = "a number" Whoami [_] = "a list of things" Whoami _ = "something else" }}} I would like to write {{{#!hs type Error ty = TypeError (Text "Expected a <...> but got ":<>: Text (Whoami ty)) }}} ---- Even when ?inlined?, it displays `Expected a GRUE but got 'Text (Whoami Int)` and not `? Expected a GRUE but got a number.`: {{{#!hs a :: TypeError (Text "Expected a GRUE but got ":<>: Text (Whoami Int)) a = 'a' }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 07:00:28 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 07:00:28 -0000 Subject: [GHC] #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) In-Reply-To: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> References: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> Message-ID: <066.c5f37e8c7e988e6e98a061df831ec88d@haskell.org> #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: @@ -1,2 +1,2 @@ - I didn't find a ticket with this, but with wiki:CustomTypeErrors you can't - define a type synonym without it erroring: + I didn't find a ticket with this, but with wiki:Proposal/CustomTypeErrors + you can't define a type synonym without it erroring: New description: I didn't find a ticket with this, but with wiki:Proposal/CustomTypeErrors you can't define a type synonym without it erroring: {{{#!hs -- error: ? -- ? onetwothree -- ? In the type synonym declaration for ?ERROR? -- Compilation failed. type ERROR = TypeError (Text "onetwothree") }}} but I often want to abstract over error messages since they are clunky to write at the type level and I often use a similar message in many different type families, especially when they can be determined by a type family. Here's a hypothetical example: {{{#!hs type family Whoami (ty :: Type) :: Symbol where Whoami Int = "a number" Whoami Float = "a number" Whoami [_] = "a list of things" Whoami _ = "something else" }}} I would like to write {{{#!hs type Error ty = TypeError (Text "Expected a <...> but got ":<>: Text (Whoami ty)) }}} ---- Even when ?inlined?, it displays `Expected a GRUE but got 'Text (Whoami Int)` and not `? Expected a GRUE but got a number.`: {{{#!hs a :: TypeError (Text "Expected a GRUE but got ":<>: Text (Whoami Int)) a = 'a' }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 07:09:50 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 07:09:50 -0000 Subject: [GHC] #12049: `OverloadedStrings` for types Message-ID: <051.42d4b7f0641b856cf6251eb9219fbe2e@haskell.org> #12049: `OverloadedStrings` for types -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: -------------------------------------+------------------------------------- Is there any sense in adding {{{#!hs class IsSymbol a where type FromSymbol (str :: Symbol) :: a instance IsSymbol ErrorMessage where type FromSymbol str = GHC.TypeLits.Text str instance IsSymbol ErrorMessage where type FromSymbol str = str }}} where `FromSymbol` gets placed before type-level string literals: {{{#!hs TypeError ("Warning: ":<>:ShowType ty:<>:" is odd.") }}} analogous to `Data.String.IsString`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 08:05:08 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 08:05:08 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.f3147635e6ea4dd096c3d66e7a3adee6@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Simon and I agreed on our call that we should pursue inserting `noinline f` for any references to `f` from an `hs-boot` file. The `noinline` gets removed during `CorePrep` and as a result we won't infinitely try to unfold when we compile the module. How do we know when to insert these `noinline`s? It should happen in the typechecker or renamer, and the idea will be to mark `Id`s which come from a boot file as "boot identities"; then we know to insert `noinline`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 09:00:47 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 09:00:47 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.d5f8ea65c2694b80fe100faa9159ad27@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Comment (by osa1): Yes, I wanted to handle that case (see also test `ExpandSynsFail3.hs`). My original implementation was method (1) in that web page. I just implemented method (3) and updated the patch. The problematic example was taking no time at all even with method (1), I guess it's now even faster. Since we have a linear behavior now maybe we can enable it by default. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 09:04:34 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 09:04:34 -0000 Subject: [GHC] #11743: Add unicode support for TH quotes (`[| |]`) In-Reply-To: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> References: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> Message-ID: <066.d9290eadbcd25d7d61d193b2b0e95cbd@haskell.org> #11743: Add unicode support for TH quotes (`[| |]`) -------------------------------------+------------------------------------- Reporter: JoshPrice247 | Owner: JoshPrice247 Type: feature request | Status: patch Priority: low | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 (Parser) | Keywords: unicode, Resolution: | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2878, #10162 | Differential Rev(s): Phab:D2185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * related: 2878, 10162 => #2878, #10162 * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 11:44:01 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 11:44:01 -0000 Subject: [GHC] #12033: [TypeApplications] GHC internal error In-Reply-To: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> References: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> Message-ID: <066.0a55566b470c0f49a4562924bc9f360e@haskell.org> #12033: [TypeApplications] GHC internal error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by sjcjoosten): * Attachment "HaskellBug.hs" added. Small example with similar behavior -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 11:47:28 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 11:47:28 -0000 Subject: [GHC] #12033: [TypeApplications] GHC internal error In-Reply-To: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> References: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> Message-ID: <066.13705fb18d45244be14e4c67ae8e2f59@haskell.org> #12033: [TypeApplications] GHC internal error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sjcjoosten): I ran into this too, I'm not sure whether it is the same bug, but I managed to reproduce the same GHC internal error in a very small example. Based on what the two examples have in common, I would say this has something to do with the TypeFamilies switch (without it, ghc works as expected). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 12:03:12 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 12:03:12 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.6a3af2ad3afa4c5d73831013581c55eb@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Comment (by osa1): Just as a test I added `-fprint-expanded-synonyms` to every `should_fail` test in `typechecker/`. Here's the diff: {{{ --- ./tcfail016.stderr.normalised 2016-05-12 08:00:33.702460710 -0400 +++ ./tcfail016.comp.stderr.normalised 2016-05-12 08:00:33.702460710 -0400 @@ -3,5 +3,8 @@ Couldn't match type ?(t, Expr t)? with ?Expr t? Expected type: AnnExpr t -> [[Char]] Actual type: Expr t -> [[Char]] + Type synonyms expanded: + Expected type: (t, Expr t) -> [[Char]] + Actual type: Expr t -> [[Char]] Relevant bindings include g :: AnnExpr t -> [[Char]] (bound at tcfail016.hs:8:1) --- ./tcfail068.stderr.normalised 2016-05-12 08:00:38.994460634 -0400 +++ ./tcfail068.comp.stderr.normalised 2016-05-12 08:00:38.994460634 -0400 @@ -13,6 +13,9 @@ at tcfail068.hs:11:10 Expected type: GHC.ST.ST s1 (IndTree s a) Actual type: GHC.ST.ST s1 (STArray s1 (Int, Int) a) + Type synonyms expanded: + Expected type: GHC.ST.ST s1 (STArray s (Int, Int) a) + Actual type: GHC.ST.ST s1 (STArray s1 (Int, Int) a) In the first argument of ?runST?, namely ?(newSTArray ((1, 1), n) x)? In the expression: runST (newSTArray ((1, 1), n) x) --- ./T9774.stderr.normalised 2016-05-12 08:01:14.797460115 -0400 +++ ./T9774.comp.stderr.normalised 2016-05-12 08:01:14.797460115 -0400 @@ -3,6 +3,9 @@ Couldn't match type ?Char? with ?[Char]? Expected type: String Actual type: Char + Type synonyms expanded: + Expected type: [Char] + Actual type: Char In the first argument of ?putStrLn?, namely ?(assert True 'a')? In the expression: putStrLn (assert True 'a') In an equation for ?foo?: foo = putStrLn (assert True 'a') }}} I think we can enable this by default as it's both stable and fast now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 12:13:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 12:13:23 -0000 Subject: [GHC] #10860: setnumcapabilities001: internal error: ASSERTION FAILED: file rts/Schedule.c, line 400 In-Reply-To: <045.1b9d7e0fabda0a4b3797cc5dc85f2044@haskell.org> References: <045.1b9d7e0fabda0a4b3797cc5dc85f2044@haskell.org> Message-ID: <060.07d75f3ef23190912670ff114d36726c@haskell.org> #10860: setnumcapabilities001: internal error: ASSERTION FAILED: file rts/Schedule.c, line 400 -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 12038 | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): I believe this is fixed, I've re-enabled the test and there's a residual issue in #12038. In [changeset:"cfc5df43a7789832a2789e517d8270650cc31b7f/ghc" cfc5df4/ghc]: {{{ Fix ASSERT failure and re-enable setnumcapabilities001 The assertion failure was fairly benign, I think, but this fixes it. I've been running the test repeatedly for the last 30 mins and it hasn't triggered. There are other problems exposed by this test (see #12038), but I've worked around those in the test itself for now. I also copied the relevant bits of the parallel library here so that we don't need parallel for the test to run. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 12:15:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 12:15:05 -0000 Subject: [GHC] #10860: setnumcapabilities001: internal error: ASSERTION FAILED: file rts/Schedule.c, line 400 In-Reply-To: <045.1b9d7e0fabda0a4b3797cc5dc85f2044@haskell.org> References: <045.1b9d7e0fabda0a4b3797cc5dc85f2044@haskell.org> Message-ID: <060.b9cb60a693652dea487e794862f187d8@haskell.org> #10860: setnumcapabilities001: internal error: ASSERTION FAILED: file rts/Schedule.c, line 400 -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonmar Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => closed * resolution: => fixed * blockedby: 12038 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 12:25:34 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 12:25:34 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.fc574f2b2d9b08937e830f571fe9bd3a@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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 hesselink): * cc: hesselink (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 12:40:24 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 12:40:24 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.fc1566442e1604dcd69ab7a2769c3af1@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"925b0aea8edc1761fcc16feba1601bea38422c92/ghc" 925b0aea/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="925b0aea8edc1761fcc16feba1601bea38422c92" Make absentError not depend on uniques As explained in the comment it will cause changes in inlining if we don't suppress them. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, goldfire, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2203 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:39:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:39:49 -0000 Subject: [GHC] #8761: Make pattern synonyms work with Template Haskell In-Reply-To: <047.c5d8ed063e9e82c354c50c5724ebe787@haskell.org> References: <047.c5d8ed063e9e82c354c50c5724ebe787@haskell.org> Message-ID: <062.00c61a244f26cf98a070f192060635b7@haskell.org> #8761: Make pattern synonyms work with Template Haskell -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bollmann Type: feature request | Status: patch Priority: normal | Milestone: Component: Template Haskell | 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): Phab:D1940 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"c079de3c43704ea88f592e441389e520313e30ad/ghc" c079de3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c079de3c43704ea88f592e441389e520313e30ad" Add TH support for pattern synonyms (fixes #8761) This commit adds Template Haskell support for pattern synonyms as requested by trac ticket #8761. Test Plan: ./validate Reviewers: thomie, jstolarek, osa1, RyanGlScott, mpickering, austin, goldfire, bgamari Reviewed By: goldfire, bgamari Subscribers: rdragon Differential Revision: https://phabricator.haskell.org/D1940 GHC Trac Issues: #8761 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:39:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:39:49 -0000 Subject: [GHC] #11768: Need a way to attach Haddock documentation to derived instances In-Reply-To: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> References: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> Message-ID: <061.779fc16d2c74eb55fee964400137e363@haskell.org> #11768: Need a way to attach Haddock documentation to derived instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11767 | Differential Rev(s): Phab:D2175 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"697143064c271c57a69e80850a768449f8bcf4ca/ghc" 6971430/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="697143064c271c57a69e80850a768449f8bcf4ca" Allow putting Haddocks on derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the parser to enable attaching Haddock comments for derived instances. Updates haddock submodule. Fixes #11768. Test Plan: ./validate Reviewers: hvr, bgamari, austin Reviewed By: austin Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2175 GHC Trac Issues: #11768 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:39:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:39:49 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.c22b759f751634f94bf29104069250a4@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: RyanGlScott Type: feature request | Status: patch Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2168 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b8e2565123de45f215277e3a92fbc7ace2b8fd71/ghc" b8e25651/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b8e2565123de45f215277e3a92fbc7ace2b8fd71" Make Generic1 poly-kinded This generalizes the `Generic1` typeclass to be of kind `k -> *`, and this also makes the relevant datatypes and typeclasses in `GHC.Generics` poly-kinded. If `PolyKinds` is enabled, `DeriveGeneric` derives `Generic1` instances such that they use the most general kind possible. Otherwise, deriving `Generic1` defaults to make an instance where the argument is of kind `* -> *` (the current behavior). Fixes #10604. Depends on D2117. Test Plan: ./validate Reviewers: kosmikus, dreixel, goldfire, austin, hvr, simonpj, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie, ekmett Differential Revision: https://phabricator.haskell.org/D2168 GHC Trac Issues: #10604 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:39:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:39:49 -0000 Subject: [GHC] #11837: GHC fails to unify kinds when deriving polykinded typeclass instance for polykinded newtype In-Reply-To: <050.9f83a773e0afc4665e5b1a4fa16ad903@haskell.org> References: <050.9f83a773e0afc4665e5b1a4fa16ad903@haskell.org> Message-ID: <065.461c88c18f7c2636d1525025f69c940a@haskell.org> #11837: GHC fails to unify kinds when deriving polykinded typeclass instance for polykinded newtype -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8865, #11833 | Differential Rev(s): Phab:D2117 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"e53f2180e89652c72e51ffa614c56294ba67cf37/ghc" e53f2180/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e53f2180e89652c72e51ffa614c56294ba67cf37" Fix deriveTyData's kind unification when two kind variables are unified When `deriveTyData` attempts to unify two kind variables (which can happen if both the typeclass and the datatype are poly-kinded), it mistakenly adds an extra mapping to its substitution which causes the unification to fail when applying the substitution. This can be prevented by checking both the domain and the range of the original substitution to see which kind variables shouldn't be put into the domain of the substitution. A more in-depth explanation is included in `Note [Unification of two kind variables in deriving]`. Fixes #11837. Test Plan: ./validate Reviewers: simonpj, hvr, goldfire, niteria, austin, bgamari Reviewed By: bgamari Subscribers: niteria, thomie Differential Revision: https://phabricator.haskell.org/D2117 GHC Trac Issues: #11837 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:42:15 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:42:15 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.076a23723b74ceb0c7c605e9c72ddeb1@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"01bc10965d993babf6c2c35d340655f683ba0ca2/ghc" 01bc1096/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="01bc10965d993babf6c2c35d340655f683ba0ca2" Document zonkTyCoVarsAndFV determinism I've changed it to use nonDetEltsUFM and documented why it's OK. Test Plan: it builds Reviewers: bgamari, austin, simonmar, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2204 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:52:12 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:52:12 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.0c8ac8d6a3070848762535b0d36ae6d2@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"6bf0eef74d2b2ce9a48c7acc08ca2a1c0c8a7fbc/ghc" 6bf0eef/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6bf0eef74d2b2ce9a48c7acc08ca2a1c0c8a7fbc" Kill varEnvElts in specImports We need the order of specialized binds and rules to be deterministic, so we use a deterministic set here. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2197 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:54:06 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:54:06 -0000 Subject: [GHC] #11837: GHC fails to unify kinds when deriving polykinded typeclass instance for polykinded newtype In-Reply-To: <050.9f83a773e0afc4665e5b1a4fa16ad903@haskell.org> References: <050.9f83a773e0afc4665e5b1a4fa16ad903@haskell.org> Message-ID: <065.138e448490798132882760a0bbb6150c@haskell.org> #11837: GHC fails to unify kinds when deriving polykinded typeclass instance for polykinded newtype -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8865, #11833 | Differential Rev(s): Phab:D2117 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 13:56:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 13:56:25 -0000 Subject: [GHC] #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint In-Reply-To: <050.cb2ddf7ed167c7a185a18760753b8ced@haskell.org> References: <050.cb2ddf7ed167c7a185a18760753b8ced@haskell.org> Message-ID: <065.64338ba80ffc03787014bc1c56db6296@haskell.org> #11833: GHC can't derive instance of polykinded typeclass for newtype that requires a class constraint -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: RyanGlScott Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8865, #11837 | Differential Rev(s): Phab:D2112 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => merge * milestone: => 8.0.2 Comment: We should merge this for 8.0.2., since #11837 is also being merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 14:01:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 14:01:21 -0000 Subject: [GHC] #10524: PolyKinds doesn't interact well with DeriveFunctor In-Reply-To: <050.7408f13045aa603e186c148218ece722@haskell.org> References: <050.7408f13045aa603e186c148218ece722@haskell.org> Message-ID: <065.53585122830f9fc6a488288607937418@haskell.org> #10524: PolyKinds doesn't interact well with DeriveFunctor -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T10561 Blocked By: | Blocking: Related Tickets: #10561 | Differential Rev(s): Phab:D2097 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * testcase: => deriving/should_compile/T10561 * resolution: => fixed * milestone: => 8.0.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 15:30:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 15:30:25 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.4b0b60903d3639f9259a5ba426e05f10@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"7c0b595e55d31f9f89e6dede11981e942c5bb32f/ghc" 7c0b595e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7c0b595e55d31f9f89e6dede11981e942c5bb32f" Fix comments about scavenging WEAK objects This is a follow-up of D2189. If fixes some comments, deletes a section in the User's Guide about the bug, and updates .mailmap as suggested on the WorkinConventions wiki page. Test Plan: It compiles. Reviewers: austin, simonmar, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2202 GHC Trac Issues: #11108 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 15:31:59 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 15:31:59 -0000 Subject: [GHC] #8761: Make pattern synonyms work with Template Haskell In-Reply-To: <047.c5d8ed063e9e82c354c50c5724ebe787@haskell.org> References: <047.c5d8ed063e9e82c354c50c5724ebe787@haskell.org> Message-ID: <062.b09c9c18ccc606a1445e083d6cdac767@haskell.org> #8761: Make pattern synonyms work with Template Haskell -------------------------------------+------------------------------------- Reporter: goldfire | Owner: bollmann Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1940 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * version: => 8.0.1 * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 15:33:00 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 15:33:00 -0000 Subject: [GHC] #11768: Need a way to attach Haddock documentation to derived instances In-Reply-To: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> References: <046.f8385aa0e2bf22414748bbc6aca23dc7@haskell.org> Message-ID: <061.be247e1b5081470fd5db37a0be7e6586@haskell.org> #11768: Need a way to attach Haddock documentation to derived instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11767 | Differential Rev(s): Phab:D2175 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 15:35:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 15:35:05 -0000 Subject: [GHC] #12050: Allow haddock comments on non-record types Message-ID: <046.f6b7a2b632eb5ba65b0da9770c2d4b66@haskell.org> #12050: Allow haddock comments on non-record types -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- There are a variety of cases I have found myself wanting to place haddock documentation on fields of non-record data types rather often in the past. The syntax for this might look like, {{{#!hs data Foo = Foo -- ^ A foo Int -- ^ how big is the foo? String -- ^ the name of the foo }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 15:45:51 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 15:45:51 -0000 Subject: [GHC] #12050: Allow haddock comments on non-record types In-Reply-To: <046.f6b7a2b632eb5ba65b0da9770c2d4b66@haskell.org> References: <046.f6b7a2b632eb5ba65b0da9770c2d4b66@haskell.org> Message-ID: <061.ccbcb81c31cbafc322d3292a8dfca988@haskell.org> #12050: Allow haddock comments on non-record types -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -1,4 +1,3 @@ - There are a variety of cases - I have found myself wanting to place haddock documentation on fields of - non-record data types rather often in the past. The syntax for this might - look like, + There are a variety of cases where I have found myself wanting to place + haddock documentation on fields of non-record data types rather often in + the past. The syntax for this might look like, New description: There are a variety of cases where I have found myself wanting to place haddock documentation on fields of non-record data types rather often in the past. The syntax for this might look like, {{{#!hs data Foo = Foo -- ^ A foo Int -- ^ how big is the foo? String -- ^ the name of the foo }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 15:50:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 15:50:21 -0000 Subject: [GHC] #12051: -.-> is accepted as a data constructor Message-ID: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> #12051: -.-> is accepted as a data constructor -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ data A = (-.->) Int }}} Is accepted by GHC without any complaints but `-.->` is not a valid data constructor as it doesn't start with a `:`. Anyone have any ideas about what is going on here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 16:00:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 16:00:49 -0000 Subject: [GHC] #12051: -.-> is accepted as a data constructor In-Reply-To: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> References: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> Message-ID: <064.2bfdce9edb31edebf219c23429e55273@haskell.org> #12051: -.-> is accepted as a data constructor -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 16:31:13 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 16:31:13 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.7e2346d7e2fdf509353ceeca1e5428ae@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"5416fadb7387cbe89752faa875b2dade60655cf2/ghc" 5416fadb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5416fadb7387cbe89752faa875b2dade60655cf2" Refactor some ppr functions to use pprUFM Nondeterminism doesn't matter in these places and pprUFM makes it obvious. I've flipped the order of arguments for convenience. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2205 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 19:42:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 19:42:21 -0000 Subject: [GHC] #12052: Split ghc-boot so we have better dependency hygiene Message-ID: <045.061983f99253ceb1981e41093fe365b7@haskell.org> #12052: Split ghc-boot so we have better dependency hygiene -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Core | Version: 8.0.1 Libraries | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- At the moment, `template-haskell` transitively depends on `bytestring`. This means that any package which depends on `template-haskell` has its `bytestring` version pinned to the version that was shipped with GHC. Which is lame, because `template-haskell` doesn't actually use `bytestring` in any interesting way. This is bad, we should split `ghc-boot` into two pieces, one which has the binary package database bits, and another which contains the Template Haskell bits, so we can have better dependency hygiene. We should also have a comment on `template-haskell` mentioning the importance of dependency hygiene, so this doesn't happen again. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 19:55:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 19:55:27 -0000 Subject: [GHC] #12052: Split ghc-boot so we have better dependency hygiene In-Reply-To: <045.061983f99253ceb1981e41093fe365b7@haskell.org> References: <045.061983f99253ceb1981e41093fe365b7@haskell.org> Message-ID: <060.d2cfbfc8e514e17bf61b5403dba625ff@haskell.org> #12052: Split ghc-boot so we have better dependency hygiene -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hvr): It's not only `bytestring` `template-haskell` started to depend on: In GHC 7.10.3 there were the following deps: {{{ "template-haskell-2.10.0.0" -> "base-4.8.2.0" "template-haskell-2.10.0.0" -> "pretty-1.1.2.0" "pretty-1.1.2.0" -> "base-4.8.2.0" "pretty-1.1.2.0" -> "deepseq-1.4.1.1" "pretty-1.1.2.0" -> "ghc-prim-0.4.0.0" "deepseq-1.4.1.1" -> "array-0.5.1.0" "deepseq-1.4.1.1" -> "base-4.8.2.0" }}} whereas with GHC 8.0 we have now {{{ "template-haskell-2.11.0.0" -> "base-4.9.0.0" "template-haskell-2.11.0.0" -> "ghc-boot-8.0.0.20160511" "template-haskell-2.11.0.0" -> "pretty-1.1.3.3" "pretty-1.1.3.3" -> "base-4.9.0.0" "pretty-1.1.3.3" -> "deepseq-1.4.2.0" "pretty-1.1.3.3" -> "ghc-prim-0.5.0.0" "deepseq-1.4.2.0" -> "array-0.5.1.1" "deepseq-1.4.2.0" -> "base-4.9.0.0" "ghc-boot-8.0.0.20160511" -> "base-4.9.0.0" "ghc-boot-8.0.0.20160511" -> "binary-0.8.3.0" "ghc-boot-8.0.0.20160511" -> "bytestring-0.10.8.0" "ghc-boot-8.0.0.20160511" -> "directory-1.2.6.2" "ghc-boot-8.0.0.20160511" -> "filepath-1.4.1.0" "binary-0.8.3.0" -> "array-0.5.1.1" "binary-0.8.3.0" -> "base-4.9.0.0" "binary-0.8.3.0" -> "bytestring-0.10.8.0" "binary-0.8.3.0" -> "containers-0.5.7.1" "directory-1.2.6.2" -> "base-4.9.0.0" "directory-1.2.6.2" -> "filepath-1.4.1.0" "directory-1.2.6.2" -> "time-1.6.0.1" "directory-1.2.6.2" -> "unix-2.7.2.0" }}} so effectively, `template-haskell` now transitively adds the following dependencies (relative to GHC 7.10.3): - `unix` - `directory` - `filepath` - `containers` - `bytestring` - `binary` this reduces a lot of flexibility from the cabal solver, and makes it impossible to use newer versions of those packages (something I did frequently in GHC 7.10.3) as soon as `template-haskell` enters install- plans. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 19:55:51 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 19:55:51 -0000 Subject: [GHC] #12053: Mode for ghc --make which only compiles the files I pass on command line Message-ID: <045.29aa132cfb016cf36b9e85269467760f@haskell.org> #12053: Mode for ghc --make which only compiles the files I pass on command line -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: backpack | 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 are a few situations where GHC picks up "too many" files when running `--make`: * Suppose a user doesn't add enough modules to `exposed-modules`/`other- modules` in Cabal. GHC will happily pick up extra source files, but those files won't get bundled in the `sdist` or be included in ABI computation. Difficult for Cabal to tell when this has happened. * Suppose the user wants to define multiple internal libraries, and give them the same hs-source-dir. This won't work: because GHC sees the source file it will prefer it over the external dependency. There's a very easy thing that GHC could do to make this better: add a mode to `--make` which says "only compile the files that are explicitly passed on the command line." Something like `ghc --make --only A.hs` will only build A.hs, and error if you try to import B.hs. Seems like this should be fairly easy to do, and would help solve a lot of problems related to GHC slurping up too many files. (I've assigned myself because this is a blocker for backpack, but if someone wants to take a crack at this be my guest.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 20:26:36 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 20:26:36 -0000 Subject: [GHC] #12052: Split ghc-boot so we have better dependency hygiene In-Reply-To: <045.061983f99253ceb1981e41093fe365b7@haskell.org> References: <045.061983f99253ceb1981e41093fe365b7@haskell.org> Message-ID: <060.503da4f0cae1ccd3ba7d8ad4d211a63c@haskell.org> #12052: Split ghc-boot so we have better dependency hygiene -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm all for it! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 20:30:26 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 20:30:26 -0000 Subject: [GHC] #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) In-Reply-To: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> References: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> Message-ID: <066.fbb3fa88ba539061e84255781019e6b2@haskell.org> #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: diatchki Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => diatchki -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 21:29:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 21:29:52 -0000 Subject: [GHC] #12053: Mode for ghc --make which only compiles the files I pass on command line In-Reply-To: <045.29aa132cfb016cf36b9e85269467760f@haskell.org> References: <045.29aa132cfb016cf36b9e85269467760f@haskell.org> Message-ID: <060.0db2344e2197489d5f3ddeb8a88b2375@haskell.org> #12053: Mode for ghc --make which only compiles the files I pass on command line -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: | -------------------------------------+------------------------------------- Comment (by mgsloan): Something like this would indeed be handy! The linker errors people get when the module isn't in their cabal file can be scary / uninformative. FYI, the approach that stack takes here is to use `-ddump-hi` and identify when there are modules / etc unmentioned in the cabal file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 22:36:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 22:36:27 -0000 Subject: [GHC] #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) In-Reply-To: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> References: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> Message-ID: <066.4838737e64faf5466b7b2453ec36712b@haskell.org> #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: diatchki Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: @@ -12,4 +12,4 @@ - but I often want to abstract over error messages since they are clunky to - write at the type level and I often use a similar message in many - different type families, especially when they can be determined by a type - family. Here's a hypothetical example: + but I often want to factor out error messages, they are clunky to write at + the type level and I often want to reuse message in many different type + families, especially when they can be determined by a type family. Here's + a hypothetical example: New description: I didn't find a ticket with this, but with wiki:Proposal/CustomTypeErrors you can't define a type synonym without it erroring: {{{#!hs -- error: ? -- ? onetwothree -- ? In the type synonym declaration for ?ERROR? -- Compilation failed. type ERROR = TypeError (Text "onetwothree") }}} but I often want to factor out error messages, they are clunky to write at the type level and I often want to reuse message in many different type families, especially when they can be determined by a type family. Here's a hypothetical example: {{{#!hs type family Whoami (ty :: Type) :: Symbol where Whoami Int = "a number" Whoami Float = "a number" Whoami [_] = "a list of things" Whoami _ = "something else" }}} I would like to write {{{#!hs type Error ty = TypeError (Text "Expected a <...> but got ":<>: Text (Whoami ty)) }}} ---- Even when ?inlined?, it displays `Expected a GRUE but got 'Text (Whoami Int)` and not `? Expected a GRUE but got a number.`: {{{#!hs a :: TypeError (Text "Expected a GRUE but got ":<>: Text (Whoami Int)) a = 'a' }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 12 23:59:41 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 12 May 2016 23:59:41 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.bd7e6a021510a4dd425e2f4aed1ec66f@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Comment (by akio): Replying to [comment:21 ryantrinkle]: > Here's a patch to add this test: https://phabricator.haskell.org/D2196 Oh I somehow didn't notice this patch, thank you for catching this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 01:01:56 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 01:01:56 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.cd24302ed6c047bc3d908f081fde52a9@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ryantrinkle): No problem; but the real thanks should go to Saulzar for putting together such a clean test case! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 01:06:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 01:06:42 -0000 Subject: [GHC] #2439: Missed optimisation with dictionaries and loops In-Reply-To: <041.4a9e022e22f0d06a0023c060ae99c7bb@haskell.org> References: <041.4a9e022e22f0d06a0023c060ae99c7bb@haskell.org> Message-ID: <056.12e297135288deb932ae1f807d9579f2@haskell.org> #2439: Missed optimisation with dictionaries and loops -------------------------------------+------------------------------------- Reporter: rl | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 6.9 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 dfeuer): Replying to [comment:26 simonpj]: > I can't say I understand what is going on here, but in reify/reflect it seems that you want something akin to a local instance declaration. You want to write: > {{{ > reify (x :: a) (\ (p :: Proxy s) -> > ...In here we have (Reifies s a)... > ) > }}} > And you want to supply the local instance of `(Reifies s a)` yourself. > > Isn't this just what implicit parameters are for? They give you local instance declarations, in effect. The `reflection` package was largely motivated by [http://okmij.org/ftp/Haskell/tr-15-04.pdf Functional Pearl: Implicit Configurations -- or, Type Classes Reflect the Values of Types], by Oleg Kiselyov and Chung-chieh Shan, although their implementation is entirely different. Section 6.2 of the paper explains in depth why implicit parameters are insufficient. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 01:32:53 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 01:32:53 -0000 Subject: [GHC] #10961: Make it possible to purely use the parser In-Reply-To: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> References: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> Message-ID: <064.447dad7b096f28bc2d61bf59eb59696a@haskell.org> #10961: Make it possible to purely use the parser -------------------------------------+------------------------------------- Reporter: mpickering | Owner: dalaing Type: task | Status: patch Priority: low | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10143 | Differential Rev(s): D2208 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dalaing): * status: new => patch * differential: => D2208 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 01:40:50 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 01:40:50 -0000 Subject: [GHC] #10961: Make it possible to purely use the parser In-Reply-To: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> References: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> Message-ID: <064.e49e8c8b9097a080b51a10f49ae2de6b@haskell.org> #10961: Make it possible to purely use the parser -------------------------------------+------------------------------------- Reporter: mpickering | Owner: dalaing Type: task | Status: patch Priority: low | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10143 | Differential Rev(s): D2208 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dalaing): I've dealt with the pretty printing of warnings by changing from `messages :: Messages` to `messages :: DynFlags -> Messages` in `PState`. This also means there are some changes to pass in `DynFlags` when `getMessages` is called. This would change back if a resolution of #10143 meant we could pretty print warnings without needing `DynFlags`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 03:55:45 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 03:55:45 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.365c4412819ba6ade6d3dead3f1b70c6@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.8.4 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2210 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => patch * differential: => Phab:D2210 * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 04:41:28 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 04:41:28 -0000 Subject: [GHC] #11744: Latest Xcode update violates POSIX compliance of `nm -P` In-Reply-To: <042.af01bf0c9281d3187ce47b8cda7a587e@haskell.org> References: <042.af01bf0c9281d3187ce47b8cda7a587e@haskell.org> Message-ID: <057.5735dcac83f7adf61d0640603fdb02a2@haskell.org> #11744: Latest Xcode update violates POSIX compliance of `nm -P` ---------------------------------+---------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): phab:D2113 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by ilovezfs): FYI upstream LLVM has now fixed this bug: https://github.com/llvm- mirror/llvm/commit/ae7cf58516cc4824e32187285dc524188afb750c So hopefully it will make its way over to Xcode soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 04:47:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 04:47:58 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 Message-ID: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> #12054: PowerPC: Unsupported relocation against x0 -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.1 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: powerpc | Type of failure: Building GHC | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- On PowerPC/Linux, the `perf` build is failing for the file `compiler/cmm/PprC.hs` with a large number of errors like: {{{ tmp/ghc29102_0/ghc_3.s:310927:0: error: Error: unsupported relocation against x0 tmp/ghc29102_0/ghc_3.s:310938:0: error: Error: unsupported relocation against x0 tmp/ghc29102_0/ghc_3.s:310959:0: error: Error: unsupported relocation against x0 }}} All of the above error lines are of the form: {{{ stwu x0, 1 , 13 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 07:35:24 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 07:35:24 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.7b7fabc3f23f9c36cb4880f60b5c7899@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+-------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+-------------------------------- Changes (by trommler): * owner: => trommler Comment: The assembly should read {{{ stwux 0,1,13 }}} It's a bug in the PPC assembler pretty printer. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:00:37 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:00:37 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.c861679bb6c02803ff35d2b6980ea732@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+-------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+-------------------------------- Comment (by erikd): Thanks @trommler! I meant to CC you on this, but then forgot. Seems I didn't need to :). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:30:38 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:30:38 -0000 Subject: [GHC] #12039: Panic with partial class definition In-Reply-To: <043.594973634c4616bf2544fe97c427a9c7@haskell.org> References: <043.594973634c4616bf2544fe97c427a9c7@haskell.org> Message-ID: <058.42dc0f7d91a735912cc9f0eb821311cf@haskell.org> #12039: Panic with partial class definition -------------------------------------+------------------------------------- Reporter: maud | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"bd01bbb24dcd9e426af85fc542ae5c9b5ab999b9/ghc" bd01bbb2/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bd01bbb24dcd9e426af85fc542ae5c9b5ab999b9" Test Trac #12039 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:45:12 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:45:12 -0000 Subject: [GHC] #12055: Typechecker panic instead of proper error Message-ID: <046.1237d444c794f470f1d99c65363ee9aa@haskell.org> #12055: Typechecker panic instead of proper error -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this modification of the testcase from #12021, {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeInType #-} import GHC.Base ( Constraint, Type ) import GHC.Exts ( type (~~) ) type Cat k = k -> k -> Type class Category (p :: Cat k) where type Ob p :: k -> Constraint class (Category (Dom f), Category (Cod f)) => Functor (f :: j -> k) where type Dom f :: Cat j type Cod f :: Cat k functor :: forall a b. Iso Constraint (:-) (:-) (Ob (Dom f) a) (Ob (Dom f) b) (Ob (Cod f) (f a)) (Ob (Cod f) (f b)) class (Functor f , Dom f ~ p, Cod f ~ q) => Fun (p :: Cat j) (q :: Cat k) (f :: j -> k) | f -> p q instance (Functor f , Dom f ~ p, Cod f ~ q) => Fun (p :: Cat j) (q :: Cat k) (f :: j -> k) data Nat (p :: Cat j) (q :: Cat k) (f :: j -> k) (g :: j -> k) type Iso k (c :: Cat k) (d :: Cat k) s t a b = forall p. (Cod p ~~ Nat d (->)) => p a b -> p s t data (p :: Constraint) :- (q :: Constraint) }}} With GHC 8.0.1 it fails with a compiler panic, {{{ $ ghc Hi.hs -fprint-explicit-kinds [1 of 1] Compiling Main ( Hi.hs, Hi.o ) Hi.hs:21:1: error: ? Non type-variable argument in the constraint: Category j (Dom k j f) (Use FlexibleContexts to permit this) ? In the context: (Category j (Dom k j f), Category k (Cod k j f)) While checking the super-classes of class ?Functor? In the class declaration for ?Functor? Hi.hs:29:20: error: ? GHC internal error: ?Dom? is not in scope during type checking, but it passed the renamer tcl_env of environment: [a2yi :-> Type variable ?j? = j, a2yj :-> Type variable ?p? = p, a2yk :-> Type variable ?k? = k, a2yl :-> Type variable ?q? = q, a2ym :-> Type variable ?f? = f, r2xT :-> ATcTyCon Fun] ? In the first argument of ?~?, namely ?Dom f? In the class declaration for ?Fun? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:46:20 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:46:20 -0000 Subject: [GHC] #12055: Typechecker panic instead of proper error In-Reply-To: <046.1237d444c794f470f1d99c65363ee9aa@haskell.org> References: <046.1237d444c794f470f1d99c65363ee9aa@haskell.org> Message-ID: <061.d1518874948e6b8096a07d6baf086980@haskell.org> #12055: Typechecker panic instead of proper error -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -65,0 +65,15 @@ + + If one adds the appropriate extensions (`FunctionalDependencies`, + `FlexibleInstances`, and `FlexibleContexts`) GHC complains that the + program fails to satisfy the coverage condition, + {{{ + Hi.hs:31:10: error: + ? Illegal instance declaration for ?Fun k j p q f? + The coverage condition fails in class ?Fun? + for functional dependency: ?f -> p q? + Reason: lhs type ?f? does not determine rhs types ?p?, ?q? + Un-determined variables: p, q + Using UndecidableInstances might help + ? In the instance declaration for + ?Fun (p :: Cat j) (q :: Cat k) (f :: j -> k)? + }}} New description: Consider this modification of the testcase from #12021, {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeInType #-} import GHC.Base ( Constraint, Type ) import GHC.Exts ( type (~~) ) type Cat k = k -> k -> Type class Category (p :: Cat k) where type Ob p :: k -> Constraint class (Category (Dom f), Category (Cod f)) => Functor (f :: j -> k) where type Dom f :: Cat j type Cod f :: Cat k functor :: forall a b. Iso Constraint (:-) (:-) (Ob (Dom f) a) (Ob (Dom f) b) (Ob (Cod f) (f a)) (Ob (Cod f) (f b)) class (Functor f , Dom f ~ p, Cod f ~ q) => Fun (p :: Cat j) (q :: Cat k) (f :: j -> k) | f -> p q instance (Functor f , Dom f ~ p, Cod f ~ q) => Fun (p :: Cat j) (q :: Cat k) (f :: j -> k) data Nat (p :: Cat j) (q :: Cat k) (f :: j -> k) (g :: j -> k) type Iso k (c :: Cat k) (d :: Cat k) s t a b = forall p. (Cod p ~~ Nat d (->)) => p a b -> p s t data (p :: Constraint) :- (q :: Constraint) }}} With GHC 8.0.1 it fails with a compiler panic, {{{ $ ghc Hi.hs -fprint-explicit-kinds [1 of 1] Compiling Main ( Hi.hs, Hi.o ) Hi.hs:21:1: error: ? Non type-variable argument in the constraint: Category j (Dom k j f) (Use FlexibleContexts to permit this) ? In the context: (Category j (Dom k j f), Category k (Cod k j f)) While checking the super-classes of class ?Functor? In the class declaration for ?Functor? Hi.hs:29:20: error: ? GHC internal error: ?Dom? is not in scope during type checking, but it passed the renamer tcl_env of environment: [a2yi :-> Type variable ?j? = j, a2yj :-> Type variable ?p? = p, a2yk :-> Type variable ?k? = k, a2yl :-> Type variable ?q? = q, a2ym :-> Type variable ?f? = f, r2xT :-> ATcTyCon Fun] ? In the first argument of ?~?, namely ?Dom f? In the class declaration for ?Fun? }}} If one adds the appropriate extensions (`FunctionalDependencies`, `FlexibleInstances`, and `FlexibleContexts`) GHC complains that the program fails to satisfy the coverage condition, {{{ Hi.hs:31:10: error: ? Illegal instance declaration for ?Fun k j p q f? The coverage condition fails in class ?Fun? for functional dependency: ?f -> p q? Reason: lhs type ?f? does not determine rhs types ?p?, ?q? Un-determined variables: p, q Using UndecidableInstances might help ? In the instance declaration for ?Fun (p :: Cat j) (q :: Cat k) (f :: j -> k)? }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:46:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:46:58 -0000 Subject: [GHC] #12021: Type variable escapes its scope In-Reply-To: <046.130748221ef7180f1063edfb1f33f5e9@haskell.org> References: <046.130748221ef7180f1063edfb1f33f5e9@haskell.org> Message-ID: <061.c0048ab0b95579430dc15d16418c1d6a@haskell.org> #12021: Type variable escapes its scope -------------------------------------+------------------------------------- Reporter: ttuegel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: ghc-devs@? (removed) * cc: simonpj (added) Comment: CCing Simon. There are a few odd things here. I've opened #12055 which describes a variant of this program which throws the typechecker into panic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:47:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:47:26 -0000 Subject: [GHC] #12021: Type variable escapes its scope In-Reply-To: <046.130748221ef7180f1063edfb1f33f5e9@haskell.org> References: <046.130748221ef7180f1063edfb1f33f5e9@haskell.org> Message-ID: <061.aa01be8a0dea3e7692044cf58b3a606d@haskell.org> #12021: Type variable escapes its scope -------------------------------------+------------------------------------- Reporter: ttuegel | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: 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: | -------------------------------------+------------------------------------- Changes (by bgamari): * version: 8.0.1-rc3 => 8.0.1-rc4 * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 08:53:47 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 08:53:47 -0000 Subject: [GHC] #12039: Panic with partial class definition In-Reply-To: <043.594973634c4616bf2544fe97c427a9c7@haskell.org> References: <043.594973634c4616bf2544fe97c427a9c7@haskell.org> Message-ID: <058.4dcbefee5c996a39d1426b9fa87f3a16@haskell.org> #12039: Panic with partial class definition -------------------------------------+------------------------------------- Reporter: maud | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: partial- | sigs/should_fail/T12039 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => partial-sigs/should_fail/T12039 * status: new => closed * resolution: => fixed Comment: Thanks. Happily already fixed in HEAD. I've added a regression test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 10:51:11 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 10:51:11 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.754447b924b57906720fdbf34ac5b2c4@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+-------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+-------------------------------- Comment (by trommler): Replying to [comment:2 erikd]: > Thanks @trommler! I meant to CC you on this, but then forgot. Seems I didn't need to :). No problem :-) I have a fix that I am currently validating on powerpc64 and powerpc64le. I will post it on Phabricator once it's done validating. If you want to take a look before, the patch is here: [https://github.com/trommler/ghc/tree/T12054] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 11:29:45 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 11:29:45 -0000 Subject: [GHC] #12055: Typechecker panic instead of proper error In-Reply-To: <046.1237d444c794f470f1d99c65363ee9aa@haskell.org> References: <046.1237d444c794f470f1d99c65363ee9aa@haskell.org> Message-ID: <061.b337e3012b9a868c452df4ea04a48982@haskell.org> #12055: Typechecker panic instead of proper error -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Well HEAD for this gives {{{ T12055.hs:18:1: error: ? Non type-variable argument in the constraint: Category (Dom f) (Use FlexibleContexts to permit this) ? In the context: (Category (Dom f), Category (Cod f)) While checking the super-classes of class ?Functor? In the class declaration for ?Functor? T12055.hs:26:1: error: ? Fundeps in class ?Fun? (Use FunctionalDependencies to allow fundeps) ? In the class declaration for ?Fun? T12055.hs:29:5: error: ? Illegal instance declaration for ?Fun p q f? (All instance types must be of the form (T a1 ... an) where a1 ... an are *distinct type variables*, and each type variable appears at most once in the instance head. Use FlexibleInstances if you want to disable this.) ? In the instance declaration for ?Fun (p :: Cat j) (q :: Cat k) (f :: j -> k)? }}} And if you add the missing language extensions {{{ {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} }}} then it compiles cleanly. I suppose someone could bisect their way to the patch that fixed HEAD. Or we could just leave it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 12:32:03 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 12:32:03 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.c5db96cfffb870aefe15241ac1fab3b2@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+-------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+-------------------------------- Comment (by trommler): I could not reproduce the bug on powerpc64le which is strange. The above code is generated when we need to move the stack pointer further than what fits into a 16 bit signed offset. The stack pointer is updated when we allocate a new stack frame or when we need to allocate additional spill slots in the current stack frame. A spill slot on 64-bit, however, has eight bytes not four so I would expect to see the issue on powerpc64le and powerpc64 too. The bug in the pretty printer affects all PowerPCs but it seems I can't tickle it on 64-bit processors. Is there another bug higher up in the code generator that affects only 32 bit? How can we produce a regression test for this bug? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 14:12:44 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 14:12:44 -0000 Subject: [GHC] #12033: [TypeApplications] GHC internal error In-Reply-To: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> References: <051.21a69c3128167eb02cb0051d0d5301ac@haskell.org> Message-ID: <066.36a68c54b9f97fe50ebbb50f1953a1bd@haskell.org> #12033: [TypeApplications] GHC internal error -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): `CatFail.hs` fails with {{{ T12033a.hs:45:31: error: Not in scope: type constructor or class ?Dict? }}} so perhaps the test isn't right. Anyway, I think #12055, which does reproduce, is a simpler test case. On the other hand `HaskellBug.hs` really is a new and quite different bug. Patch coming for that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 14:37:35 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 14:37:35 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" In-Reply-To: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> References: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> Message-ID: <066.79e23209e4c724bc4df8a7b1f4f6e7e6@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj Comment: I'm on this -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 14:37:44 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 14:37:44 -0000 Subject: [GHC] #12051: -.-> is accepted as a data constructor In-Reply-To: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> References: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> Message-ID: <064.cef206f6bfeee8bf5800cca8cfa58966@haskell.org> #12051: -.-> is accepted as a data constructor -------------------------------------+------------------------------------- Reporter: mpickering | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 15:20:02 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 15:20:02 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.a575f2295afb7783f99c69f1dd9859f7@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+---------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2214 Wiki Page: | ----------------------------------------+---------------------------------- Changes (by trommler): * status: new => patch * differential: => Phab:D2214 Comment: Here is the fix for the native code generator issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 15:42:47 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 15:42:47 -0000 Subject: [GHC] #10746: No non-exhaustive pattern match warning given for empty case analysis In-Reply-To: <046.7124d47aa8c745a5f8757fe53c21a64c@haskell.org> References: <046.7124d47aa8c745a5f8757fe53c21a64c@haskell.org> Message-ID: <061.8685b2fc591c1016922d54f0b28d2bc2@haskell.org> #10746: No non-exhaustive pattern match warning given for empty case analysis -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #7669, #11806 | Differential Rev(s): Phab:D2105 Wiki Page: | -------------------------------------+------------------------------------- Comment (by gkaracha): Replying to [comment:25 simonpj]: > * Normalise `x`'s type, to get it to the form `T ty1 .. tyn`. (I don't understand the "bounded" bit.) For this, we must reduce type families, but NOT newtypes. For pattern matching purposes, newtypes behave just like data types. So use `FamInstEnv.normaliseType`. This sounds wrong to me. Newtypes and data types do not behave the same when it comes to pattern matching. From [https://wiki.haskell.org/Newtype Newtype Wiki Page]: {{{#!hs data Foo1 = Foo1 Int newtype Foo3 = Foo3 Int y1 = case undefined of Foo1 _ -> 1 -- undefined y3 = case undefined of Foo3 _ -> 1 -- 1 }}} which is verified by my GHCi (7.10). Additionally, by bounded I mean that when we have a family {{{#!hs type family F (a :: *) :: * type instance F a = F a }}} we do not want to keep rewriting forever. Hence, I would bound normalization with a fixed number of maximum iterations. If we exceed that, we (playing on the safe side) assume that the type is inhabited and issue a warning. The rest you mentioned I agree with, but I missed a bit: > * If some of `T`'s data constructor are GADTs, then enumerate them all and recurse. What do you mean by **recurse** in this case? Does `EmptyCase` imply deep evaluation (is it really strict pattern matching) or just in WHNF? Because I thought that it means the latter. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 16:04:05 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 16:04:05 -0000 Subject: [GHC] #12056: Too aggressive `-w` option Message-ID: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- By running {{{ ghc -w -Wunrecognised-warning-flags -Wfoo Main.hs }}} I would expect the warning {{{ on the commandline: warning: unrecognised warning flag: -Wfoo }}} however this warning isn't reported. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 16:05:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 16:05:19 -0000 Subject: [GHC] #10746: No non-exhaustive pattern match warning given for empty case analysis In-Reply-To: <046.7124d47aa8c745a5f8757fe53c21a64c@haskell.org> References: <046.7124d47aa8c745a5f8757fe53c21a64c@haskell.org> Message-ID: <061.c2bdc1b06f3b922267fbc640094c2ec0@haskell.org> #10746: No non-exhaustive pattern match warning given for empty case analysis -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #7669, #11806 | Differential Rev(s): Phab:D2105 Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I don't know about the other stuff, but I think I disagree on the bounded bit. In that situation, I would expect the compiler to go into an infinite loop (unless it has pity on us in that particular case and happens to detect the loop, which is not the pattern checker's problem in any case). If I tell the type checker to go into an infinite loop and heat up my computer, it's really okay if it does that. Again, I can always write {{{#!hs foo :: F Int -> a foo !_ = error "Unreachable, but that's not provable within Haskell." }}} if I want to impose an ad hoc postulate about program behavior. Empty case is for what GHC *can* prove. The case of terminally stuck closed type families (ones that no additional information could possibly reduce) is a bit weird; I think for now at least you should probably treat them the same as stuck open type families and assume them inhabited. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 19:22:35 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 19:22:35 -0000 Subject: [GHC] #12001: RFC: Add pattern synonyms to base In-Reply-To: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> References: <051.a75667959d8601b2c7daa93e0c0a6683@haskell.org> Message-ID: <066.ff9f3e9295c0592a582fa6e9a3adb441@haskell.org> #12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): === GHC.Generics === {{{#!hs pattern From :: Generic a => (Rep a) x -> a pattern From rep <- (from ? rep) where From rep = to rep pattern From1 :: Generic1 f => (Rep1 f) a -> f a pattern From1 rep <- (from1 ? rep) where From1 rep = to1 rep }}} or corresponding `To`, `To1` patterns. === Text.Read === {{{#!hs pattern Read :: Read a => a -> String pattern Read a <- (readMaybe -> Just a) }}} with the caveat that they parse different types, {{{#!hs foo :: String -> String foo (Read 42) = "answer" foo (Read n) = "some other number " ++ show n foo _ = "can't parse" }}} {{{ ghci> foo "()" "some other number ()" }}} If the types are made explicit with #11350 {{{#!hs foo :: String -> String foo (Read @Integer 42) = "answer" foo (Read @() n) = "some other number " ++ show n foo _ = "can't parse" }}} it is a common action and pattern (search for `pattern` and `readMaybe -> Just`), and is often use to pattern match on numbers. Artificially restricting the type avoids it matching `()` {{{#!hs pattern ReadNumber :: (Num a, Read a) => a -> String }}} This is cool {{{ ghci> [ n | ReadNumber n <- words "from 2010 ... 2016 they were 4" ] [2010,2016,4] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 19:37:28 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 19:37:28 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on GHC.Generic's `Rep` Message-ID: <051.38c482983531342047bddb8add84ef15@haskell.org> #12057: TypeFamilyDependencies on GHC.Generic's `Rep` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | Keywords: TypeFamilies, | Operating System: Unknown/Multiple Injective | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With `TypeFamilyDependencies` (`InjectiveTypeFamilies`) can't `Rep` from `Generic` have a dependency? {{{#!hs class Generic a where type Rep a = (res :: Type -> Type) | res -> a ... }}} Assuming the meta data is always unique. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 19:38:02 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 19:38:02 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on GHC.Generic's `Rep` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.75cc7a40e2ef077bd2777b9a5a2c3256@haskell.org> #12057: TypeFamilyDependencies on GHC.Generic's `Rep` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective Operating System: 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): `Rep1` also -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 20:42:03 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 20:42:03 -0000 Subject: [GHC] #12045: Visible kind application In-Reply-To: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> References: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> Message-ID: <066.7829deb606d1a1c06132d979c76b46d7@haskell.org> #12045: Visible kind application -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This is one of the great many things I would love to work on if I had time. Popping up a level: you've written a great many bug reports / feature requests recently. These are very helpful! Thanks! A good deal of them would naturally fall to me to implement/fix, but I'm dreadfully short of time these days. (And will be until September, at least.) So: Would you care to try to fix some of these infelicities? You have a great grasp of GHC's type system and how to abuse it (I mean that, quite surely, as a compliment), and I imagine you would have fun getting into the gearbox and getting your hands dirty. I conjecture that this ticket is actually a good place to start. My rule of thumb is that writing a new feature is easier than debugging someone else's mistake. For a user-facing feature like this, just start by extending the abstract syntax (in hsSyn/HsType.hs, to be specific), add some rules to the parser, and then follow the errors / warnings that ensue. Unlike adding `TypeApplications` to expressions, the type-level type checker (er, kind checker) already does lazy instantiation, so this shouldn't be a terribly invasive change. I'm quite happy to advise, even being short of time. One mode of collaboration might be to start a patch and submit it to Phabricator, and then I can offer feedback. (PS: I sometimes let tickets / Phab requests slip by me these days. If you want to be sure to get a response to something, email me. My contact info is [http://www.cis.upenn.edu/~eir here].) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 20:45:24 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 20:45:24 -0000 Subject: [GHC] #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer In-Reply-To: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> References: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> Message-ID: <060.3e889f29235370f31d5898248aa96339@haskell.org> #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Template Haskell | Version: 8.0.1-rc2 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 goldfire): * component: Compiler (Type checker) => Template Haskell -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 21:11:31 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 21:11:31 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on GHC.Generic's `Rep` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.f4657ce8658d377223d774f9cadd60a9@haskell.org> #12057: TypeFamilyDependencies on GHC.Generic's `Rep` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective Operating System: 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): `Data.Type.Bool.Not` can be made injective {{{#!hs type family Not (a :: Bool) = (res :: Bool) | res -> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 21:59:31 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 21:59:31 -0000 Subject: [GHC] #12035: hs-boot knot tying insufficient for ghc --make In-Reply-To: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> References: <045.e388ac2b960dff94b80b0bffb9130187@haskell.org> Message-ID: <060.df08d00fe49c2111546682f1a9320cc4@haskell.org> #12035: hs-boot knot tying insufficient for ghc --make -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: hs-boot Resolution: | backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2213 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => patch * differential: => Phab:D2213 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 22:02:20 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 22:02:20 -0000 Subject: [GHC] #11062: Type families + hs-boot files = panic In-Reply-To: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> References: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> Message-ID: <062.8a73c3d8e98b4f50ebfad179ef282ce3@haskell.org> #11062: Type families + hs-boot files = panic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeFamilies | hs-boot 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 ezyang): * keywords: TypeFamilies => TypeFamilies hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 22:02:31 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 22:02:31 -0000 Subject: [GHC] #9562: Type families + hs-boot files = unsafeCoerce In-Reply-To: <047.0928965f4d9302995273a5c9d11eab3c@haskell.org> References: <047.0928965f4d9302995273a5c9d11eab3c@haskell.org> Message-ID: <062.fa471d9032c93c7c653295f0266f89f8@haskell.org> #9562: Type families + hs-boot files = unsafeCoerce -------------------------------------+------------------------------------- Reporter: goldfire | Owner: ezyang Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: TypeFamilies, | SafeHaskell hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: #10270 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * keywords: TypeFamilies, SafeHaskell => TypeFamilies, SafeHaskell hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 22:03:52 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 22:03:52 -0000 Subject: [GHC] #11062: Type families + hs-boot files = panic In-Reply-To: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> References: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> Message-ID: <062.ee33b3a5d9c5c19e32c3121897c7be11@haskell.org> #11062: Type families + hs-boot files = panic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeFamilies | hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): OK, it's actually pretty obvious what's going on here: family instance consistency gets checked in the renamer but this is too early, because we haven't put enough things in the type environment. The solution is to move the check later in the typechecking process. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 13 22:18:56 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 13 May 2016 22:18:56 -0000 Subject: [GHC] #11062: Type families + hs-boot files = panic In-Reply-To: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> References: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> Message-ID: <062.9678451d47abd0bd074415220135e63b@haskell.org> #11062: Type families + hs-boot files = panic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeFamilies | hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2215 Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => patch * differential: => Phab:D2215 Comment: If it is completely unacceptable to check type family instance consistency after type checking, then we'll have to look into a different way of fixing this problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 04:49:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 04:49:35 -0000 Subject: [GHC] #12045: Visible kind application In-Reply-To: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> References: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> Message-ID: <066.4ee9b0eca870ec302a5ffc2fdb368532@haskell.org> #12045: Visible kind application -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * owner: => Iceland_jack -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 05:31:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 05:31:11 -0000 Subject: [GHC] #12045: Visible kind application In-Reply-To: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> References: <051.f572b464c11770181720f8a1a7ec05a5@haskell.org> Message-ID: <066.a805b8c733745f40b762652e0c0c527a@haskell.org> #12045: Visible kind application -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): ?Phab:D2216 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * differential: => ?Phab:D2216 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 06:42:55 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 06:42:55 -0000 Subject: [GHC] #12058: Documentation will not build on platforms where GNU make is not called make Message-ID: <042.c257273eaff4f54de3cc8f115007061d@haskell.org> #12058: Documentation will not build on platforms where GNU make is not called make -------------------------------------+------------------------------------- Reporter: pgj | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Build System | Version: 8.0.1 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 have tried to build the source tarball on FreeBSD, but it always stops somewhere around the documentation bits with the following error message: {{{ [..] make -C utils/haddock/doc html SPHINX_BUILD=/usr/local/bin/sphinx-build make: illegal option -- - usage: make [-BPSXeiknpqrstv] [-C directory] [-D variable] [-d flags] [-E variable] [-f makefile] [-I directory] [-j max_jobs] [-m directory] [-V variable] [variable=value] [target ...] utils/haddock/doc/ghc.mk:22: recipe for target 'html_utils/haddock/doc' failed gmake[1]: *** [html_utils/haddock/doc] Error 2 Makefile:129: recipe for target 'all' failed gmake: *** [all] Error 2 }}} That is probably because FreeBSD has GNU make(1) as {{{gmake}}}, it should be invoked with that name, that is, the value of the {{{$(MAKE)}}} variable is not respected at the recursive invocation of make(1). I have attached a patch for the {{{haddock}}} repository that fixes this problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 06:43:16 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 06:43:16 -0000 Subject: [GHC] #12058: Documentation will not build on platforms where GNU make is not called make In-Reply-To: <042.c257273eaff4f54de3cc8f115007061d@haskell.org> References: <042.c257273eaff4f54de3cc8f115007061d@haskell.org> Message-ID: <057.348d97f79f32e49ac15b44fd778772e5@haskell.org> #12058: Documentation will not build on platforms where GNU make is not called make -------------------------------------+------------------------------------- Reporter: pgj | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Build System | Version: 8.0.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 pgj): * Attachment "haddock.ghc.mk.diff" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 08:11:38 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 08:11:38 -0000 Subject: [GHC] #12058: Documentation will not build on platforms where GNU make is not called make In-Reply-To: <042.c257273eaff4f54de3cc8f115007061d@haskell.org> References: <042.c257273eaff4f54de3cc8f115007061d@haskell.org> Message-ID: <057.00f3a6c46ba9933288b7e3e4dfe026a7@haskell.org> #12058: Documentation will not build on platforms where GNU make is not called make -------------------------------------+------------------------------------- Reporter: pgj | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Build System | Version: 8.0.1 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: new => closed * resolution: => fixed Comment: Thanks P?li! This should now be fixed in `ghc-8.0` (7eb2ad9595c90abdb792a291d6473b4b3a2934e6) and `master` (sorry, I didn't notice your patch until I had already pushed my own). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 09:34:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 09:34:51 -0000 Subject: [GHC] #12059: Add primop to query for pinned-ness of a ByteArray Message-ID: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> #12059: Add primop to query for pinned-ness of a ByteArray -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature | Status: new request | Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It would be useful to have, {{{#!hs isPinnedByteArray# :: MutableByteArray# -> Int# }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 09:50:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 09:50:17 -0000 Subject: [GHC] #12059: Add primop to query for pinned-ness of a ByteArray In-Reply-To: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> References: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> Message-ID: <061.e821146f7d5c91583ab6443b2285c622@haskell.org> #12059: Add primop to query for pinned-ness of a ByteArray -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2217 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2217 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 10:47:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 10:47:31 -0000 Subject: [GHC] #12059: Add primop to query for pinned-ness of a ByteArray In-Reply-To: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> References: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> Message-ID: <061.b99afb7227ce5a69b04832aba722e0b6@haskell.org> #12059: Add primop to query for pinned-ness of a ByteArray -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2217 Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -5,0 +5,3 @@ + + This, for instance, allows one to construct a `ByteString` from a + `ByteArray` in an opportunistically zero-copy manner. New description: It would be useful to have, {{{#!hs isPinnedByteArray# :: MutableByteArray# -> Int# }}} This, for instance, allows one to construct a `ByteString` from a `ByteArray` in an opportunistically zero-copy manner. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 11:26:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 11:26:58 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named Message-ID: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> #12060: GHC panic depending on what a Haskell module is named --------------------------------------+---------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: --------------------------------------+---------------------------------- I'm trying to make bindings for the imgui C++ library and have encountered an apparent bug. I'm unable to produce a minimal example so I've packed up the whole project in a zip file. It only works on Windows for now but I assume this problem is platform dependant anyways. There's a module `UI.Imgui` that imports two things. A `FunPtr` wrapping function and an actual function defined in a .cpp file. Another module Main imports this module. If the project is run in a repl (in my case I'm doing `stack repl`) and then the `test` function is evaluated it results in a GHC panic {{{#!hs ghc.exe: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-mingw32): loadObj "C:\\Users\\Luka\\AppData\\Local\\Temp\\ghc5900_0\\ghc_5.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Now here's the fun part. If you rename the module, file and it's import to something like Imgui2 it works. If you rename it to UI2.Imgui (with appropriate folder renaming) it also works! I'm sure a huge portion of the code is irrelevant. I couldn't reproduce this with simple .cpp files. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 11:27:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 11:27:48 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named In-Reply-To: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> References: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> Message-ID: <063.a980b37e23a4030caeb383c1b73c6d9c@haskell.org> #12060: GHC panic depending on what a Haskell module is named ----------------------------------+-------------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: | ----------------------------------+-------------------------------------- Description changed by Darwin226: @@ -28,0 +28,3 @@ + + Here's a link to the file (3MB) + https://dl.dropboxusercontent.com/u/35032740/ShareX/2016/05/imgui.zip New description: I'm trying to make bindings for the imgui C++ library and have encountered an apparent bug. I'm unable to produce a minimal example so I've packed up the whole project in a zip file. It only works on Windows for now but I assume this problem is platform dependant anyways. There's a module `UI.Imgui` that imports two things. A `FunPtr` wrapping function and an actual function defined in a .cpp file. Another module Main imports this module. If the project is run in a repl (in my case I'm doing `stack repl`) and then the `test` function is evaluated it results in a GHC panic {{{#!hs ghc.exe: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-mingw32): loadObj "C:\\Users\\Luka\\AppData\\Local\\Temp\\ghc5900_0\\ghc_5.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Now here's the fun part. If you rename the module, file and it's import to something like Imgui2 it works. If you rename it to UI2.Imgui (with appropriate folder renaming) it also works! I'm sure a huge portion of the code is irrelevant. I couldn't reproduce this with simple .cpp files. Here's a link to the file (3MB) https://dl.dropboxusercontent.com/u/35032740/ShareX/2016/05/imgui.zip -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 13:30:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 13:30:37 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named In-Reply-To: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> References: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> Message-ID: <063.997b336b9658d98251a89a515f89acd6@haskell.org> #12060: GHC panic depending on what a Haskell module is named ----------------------------------+-------------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: | ----------------------------------+-------------------------------------- Description changed by Darwin226: @@ -31,0 +31,11 @@ + + Update: Ok so it seems that the "reason" why renaming the file works is + because I forgot to change the entry in the cabal file so the next time I + run the repl it doesn't recompile the project but it launches the repl + using the previous build. Why it doesn't panic in that case I have no + idea. + + Also, here's another thing that fixes is: + Run the repl -> try test -> GHC panic -> save the Imgui file (without + changing anything, just so you can :r it) -> do :r in GHCi -> try test -> + works New description: I'm trying to make bindings for the imgui C++ library and have encountered an apparent bug. I'm unable to produce a minimal example so I've packed up the whole project in a zip file. It only works on Windows for now but I assume this problem is platform dependant anyways. There's a module `UI.Imgui` that imports two things. A `FunPtr` wrapping function and an actual function defined in a .cpp file. Another module Main imports this module. If the project is run in a repl (in my case I'm doing `stack repl`) and then the `test` function is evaluated it results in a GHC panic {{{#!hs ghc.exe: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-mingw32): loadObj "C:\\Users\\Luka\\AppData\\Local\\Temp\\ghc5900_0\\ghc_5.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Now here's the fun part. If you rename the module, file and it's import to something like Imgui2 it works. If you rename it to UI2.Imgui (with appropriate folder renaming) it also works! I'm sure a huge portion of the code is irrelevant. I couldn't reproduce this with simple .cpp files. Here's a link to the file (3MB) https://dl.dropboxusercontent.com/u/35032740/ShareX/2016/05/imgui.zip Update: Ok so it seems that the "reason" why renaming the file works is because I forgot to change the entry in the cabal file so the next time I run the repl it doesn't recompile the project but it launches the repl using the previous build. Why it doesn't panic in that case I have no idea. Also, here's another thing that fixes is: Run the repl -> try test -> GHC panic -> save the Imgui file (without changing anything, just so you can :r it) -> do :r in GHCi -> try test -> works -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 13:31:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 13:31:11 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named In-Reply-To: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> References: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> Message-ID: <063.0087f928ca632619789d767ee4ce0981@haskell.org> #12060: GHC panic depending on what a Haskell module is named ----------------------------------+-------------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: | ----------------------------------+-------------------------------------- Description changed by Darwin226: @@ -34,1 +34,1 @@ - run the repl it doesn't recompile the project but it launches the repl + run the repl it fails to recompile the project but it launches the repl New description: I'm trying to make bindings for the imgui C++ library and have encountered an apparent bug. I'm unable to produce a minimal example so I've packed up the whole project in a zip file. It only works on Windows for now but I assume this problem is platform dependant anyways. There's a module `UI.Imgui` that imports two things. A `FunPtr` wrapping function and an actual function defined in a .cpp file. Another module Main imports this module. If the project is run in a repl (in my case I'm doing `stack repl`) and then the `test` function is evaluated it results in a GHC panic {{{#!hs ghc.exe: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-mingw32): loadObj "C:\\Users\\Luka\\AppData\\Local\\Temp\\ghc5900_0\\ghc_5.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} Now here's the fun part. If you rename the module, file and it's import to something like Imgui2 it works. If you rename it to UI2.Imgui (with appropriate folder renaming) it also works! I'm sure a huge portion of the code is irrelevant. I couldn't reproduce this with simple .cpp files. Here's a link to the file (3MB) https://dl.dropboxusercontent.com/u/35032740/ShareX/2016/05/imgui.zip Update: Ok so it seems that the "reason" why renaming the file works is because I forgot to change the entry in the cabal file so the next time I run the repl it fails to recompile the project but it launches the repl using the previous build. Why it doesn't panic in that case I have no idea. Also, here's another thing that fixes is: Run the repl -> try test -> GHC panic -> save the Imgui file (without changing anything, just so you can :r it) -> do :r in GHCi -> try test -> works -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 14 18:19:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 14 May 2016 18:19:18 -0000 Subject: [GHC] #10832: Generalize injective type families In-Reply-To: <048.1487f224b00112fe37d31a1812a748a4@haskell.org> References: <048.1487f224b00112fe37d31a1812a748a4@haskell.org> Message-ID: <063.c83515776b50a536c6af46c7269ec2d6@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) | Resolution: | Keywords: TypeFamilies 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 carter): I've hit needing this feature for what I was hoping would be pretty elementary code :( {{{ type family ReverseTC (a :: [ k ]) (res :: [ k ] ) = result where ReverseTC '[] res = res ReverseTC (a ': bs ) res = ReverseTC bs (a ': res) type family Reverse (a :: [k]) = (result :: [k]) where Reverse a = ReverseTC a '[] }}} I would like to explain to GHC that if i know a and result , or res and result, i know the remaining variable, so that my "stack safe" Reverse computation can also be treated as Injective (which it is! ) -- Ticket URL: GHC The Glasgow Haskell Compiler From matthew at wellquite.org Sat May 14 23:19:41 2016 From: matthew at wellquite.org (matthew at wellquite.org) Date: Sun, 15 May 2016 02:19:41 +0300 Subject: Fw: new message Message-ID: <0000addc23d7$cad9f30a$4456f627$@wellquite.org> Hello! You have a new message, please read matthew at wellquite.org -------------- next part -------------- An HTML attachment was scrubbed... URL: From ghc-devs at haskell.org Sun May 15 01:56:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 01:56:18 -0000 Subject: [GHC] #12061: Allow duplicate record fields in pattern synonyms Message-ID: <051.ca1b3aaea806961ea5212ae77452a5a2@haskell.org> #12061: Allow duplicate record fields in pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `DuplicateRecordFields` seems to not work for pattern synonyms {{{#!hs {-# Language PatternSynonyms, DuplicateRecordFields, NamedFieldPuns #-} pattern A{x} = Just x pattern B{x} = Just x }}} {{{ tg4t.hs:4:11: error: ? Multiple declarations of ?x? Declared at: /tmp/tg4t.hs:3:11 /tmp/tg4t.hs:4:11 Compilation failed. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 02:43:22 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 02:43:22 -0000 Subject: [GHC] #12061: Allow duplicate record fields in pattern synonyms In-Reply-To: <051.ca1b3aaea806961ea5212ae77452a5a2@haskell.org> References: <051.ca1b3aaea806961ea5212ae77452a5a2@haskell.org> Message-ID: <066.483e9174a9594167cc56b2104b78a32a@haskell.org> #12061: Allow duplicate record fields in pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 02:59:50 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 02:59:50 -0000 Subject: [GHC] #10352: Properly link Haskell shared libs on ELF systems In-Reply-To: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> References: <045.f54c0b53e462b1ea305eb5f3c38d7688@haskell.org> Message-ID: <060.44990aa31dca4473220e4d358efa3d69@haskell.org> #10352: Properly link Haskell shared libs on ELF systems -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (Linking) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by DanielG): * cc: DanielG (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:01:47 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:01:47 -0000 Subject: [GHC] #4003: tcIfaceGlobal panic building HEAD with 6.12.2 In-Reply-To: <047.53ac5fea0b657f76a262878b5cc2f709@haskell.org> References: <047.53ac5fea0b657f76a262878b5cc2f709@haskell.org> Message-ID: <062.0a060e810a1b72205528124be0bb1f4d@haskell.org> #4003: tcIfaceGlobal panic building HEAD with 6.12.2 -------------------------------------+------------------------------------- Reporter: simonmar | Owner: igloo Type: bug | Status: closed Priority: highest | Milestone: 6.12.3 Component: Compiler | Version: 6.12.2 Resolution: fixed | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: T4003 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * keywords: => hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:02:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:02:26 -0000 Subject: [GHC] #12042: Infinite loop with type synonyms and hs-boot In-Reply-To: <045.2af2d998455883876e6ff4ff050c9c9d@haskell.org> References: <045.2af2d998455883876e6ff4ff050c9c9d@haskell.org> Message-ID: <060.d88d6254259aa40fd5a92230b44a9ca7@haskell.org> #12042: Infinite loop with type synonyms and hs-boot -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Keywords: hs-boot Resolution: | 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: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -80,3 +80,0 @@ - - I take this bug as evidence that we should NOT attempt to knot-tie in this - situation. New description: This is a "known" bug, but the source code comment which mentioned this could happen didn't give a test case so I thought I'd supply one. {{{ -- A.hs-boot module A where data S type R = S -- B.hs module B (module A, module B) where import {-# SOURCE #-} A type U = S -- A.hs module A where import qualified B type S = B.R type R = B.U }}} When I try to build `A.hs` in one-shot I infinite loop: {{{ ezyang at sabre:~$ ghc-8.0 --make A.hs -fforce-recomp [1 of 3] Compiling A[boot] ( A.hs-boot, A.o-boot ) [2 of 3] Compiling B ( B.hs, B.o ) [3 of 3] Compiling A ( A.hs, A.o ) A.hs-boot:2:1: error: Type constructor ?S? has conflicting definitions in the module and its hs-boot file Main module: type S = R Boot file: abstract S ezyang at sabre:~$ ghc-8.0 -c A.hs -fforce-recomp ^C }}} The problem is that `-c` properly knot ties `data S` in the boot file to the local type synonym (`--make` is unaffected due to #12035), and then we have a type synonym loop which GHC doesn't catch early enough. `TcTyDecls.hs` has a nice comment which suggests that this is a known bug: {{{ Checking for class-decl loops is easy, because we don't allow class decls in interface files. We allow type synonyms in hi-boot files, but we *trust* hi-boot files, so we don't check for loops that involve them. So we only look for synonym loops in the module being compiled. We check for type synonym and class cycles on the *source* code. Main reasons: a) Otherwise we'd need a special function to extract type-synonym tycons from a type, whereas we already have the free vars pinned on the decl b) If we checked for type synonym loops after building the TyCon, we can't do a hoistForAllTys on the type synonym rhs, (else we fall into a black hole) which seems unclean. Apart from anything else, it'd mean that a type-synonym rhs could have for-alls to the right of an arrow, which means adding new cases to the validity checker Indeed, in general, checking for cycles beforehand means we need to be less careful about black holes through synonym cycles. The main disadvantage is that a cycle that goes via a type synonym in an .hi-boot file can lead the compiler into a loop, because it assumes that cycles only occur entirely within the source code of the module being compiled. But hi-boot files are trusted anyway, so this isn't much worse than (say) a kind error. }}} although the circumstances in this example are a little different. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:02:50 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:02:50 -0000 Subject: [GHC] #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer In-Reply-To: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> References: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> Message-ID: <060.5886d7ece75839f0b4a22362da113aaa@haskell.org> #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Template Haskell | Version: 8.0.1-rc2 Resolution: | Keywords: backpack hs- | boot 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 ezyang): * keywords: backpack => backpack hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:05:40 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:05:40 -0000 Subject: [GHC] #1012: ghc panic with mutually recursive modules and template haskell In-Reply-To: <044.e3ec0fd0938800cc6a7ce608eb8687c2@haskell.org> References: <044.e3ec0fd0938800cc6a7ce608eb8687c2@haskell.org> Message-ID: <059.c95c44a95c17e9f56efe223b93a1717d@haskell.org> #1012: ghc panic with mutually recursive modules and template haskell -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Template Haskell | Version: 6.8.2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | TH_import_loop Blocked By: | Blocking: Related Tickets: #9032 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * keywords: => hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:10:16 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:10:16 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.77e87861a657ff8632e08121561f9a34@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ivanm): * cc: ivanm (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:29:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:29:05 -0000 Subject: [GHC] #12062: Parallel make with -j0 and hs-boot leads to floating point exception Message-ID: <045.f05741a711c24d381cb39c4a23db2a0e@haskell.org> #12062: Parallel make with -j0 and hs-boot leads to floating point exception -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Runtime | Version: 8.0.1-rc2 System | Keywords: newcomer | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I run https://ghc.haskell.org/trac/ghc/ticket/1012#comment:5 with `ghc-8.0 --make ModuleB.hs -j0 -fforce-recomp` (the `-j0` is important) I get a `Floating point exception (core dumped)`. When I run under GDB, I get: {{{ (gdb) r Starting program: /srv/code/ghc-8.0.0.20160204/usr/lib/ghc-8.0.0.20160204/bin/ghc -B/home/ezyang/Dev/ghc-8.0.0.20160204/usr/lib/ghc-8.0.0.20160204 --make ModuleB.hs -j0 -fforce-recomp [Thread debugging using libthread_db enabled] Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1". [New Thread 0x7fffecd7f700 (LWP 28877)] [New Thread 0x7fffe7fff700 (LWP 28878)] [New Thread 0x7fffe77fe700 (LWP 28879)] [1 of 4] Compiling ModuleA[boot] ( ModuleA.hs-boot, ModuleA.o-boot ) [2 of 4] Compiling ModuleC ( ModuleC.hs, ModuleC.o ) [3 of 4] Compiling ModuleA ( ModuleA.hs, ModuleA.o ) [4 of 4] Compiling ModuleB ( ModuleB.hs, ModuleB.o ) Program received signal SIGFPE, Arithmetic exception. [Switching to Thread 0x7fffecd7f700 (LWP 28877)] schedule (initialCapability=, task=task at entry=0x7b6310) at rts/Schedule.c:373 373 rts/Schedule.c: No such file or directory. (gdb) bt #0 schedule (initialCapability=, task=task at entry=0x7b6310) at rts/Schedule.c:373 #1 0x00007fffed65018c in scheduleWorker (cap=, task=0x7b6310) at rts/Schedule.c:2378 #2 0x00007ffff738a6aa in start_thread (arg=0x7fffecd7f700) at pthread_create.c:333 #3 0x00007fffed14fe9d in clone () at ../sysdeps/unix/sysv/linux/x86_64/clone.S:109 }}} I once got a different error running this: {{{ warning: Corrupted shared library list: 0x7e1ee0 != 0x7ffff7ffd9d8 }}} Looking at the code which is a `capabilities[cap->no % enabled_capabilities]`, I guess this is just something goofy, like GHC not rejecting `-j0` and then however we're setting the capabilities not checking this case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:34:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:34:45 -0000 Subject: [GHC] #1012: ghc panic with mutually recursive modules and template haskell In-Reply-To: <044.e3ec0fd0938800cc6a7ce608eb8687c2@haskell.org> References: <044.e3ec0fd0938800cc6a7ce608eb8687c2@haskell.org> Message-ID: <059.06ea6852bb056d61f428b3d07b67b0b9@haskell.org> #1012: ghc panic with mutually recursive modules and template haskell -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Template Haskell | Version: 6.8.2 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | TH_import_loop Blocked By: | Blocking: Related Tickets: #9032 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): This bug still exists in GHC 8.0, although it can be a bit tricky to trigger if the topsort picks an ordering of modules which masks the error. I found this especially surprising because in the parallel upsweep case we seem to try to block, c.f. this comment in GhcMake {{{ 2. A module that depends on a module in an external loop can't proceed until the entire loop is re-typechecked. }}} and this code: {{{ -- If this module depends on a module within a loop then it must wait for -- that loop to get re-typechecked, i.e. it must wait on the module that -- finishes that loop. These extra dependencies are this module's -- "external" loop dependencies, because this module is outside of the -- loop(s) in question. let ext_loop_deps = Set.fromList [ head loop | loop <- comp_graph_loops , any (`Set.member` textual_deps) loop , this_build_mod `notElem` loop ] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:50:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:50:10 -0000 Subject: [GHC] #12063: Knot-tying failure when type-synonym refers to non-existent data Message-ID: <045.5d0eb098fb5e4585a85062e98ec9f2c1@haskell.org> #12063: Knot-tying failure when type-synonym refers to non-existent data -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: hs-boot | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider: {{{ -- A.hs-boot module A data T -- B.hs module B import {-# SOURCE #-} A type S = T -- A.hs module A import B x :: S }}} This will cause a tcIfaceGlobal panic when compiling `A.hs` in one-shot mode. The reason is that we will attempt to knot tie `B.hi`'s reference to `A:T` when typechecking the contents of `A.hs`, but unfortunately there is no declaration of `T` in the real `A.hs`, so the knot tying will fail. It's not entirely clear to me how to deal with this problem. The obvious thing to do is to fault in the `TyThing` from the ModDetails of the hs- boot file (great care must be taken because we don't actually want to load the hs-boot file!) We'll then fail in due course when we check if we actually implement everything the hs-boot file needs. But this could complicate things: 1. This "robustness" could mask another, much more difficult to diagnose bug when there was an actual knot-tying failure. Then, we will silently fail to tie the knot, and then if something bad happens it is a lot less obvious what went wrong. However! I think there is an ASSERT we can add in this case: when we add things to the type environment (and update the knot tying variable), we can check if we have faulted in the relevant entity from the hs-boot file. If we have, then we know there is knot-tying failure and we should fail. 2. Having two sets of `TyThing`s for the same `Name` could lead to hard to diagnose errors; e.g., you are comparing `S` for equality with `S`, but they return not equal because one of these is a type synonym tycon and the other is an abstract tycon. There might be some adjustments to the debug printing mechanism to make such situations more obvious. Here is another way to fix the bug: check if all the types declared in the hs-boot file are actually defined before doing any typechecking proper. Interestingly, this is a possible solution for #12034: the implication is that all types mentioned in the hs-boot file must be defined PRIOR to the first splice. If we look at #1012, this would not be a burden for users that use TH and hs-boot. Also, it nicely fits with a solution for #12042, since we need to check for type synonym loops at some point BEFORE typechecking, and this is the obvious place to do so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 03:52:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 03:52:15 -0000 Subject: [GHC] #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer In-Reply-To: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> References: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> Message-ID: <060.ebe7f02305fbc13b8b020ac319d08669@haskell.org> #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Template Haskell | Version: 8.0.1-rc2 Resolution: | Keywords: backpack hs- | boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Here is a restriction for hs-boot files and TH which might solve this problem: all TYPEs in the hs-boot file (values can wait) must be defined in the section of the file PRIOR to the first Template Haskell splice. This ensures we have a consistent environment for knot-tying, and also is an obvious place to check for missing types #12063 or type synonym loops #12042. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 05:34:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 05:34:17 -0000 Subject: [GHC] #2412: Interaction between type synonyms and .hs-boot causes panic "tcIfaceGlobal (local): not found" In-Reply-To: <053.250fd8f3285636d4b0e7d255649c2b44@haskell.org> References: <053.250fd8f3285636d4b0e7d255649c2b44@haskell.org> Message-ID: <068.8b1df78951a631385d5ba886e7f6c9ae@haskell.org> #2412: Interaction between type synonyms and .hs-boot causes panic "tcIfaceGlobal (local): not found" -------------------------------------+------------------------------------- Reporter: batterseapower | Owner: igloo Type: bug | Status: closed Priority: normal | Milestone: 6.10.1 Component: Compiler | Version: 6.9 Resolution: fixed | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T2412 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * keywords: => hs-boot * failure: => None/Unknown -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 05:41:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 05:41:51 -0000 Subject: [GHC] #12064: tcIfaceGlobal error with existentially quantified types Message-ID: <045.3f2e9cf37ca8869e1da5dbbed8082702@haskell.org> #12064: tcIfaceGlobal error with existentially quantified types -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: hs-boot | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following program: {{{ -- A.hs-boot module A where data D -- B.hs module B where import {-# SOURCE #-} A class K a where method :: D -> a -- A.hs {-# LANGUAGE ExistentialQuantification #-} module A where import A data D = forall n. K n => D }}} We get a `tcIfaceGlobal` error in this case (one-shot of course.) I reduced this case out of prog006. So for some reason we're tugging on `K` too early?that's as far as I know at this point. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 06:32:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 06:32:59 -0000 Subject: [GHC] #12065: there is a way to override the .tix path with HPCTIXFILE Message-ID: <045.acf890da63effd264c753e4e22e0c6f2@haskell.org> #12065: there is a way to override the .tix path with HPCTIXFILE -------------------------------------+------------------------------------- Reporter: kostmo | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Documentation Unknown/Multiple | bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Under the [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/hpc.html#idp46686522167856 "Caveats and Shortcomings of Haskell Program Coverage" section], it says: > There is no way to change the name of the .tix file generated, apart from renaming the binary. However, specifying `HPCTIXFILE` as an environment variable when running the executable program does change the output path of the `.tix` file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 09:36:39 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 09:36:39 -0000 Subject: [GHC] #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() In-Reply-To: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> References: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> Message-ID: <060.9714b41467b884970fc62909a9e8fd4c@haskell.org> #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() -------------------------------------+------------------------------------- Reporter: enolan | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * differential: => Phab:D2170 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 09:36:57 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 09:36:57 -0000 Subject: [GHC] #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() In-Reply-To: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> References: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> Message-ID: <060.1b3dbe24363f2474f7bd4bebe1a37dd1@haskell.org> #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() -------------------------------------+------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: => enolan -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 09:38:01 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 09:38:01 -0000 Subject: [GHC] #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() In-Reply-To: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> References: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> Message-ID: <060.ec9fde4eda88cc86bb3d844cb8625c92@haskell.org> #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() -------------------------------------+------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Phyx-): * owner: enolan => * status: patch => new * differential: Phab:D2170 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 09:38:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 09:38:18 -0000 Subject: [GHC] #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() In-Reply-To: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> References: <045.1d8b8b19fc3bbac40a93311c1ba3456a@haskell.org> Message-ID: <060.39596d2bca90e212c323d2a34327f452@haskell.org> #12012: Socket operations on Windows check errno instead of calling WSAGetLastError() -------------------------------------+------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: | Keywords: Operating System: Windows | 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-): Whoops, sorry, confused this with #12010 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 09:44:22 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 09:44:22 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.d3355d298a962a4034c034fa752b9f42@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Phyx-): Hi @enolan, Windows hasn't validated cleanly in a long while. We're working on getting it to, but for now it doesn't. The GHC 8.0.1 tests for `rts/T11223` should all pass, except if you tested for `x86` since there's a slight difference in the output. I'll have to change my sanitize function to account for it. in terms of head: ghci.debugger/scripts break011 - New output just needs to be accepted ghci/prog003 prog003 - Known segfault, there's a ticket for this already partial-sigs/should_compile PatBind [exit code non-0] (normal) plugins plugins01 [bad exit code] (normal) - These two I haven't looked into yet rts T7037 [bad stdout] (normal) - This is a sporadic failure due to Python and how the files are flushed. There's a diff to fix this but hasn't been committed yet/ rts T9405 [bad exit code] (normal) rts testmblockalloc [bad exit code] (normal) - These two might be new, don't remember them.. rts/T11223 T11223_simple_duplicate_lib [bad exit code] (normal) - This will be fixed soon, the test output was changed but the Windows test results not updated. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 10:28:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 10:28:37 -0000 Subject: [GHC] #8207: Pretty Printer for textual version of Language (name) in DynFlags In-Reply-To: <047.ff066453d0b5bb8959d2c8e8b4d65d05@haskell.org> References: <047.ff066453d0b5bb8959d2c8e8b4d65d05@haskell.org> Message-ID: <062.e2f1b3d4bfab488cecaae49b9f7f4982@haskell.org> #8207: Pretty Printer for textual version of Language (name) in DynFlags -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: seraphime Type: feature request | Status: new Priority: low | Milestone: Component: GHC API | Version: 7.7 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 seraphime): * owner: => seraphime -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 11:02:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 11:02:29 -0000 Subject: [GHC] #10547: feature request: expanding type synonyms in error messages In-Reply-To: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> References: <043.c20ed6dece31f72a0d7c2a22033dd48e@haskell.org> Message-ID: <058.3c3a87c40f526dba1aece6c25ec4a8b2@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature request | Status: new Priority: low | Milestone: 8.0.1 Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/ExpandSynsFail1,2,3,4 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1016, Wiki Page: | Phab:D2198 -------------------------------------+------------------------------------- Comment (by ?mer Sinan A?acan ): In [changeset:"e4834edf4418ace657361649365979e29ebd9daa/ghc" e4834ed/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e4834edf4418ace657361649365979e29ebd9daa" Fix a performance issue with -fprint-expanded-synonyms The type synonym expander was doing redundant work by looking at same types again and again. This patch fixes the loop code when both of the types can be expanded, to do `O(min(n, m))` comparisons and `O(n + m)` expansions, where `n` is expansions of the first type and `m` is expansions of the second type. Reported by sjcjoosten in T10547. Test Plan: Added a regression test that was taking several minutes to type check before this patch. Reviewers: bgamari, simonpj, austin, ezyang Reviewed By: bgamari, simonpj, austin, ezyang Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2198 GHC Trac Issues: #10547 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 13:26:49 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 13:26:49 -0000 Subject: [GHC] #4900: Consider usage files in the GHCi recompilation check In-Reply-To: <046.52f138a2609bf72d7f5381a2c64d358e@haskell.org> References: <046.52f138a2609bf72d7f5381a2c64d358e@haskell.org> Message-ID: <061.5d42517b0a7c743cb4aabc66d08a84a4@haskell.org> #4900: Consider usage files in the GHCi recompilation check -------------------------------------+------------------------------------- Reporter: cdsmith | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: TH_Depends Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by shahn): * cc: soenkehahn@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 13:31:38 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 13:31:38 -0000 Subject: [GHC] #12061: Allow duplicate record fields in pattern synonyms In-Reply-To: <051.ca1b3aaea806961ea5212ae77452a5a2@haskell.org> References: <051.ca1b3aaea806961ea5212ae77452a5a2@haskell.org> Message-ID: <066.d94f2f8d4b3dd8e26f1005d6831882b8@haskell.org> #12061: Allow duplicate record fields in pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: Resolution: duplicate | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11228 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate * related: => #11228 Comment: This has been discussed a bit on #11228. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 13:40:57 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 13:40:57 -0000 Subject: [GHC] #10355: Dynamic linker not initialised In-Reply-To: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> References: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> Message-ID: <061.6ae6b2c2bd68c351a17db45d4dedcc11@haskell.org> #10355: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: dpiponi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9868, #10919 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): I have this with 7.10.3. Thankfully I'm also using NixOS, so reproduction /should/ be easier. {{{ [nix-shell:~/src/corr]$ cabal clean && cabal build cleaning... Package has never been configured. Configuring with default flags. If this fails, please run configure manually. Warning: The package list for 'hackage.haskell.org' is 83.0 days old. Run 'cabal update' to get the latest list of available packages. Resolving dependencies... Configuring youtrack-tools-0.0.5... Building youtrack-tools-0.0.5... Preprocessing executable 'corr' for youtrack-tools-0.0.5... [1 of 8] Compiling Table ( Table.hs, dist/build/corr/corr- tmp/Table.o ) : ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): Dynamic linker not initialised Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug [2 of 8] Compiling Supplementary ( Supplementary.hs, dist/build/corr /corr-tmp/Supplementary.o ) : Failed to load interface for ?Types? There are files missing in the ?youtrack-0.0.5? package, try running 'ghc-pkg check'. Use -v to see a list of the files searched for. [3 of 8] Compiling Radio ( Radio.hs, dist/build/corr/corr- tmp/Radio.o ) : : can't load .so/.DLL for: /nix/store /l4m6gibfh45d6z9401j3p2rzrmj8zi4q- youtrack-0.0.5/lib/ghc-7.10.3/youtrack-0.0.5/libHSyoutrack-0.0.5-DFajfBx8BmuHqbhbeFC750-ghc7.10.3.so (/nix/store/l4m6gibfh45d6z9401j3p2rzrmj8zi4q- youtrack-0.0.5/lib/ghc-7.10.3/youtrack-0.0.5/libHSyoutrack-0.0.5-DFajfBx8BmuHqbhbeFC750-ghc7.10.3.so: undefined symbol: youtrzuDFajfBx8BmuHqbhbeFC750_Exchanges_requestzutype_info) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 13:45:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 13:45:29 -0000 Subject: [GHC] #10355: Dynamic linker not initialised In-Reply-To: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> References: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> Message-ID: <061.73630f35ed5780d5e938fa0417fc0732@haskell.org> #10355: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: dpiponi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9868, #10919 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): GHC 8.0.1-rc4 fails differently: {{{ <- [1 of 8] Compiling Table ( Table.hs, interpreted ) <- [2 of 8] Compiling Supplementary ( Supplementary.hs, interpreted ) <- Supplementary.hs:120:20-25: error: ? Can't find interface-file declaration for type constructor or class MLogin Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ? In the first argument of ?Default?, namely ?MLogin? In the instance declaration for ?Default MLogin? Supplementary.hs:121:20-25: error: ? Can't find interface-file declaration for type constructor or class MLogin Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ? In the first argument of ?Arbitrary?, namely ?MLogin? In the instance declaration for ?Arbitrary MLogin? Supplementary.hs:122:20-28: error: ? Can't find interface-file declaration for type constructor or class MFullName Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ? In the first argument of ?Default?, namely ?MFullName? In the instance declaration for ?Default MFullName? Supplementary.hs:123:20-28: error: ? Can't find interface-file declaration for type constructor or class MFullName Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ? In the first argument of ?Arbitrary?, namely ?MFullName? In the instance declaration for ?Arbitrary MFullName? Supplementary.hs:125:20-25: error: ? Can't find interface-file declaration for type constructor or class Member Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ? In the first argument of ?Default?, namely ?Member? In the instance declaration for ?Default Member? Supplementary.hs:126:20-25: error: ? Can't find interface-file declaration for type constructor or class Member Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ? In the first argument of ?Arbitrary?, namely ?Member? In the instance declaration for ?Arbitrary Member? Failed, modules loaded: Table. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 13:47:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 13:47:02 -0000 Subject: [GHC] #10355: Dynamic linker not initialised In-Reply-To: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> References: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> Message-ID: <061.34e72221a2bc15a1f5232f57238d7039@haskell.org> #10355: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: dpiponi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9868, #10919 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * cc: _deepfire@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 13:51:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 13:51:29 -0000 Subject: [GHC] #10355: Dynamic linker not initialised In-Reply-To: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> References: <046.b020405a0b5eb69acc1047433b42d151@haskell.org> Message-ID: <061.5e5dccff5a0d3c95827635dc7663ddab@haskell.org> #10355: Dynamic linker not initialised -------------------------------------+------------------------------------- Reporter: dpiponi | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9868, #10919 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): adamgundry: indeed, I can independently verify that 7.10.3 was healed by adding modules to the Cabal `exposed-modules`! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 16:08:39 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 16:08:39 -0000 Subject: [GHC] #12066: Symbol not found: _stg_ap_0_upd_info Message-ID: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> #12066: Symbol not found: _stg_ap_0_upd_info -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: MacOS X Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When compiling project for which `double-conversion` is a dependency: {{{ [ 1 of 12] Compiling Models.TH ( src/Models/TH.hs, dist/build/Models/TH.o ) : can't load .so/.DLL for: /nix/store /m8whp07czawywfis99bfqpjmfy3vj1bf-double-conversion-2.0.1.0/lib/ghc-8.0.1 /double-conversion-2.0.1.0/libHSdouble-conversion-2.0.1.0 -CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib (dlopen(/nix/store /m8whp07czawywfis99bfqpjmfy3vj1bf-double-conversion-2.0.1.0/lib/ghc-8.0.1 /double-conversion-2.0.1.0/libHSdouble-conversion-2.0.1.0 -CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib, 5): Symbol not found: _stg_ap_0_upd_info Referenced from: /nix/store/m8whp07czawywfis99bfqpjmfy3vj1bf-double- conversion-2.0.1.0/lib/ghc-8.0.1/double-conversion-2.0.1.0/libHSdouble- conversion-2.0.1.0-CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib Expected in: flat namespace in /nix/store/m8whp07czawywfis99bfqpjmfy3vj1bf-double- conversion-2.0.1.0/lib/ghc-8.0.1/double-conversion-2.0.1.0/libHSdouble- conversion-2.0.1.0-CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 16:08:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 16:08:59 -0000 Subject: [GHC] #12066: Symbol not found: _stg_ap_0_upd_info In-Reply-To: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> References: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> Message-ID: <062.02486be3b5a1bb2d9dd2cb4ae32dadff@haskell.org> #12066: Symbol not found: _stg_ap_0_upd_info -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by pikajude: @@ -1,1 +1,1 @@ - When compiling project for which `double-conversion` is a dependency: + When compiling a project for which `double-conversion` is a dependency: New description: When compiling a project for which `double-conversion` is a dependency: {{{ [ 1 of 12] Compiling Models.TH ( src/Models/TH.hs, dist/build/Models/TH.o ) : can't load .so/.DLL for: /nix/store /m8whp07czawywfis99bfqpjmfy3vj1bf-double-conversion-2.0.1.0/lib/ghc-8.0.1 /double-conversion-2.0.1.0/libHSdouble-conversion-2.0.1.0 -CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib (dlopen(/nix/store /m8whp07czawywfis99bfqpjmfy3vj1bf-double-conversion-2.0.1.0/lib/ghc-8.0.1 /double-conversion-2.0.1.0/libHSdouble-conversion-2.0.1.0 -CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib, 5): Symbol not found: _stg_ap_0_upd_info Referenced from: /nix/store/m8whp07czawywfis99bfqpjmfy3vj1bf-double- conversion-2.0.1.0/lib/ghc-8.0.1/double-conversion-2.0.1.0/libHSdouble- conversion-2.0.1.0-CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib Expected in: flat namespace in /nix/store/m8whp07czawywfis99bfqpjmfy3vj1bf-double- conversion-2.0.1.0/lib/ghc-8.0.1/double-conversion-2.0.1.0/libHSdouble- conversion-2.0.1.0-CatAMVNq05S8lUOKX28ozh-ghc8.0.1.dylib) }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 18:45:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 18:45:46 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.1453bf3dc5638f2a09efcffe37a6f22b@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by avd): @bgamari, @thomie, I would like to work on this ticket. I reproduced it and already have a patch, need to submit it to Phabricator. Can you make me an owner (as https://ghc.haskell.org/trac/ghc/wiki/Phabricator requires) or should I do this by myself? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 18:54:41 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 18:54:41 -0000 Subject: [GHC] #12067: warn-unused-imports does not detect coersions Message-ID: <047.e234196f4d28c1786926628389b4a6f1@haskell.org> #12067: warn-unused-imports does not detect coersions -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When using `coerce`, GHC can erroneously warn that imports are unnecessary. For example: Foo.hs {{{ module Foo (MT(..), M) where import Control.Monad.Identity newtype MT m b = MT (m b) type M b = MT Identity b }}} Main.hs {{{ import Control.Monad.Identity import Data.Coerce import Foo foo :: M [a] -> MT [] a foo = coerce }}} GHC (with `-fwarn-unused-imports`) warns {{{ Main.hs:1:1: Warning: The import of ?Control.Monad.Identity? is redundant except perhaps to import instances from ?Control.Monad.Identity? To import instances alone, use: import Control.Monad.Identity() }}} But this is incorrect: we need the constructor `Identity` to be in scope in order for the coercion to succeed. Thus the import is not redundant, nor is it needed to import instances. In particular, the two implied suggestions 1. remove the import altogether 2. change the import to `import Control.Monad.Identity` both (correctly) result in compile errors. At a minimum, the warning message should be updated to include this possibility, but it would be even better if GHC could detect this and not throw a warning at all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 20:00:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 20:00:58 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.d33ab6c90a739134ad5e2be90e03e35a@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by avd): * cc: avd (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 20:16:38 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 20:16:38 -0000 Subject: [GHC] #12068: RULE too complicated to desugar when using constraint synonyms Message-ID: <047.446f8f83cd16c15c289d2bf01aaa7058@haskell.org> #12068: RULE too complicated to desugar when using constraint synonyms -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With the following minimal-as-I-could-get-it example, {{{ {-# LANGUAGE ConstraintKinds #-} class Qux a class (Num r) => Class1 r class (Num r) => Class2 r newtype Foo q z = Foo z type Qux' q z = (Qux q, Integral z) instance (Num z) => Num (Foo q z) instance (Qux' q z, Num z) => Class1 (Foo q z) instance (Qux' q z, Num z) => Class2 (Foo q z) newtype Bar r = Bar r {-# SPECIALIZE bar :: (Qux q) => Bar (Foo q Int) -> Bar (Foo q Int) #-} bar :: (Class1 r, Class2 r) => Bar r -> Bar r bar = undefined }}} I get the warning: {{{ RULE left-hand side too complicated to desugar Optimised lhs: let { $dNum_aGE :: Num (Foo q Int) [LclId, Str=DmdType] $dNum_aGE = Main.$fNumFoo @ q @ Int GHC.Num.$fNumInt } in bar @ (Foo q Int) (Main.$fClass1Foo @ q @ Int $dNum_aGE ($dQux_aFH, $dIntegral_aGI) GHC.Num.$fNumInt) (Main.$fClass2Foo @ q @ Int $dNum_aGE ($dQux_aFH, $dIntegral_aGI) GHC.Num.$fNumInt) Orig lhs: let { $dIntegral_aGI :: Integral Int [LclId, Str=DmdType] $dIntegral_aGI = GHC.Real.$fIntegralInt } in let { tup_aGJ :: Qux' q Int [LclId, Str=DmdType] tup_aGJ = ($dQux_aFH, $dIntegral_aGI) } in let { $dNum_aGH :: Num Int [LclId, Str=DmdType] $dNum_aGH = GHC.Num.$fNumInt } in let { $dNum_aGG :: Num Int [LclId, Str=DmdType] $dNum_aGG = $dNum_aGH } in let { tup_aGF :: Qux' q Int [LclId, Str=DmdType] tup_aGF = ($dQux_aFH, $dIntegral_aGI) } in let { $dNum_aGE :: Num (Foo q Int) [LclId, Str=DmdType] $dNum_aGE = Main.$fNumFoo @ q @ Int $dNum_aGH } in let { $dClass2_aFK :: Class2 (Foo q Int) [LclId, Str=DmdType] $dClass2_aFK = Main.$fClass2Foo @ q @ Int $dNum_aGE tup_aGJ $dNum_aGH } in let { $dClass1_aFJ :: Class1 (Foo q Int) [LclId, Str=DmdType] $dClass1_aFJ = Main.$fClass1Foo @ q @ Int $dNum_aGE tup_aGF $dNum_aGG } in bar @ (Foo q Int) $dClass1_aFJ $dClass2_aFK }}} This is apparently due to my use of a constraint synonym. In this code it would be quite simple to just replace the synonym with the constraints on its RHS, but in my real code my constraint synonym is an associated type, so that is not an option. It would be great o be able to specialize in the presence of constraint synonyms. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 23:01:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 23:01:05 -0000 Subject: [GHC] #12064: tcIfaceGlobal error with existentially quantified types In-Reply-To: <045.3f2e9cf37ca8869e1da5dbbed8082702@haskell.org> References: <045.3f2e9cf37ca8869e1da5dbbed8082702@haskell.org> Message-ID: <060.d22f19794750a6f9630ebcf245de7ecb@haskell.org> #12064: tcIfaceGlobal error with existentially quantified types -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: hs-boot 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 ezyang): * owner: => ezyang -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 23:03:07 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 23:03:07 -0000 Subject: [GHC] #12064: tcIfaceGlobal error with existentially quantified types In-Reply-To: <045.3f2e9cf37ca8869e1da5dbbed8082702@haskell.org> References: <045.3f2e9cf37ca8869e1da5dbbed8082702@haskell.org> Message-ID: <060.c7365369b7cc31fbd4546e1f1c83a5f9@haskell.org> #12064: tcIfaceGlobal error with existentially quantified types -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: hs-boot 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 ezyang: @@ -17,1 +17,1 @@ - import A + import B New description: Consider the following program: {{{ -- A.hs-boot module A where data D -- B.hs module B where import {-# SOURCE #-} A class K a where method :: D -> a -- A.hs {-# LANGUAGE ExistentialQuantification #-} module A where import B data D = forall n. K n => D }}} We get a `tcIfaceGlobal` error in this case (one-shot of course.) I reduced this case out of prog006. So for some reason we're tugging on `K` too early?that's as far as I know at this point. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 23:25:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 23:25:26 -0000 Subject: [GHC] #12063: Knot-tying failure when type-synonym refers to non-existent data In-Reply-To: <045.5d0eb098fb5e4585a85062e98ec9f2c1@haskell.org> References: <045.5d0eb098fb5e4585a85062e98ec9f2c1@haskell.org> Message-ID: <060.bb233489e1b1955795f724eb20e5479a@haskell.org> #12063: Knot-tying failure when type-synonym refers to non-existent data -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: hs-boot 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 ezyang: @@ -17,0 +17,1 @@ + x = undefined New description: Consider: {{{ -- A.hs-boot module A data T -- B.hs module B import {-# SOURCE #-} A type S = T -- A.hs module A import B x :: S x = undefined }}} This will cause a tcIfaceGlobal panic when compiling `A.hs` in one-shot mode. The reason is that we will attempt to knot tie `B.hi`'s reference to `A:T` when typechecking the contents of `A.hs`, but unfortunately there is no declaration of `T` in the real `A.hs`, so the knot tying will fail. It's not entirely clear to me how to deal with this problem. The obvious thing to do is to fault in the `TyThing` from the ModDetails of the hs- boot file (great care must be taken because we don't actually want to load the hs-boot file!) We'll then fail in due course when we check if we actually implement everything the hs-boot file needs. But this could complicate things: 1. This "robustness" could mask another, much more difficult to diagnose bug when there was an actual knot-tying failure. Then, we will silently fail to tie the knot, and then if something bad happens it is a lot less obvious what went wrong. However! I think there is an ASSERT we can add in this case: when we add things to the type environment (and update the knot tying variable), we can check if we have faulted in the relevant entity from the hs-boot file. If we have, then we know there is knot-tying failure and we should fail. 2. Having two sets of `TyThing`s for the same `Name` could lead to hard to diagnose errors; e.g., you are comparing `S` for equality with `S`, but they return not equal because one of these is a type synonym tycon and the other is an abstract tycon. There might be some adjustments to the debug printing mechanism to make such situations more obvious. Here is another way to fix the bug: check if all the types declared in the hs-boot file are actually defined before doing any typechecking proper. Interestingly, this is a possible solution for #12034: the implication is that all types mentioned in the hs-boot file must be defined PRIOR to the first splice. If we look at #1012, this would not be a burden for users that use TH and hs-boot. Also, it nicely fits with a solution for #12042, since we need to check for type synonym loops at some point BEFORE typechecking, and this is the obvious place to do so. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 15 23:51:52 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 15 May 2016 23:51:52 -0000 Subject: [GHC] #11953: Export Word32#, Word64# on all architectures In-Reply-To: <046.593317f13858c2d1c5dc11a464cab3d1@haskell.org> References: <046.593317f13858c2d1c5dc11a464cab3d1@haskell.org> Message-ID: <061.15d454d49d51fede6c9477c6319b1ba5@haskell.org> #11953: Export Word32#, Word64# on all architectures -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carter): Would also perhaps be worth considering adding a WordNative# and associated lifted sibling that is explicitly guaranteed to match native pointer / max addressable virtual memory? For ghc that would always been one of Word32 or Word64 sized, whichever is currently also called Word, but that's only a result of ghc specific rts and compilation strategy choices rather than being part of the language standard. A large number of current libraries make that assumption in their data structure rep and it's not guaranteed to be true at all by any specification currently. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 02:29:30 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 02:29:30 -0000 Subject: [GHC] #11228: Interaction between ORF and record pattern synonyms needs to be resolved. In-Reply-To: <049.5473d22bfd3f33e57adb2d754a0b62d6@haskell.org> References: <049.5473d22bfd3f33e57adb2d754a0b62d6@haskell.org> Message-ID: <064.8c6b80308a877b239711773174bfb010@haskell.org> #11228: Interaction between ORF and record pattern synonyms needs to be resolved. -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: | PatternSynonyms, orf Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9975, #11283 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 03:35:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 03:35:17 -0000 Subject: [GHC] #12013: CallStack is available from base 4.8, not 4.9 In-Reply-To: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> References: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> Message-ID: <059.cf7ea26193f857f1febb65cf91d94961@haskell.org> #12013: CallStack is available from base 4.8, not 4.9 -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by edsko): Hmmm, fair enough. So it's just a documentation bug for 7.10 then (https://hackage.haskell.org/package/base-4.8.2.0/docs/GHC-Stack.html). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 08:30:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 08:30:42 -0000 Subject: [GHC] #12069: Possible type inference regression: "Expected a type, but 'a' has kind 'k0'" Message-ID: <043.d7df993a4f813fd6136f7a76d98de437@haskell.org> #12069: Possible type inference regression: "Expected a type, but 'a' has kind 'k0'" -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program causes GHC HEAD to give an error: {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} module Foo where foo (_ :: p a) = [] :: [a] }}} {{{ [1 of 1] Compiling Foo ( kind.hs, kind.o ) kind.hs:4:25: error: ? Expected a type, but ?a? has kind ?k0? ? In an expression type signature: [a] In the expression: [] :: [a] In an equation for ?foo?: foo (_ :: p a) = [] :: [a] }}} GHC 7.10.1 compiles it fine, and infers the type `foo :: p a -> [a]`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 08:53:32 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 08:53:32 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.ef95d30ca8fd1ebb35ac08fd5ef8333b@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Changes (by bgamari): * owner: erikd => * status: patch => new -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 08:58:30 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 08:58:30 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) Message-ID: <042.6005740c057129846795abd119cdb8ea@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+------------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime | Version: 8.0.1-rc4 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 originally noticed this when working on the AIX port (32-bit powerpc), and recently saw this also on Linux/powerpc64, which lead to talking to Peter Trommler who already had a suspicion: Here's for example the CAS definition (in ``): {{{#!c StgWord cas(StgVolatilePtr p, StgWord o, StgWord n) { StgWord result; __asm__ __volatile__ ( "1: ldarx %0, 0, %3\n" " cmpd %0, %1\n" " bne 2f\n" " stdcx. %2, 0, %3\n" " bne- 1b\n" "2:" :"=&r" (result) :"r" (o), "r" (n), "r" (p) :"cc", "memory" ); return result; }}} The important detail is the lack any barrier instructions, such as `isync` at the end. This results in infrequent heap-corruptions which in turn result in all sorts of infrequent and hard to track down runtime-crashes (including in `ghc -j`). Peter has already a patch in the works which simply replaces the atomic powerpc primitives with `__sync_*` intrinsics which turn out to be more portable than inline-asm. I've been testing the patch already and it seems to have made all issues I experienced so far disappear, as well as fixing the `concprog01` test which was also failing infrequently. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 08:58:41 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 08:58:41 -0000 Subject: [GHC] #12071: PowerPC: RTS SMP functions lack memory barriers Message-ID: <047.016b7cc20d1f4625b4de951cadfd60f1@haskell.org> #12071: PowerPC: RTS SMP functions lack memory barriers -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Runtime | Version: 8.0.1 System | Keywords: PowerPC SMP | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime crash Unknown/Multiple | Test Case: | Blocked By: concurrent/prog001/concprog001 | Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- @hvr reported on POWER7 big endian (powerpc64) and on AIX (powerpc): {{{ internal error: END_TSO_QUEUE object entered! (GHC version 8.0.0.20160421 for powerpc64_unknown_linux) }}} Also `concprog001` segfaults, which I falsely attributed to #11259 (no runtime linker support) when I marked the test broken on powerpc64. I propose to use gcc and clang `_sync_*` built-ins that are already used in `libraries/ghc-prim/cbits/atomic.c` instead of CPP ifdefs and inline assembly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 09:00:52 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 09:00:52 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.237d3e1d8b71a56c3b87f85a8737466c@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+--------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+--------------------------------- Changes (by hvr): * architecture: Unknown/Multiple => powerpc -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 09:03:05 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 09:03:05 -0000 Subject: [GHC] #12071: PowerPC: RTS SMP functions lack memory barriers In-Reply-To: <047.016b7cc20d1f4625b4de951cadfd60f1@haskell.org> References: <047.016b7cc20d1f4625b4de951cadfd60f1@haskell.org> Message-ID: <062.82077e3f48286f88522ce5c0a2ec4392@haskell.org> #12071: PowerPC: RTS SMP functions lack memory barriers -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Runtime System | Version: 8.0.1 Resolution: duplicate | Keywords: PowerPC SMP Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: | concurrent/prog001/concprog001 Blocked By: | Blocking: Related Tickets: #12070 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by trommler): * status: new => closed * resolution: => duplicate * related: => #12070 Comment: @hvr was quicker :-) see #12070 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 09:08:52 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 09:08:52 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.d5f7073dc28012cc2444dc8c0a156ad3@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+--------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+--------------------------------- Description changed by hvr: @@ -24,0 +24,1 @@ + } @@ -29,1 +30,7 @@ - (including in `ghc -j`). + (including in `ghc --make -j`) such as for instance + + {{{ + internal error: END_TSO_QUEUE object entered! + (GHC version 8.0.0.20160421 for powerpc64_unknown_linux) + }}} + @@ -33,3 +40,30 @@ - portable than inline-asm. I've been testing the patch already and it seems - to have made all issues I experienced so far disappear, as well as fixing - the `concprog01` test which was also failing infrequently. + portable than inline-asm. This would result in e.g. + + + {{{#!c + StgWord + cas(StgVolatilePtr p, StgWord o, StgWord n) + { + return __sync_val_compare_and_swap (p, o, n); + } + }}} + + which then gets compiled as + + {{{#!asm + 000000000000004c <.cas>: + 4c: 7c 00 04 ac sync + 50: 7d 20 18 a8 ldarx r9,0,r3 + 54: 7c 29 20 00 cmpd r9,r4 + 58: 40 c2 00 0c bne- 64 <.cas+0x18> + 5c: 7c a0 19 ad stdcx. r5,0,r3 + 60: 40 c2 ff f0 bne- 50 <.cas+0x4> + 64: 4c 00 01 2c isync + 68: 7d 23 4b 78 mr r3,r9 + 6c: 4e 80 00 20 blr + }}} + + + I've been testing the patch already and it seems to have made all issues I + experienced so far disappear, as well as fixing the `concprog01` test + which was also failing infrequently. New description: I originally noticed this when working on the AIX port (32-bit powerpc), and recently saw this also on Linux/powerpc64, which lead to talking to Peter Trommler who already had a suspicion: Here's for example the CAS definition (in ``): {{{#!c StgWord cas(StgVolatilePtr p, StgWord o, StgWord n) { StgWord result; __asm__ __volatile__ ( "1: ldarx %0, 0, %3\n" " cmpd %0, %1\n" " bne 2f\n" " stdcx. %2, 0, %3\n" " bne- 1b\n" "2:" :"=&r" (result) :"r" (o), "r" (n), "r" (p) :"cc", "memory" ); return result; } }}} The important detail is the lack any barrier instructions, such as `isync` at the end. This results in infrequent heap-corruptions which in turn result in all sorts of infrequent and hard to track down runtime-crashes (including in `ghc --make -j`) such as for instance {{{ internal error: END_TSO_QUEUE object entered! (GHC version 8.0.0.20160421 for powerpc64_unknown_linux) }}} Peter has already a patch in the works which simply replaces the atomic powerpc primitives with `__sync_*` intrinsics which turn out to be more portable than inline-asm. This would result in e.g. {{{#!c StgWord cas(StgVolatilePtr p, StgWord o, StgWord n) { return __sync_val_compare_and_swap (p, o, n); } }}} which then gets compiled as {{{#!asm 000000000000004c <.cas>: 4c: 7c 00 04 ac sync 50: 7d 20 18 a8 ldarx r9,0,r3 54: 7c 29 20 00 cmpd r9,r4 58: 40 c2 00 0c bne- 64 <.cas+0x18> 5c: 7c a0 19 ad stdcx. r5,0,r3 60: 40 c2 ff f0 bne- 50 <.cas+0x4> 64: 4c 00 01 2c isync 68: 7d 23 4b 78 mr r3,r9 6c: 4e 80 00 20 blr }}} I've been testing the patch already and it seems to have made all issues I experienced so far disappear, as well as fixing the `concprog01` test which was also failing infrequently. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 09:18:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 09:18:42 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.eec59e2da6aa75691e94e6c09da91b2f@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+--------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+--------------------------------- Changes (by erikd): * cc: erikd (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 09:22:39 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 09:22:39 -0000 Subject: [GHC] #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV In-Reply-To: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> References: <045.e7ec8175631a08659d1526a914fb3334@haskell.org> Message-ID: <060.5859d68b9b8303a40145514c977de540@haskell.org> #11978: running a profiled build of shake test suite with rts args +RTS -hb -N10 triggers SIGSEGV ---------------------------------+---------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4820 | Differential Rev(s): Phab:D2174 Wiki Page: | ---------------------------------+---------------------------------------- Comment (by erikd): I have some tests I'd like to add for this after phab:D1187 lands. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 09:24:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 09:24:14 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.4353f2f18023d0f7b77e86eb5ff17a36@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+------------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: | concurrent/prog001/concprog001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by trommler): * testcase: => concurrent/prog001/concprog001 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 10:52:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 10:52:40 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.aae53cbffb4997f049d7a1572147bf1e@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nomeata): You are very welcome to make yourself the owner of the ticket, using the ?assign to? feature below. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 11:40:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 11:40:16 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.7b7492fb99a9ca564d07012dff2f53ce@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+------------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: | concurrent/prog001/concprog001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2225 Wiki Page: | -------------------------------------+------------------------------------- Changes (by trommler): * status: new => patch * differential: => Phab:D2225 Comment: Validated on powerpc64 and AMD64. Please, someone check that it does not break on ARM. The description for the built_in used in `xchg` suggests that the value stored in memory is implementation dependent. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 11:42:04 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 11:42:04 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.927e05c88e111508e51a5a65657473f5@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by avd): * owner: => avd -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 12:09:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 12:09:58 -0000 Subject: [GHC] #12004: Windows unexpected failures In-Reply-To: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> References: <045.5ea81afe7a35bbc5a069ce4325c9151d@haskell.org> Message-ID: <060.1c7f9f55a9e5e1bd8c3646a4ceff0cc9@haskell.org> #12004: Windows unexpected failures ---------------------------------+---------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by simonpj): The failures on my Windows laptop, with HEAD, as of a couple of days ago, were: {{{ ghci.debugger/scripts break011 [bad stdout] (ghci) ghci/scripts T5975a [bad stderr] (ghci) rts T9405 [bad exit code] (normal) rts/T11223 T11223_simple_duplicate_lib [bad stderr] (normal) }}} Those have been failing for ages. But these three are new {{{ ghci.debugger/scripts break006 [bad stderr] (ghci) th T8761 [stderr mismatch] (normal) typecheck/should_fail T5095 [stderr mismatch] (normal) }}} Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 12:12:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 12:12:23 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.d97a7888c86498bad2d31aeb245cd1f9@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2226 Wiki Page: | -------------------------------------+------------------------------------- Changes (by avd): * differential: => Phab:D2226 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 12:53:55 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 12:53:55 -0000 Subject: [GHC] #12072: GHC panic on type wildcard in left-hand side of data family Message-ID: <047.e584aa3b910eba55b26f4ea236a6c9a5@haskell.org> #12072: GHC panic on type wildcard in left-hand side of data family -------------------------------------+------------------------------------- Reporter: andreash | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- While playing around with data families I received the following output by ghc/ghci: {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.10.3 for x86_64-unknown-linux): rnHsTyKi HsWildcardTy Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I had accidentally left a wildcard `_` on the left-hand side of a data instance definition. To reproduce enter the following code into a file and try to load that file into ghci, or try to compile it with ghc: {{{#!hs data family Bug x data instance Bug _ = Bug }}} The expected behavior would be a (non-panic) error message of some sort. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 13:29:28 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 13:29:28 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.30acdbe7ac020eeaf584fc826e06047a@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+---------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2214 Wiki Page: | ----------------------------------------+---------------------------------- Changes (by hvr): * priority: normal => highest * milestone: 8.0.2 => 8.0.1 Comment: I consider the patch safe & low-risk enough to include in 8.0.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 14:50:11 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 14:50:11 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.eb963809e246d272a1ec0e12edbfa26d@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+------------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: | concurrent/prog001/concprog001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2225 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"563a4857abcee4a6e43c68323274309c58f42aa0/ghc" 563a485/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="563a4857abcee4a6e43c68323274309c58f42aa0" PPC: Implement SMP primitives using gcc built-ins The SMP primitives were missing appropriate memory barriers (sync, isync instructions) on all PowerPCs. Use the built-ins _sync_* provided by gcc and clang. This reduces code size significantly. Remove broken mark for concprog001 on powerpc64. The referenced ticket number (11259) was wrong. Test Plan: validate on powerpc and ARM Reviewers: erikd, austin, simonmar, bgamari, hvr Reviewed By: bgamari, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2225 GHC Trac Issues: #12070 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 14:50:11 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 14:50:11 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.d923e8243c249a2a73e357dd03030a38@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+---------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: patch Priority: highest | Milestone: 8.0.1 Component: Compiler (CodeGen) | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2214 Wiki Page: | ----------------------------------------+---------------------------------- Comment (by Ben Gamari ): In [changeset:"2dbdc79bb9e2760394ebfe630908813b630146c7/ghc" 2dbdc79b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2dbdc79bb9e2760394ebfe630908813b630146c7" PPC NCG: Fix pretty printing of st[wd]ux instr. Printing STU was mixed up. The tab character must appear after the 'x'. Test Plan: validate on powerpc Reviewers: bgamari, austin, erikd Reviewed By: austin, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2214 GHC Trac Issues: #12054 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 15:18:00 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 15:18:00 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.76ce2c5004dc4fa45553ce828f128122@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"21fe4ffd049c8ab4b9ee36af3cf8f70b46d6beda/ghc" 21fe4ff/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="21fe4ffd049c8ab4b9ee36af3cf8f70b46d6beda" Kill varSetElems in tcInferPatSynDecl varSetElems introduces unnecessary non-determinism and while I didn't estabilish experimentally that this matters here I'm convinced that it will, because I expect pattern synonyms to end up in interface files. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, mpickering, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2206 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 15:32:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 15:32:22 -0000 Subject: [GHC] #12073: Missing instance of MonadFix for Q Message-ID: <046.40bbc19dbb6e691647fd4beba8f8097c@haskell.org> #12073: Missing instance of MonadFix for Q -------------------------------------+------------------------------------- Reporter: jophish | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Template | Version: 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: -------------------------------------+------------------------------------- `Q` is capable of being an instance of `MonadFix`. The definition of `mfix` is the same as `fixIO` except that the `MVar` handling is wrapped in `runIO`. {{{#!hs instance MonadFix Q where mfix k = do m <- runIO newEmptyMVar ans <- runIO (unsafeInterleaveIO (takeMVar m)) result <- k ans runIO (putMVar m result) pure result }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:40:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:40:14 -0000 Subject: [GHC] #10333: hs-boot modification doesn't induce recompilation In-Reply-To: <045.b2a6545e2380bf06a403c64b9db0df81@haskell.org> References: <045.b2a6545e2380bf06a403c64b9db0df81@haskell.org> Message-ID: <060.99ac7c09a55fbac8128b4db2f93639ea@haskell.org> #10333: hs-boot modification doesn't induce recompilation -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:40:33 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:40:33 -0000 Subject: [GHC] #7672: boot file entities are sometimes invisible and are not (semantically) unified with corresponding entities in implementing module In-Reply-To: <046.ebf20f155e05760df4b4c62188044473@haskell.org> References: <046.ebf20f155e05760df4b4c62188044473@haskell.org> Message-ID: <061.9877546ac030b391e203da5e6ad124a7@haskell.org> #7672: boot file entities are sometimes invisible and are not (semantically) unified with corresponding entities in implementing module -------------------------------------+------------------------------------- Reporter: skilpat | Owner: ezyang Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler (Type | Version: 7.4.2 checker) | Keywords: backpack, hs- Resolution: fixed | boot Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: GHC rejects | Test Case: valid program | rename/should_compile/T7672 Blocked By: | Blocking: 10336 Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: backpack => backpack, hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:41:20 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:41:20 -0000 Subject: [GHC] #8441: Allow family instances in an hs-boot file In-Reply-To: <047.1fa915ff10b87e82918754b9e5d340d2@haskell.org> References: <047.1fa915ff10b87e82918754b9e5d340d2@haskell.org> Message-ID: <062.dc4e542598dff70c45b479d407843ad2@haskell.org> #8441: Allow family instances in an hs-boot file -------------------------------------+------------------------------------- Reporter: goldfire | Owner: ezyang Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: backpack, | TypeFamilies, hs-boot 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: backpack, TypeFamilies => backpack, TypeFamilies, hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:41:55 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:41:55 -0000 Subject: [GHC] #9450: GHC instantiates Data instances before checking hs-boot files In-Reply-To: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> References: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> Message-ID: <059.91c02107b7a79eae6c89e834cbfe56b0@haskell.org> #9450: GHC instantiates Data instances before checking hs-boot files -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Keywords: hs- Resolution: | boot,deriving Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: boot,deriving => hs-boot,deriving -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:42:39 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:42:39 -0000 Subject: [GHC] #9450: GHC instantiates Data instances before checking hs-boot files In-Reply-To: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> References: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> Message-ID: <059.c64a96a93636205ca9a95326d21556ad@haskell.org> #9450: GHC instantiates Data instances before checking hs-boot files -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Keywords: hs-boot, Resolution: | deriving Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: hs-boot,deriving => hs-boot, deriving -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:45:03 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:45:03 -0000 Subject: [GHC] #9450: GHC instantiates Data instances before checking hs-boot files In-Reply-To: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> References: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> Message-ID: <059.fcd326d5a2eb37c39e71ca027f235e65@haskell.org> #9450: GHC instantiates Data instances before checking hs-boot files -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Keywords: hs-boot Resolution: | deriving Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: hs-boot, deriving => hs-boot deriving -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:47:25 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:47:25 -0000 Subject: [GHC] #9450: GHC instantiates Data instances before checking hs-boot files In-Reply-To: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> References: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> Message-ID: <059.29dcaa4474e7c052832f56e9e41c72e4@haskell.org> #9450: GHC instantiates Data instances before checking hs-boot files -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Resolution: | Keywords: hs-boot Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: hs-boot deriving => hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:47:50 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:47:50 -0000 Subject: [GHC] #9450: GHC instantiates Data instances before checking hs-boot files In-Reply-To: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> References: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> Message-ID: <059.5ec6dac6f9e6cd658f5f13f686c1f53c@haskell.org> #9450: GHC instantiates Data instances before checking hs-boot files -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Keywords: deriving hs- Resolution: | boot Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: hs-boot => deriving hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 16:48:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 16:48:08 -0000 Subject: [GHC] #9450: GHC instantiates Data instances before checking hs-boot files In-Reply-To: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> References: <044.e97ab0330439b82d1df8c46c46f1a39d@haskell.org> Message-ID: <059.5564e31c94e4b67dbf3edf35f9a1f0e9@haskell.org> #9450: GHC instantiates Data instances before checking hs-boot files -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Keywords: deriving, hs- Resolution: | boot Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: deriving hs-boot => deriving, hs-boot -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 17:01:55 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 17:01:55 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.bee6f5528c964b7d78d6dc6f28446f7e@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+---------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (CodeGen) | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2214 Wiki Page: | ----------------------------------------+---------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as 87a3ea5612b0b9a174131a9a0bf9287c0820e8db. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 17:01:55 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 17:01:55 -0000 Subject: [GHC] #12070: SMP primitives broken on power(pc) In-Reply-To: <042.6005740c057129846795abd119cdb8ea@haskell.org> References: <042.6005740c057129846795abd119cdb8ea@haskell.org> Message-ID: <057.e361be760169f2309477b1ebace7f6cc@haskell.org> #12070: SMP primitives broken on power(pc) -------------------------------------+------------------------------------- Reporter: hvr | Owner: trommler Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Runtime System | Version: 8.0.1-rc4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: None/Unknown | Test Case: | concurrent/prog001/concprog001 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2225 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged to `ghc-8.0` as f4e6b32831bd718a040b382865ac7aea1254bf4e. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 17:17:05 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 17:17:05 -0000 Subject: [GHC] #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) In-Reply-To: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> References: <044.964f395db837bc5476c78bdf60ac31bf@haskell.org> Message-ID: <059.1e393330895121203426535edb25cea2@haskell.org> #12028: Large let bindings are 6x slower (since 6.12.x to 7.10.x) -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tommd): On 8.0 rc2: {{{ $ time ghc -O2 -fforce-recomp regression-md5.hs [1 of 1] Compiling Data.Digest.Pure.MD5 ( regression-md5.hs, regression- md5.o ) real 0m1.497s user 0m1.460s sys 0m0.028s }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 17:20:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 17:20:08 -0000 Subject: [GHC] #12032: Performance regression with large numbers of equation-style decls In-Reply-To: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> References: <044.eaba811a9985de0a6f5f10ce09f2ca2c@haskell.org> Message-ID: <059.9c43465405c80d9de41b96ae2814ca50@haskell.org> #12032: Performance regression with large numbers of equation-style decls -------------------------------------+------------------------------------- Reporter: tommd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tommd): Things have improves since 7.10.x but are still behind 6.12.x: {{{ vagrant at debian-jessie:~$ time ghc-6.12.3 -O2 -c -fforce-recomp regression- cpoly.hs real 0m0.069s user 0m0.056s sys 0m0.004s vagrant at debian-jessie:~$ time ghc-7.10.3 -O2 -c -fforce-recomp regression- cpoly.hs real 0m0.498s user 0m0.160s sys 0m0.064s vagrant at debian-jessie:~$ time ghc-8.0.0.20160204 -O2 -c -fforce-recomp regression-cpoly.hs real 0m0.225s user 0m0.196s sys 0m0.028s }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 18:33:34 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 18:33:34 -0000 Subject: [GHC] #11783: Very large slowdown when using parallel garbage collector In-Reply-To: <048.dfe418c8e00a9964b98ea3634140ac6c@haskell.org> References: <048.dfe418c8e00a9964b98ea3634140ac6c@haskell.org> Message-ID: <063.66b52302cd37f66b0048862eee022190@haskell.org> #11783: Very large slowdown when using parallel garbage collector -------------------------------------+------------------------------------- Reporter: luispedro | Owner: simonmar Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.3 Resolution: fixed | Keywords: performance, | garbage collector Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: 8.0.2 => 8.0.1 Comment: Merged to `ghc-8.0` as 9649973c8038591a2c9f77e1183dd920b724daa5. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 18:50:36 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 18:50:36 -0000 Subject: [GHC] #12074: RULE too complicated to desugar Message-ID: <047.97cdb8352868f06b8c197021d0e4e975@haskell.org> #12074: RULE too complicated to desugar -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Another example of specialization failing. Unlike #12068, this example doesn't use constraint/type synonyms. {{{ {-# LANGUAGE FlexibleContexts #-} data Bar a instance (Num a) => Num (Bar a) data Foo q instance (C1 q) => Num (Foo q) class C1 a class (Num r, Num (Bar r)) => C2 r instance (C1 q) => C2 (Foo q) instance (C2 r) => C2 (Bar r) {-# SPECIALIZE f :: (C1 q) => Foo q -> Foo q #-} f :: (C2 r, C2 (Bar r)) => r -> r f = undefined }}} Warning: {{{ RULE left-hand side too complicated to desugar Optimised lhs: let { $dNum_aFp :: Num (Foo q) [LclId, Str=DmdType] $dNum_aFp = Main.$fNumFoo @ q $dC1_aEj } in let { $dNum_aFq :: Num (Bar (Foo q)) [LclId, Str=DmdType] $dNum_aFq = Main.$fNumBar @ (Foo q) $dNum_aFp } in f @ (Foo q) $dC2_aEl (Main.$fC2Bar @ (Foo q) $dNum_aFq (Main.$fNumBar @ (Bar (Foo q)) $dNum_aFq) $dC2_aEl) Orig lhs: let { $dNum_aFp :: Num (Foo q) [LclId, Str=DmdType] $dNum_aFp = Main.$fNumFoo @ q $dC1_aEj } in let { $dNum_aFq :: Num (Bar (Foo q)) [LclId, Str=DmdType] $dNum_aFq = Main.$fNumBar @ (Foo q) $dNum_aFp } in let { $dNum_aFr :: Num (Bar (Bar (Foo q))) [LclId, Str=DmdType] $dNum_aFr = Main.$fNumBar @ (Bar (Foo q)) $dNum_aFq } in let { $dC2_aEl :: C2 (Foo q) [LclId, Str=DmdType] $dC2_aEl = Main.$fC2Foo @ q $dNum_aFp $dNum_aFq $dC1_aEj } in let { $dC2_aEm :: C2 (Bar (Foo q)) [LclId, Str=DmdType] $dC2_aEm = Main.$fC2Bar @ (Foo q) $dNum_aFq $dNum_aFr $dC2_aEl } in f @ (Foo q) $dC2_aEl $dC2_aEm }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 20:29:14 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 20:29:14 -0000 Subject: [GHC] #12074: RULE too complicated to desugar In-Reply-To: <047.97cdb8352868f06b8c197021d0e4e975@haskell.org> References: <047.97cdb8352868f06b8c197021d0e4e975@haskell.org> Message-ID: <062.163b20d7900828c08d0a0223f7fda07b@haskell.org> #12074: RULE too complicated to desugar -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): You are asking for something quite trikcy, and I'm not altogether surprised it fails. Let's step through it. You are asking that whenever GHC sees a call {{{ ...(f @(Foo ty) d1 d2)... }}} where `d1 :: C2 (Foo ty)` and `d2 :: C2 (Bar (Foo ty))`, you want it to be replace with a call to the specialised function {{{ ...($sf @ty d3)... }}} where `$sf :: (C1 q) => Foo q -> Foo q` and `d3 :: C2 ty`. The binding for `$sf` is no problem. The problem is: what rewrite rule can rewrite the call to `f` into the call for `$sf`. In particular, where does the rewrite rule get hold of a dictionary for `d3`? The only thing we can do is to unpick the dictionary applications on the LHS. For example, simplifying the signature for `f` to {{{ f :: C2 (Bar r) => r -> r }}} with HEAD we get the specialisation rule {{{ "SPEC f" [ALWAYS] forall (@ q_a1Im) ($dC1_a1In :: C1 q_a1Im). f @ (Foo q_a1Im) (T12074.$fC2Bar @ (Foo q_a1Im) (T12074.$fC2Foo @ q_a1Im $dC1_a1In)) = T12074.f_$sf @ q_a1Im $dC1_a1In }}} Notice the rather deeply-nested form of the LHS, which makes it hard ot match. But we need all that nesting to extract `$dC1_a1In` which is what's needed on the RHS (`d3` in the above). Now in the actual example you give, even HEAD fails with {{{ RULE left-hand side too complicated to desugar Optimised lhs: let { $dC2_a1HS :: C2 (Foo q) [LclId] $dC2_a1HS = T12074.$fC2Foo @ q $dC1_a1HQ } in f @ (Foo q) $dC2_a1HS (T12074.$fC2Bar @ (Foo q) $dC2_a1HS) }}} That `let` is defeating it! We could perhaps inline the `let` to get an LHS like {{{ f @ (Foo q) (T12074.$fC2Foo @ q $dC1_a1HQ) (T12074.$fC2Bar @ (Foo q) (T12074.$fC2Foo @ q $dC1_a1HQ)) }}} But we only need to bind `$dC1_a1H1` (needed on the RHS) once. So we could make do with the simpler LHS {{{ f @ (Foo q) (T12074.$fC2Foo @ q $dC1_a1HQ) _ }}} where `_` is just a wildcard match. That's be a better outcome. But it's not obvious how to achieve it. We want to pick just one of the several occurrences of `$dC1_a1HQ`, turn the rest into wildcards. There's an interesting graph algorithm in here, a kind of minimum-cover algorithm. But someone else will have to work on it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 20:33:32 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 20:33:32 -0000 Subject: [GHC] #12068: RULE too complicated to desugar when using constraint synonyms In-Reply-To: <047.446f8f83cd16c15c289d2bf01aaa7058@haskell.org> References: <047.446f8f83cd16c15c289d2bf01aaa7058@haskell.org> Message-ID: <062.529d6de1fd3ed66036407b0f39b576a8@haskell.org> #12068: RULE too complicated to desugar when using constraint synonyms -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): This is actually OK in HEAD. We get the RULE {{{ "SPEC bar" [ALWAYS] forall (@ q_a1SJ) ($dQux_a1SK :: Qux q_a1SJ) ($dIntegral_a1U3 :: Integral Int) ($dNum_a1U2 :: Num Int) ($dClass1_a1SM :: Class1 (Foo q_a1SJ Int)). bar @ (Foo q_a1SJ Int) $dClass1_a1SM (T12068.$fClass2Foo @ q_a1SJ @ Int ($dQux_a1SK, $dIntegral_a1U3) $dNum_a1U2) = T12068.bar_$sbar @ q_a1SJ $dQux_a1SK }}} (How likely that rule is to fire in practice isn't clear to me, but perhaps it will.) It works in HEAD because the "silent superclass" story, which adds extra parameters to dfuns, has gone away. c.ff #12074, which is defeated by a `let`. I'm not sure if it's worth adding a regression test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 20:47:21 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 20:47:21 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly Message-ID: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly --------------------------------+---------------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Linux Architecture: powerpc | Type of failure: Building GHC failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------+---------------------------------------- Hello! I'm currently bootstrapping GHC on powerpcspe (e500v2) which is a PowerPC architecture without an FPU but with signal processing extensions (hence SPE). When building GHC on this architecture, it detects the host architecture as powerpc-linux-gnuspe or short "powerpc" which works most of the time. However, GHC contains some inline assembly in rts/StgCRunAsm.s which uses FPU instructions not available on e500v2 CPUs resulting in assembler error, here with GHC 7.10.3: {{{ "inplace/bin/ghc-stage1" -optc-fno-stack-protector -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-Iincludes -optc-Iincludes/dist -optc-Iincludes/dist- derivedconstants/header -optc-Iincludes/dist-ghcconstants/header -optc- Irts -optc-Irts/dist/build -optc-DCOMPILING_RTS -optc- DUSE_LIBFFI_FOR_ADJUSTORS -optc-fno-strict-aliasing -optc-fno-common -optc-Irts/dist/build/autogen -optc-O2 -optc-fomit-frame-pointer -optc-g -optc-DRtsWay=\"rts_v\" -optc-w -static -H32m -O -lffi -optl-pthread -lffi -optl-pthread -Iincludes -Iincludes/dist -Iincludes/dist- derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-package-key rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/StgCRun.c -o rts/dist/build/StgCRun.o /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /tmp/ghcf20d_0/ghc_1.s: Assembler messages: /tmp/ghcf20d_0/ghc_1.s:24:0: Error: unrecognized opcode: `stfd' (...) /tmp/ghcf20d_0/ghc_1.s:67:0: Error: unrecognized opcode: `lfd' /tmp/ghcf20d_0/ghc_1.s:68:0: Error: unrecognized opcode: `lfd' /tmp/ghcf20d_0/ghc_1.s:69:0: Error: unrecognized opcode: `lfd' rts/ghc.mk:236: recipe for target 'rts/dist/build/StgCRun.o' failed make[3]: *** [rts/dist/build/StgCRun.o] Error 1 Makefile:71: recipe for target 'all' failed make[2]: *** [all] Error 2 make[2]: Leaving directory '/usr/src/ghc-7.10.3' dh_auto_build: make -j1 returned exit code 2 debian/rules:109: recipe for target 'override_dh_auto_build' failed make[1]: *** [override_dh_auto_build] Error 2 make[1]: Leaving directory '/usr/src/ghc-7.10.3' debian/rules:47: recipe for target 'binary-arch' failed make: *** [binary-arch] Error 2 (sid2-powerpcspe-sbuild)root at atlantis:/usr/src/ghc-7.10.3# }}} This can be verified by commenting out the assembly which will make the above compile command execute without any problems. Trying to continue compiling GHC will still fail with: {{{ "inplace/bin/ghc-stage1" -static -H32m -O -lffi -optl-pthread -lffi -optl-pthread -Iincludes -Iincludes/dist -Iincludes/dist- derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-package-key rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /tmp/ghcca51_0/ghc_3.s: Assembler messages: /tmp/ghcca51_0/ghc_3.s:525:0: Error: unrecognized opcode: `lfs' /tmp/ghcca51_0/ghc_3.s:538:0: Error: unrecognized opcode: `lfd' /tmp/ghcca51_0/ghc_3.s:592:0: Error: unrecognized opcode: `stfs' /tmp/ghcca51_0/ghc_3.s:604:0: Error: unrecognized opcode: `stfd' rts/ghc.mk:236: recipe for target 'rts/dist/build/HeapStackCheck.o' failed make[3]: *** [rts/dist/build/HeapStackCheck.o] Error 1 Makefile:71: recipe for target 'all' failed make[2]: *** [all] Error 2 make[2]: Leaving directory '/usr/src/ghc-7.10.3' dh_auto_build: make -j1 returned exit code 2 debian/rules:109: recipe for target 'override_dh_auto_build' failed make[1]: *** [override_dh_auto_build] Error 2 make[1]: Leaving directory '/usr/src/ghc-7.10.3' debian/rules:47: recipe for target 'binary-arch' failed make: *** [binary-arch] Error 2 (sid2-powerpcspe-sbuild)root at atlantis:/usr/src/ghc-7.10.3# }}} So, there is obviously more assembly code that needs to be disabled on powerpcspe. For that, I suggest testing whether the compiler sets __NO_FPRS__which is only set on powerpc hosts without FP registers: {{{ root at atlantis:~# echo | gcc -E -dM -|grep -i FP #define __NO_FPRS__ 1 root at atlantis:~# dpkg --print-architecture powerpcspe root at atlantis:~# uname -m ppc root at atlantis:~# }}} For reference, on a real powerpc host, the output is as follows: {{{ (sid_powerpc-dchroot)glaubitz at partch:~$ echo | gcc -E -dM -|grep -i FP #define __FP_FAST_FMAF 1 #define __FP_FAST_FMA 1 (sid_powerpc-dchroot)glaubitz at partch:~$ dpkg --print-architecture powerpc (sid_powerpc-dchroot)glaubitz at partch:~$ uname -m ppc (sid_powerpc-dchroot)glaubitz at partch:~$ }}} If you need any more input, please let me know. Adrian -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 20:51:07 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 20:51:07 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly In-Reply-To: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> References: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> Message-ID: <062.6157a577f78df31180a62b1005f2fa20@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly ----------------------------------------+------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+------------------------------- Description changed by glaubitz: @@ -126,0 +126,6 @@ + For reference, the list of supported instructions on e500(v2) CPUs can be + found here: + + http://www.nxp.com/files/32bit/doc/ref_manual/E500CORERM.pdf (page 3-66 or + 196) + New description: Hello! I'm currently bootstrapping GHC on powerpcspe (e500v2) which is a PowerPC architecture without an FPU but with signal processing extensions (hence SPE). When building GHC on this architecture, it detects the host architecture as powerpc-linux-gnuspe or short "powerpc" which works most of the time. However, GHC contains some inline assembly in rts/StgCRunAsm.s which uses FPU instructions not available on e500v2 CPUs resulting in assembler error, here with GHC 7.10.3: {{{ "inplace/bin/ghc-stage1" -optc-fno-stack-protector -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-Iincludes -optc-Iincludes/dist -optc-Iincludes/dist- derivedconstants/header -optc-Iincludes/dist-ghcconstants/header -optc- Irts -optc-Irts/dist/build -optc-DCOMPILING_RTS -optc- DUSE_LIBFFI_FOR_ADJUSTORS -optc-fno-strict-aliasing -optc-fno-common -optc-Irts/dist/build/autogen -optc-O2 -optc-fomit-frame-pointer -optc-g -optc-DRtsWay=\"rts_v\" -optc-w -static -H32m -O -lffi -optl-pthread -lffi -optl-pthread -Iincludes -Iincludes/dist -Iincludes/dist- derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-package-key rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/StgCRun.c -o rts/dist/build/StgCRun.o /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /tmp/ghcf20d_0/ghc_1.s: Assembler messages: /tmp/ghcf20d_0/ghc_1.s:24:0: Error: unrecognized opcode: `stfd' (...) /tmp/ghcf20d_0/ghc_1.s:67:0: Error: unrecognized opcode: `lfd' /tmp/ghcf20d_0/ghc_1.s:68:0: Error: unrecognized opcode: `lfd' /tmp/ghcf20d_0/ghc_1.s:69:0: Error: unrecognized opcode: `lfd' rts/ghc.mk:236: recipe for target 'rts/dist/build/StgCRun.o' failed make[3]: *** [rts/dist/build/StgCRun.o] Error 1 Makefile:71: recipe for target 'all' failed make[2]: *** [all] Error 2 make[2]: Leaving directory '/usr/src/ghc-7.10.3' dh_auto_build: make -j1 returned exit code 2 debian/rules:109: recipe for target 'override_dh_auto_build' failed make[1]: *** [override_dh_auto_build] Error 2 make[1]: Leaving directory '/usr/src/ghc-7.10.3' debian/rules:47: recipe for target 'binary-arch' failed make: *** [binary-arch] Error 2 (sid2-powerpcspe-sbuild)root at atlantis:/usr/src/ghc-7.10.3# }}} This can be verified by commenting out the assembly which will make the above compile command execute without any problems. Trying to continue compiling GHC will still fail with: {{{ "inplace/bin/ghc-stage1" -static -H32m -O -lffi -optl-pthread -lffi -optl-pthread -Iincludes -Iincludes/dist -Iincludes/dist- derivedconstants/header -Iincludes/dist-ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-package-key rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /bin/bash: warning: setlocale: LC_ALL: cannot change locale (en_US.UTF-8) /tmp/ghcca51_0/ghc_3.s: Assembler messages: /tmp/ghcca51_0/ghc_3.s:525:0: Error: unrecognized opcode: `lfs' /tmp/ghcca51_0/ghc_3.s:538:0: Error: unrecognized opcode: `lfd' /tmp/ghcca51_0/ghc_3.s:592:0: Error: unrecognized opcode: `stfs' /tmp/ghcca51_0/ghc_3.s:604:0: Error: unrecognized opcode: `stfd' rts/ghc.mk:236: recipe for target 'rts/dist/build/HeapStackCheck.o' failed make[3]: *** [rts/dist/build/HeapStackCheck.o] Error 1 Makefile:71: recipe for target 'all' failed make[2]: *** [all] Error 2 make[2]: Leaving directory '/usr/src/ghc-7.10.3' dh_auto_build: make -j1 returned exit code 2 debian/rules:109: recipe for target 'override_dh_auto_build' failed make[1]: *** [override_dh_auto_build] Error 2 make[1]: Leaving directory '/usr/src/ghc-7.10.3' debian/rules:47: recipe for target 'binary-arch' failed make: *** [binary-arch] Error 2 (sid2-powerpcspe-sbuild)root at atlantis:/usr/src/ghc-7.10.3# }}} So, there is obviously more assembly code that needs to be disabled on powerpcspe. For that, I suggest testing whether the compiler sets __NO_FPRS__which is only set on powerpc hosts without FP registers: {{{ root at atlantis:~# echo | gcc -E -dM -|grep -i FP #define __NO_FPRS__ 1 root at atlantis:~# dpkg --print-architecture powerpcspe root at atlantis:~# uname -m ppc root at atlantis:~# }}} For reference, on a real powerpc host, the output is as follows: {{{ (sid_powerpc-dchroot)glaubitz at partch:~$ echo | gcc -E -dM -|grep -i FP #define __FP_FAST_FMAF 1 #define __FP_FAST_FMA 1 (sid_powerpc-dchroot)glaubitz at partch:~$ dpkg --print-architecture powerpc (sid_powerpc-dchroot)glaubitz at partch:~$ uname -m ppc (sid_powerpc-dchroot)glaubitz at partch:~$ }}} If you need any more input, please let me know. For reference, the list of supported instructions on e500(v2) CPUs can be found here: http://www.nxp.com/files/32bit/doc/ref_manual/E500CORERM.pdf (page 3-66 or 196) Adrian -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 21:44:34 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 21:44:34 -0000 Subject: [GHC] #12054: PowerPC: Unsupported relocation against x0 In-Reply-To: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> References: <044.f40c6524bf6d5ba70a641a8992f8a184@haskell.org> Message-ID: <059.155a1ed4ba02d373655b3e7351db2a46@haskell.org> #12054: PowerPC: Unsupported relocation against x0 ----------------------------------------+---------------------------------- Reporter: erikd | Owner: trommler Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler (CodeGen) | Version: 8.0.1-rc4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2214 Wiki Page: | ----------------------------------------+---------------------------------- Changes (by hvr): * version: 8.1 => 8.0.1-rc4 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 16 23:48:46 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 16 May 2016 23:48:46 -0000 Subject: [GHC] #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' Message-ID: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 (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: -------------------------------------+------------------------------------- This is basically the same thing as #11155 but triggered differently. {{{ -- M.hs {-# OPTIONS_GHC -O0 #-} module M(f) where import GHC.Exts {-# NOINLINE z #-} z = () f :: () -> () f _ = let x = lazy z in g x x {-# NOINLINE g #-} g :: () -> () -> () g _ _ = () -- MM.hs import M main = f `seq` return () }}} On GHC 8.0, I get: {{{ ezyang at sabre:~$ ghc-8.0 --make MM.hs -fforce-recomp [1 of 2] Compiling M ( M.hs, M.o ) [2 of 2] Compiling Main ( MM.hs, MM.o ) Linking MM ... ./M.o: In function `r2aD_info': (.text+0x4a): undefined reference to `stg_ap_0_upd_info' collect2: error: ld returned 1 exit status `gcc' failed in phase `Linker'. (Exit code: 1) }}} Error goes away when you turn on optimization. My understanding is that removing `lazy` in `CorePrep` is too late, because there's no pass afterwards that eliminates the trivial thunk assignment. This is blocking Phab:D2211, where the insertion of a `noinline` (which is optimized out similarly to `lazy`) triggers a stage 2 linker failure when you don't compile with optimization (unfortunately, this is NOT caught validate since we build GHC with optimization... but with this test it will be!) Perhaps there should be an ASSERT in the codegen so it doesn't create this symbol? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 00:00:35 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 00:00:35 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.dc2b2a7f84bc304af73ae85c297febde@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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 mgsloan): * cc: mgsloan (added) Comment: +1 for resolving this (though I realize it's tricky)! Stack's build on 8.0 has this issue with ErrorCall's pattern synonym. Due to `-fwarn- incomplete-uni-patterns`, `catch f (\(ErrorCall x) -> g x)` causes a non- exhaustive case warning. See https://github.com/commercialhaskell/stack/pull/2145#issuecomment-219472907 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 03:36:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 03:36:07 -0000 Subject: [GHC] #2260: Non-ideal error message for misplaced LANGUAGE pragma In-Reply-To: <044.7cbacc8885ebc555467b0dece9c1a57d@haskell.org> References: <044.7cbacc8885ebc555467b0dece9c1a57d@haskell.org> Message-ID: <059.7b0bf54f9b62474bcb14454d34c410d0@haskell.org> #2260: Non-ideal error message for misplaced LANGUAGE pragma -------------------------------------+------------------------------------- Reporter: TomMD | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 6.8.2 (Parser) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #12002 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #12002 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 03:38:04 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 03:38:04 -0000 Subject: [GHC] #12002: Pragmas after a module declaration are ignored without warning. In-Reply-To: <050.a06dfff8e83390aaf98ce91845f96e30@haskell.org> References: <050.a06dfff8e83390aaf98ce91845f96e30@haskell.org> Message-ID: <065.d6ad9354e552bcd8bbaecb2cde4937b8@haskell.org> #12002: Pragmas after a module declaration are ignored without warning. -------------------------------------+------------------------------------- Reporter: seanparsons | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #2260 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Compiler (Parser) * related: => #2260 Comment: Also reported as #2260. igloo says: > That's a good idea, although sadly not quite as easy to implement right as you might imagine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 04:04:59 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 04:04:59 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.c007d2ff4ee7e1d164f86ca5054f3f7f@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Here was my WIP branch https://github.com/ezyang/ghc/tree/ghc-pprflags -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 04:49:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 04:49:07 -0000 Subject: [GHC] #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' In-Reply-To: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> References: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> Message-ID: <060.4c4ab12203852e0a0d33394714b52cb4@haskell.org> #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by ezyang: @@ -41,1 +41,22 @@ - afterwards that eliminates the trivial thunk assignment. + afterwards that eliminates the trivial thunk assignment. Here's the STG: + + {{{ + z_r2aC :: () + [GblId, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] = + NO_CCS ()! []; + + g_r2aD :: () -> () -> () + [GblId, Arity=2, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] = + sat-only \r srt:SRT:[] [ds_s2rW ds1_s2rX] () []; + + M.f :: () -> () + [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] = + \r srt:SRT:[] [ds_s2rY] + let { + x_s2rZ :: () + [LclId, Str=DmdType, Unf=OtherCon []] = + \u srt:SRT:[] [] z_r2aC; + } in g_r2aD x_s2rZ x_s2rZ; + }}} + + so we need, instead, something like `x_s2rZ = z_r2aC`. New description: This is basically the same thing as #11155 but triggered differently. {{{ -- M.hs {-# OPTIONS_GHC -O0 #-} module M(f) where import GHC.Exts {-# NOINLINE z #-} z = () f :: () -> () f _ = let x = lazy z in g x x {-# NOINLINE g #-} g :: () -> () -> () g _ _ = () -- MM.hs import M main = f `seq` return () }}} On GHC 8.0, I get: {{{ ezyang at sabre:~$ ghc-8.0 --make MM.hs -fforce-recomp [1 of 2] Compiling M ( M.hs, M.o ) [2 of 2] Compiling Main ( MM.hs, MM.o ) Linking MM ... ./M.o: In function `r2aD_info': (.text+0x4a): undefined reference to `stg_ap_0_upd_info' collect2: error: ld returned 1 exit status `gcc' failed in phase `Linker'. (Exit code: 1) }}} Error goes away when you turn on optimization. My understanding is that removing `lazy` in `CorePrep` is too late, because there's no pass afterwards that eliminates the trivial thunk assignment. Here's the STG: {{{ z_r2aC :: () [GblId, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] = NO_CCS ()! []; g_r2aD :: () -> () -> () [GblId, Arity=2, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] = sat-only \r srt:SRT:[] [ds_s2rW ds1_s2rX] () []; M.f :: () -> () [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] = \r srt:SRT:[] [ds_s2rY] let { x_s2rZ :: () [LclId, Str=DmdType, Unf=OtherCon []] = \u srt:SRT:[] [] z_r2aC; } in g_r2aD x_s2rZ x_s2rZ; }}} so we need, instead, something like `x_s2rZ = z_r2aC`. This is blocking Phab:D2211, where the insertion of a `noinline` (which is optimized out similarly to `lazy`) triggers a stage 2 linker failure when you don't compile with optimization (unfortunately, this is NOT caught validate since we build GHC with optimization... but with this test it will be!) Perhaps there should be an ASSERT in the codegen so it doesn't create this symbol? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 06:58:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 06:58:30 -0000 Subject: [GHC] #8207: Pretty Printer for textual version of Language (name) in DynFlags In-Reply-To: <047.ff066453d0b5bb8959d2c8e8b4d65d05@haskell.org> References: <047.ff066453d0b5bb8959d2c8e8b4d65d05@haskell.org> Message-ID: <062.b52d45a392b14e9f58b76a226e85b474@haskell.org> #8207: Pretty Printer for textual version of Language (name) in DynFlags -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: seraphime Type: feature request | Status: closed Priority: low | Milestone: 8.0.1 Component: GHC API | Version: 7.7 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.0.1 @@ -7,1 +7,1 @@ - {{{ + {{{#!hs New description: I feel that the GHC API could benefit from a Show instance for Language in DynFlags.hs. Currently, if we want to display the language being used we have to do something like {{{#!hs foo inf = case hmi_language inf of Nothing -> Nothing Just Haskell98 -> Just "Haskell98" Just Haskell2010 -> Just "Haskell2010" }}} This is pretty much just the Show instance (over Maybe) and Haskell can derive it for us automatically: we just need to change `deriving Enum` to `deriving (Enum, Show)`. The above solution is not the most robust ever as if this data type is ever changed, this starts to form an incomplete pattern. If we have a catch all `_`, GHC complains about overlapping patterns. Easily solved with `show <$> hmi_language inf`. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 06:59:10 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 06:59:10 -0000 Subject: [GHC] #8207: Pretty Printer for textual version of Language (name) in DynFlags In-Reply-To: <047.ff066453d0b5bb8959d2c8e8b4d65d05@haskell.org> References: <047.ff066453d0b5bb8959d2c8e8b4d65d05@haskell.org> Message-ID: <062.ab23693074c7ccbadb4c5e2ec0798725@haskell.org> #8207: Pretty Printer for textual version of Language (name) in DynFlags -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: seraphime Type: feature request | Status: closed Priority: low | Milestone: 8.0.1 Component: GHC API | Version: 7.7 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: | -------------------------------------+------------------------------------- Comment (by bgamari): An `Outputable` instance for this was added in 2ad46a860f0b648aaeff224109b6045da30304d7. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 07:28:22 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 07:28:22 -0000 Subject: [GHC] #12077: T8761 (Make pattern synonyms work with Template Haskell) is failing on Travis Message-ID: <045.60294a744526480b093ee47fef543bec@haskell.org> #12077: T8761 (Make pattern synonyms work with Template Haskell) is failing on Travis -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #8761 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Note that Travis uses `DYNAMIC_GHC_PROGRAMS=NO`. First failure: https://travis-ci.org/ghc/ghc/builds/129738012 {{{ Actual stderr output differs from expected: --- ./th/T8761.stderr.normalised 2016-05-12 15:08:16.512921981 +0000 +++ ./th/T8761.comp.stderr.normalised 2016-05-12 15:08:16.512921981 +0000 @@ -1,7 +1,3 @@ -pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _) -pattern x1_0 Q2 x2_1 = ((x1_0, x2_1)) -pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where - Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3]) T8761.hs:(15,1)-(38,13): Splicing declarations do { [qx1, qy1, qz1] <- mapM (/ i -> newName $ "x" ++ show i) [1, 2, 3]; @@ -123,30 +119,6 @@ pattern Pup x <- MkUnivProv x pattern Puep :: forall a. forall b. Show b => a -> b -> (ExProv, a) pattern Puep x y <- (MkExProv y, x) -pattern T8761.P :: GHC.Types.Bool -pattern T8761.Pe :: () => forall (a0_0 :: *) . a0_0 -> T8761.Ex -pattern T8761.Pu :: forall (a0_0 :: *) . a0_0 -> a0_0 -pattern T8761.Pue :: forall (a0_0 :: *) . () => forall (b0_1 :: *) . - a0_0 -> b0_1 -> (a0_0, T8761.Ex) -pattern T8761.Pur :: forall (a0_0 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - a0_0 -> [a0_0] -pattern T8761.Purp :: forall (a0_0 :: *) (b0_1 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - GHC.Show.Show b0_1 => a0_0 -> b0_1 -> ([a0_0], T8761.UnivProv b0_1) -pattern T8761.Pure :: forall (a0_0 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - forall (b0_1 :: *) . a0_0 -> b0_1 -> ([a0_0], T8761.Ex) -pattern T8761.Purep :: forall (a0_0 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - forall (b0_1 :: *) . GHC.Show.Show b0_1 => - a0_0 -> b0_1 -> ([a0_0], T8761.ExProv) -pattern T8761.Pep :: () => forall (a0_0 :: *) . GHC.Show.Show a0_0 => - a0_0 -> T8761.ExProv -pattern T8761.Pup :: forall (a0_0 :: *) . () => GHC.Show.Show a0_0 => - a0_0 -> T8761.UnivProv a0_0 -pattern T8761.Puep :: forall (a0_0 :: *) . () => forall (b0_1 :: *) . GHC.Show.Show b0_1 => - a0_0 -> b0_1 -> (T8761.ExProv, a0_0) T8761.hs:(107,1)-(111,25): Splicing declarations do { infos <- mapM reify *** unexpected failure for T8761(normal) }}} @bollmann added the test in c079de3c43704ea88f592e441389e520313e30ad. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 09:53:53 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 09:53:53 -0000 Subject: [GHC] #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' In-Reply-To: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> References: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> Message-ID: <060.192aeee1d3a2ef79c261caa66f720bde@haskell.org> #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.0.2 Comment: > Perhaps there should be an ASSERT in the codegen so it doesn't create this symbol? +1. It's silly that we get all the way to linking with this code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 10:06:25 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 10:06:25 -0000 Subject: [GHC] #11155: Trivial thunk gives "undefined reference to stg_ap_0_upd_info" In-Reply-To: <046.d8196c999608fededc5ef9d4e2e29843@haskell.org> References: <046.d8196c999608fededc5ef9d4e2e29843@haskell.org> Message-ID: <061.e891274b86b33914744d33dc9f992ee5@haskell.org> #11155: Trivial thunk gives "undefined reference to stg_ap_0_upd_info" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T11155 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): See Phab:D2230 for a quick patch to catch this sort of issue during C-- pretty-printing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 10:37:45 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 10:37:45 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.94916e15741fe6ac89a1285fc6743499@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"dc94914eb0da985a2f006e2bd390fa1fdbafcc33/ghc" dc94914e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dc94914eb0da985a2f006e2bd390fa1fdbafcc33" Document determinism in shortOutIndirections varEnvElts didn't introduce nondeterminism here. This makes it obvious that it could and explains why it doesn't. Test Plan: ./validate Reviewers: bgamari, simonmar, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2228 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 10:41:38 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 10:41:38 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.54432c31dfeb20b4ea4445fd46391096@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by nh2): I just want to leave a quick note here saying that it's great to see this stream of improvements on deterministic compilation. It's super appreciated that you invest your time into this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 11:34:22 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 11:34:22 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.bd4bb9b67b5096efc2589b4eae661805@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dalaing): I've been having a go at this, and I'm up to the code gen part. It looks like there's a decent amount of the Cmm code that takes a `DynFlags` argument in order to get access to `PlatformConstants`. The `PprFlags` change might be easier if these functions took `PlatformConstants` as an argument (which would then become part of the `PprFlags` structure). Does anyone have thoughts on whether I should just go ahead and do this? Or should I make `CmmFlags` and `cmmFlags :: DynFlags -> CmmFlags` in order to wrap it nicely? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 14:15:24 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 14:15:24 -0000 Subject: [GHC] #12052: Split ghc-boot so we have better dependency hygiene In-Reply-To: <045.061983f99253ceb1981e41093fe365b7@haskell.org> References: <045.061983f99253ceb1981e41093fe365b7@haskell.org> Message-ID: <060.74cfafd97c2ec5ddf738f209d2117362@haskell.org> #12052: Split ghc-boot so we have better dependency hygiene -------------------------------------+------------------------------------- Reporter: ezyang | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Core Libraries | Version: 8.0.1-rc4 Resolution: | Keywords: 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 hvr): * priority: high => highest * owner: => bgamari * version: 8.0.1 => 8.0.1-rc4 * milestone: 8.0.2 => 8.0.1 Comment: see eed820b672e6c3d23106cd151b1e31ce29326e32 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 14:23:00 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 14:23:00 -0000 Subject: [GHC] #12052: Split ghc-boot so we have better dependency hygiene In-Reply-To: <045.061983f99253ceb1981e41093fe365b7@haskell.org> References: <045.061983f99253ceb1981e41093fe365b7@haskell.org> Message-ID: <060.072494554686aee8e9a2b416abe76b89@haskell.org> #12052: Split ghc-boot so we have better dependency hygiene -------------------------------------+------------------------------------- Reporter: ezyang | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Core Libraries | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: 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 direction of travel here, but I do beg for a wiki page or clearly-signposted summary somewhere that explains * What packages there are * What they contain * Crucially, what the thinking behind the architecture is For example, summarising what is in `ghc-boot-th`, ''and what criteria guided that choice''. Similarly `ghc-prim`. Etc. There is some stuff already * [wiki:Repositories] * [wiki:Commentary/Libraries] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:03:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:03:11 -0000 Subject: [GHC] #11980: Testsuite: run each test in its own /tmp directory, after copying required files In-Reply-To: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> References: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> Message-ID: <060.837966373e0813bb21837d5867493d58@haskell.org> #11980: Testsuite: run each test in its own /tmp directory, after copying required files -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: task | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D1187 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"3f3dc23ea64573a12e2f4bfdaaa3aa536ad3188d/ghc" 3f3dc23/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3f3dc23ea64573a12e2f4bfdaaa3aa536ad3188d" Testsuite: run tests in /tmp after copying required files Major change to the testsuite driver. For each TEST: * create a directory `` inside `/tmp`. * link/copy all source files that the test needs into ``. * run the test inside ``. * delete `` Extra files are (temporarily) tracked in `testsuite/driver/extra_files.py`, but can also be specified using the `extra_files` setup function. Differential Revision: https://phabricator.haskell.org/D1187 Reviewed by: Rufflewind, bgamari Trac: #11980 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:03:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:03:11 -0000 Subject: [GHC] #11980: Testsuite: run each test in its own /tmp directory, after copying required files In-Reply-To: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> References: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> Message-ID: <060.5276c2df33d4262df3ea868c2a34b355@haskell.org> #11980: Testsuite: run each test in its own /tmp directory, after copying required files -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: task | Status: patch Priority: normal | Milestone: 8.2.1 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): Phab:D1187 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"1a9ae4b39c057d2a21192f6be033c8545702f345/ghc" 1a9ae4b3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1a9ae4b39c057d2a21192f6be033c8545702f345" Testsuite: delete old cleanup code (#11980) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:22:34 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:22:34 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies Message-ID: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The `ghc-boot-th` introduced in the resolution of #12052 seems to have uncovered a bug in the build system's treatment of transitive dependencies. Namely, it seems to be possible for the build system to attempt to link `ghc-pkg` before `libghc-boot-th` has been produced. This is odd since `ghc-pkg` has a dependency on `ghc-boot`, which in turn has a dependency on `ghc-boot-th`. In the interest of moving the 8.0.1 release along I'm going to work around this for the time being by adding -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:23:40 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:23:40 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies In-Reply-To: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> References: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> Message-ID: <061.7221e11a0f33cb89b09c7087ede34ecb@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -9,1 +9,2 @@ - this for the time being by adding + this for the time being by adding transitive dependencies to the rule in + `rules/build-prog.mk` which builds programs (including `ghc-pkg`). New description: The `ghc-boot-th` introduced in the resolution of #12052 seems to have uncovered a bug in the build system's treatment of transitive dependencies. Namely, it seems to be possible for the build system to attempt to link `ghc-pkg` before `libghc-boot-th` has been produced. This is odd since `ghc-pkg` has a dependency on `ghc-boot`, which in turn has a dependency on `ghc-boot-th`. In the interest of moving the 8.0.1 release along I'm going to work around this for the time being by adding transitive dependencies to the rule in `rules/build-prog.mk` which builds programs (including `ghc-pkg`). -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:25:35 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:25:35 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies In-Reply-To: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> References: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> Message-ID: <061.9e0652f4d7b0fc7a704a4005fc6f4be0@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -10,1 +10,3 @@ - `rules/build-prog.mk` which builds programs (including `ghc-pkg`). + `rules/build-prog.mk` which builds programs (including `ghc-pkg`). It + doesn't seem like this should be necessary, but with Hadian being so near + it seems like a good enough work around. New description: The `ghc-boot-th` introduced in the resolution of #12052 seems to have uncovered a bug in the build system's treatment of transitive dependencies. Namely, it seems to be possible for the build system to attempt to link `ghc-pkg` before `libghc-boot-th` has been produced. This is odd since `ghc-pkg` has a dependency on `ghc-boot`, which in turn has a dependency on `ghc-boot-th`. In the interest of moving the 8.0.1 release along I'm going to work around this for the time being by adding transitive dependencies to the rule in `rules/build-prog.mk` which builds programs (including `ghc-pkg`). It doesn't seem like this should be necessary, but with Hadian being so near it seems like a good enough work around. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:26:27 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:26:27 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies In-Reply-To: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> References: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> Message-ID: <061.1995eb714eb8e1e7b76d334424afdf02@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"5d80d14196ef048ffe037b2d92af2e9af0cb9e19/ghc" 5d80d141/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5d80d14196ef048ffe037b2d92af2e9af0cb9e19" rules/build-prog: Ensure programs depend upon their transitive deps Previously programs only depended upon the direct dependencies; while I would have thought that this would be sufficient, somehow we were getting to the link step of building `ghc-pkg` before `ghc-boot-th` was built (despite the fact that `ghc-boot` has a direct dependency on `ghc-boot-th`). See #12078. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:37:09 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:37:09 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies In-Reply-To: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> References: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> Message-ID: <061.a49c6598fb04b38a59896f9276140c41@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): These commits are relevant: * 5bde27949bdda22c9d5dac254a3c783eb0f6839f {{{ Author: Ian Lynagh Date: Sun Jan 16 15:56:27 2011 +0000 Handle dependencies of programs on libraries correctly }}} * 5874a66b4baff3ff8dba38f629d71cbfdf7f67fc {{{ Author: Ian Lynagh Date: Sun Nov 18 01:11:55 2012 +0000 Remove some dependencies I don't think we need these, and they haven't been doing anything useful for dynamic-by-default builds anyway as they hardcode the 'v' way. }}} Especially this comment: {{{ # These deps aren't technically necessary in themselves, but they # turn the dependencies of programs on libraries into transitive # dependencies. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 16:45:50 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 16:45:50 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies In-Reply-To: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> References: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> Message-ID: <061.8fedf0cddef50b01b35f447ce95f8c47@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -4,1 +4,2 @@ - attempt to link `ghc-pkg` before `libghc-boot-th` has been produced. This + attempt to link `ghc-pkg` before `libghc-boot-th` has been produced + (although this will typically only happen when building with `-j1`). This New description: The `ghc-boot-th` introduced in the resolution of #12052 seems to have uncovered a bug in the build system's treatment of transitive dependencies. Namely, it seems to be possible for the build system to attempt to link `ghc-pkg` before `libghc-boot-th` has been produced (although this will typically only happen when building with `-j1`). This is odd since `ghc-pkg` has a dependency on `ghc-boot`, which in turn has a dependency on `ghc-boot-th`. In the interest of moving the 8.0.1 release along I'm going to work around this for the time being by adding transitive dependencies to the rule in `rules/build-prog.mk` which builds programs (including `ghc-pkg`). It doesn't seem like this should be necessary, but with Hadian being so near it seems like a good enough work around. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 17 21:26:34 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 17 May 2016 21:26:34 -0000 Subject: [GHC] #9214: UNPACK support for sum types In-Reply-To: <047.5213ff1d75a2abd5ff04d6c7bb79813f@haskell.org> References: <047.5213ff1d75a2abd5ff04d6c7bb79813f@haskell.org> Message-ID: <062.b6ddb46a538c9c66507230fd2087304a@haskell.org> #9214: UNPACK support for sum types -------------------------------------+------------------------------------- Reporter: mojojojo | Owner: osa1 Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1540 Wiki Page: UnpackedSumTypes | Phab:D1559 -------------------------------------+------------------------------------- Comment (by dfeuer): I'm just popping in to +1 this. Currently, `Data.IntMap` defines {{{#!hs data IntMap a = Bin ... !(IntMap a) !(IntMap a) | Tip ... | Nil }}} Logically, it *should* be {{{#!hs data IntMap a = IM !(IntMap1) | Nil data IntMap1 a = Bin ... !(IntMap1) !(IntMap1) | Tip ... }}} which would enforce the invariant that no `Nil`s can occur within a tree. But that has an extra indirection, which seems likely unacceptable. If we could `UNPACK` the `IntMap1` into the `IntMap`, we'd get the current performance with much nicer type guarantees. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 02:26:18 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 02:26:18 -0000 Subject: [GHC] #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies In-Reply-To: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> References: <046.6019618d9346ef3dc1dba7e35f618b58@haskell.org> Message-ID: <061.48fd7002f7029270304677d9d1b3d77e@haskell.org> #12078: ghc-boot-th package reveals issue with build system's treatment of transitive dependencies -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by asr): Replying to [ticket:12078 bgamari]: > (although this will typically only happen when building with `-j1`) I confirm it. I was using `-j1` when I found the error: {{{ $ make /usr/bin/ld: cannot find -lHSghc-boot-th-8.0.1 collect2: ld returned 1 exit status make[1]: *** [utils/ghc-pkg/dist/build/tmp/ghc-pkg] Error 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 02:57:07 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 02:57:07 -0000 Subject: [GHC] #12079: seg fault while using gtk Message-ID: <045.95402382996132bdb463dfe148e7d190@haskell.org> #12079: seg fault while using gtk --------------------------------------+---------------------------------- Reporter: doofin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: Runtime crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+---------------------------------- {{{#!hs {-# LANGUAGE OverloadedStrings #-} module Main where import Graphics.UI.Gtk import System.Glib.Signals import Graphics.UI.Gtk.SourceView import Graphics.UI.Gtk.SourceView.SourceGutter import Graphics.UI.Gtk.SourceView.SourceCompletion import Graphics.UI.Gtk.SourceView.SourceMark import Graphics.UI.Gtk.SourceView.SourceBuffer import Graphics.UI.Gtk.Multiline.TextBuffer import Graphics.UI.Gtk.Gdk.EventM import Control.Monad.Trans import System.FSNotify import System.Environment import Control.Concurrent (threadDelay) import Control.Monad (forever) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Tuple import Data.Tuple.HT import Control.Concurrent main=do args<-getArgs print args let filename=head args txt<-T.readFile filename gtk txt $ \srcbf->do notify $ \evt -> case evt of Modified fp _->if (T.unpack $ Prelude.last $ T.splitOn "/" $ T.pack fp)==filename then do txtnew<-T.readFile $ head args postGUIAsync $ textBufferSetText srcbf (txtnew::T.Text) else return () _->return () return () notify action=withManager $ \mgr-> do --mgr<-startManager watchTree mgr -- manager "." -- directory to watch (const True) -- predicate $ \evt->do print evt-- action action evt forever $ threadDelay 1000000 -- sleep forever (until interrupted) gtk inittext act= do initGUI window <- windowNew windowSetDefaultSize window 900 600 windowSetPosition window WinPosCenter srcbf<-sourceBufferNew Nothing sourceView <- sourceViewNewWithBuffer srcbf scrolledWindow <- scrolledWindowNew Nothing Nothing sourceViewSetShowLineNumbers sourceView True textViewSetWrapMode sourceView WrapWord textBufferInsertAtCursor srcbf ("fdsf"::String) textBufferSetText srcbf inittext scrolledWindow `containerAdd` sourceView window `containerAdd` scrolledWindow widgetShowAll window on sourceView keyPressEvent $ do kl<-eventKeyName liftIO $ putStr $ show $ kl liftIO $ mapM_ (\(x,y)->if x==kl then textBufferInsertAtCursor srcbf (y::String) else return ()) pairs return False on window deleteEvent $ liftIO mainQuit >> return False connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" forkIO $ do act srcbf --onDestroy window mainQuit mainGUI pairs=[("parenleft",")"),("[","]")] }}} the program runs ok before adding the line {{{#!hs connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" }}} then i run ghc thisfile.hs -debug gdb thisfile run somefile move the cursor inside the textview,then seg fault happened bt {{{ result: Program received signal SIGSEGV, Segmentation fault. 0x00007fffeea0f4f0 in ?? () (gdb) bt #0 0x00007fffeea0f4f0 in ?? () #1 0x00000000000002f5 in ?? () #2 0x0000000000000309 in ?? () #3 0x00007fffffff44f8 in ?? () #4 0x00007fffffff4458 in ?? () #5 0x00007fff04fe0101 in ?? () #6 0x0000000000000113 in ?? () #7 0x00000000000002e5 in ?? () #8 0x0000000001db00ac in ?? () #9 0x00007fffeea13a21 in ?? () #10 0x00007fffeeaf5010 in ?? () #11 0x0000000000a8d709 in base_GHCziIOziFD_zdfBufferedIOFD2_closure () #12 0x00007fffeea07942 in ?? () #13 0x0000000000a8593a in base_GHCziIOziBuffer_WriteBuffer_closure () #14 0x0000000000000800 in ?? () #15 0x0000000000000000 in ?? () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 02:58:05 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 02:58:05 -0000 Subject: [GHC] #12079: seg fault while using gtk In-Reply-To: <045.95402382996132bdb463dfe148e7d190@haskell.org> References: <045.95402382996132bdb463dfe148e7d190@haskell.org> Message-ID: <060.1adc4e32d5bd43162c962fc0a272cdfb@haskell.org> #12079: seg fault while using gtk ----------------------------------+-------------------------------------- Reporter: doofin | Owner: 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: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Description changed by doofin: @@ -0,0 +1,2 @@ + the simple source file: + New description: the simple source file: {{{#!hs {-# LANGUAGE OverloadedStrings #-} module Main where import Graphics.UI.Gtk import System.Glib.Signals import Graphics.UI.Gtk.SourceView import Graphics.UI.Gtk.SourceView.SourceGutter import Graphics.UI.Gtk.SourceView.SourceCompletion import Graphics.UI.Gtk.SourceView.SourceMark import Graphics.UI.Gtk.SourceView.SourceBuffer import Graphics.UI.Gtk.Multiline.TextBuffer import Graphics.UI.Gtk.Gdk.EventM import Control.Monad.Trans import System.FSNotify import System.Environment import Control.Concurrent (threadDelay) import Control.Monad (forever) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Tuple import Data.Tuple.HT import Control.Concurrent main=do args<-getArgs print args let filename=head args txt<-T.readFile filename gtk txt $ \srcbf->do notify $ \evt -> case evt of Modified fp _->if (T.unpack $ Prelude.last $ T.splitOn "/" $ T.pack fp)==filename then do txtnew<-T.readFile $ head args postGUIAsync $ textBufferSetText srcbf (txtnew::T.Text) else return () _->return () return () notify action=withManager $ \mgr-> do --mgr<-startManager watchTree mgr -- manager "." -- directory to watch (const True) -- predicate $ \evt->do print evt-- action action evt forever $ threadDelay 1000000 -- sleep forever (until interrupted) gtk inittext act= do initGUI window <- windowNew windowSetDefaultSize window 900 600 windowSetPosition window WinPosCenter srcbf<-sourceBufferNew Nothing sourceView <- sourceViewNewWithBuffer srcbf scrolledWindow <- scrolledWindowNew Nothing Nothing sourceViewSetShowLineNumbers sourceView True textViewSetWrapMode sourceView WrapWord textBufferInsertAtCursor srcbf ("fdsf"::String) textBufferSetText srcbf inittext scrolledWindow `containerAdd` sourceView window `containerAdd` scrolledWindow widgetShowAll window on sourceView keyPressEvent $ do kl<-eventKeyName liftIO $ putStr $ show $ kl liftIO $ mapM_ (\(x,y)->if x==kl then textBufferInsertAtCursor srcbf (y::String) else return ()) pairs return False on window deleteEvent $ liftIO mainQuit >> return False connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" forkIO $ do act srcbf --onDestroy window mainQuit mainGUI pairs=[("parenleft",")"),("[","]")] }}} the program runs ok before adding the line {{{#!hs connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" }}} then i run ghc thisfile.hs -debug gdb thisfile run somefile move the cursor inside the textview,then seg fault happened bt {{{ result: Program received signal SIGSEGV, Segmentation fault. 0x00007fffeea0f4f0 in ?? () (gdb) bt #0 0x00007fffeea0f4f0 in ?? () #1 0x00000000000002f5 in ?? () #2 0x0000000000000309 in ?? () #3 0x00007fffffff44f8 in ?? () #4 0x00007fffffff4458 in ?? () #5 0x00007fff04fe0101 in ?? () #6 0x0000000000000113 in ?? () #7 0x00000000000002e5 in ?? () #8 0x0000000001db00ac in ?? () #9 0x00007fffeea13a21 in ?? () #10 0x00007fffeeaf5010 in ?? () #11 0x0000000000a8d709 in base_GHCziIOziFD_zdfBufferedIOFD2_closure () #12 0x00007fffeea07942 in ?? () #13 0x0000000000a8593a in base_GHCziIOziBuffer_WriteBuffer_closure () #14 0x0000000000000800 in ?? () #15 0x0000000000000000 in ?? () }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 03:05:34 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 03:05:34 -0000 Subject: [GHC] #12079: segmentation fault in both ghci and compiled program causing by gtk (was: seg fault while using gtk) In-Reply-To: <045.95402382996132bdb463dfe148e7d190@haskell.org> References: <045.95402382996132bdb463dfe148e7d190@haskell.org> Message-ID: <060.20124a5ebed2fa9270cc78fd58dbb6e0@haskell.org> #12079: segmentation fault in both ghci and compiled program causing by gtk ----------------------------------+-------------------------------------- Reporter: doofin | Owner: doofin Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Changes (by doofin): * owner: => doofin * priority: normal => high -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 03:08:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 03:08:41 -0000 Subject: [GHC] #12079: segmentation fault in both ghci and compiled program involves gtk library (was: segmentation fault in both ghci and compiled program causing by gtk) In-Reply-To: <045.95402382996132bdb463dfe148e7d190@haskell.org> References: <045.95402382996132bdb463dfe148e7d190@haskell.org> Message-ID: <060.960fc9501c6163d54c2bdd468e4aa969@haskell.org> #12079: segmentation fault in both ghci and compiled program involves gtk library ----------------------------------+-------------------------------------- Reporter: doofin | Owner: doofin Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Description changed by doofin: @@ -97,0 +97,2 @@ + + @@ -104,0 +106,1 @@ + it crashes both under ghc -make ,ghc -make -threaded and runhaskell New description: the simple source file: {{{#!hs {-# LANGUAGE OverloadedStrings #-} module Main where import Graphics.UI.Gtk import System.Glib.Signals import Graphics.UI.Gtk.SourceView import Graphics.UI.Gtk.SourceView.SourceGutter import Graphics.UI.Gtk.SourceView.SourceCompletion import Graphics.UI.Gtk.SourceView.SourceMark import Graphics.UI.Gtk.SourceView.SourceBuffer import Graphics.UI.Gtk.Multiline.TextBuffer import Graphics.UI.Gtk.Gdk.EventM import Control.Monad.Trans import System.FSNotify import System.Environment import Control.Concurrent (threadDelay) import Control.Monad (forever) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Tuple import Data.Tuple.HT import Control.Concurrent main=do args<-getArgs print args let filename=head args txt<-T.readFile filename gtk txt $ \srcbf->do notify $ \evt -> case evt of Modified fp _->if (T.unpack $ Prelude.last $ T.splitOn "/" $ T.pack fp)==filename then do txtnew<-T.readFile $ head args postGUIAsync $ textBufferSetText srcbf (txtnew::T.Text) else return () _->return () return () notify action=withManager $ \mgr-> do --mgr<-startManager watchTree mgr -- manager "." -- directory to watch (const True) -- predicate $ \evt->do print evt-- action action evt forever $ threadDelay 1000000 -- sleep forever (until interrupted) gtk inittext act= do initGUI window <- windowNew windowSetDefaultSize window 900 600 windowSetPosition window WinPosCenter srcbf<-sourceBufferNew Nothing sourceView <- sourceViewNewWithBuffer srcbf scrolledWindow <- scrolledWindowNew Nothing Nothing sourceViewSetShowLineNumbers sourceView True textViewSetWrapMode sourceView WrapWord textBufferInsertAtCursor srcbf ("fdsf"::String) textBufferSetText srcbf inittext scrolledWindow `containerAdd` sourceView window `containerAdd` scrolledWindow widgetShowAll window on sourceView keyPressEvent $ do kl<-eventKeyName liftIO $ putStr $ show $ kl liftIO $ mapM_ (\(x,y)->if x==kl then textBufferInsertAtCursor srcbf (y::String) else return ()) pairs return False on window deleteEvent $ liftIO mainQuit >> return False connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" forkIO $ do act srcbf --onDestroy window mainQuit mainGUI pairs=[("parenleft",")"),("[","]")] }}} the program runs ok before adding the line {{{#!hs connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" }}} it crashes both under ghc -make ,ghc -make -threaded and runhaskell then i run ghc thisfile.hs -debug gdb thisfile run somefile move the cursor inside the textview,then seg fault happened bt {{{ result: Program received signal SIGSEGV, Segmentation fault. 0x00007fffeea0f4f0 in ?? () (gdb) bt #0 0x00007fffeea0f4f0 in ?? () #1 0x00000000000002f5 in ?? () #2 0x0000000000000309 in ?? () #3 0x00007fffffff44f8 in ?? () #4 0x00007fffffff4458 in ?? () #5 0x00007fff04fe0101 in ?? () #6 0x0000000000000113 in ?? () #7 0x00000000000002e5 in ?? () #8 0x0000000001db00ac in ?? () #9 0x00007fffeea13a21 in ?? () #10 0x00007fffeeaf5010 in ?? () #11 0x0000000000a8d709 in base_GHCziIOziFD_zdfBufferedIOFD2_closure () #12 0x00007fffeea07942 in ?? () #13 0x0000000000a8593a in base_GHCziIOziBuffer_WriteBuffer_closure () #14 0x0000000000000800 in ?? () #15 0x0000000000000000 in ?? () }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 07:19:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 07:19:48 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.cd7cf39b8ae3d8e8a3bab960525b2fe1@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Here's is an odd thing, it works if you quantify it! {{{#!hs -- Doesn't work! -- pattern F :: b -> forall x. Char -> b -- pattern F a <- (($ 'a') -> a) -- Does work for some reason pattern F1 :: b -> forall x. Char -> b pattern F1 a <- (($ 'a') -> a) -- Wait what? pattern F2 :: b -> forall b. Char -> b pattern F2 a <- (($ 'a') -> a) }}} How does this play out {{{#!hs -- Inferred type f1 :: (forall (x :: k). Char -> b) -> b f1 (F1 x) = x -- Works exactly like: -- -- f1 (($ 'a') -> x) = x -- f1 :: (Char -> b) -> b f1 (F1 x) = x }}} with `F2`: {{{#!hs f2 :: (forall b. Char -> b) -> b1 f2 (F2 x) = ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 07:30:54 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 07:30:54 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.a19daa53f94146812f401ac28ef91fad@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Noticed while looking at Carter's [https://gist.github.com/cartazio/60eac732e7ac162916eaf828c9b1483c copatterns] and saw that the following compiles: {{{#!hs type Stream a = forall res . StreamTag a res -> res data StreamTag a res where HeadTag :: StreamTag a a -- TailTag :: StreamTag a (Stream a) pattern Head' :: res -> Stream res pattern Head' x <- (($ HeadTag) -> x) }}} but it is my understanding that `Stream` must be a newtype/data (generative) to be able to define `TailTag`: {{{#!hs newtype Stream a = Stream (forall res. StreamTag a res -> res) data StreamTag a res where HeadTag :: StreamTag a a TailTag :: StreamTag a (Stream a) pattern Head :: a -> Stream a pattern Head x <- ((\(Stream str) -> str HeadTag) -> x) pattern Tail :: Stream a -> Stream a pattern Tail xs <- ((\(Stream str) -> str TailTag) -> xs) pattern Cons :: a -> Stream a -> Stream a pattern Cons x xs <- ((\(Stream str) -> (str HeadTag, str TailTag)) -> (x, xs)) headStream :: Stream a -> a headStream (Head x) = x tailStream :: Stream a -> Stream a tailStream (Tail xs) = xs rawRawZipWith :: (a -> b -> c) -> (Stream a -> Stream b -> Stream c ) rawRawZipWith f sta stb = Stream $ \str -> do let Head x = sta Head y = stb Tail xs = sta Tail ys = stb case str of HeadTag -> f x y TailTag -> rawRawZipWith f xs ys rawRawZipWith' :: (a -> b -> c) -> (Stream a -> Stream b -> Stream c) rawRawZipWith' f (Cons x xs) (Cons y ys) = Stream $ \case HeadTag -> f x y TailTag -> rawRawZipWith f xs ys }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 07:45:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 07:45:49 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord Message-ID: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11396 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The code generated with `deriving (Ord)` includes if-expressions which are subject to rebindable syntax: {{{ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE RebindableSyntax #-} import Prelude class IfThenElse a b where ifThenElse :: a -> b -> b -> b instance IfThenElse Bool b where ifThenElse c x y = if c then x else y data Foo = Foo | Bar | Baz deriving (Eq, Ord) main :: IO () main = print $ Foo < Bar }}} when loaded into ghci (7.10, but not specific to that version): {{{ [1 of 1] Compiling Main ( Foo.hs, interpreted ) Foo.hs:13:42: Bad call to tagToEnum# at type a_aQy Specify the type by giving a type signature e.g. (tagToEnum# x) :: Bool In the expression: (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) In the expression: if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then LT else if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT In a case alternative: b# -> if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then LT else if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT When typechecking the code for ?compare? in a derived instance for ?Ord Foo?: To see the code I am typechecking, use -ddump-deriv Foo.hs:13:42: No instance for (IfThenElse a0 Ordering) arising from an if statement The type variable ?a0? is ambiguous Note: there is a potential instance available: instance IfThenElse Bool b -- Defined at Foo.hs:10:10 In the expression: if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then LT else if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT In a case alternative: b# -> if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then LT else if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT In the expression: case (Main.$con2tag_rjG b) of { b# -> if (GHC.Prim.tagToEnum# (a# GHC.Prim.<# b#)) then LT else if (GHC.Prim.tagToEnum# (a# GHC.Prim.==# b#)) then EQ else GT } When typechecking the code for ?compare? in a derived instance for ?Ord Foo?: To see the code I am typechecking, use -ddump-deriv Failed, modules loaded: none. }}} The if-expressions are generated by `nlHsIf`, which calls `mkHsIf`, which uses `Just noSyntaxExpr` as its first argument. I'm going to add a new function `nlBuiltInHsIf` which uses `Nothing` as the first argument, forcing the built-in if (according to Note [Rebindable if]), then use this new function when deriving stuff. I'll post a patch soonish. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 07:49:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 07:49:41 -0000 Subject: [GHC] #12072: GHC panic on type wildcard in left-hand side of data family In-Reply-To: <047.e584aa3b910eba55b26f4ea236a6c9a5@haskell.org> References: <047.e584aa3b910eba55b26f4ea236a6c9a5@haskell.org> Message-ID: <062.d0c0f7d5d10d405b8664cb94ca5fc2aa@haskell.org> #12072: GHC panic on type wildcard in left-hand side of data family -------------------------------------+------------------------------------- Reporter: andreash | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Thanks. This is OK in HEAD (and I hope 8.0). Wildcards are explicitly allowed on the LHS of type/data family instances. See the [http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html #data-instance-declarations user manual Section 9.9.1.2]. You are right that it's a bug in 7.10.3. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 08:22:09 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 08:22:09 -0000 Subject: [GHC] #11704: Word and Int literals not correctly truncated when cross compiling 64 -> 32 bit In-Reply-To: <044.ef02078386f7a5f7e48e062dab051f3c@haskell.org> References: <044.ef02078386f7a5f7e48e062dab051f3c@haskell.org> Message-ID: <059.0dcfe7f9dc257c3be3c55eaeaed2616b@haskell.org> #11704: Word and Int literals not correctly truncated when cross compiling 64 -> 32 bit -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc2 Resolution: | Keywords: cross- | compiling Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codeGen/should_run/T5785 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => codeGen/should_run/T5785 * keywords: => cross-compiling @@ -31,2 +31,2 @@ - This makes testcase `codeGen/5785.hs` fail when compiled with optimization - with GHCJS on 64 bit GHC. + This makes testcase `codeGen/should_run/T5785` fail when compiled with + optimization with GHCJS on 64 bit GHC. New description: GHC does not take the target word size into account for some of the rules in `PrelRules`: {{{#!hs rule_convert "integerToWord" integerToWordName mkWordLitWord, rule_convert "integerToInt" integerToIntName mkIntLitInt, }}} The relevant code from `CoreSyn`: {{{#!hs -- | Create a machine word literal expression of type @Word#@ from a @Word at . -- If you want an expression of type @Word@ use 'MkCore.mkWordExpr' mkWordLitWord :: DynFlags -> Word -> Expr b mkWordLit dflags w = Lit (mkMachWord dflags w) mkWordLitWord dflags w = Lit (mkMachWord dflags (toInteger w)) -- | Create a machine integer literal expression of type @Int#@ from an @Int at . -- If you want an expression of type @Int@ use 'MkCore.mkIntExpr' mkIntLitInt :: DynFlags -> Int -> Expr b mkIntLitInt dflags n = Lit (mkMachInt dflags (toInteger n)) }}} If a literal is bigger than the target word size, these rules can lead to loss of truncation when optimizing a `fromInteger` / `toInteger` pair. This makes testcase `codeGen/should_run/T5785` fail when compiled with optimization with GHCJS on 64 bit GHC. It probably also affects targeting 64 platforms with 32 bit compilers, where literals would be truncated too much, but I don't have a way of testing that. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 08:26:45 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 08:26:45 -0000 Subject: [GHC] #10843: Allow do blocks without dollar signs as arguments In-Reply-To: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> References: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> Message-ID: <064.56efdf3cd8930d1761e0bd114256fd9e@haskell.org> #10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #11706 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 08:36:43 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 08:36:43 -0000 Subject: [GHC] #11140: add command-line option to GHC to dump raw parse trees of Haskell programs In-Reply-To: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> References: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> Message-ID: <059.f8b78091ad2b2442e4fc8e37df131fde@haskell.org> #11140: add command-line option to GHC to dump raw parse trees of Haskell programs -------------------------------------+------------------------------------- Reporter: bollu | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: newcomer => Comment: Why should this be a GHC feature? Why not use `apply-refact`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 09:11:06 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 09:11:06 -0000 Subject: [GHC] #11730: GHC panics ('unload: no interpreter") during T10052 test In-Reply-To: <042.b5a574f763a8972e0dd59e722775b101@haskell.org> References: <042.b5a574f763a8972e0dd59e722775b101@haskell.org> Message-ID: <057.170a660049d97bfe4d6915f8f3c5483f@haskell.org> #11730: GHC panics ('unload: no interpreter") during T10052 test -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"b088c0297db2f0a86746fdc60977462ffb8c22ca/ghc" b088c029/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b088c0297db2f0a86746fdc60977462ffb8c22ca" Testsuite: T10052 requires interpreter (#11730) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 09:12:59 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 09:12:59 -0000 Subject: [GHC] #11730: GHC panics ('unload: no interpreter") during T10052 test In-Reply-To: <042.b5a574f763a8972e0dd59e722775b101@haskell.org> References: <042.b5a574f763a8972e0dd59e722775b101@haskell.org> Message-ID: <057.96b7c19d72d73d041ac2420e3bd5df2b@haskell.org> #11730: GHC panics ('unload: no interpreter") during T10052 test -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: If you find there are more tests that require GHCi, just add the setup function `req_interp`, and they will be skipped when GHCi isn't available. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 09:30:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 09:30:46 -0000 Subject: [GHC] #11738: A command to remove modules from the target list In-Reply-To: <045.65676ccdbab0a07c8eeb4e3b8e859349@haskell.org> References: <045.65676ccdbab0a07c8eeb4e3b8e859349@haskell.org> Message-ID: <060.b0cd341fc4837eb243c5c21244cd6c9a@haskell.org> #11738: A command to remove modules from the target list -------------------------------------+------------------------------------- Reporter: jh3141 | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Maybe `:a modulename` should just not result in a broken state. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 09:34:43 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 09:34:43 -0000 Subject: [GHC] #11740: RFC kind synonyms In-Reply-To: <051.0e72c4f1c3d54cad33a28cc5a9b7fcc3@haskell.org> References: <051.0e72c4f1c3d54cad33a28cc5a9b7fcc3@haskell.org> Message-ID: <066.c6f7cb1963f24712438f418925c2fb93@haskell.org> #11740: RFC kind synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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 thomie): * status: new => closed * resolution: => wontfix Comment: Since @goldfire and @Iceland_jack both agree this shouldn't go in base at the moment, I'm going to close this ticket, to give those other 1825 tickets some more room to breathe. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 09:49:05 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 09:49:05 -0000 Subject: [GHC] #11749: Add long forms for multi-character short-form flags and possibly deprecate short forms In-Reply-To: <046.6395df32b5dfef07d0ac806a2a326d62@haskell.org> References: <046.6395df32b5dfef07d0ac806a2a326d62@haskell.org> Message-ID: <061.441026a141db4657adb355a27403c725@haskell.org> #11749: Add long forms for multi-character short-form flags and possibly deprecate short forms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): I would just like to point out that these flagnames do follow a system currently. Only the [https://downloads.haskell.org/~ghc/master/users- guide/using.html#modes-of-operation mode flags] start with two dashes. These are: {{{ $ ghc801 --show-options | grep '^--' --help --version --numeric-version --info --show-options --supported-languages --supported-extensions --show-packages --print-project-version --print-project-git-commit-id --print-booter-version --print-stage --print-build-platform --print-host-platform --print-target-platform --print-have-interpreter --print-object-splitting-supported --print-have-native-code-generator --print-support-smp --print-unregisterised --print-tables-next-to-code --print-rts-ways --print-leading-underscore --print-debug-on --print-libdir --print-global-package-db --print-c-compiler-flags --print-c-compiler-link-flags --print-ld-flags --show-iface --make --interactive --abi-hash --frontend }}} The other 877 flags all start with a single dash. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 10:01:51 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 10:01:51 -0000 Subject: [GHC] #11140: add command-line option to GHC to dump raw parse trees of Haskell programs In-Reply-To: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> References: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> Message-ID: <059.cfa11eb23ac7363b4ebf6d3b10e86c59@haskell.org> #11140: add command-line option to GHC to dump raw parse trees of Haskell programs -------------------------------------+------------------------------------- Reporter: bollu | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Because I think it would be useful when working on the parser to see the parse trees. It is often not obvious how the parser works, see for example the recent work I have been doing with export lists and there's another ticket about how `BooleanFormula` is parsed in a very strange way. Both would be easier to debug with this flag. There is already precedent for this, after all the other stages in the compiler pipeline there is an flag which dumps the correct compiler output (`-ddump-simple`, `-ddump-rn`, `-ddump-rn` etc) so why not for dumping parse trees as well? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 10:34:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 10:34:40 -0000 Subject: [GHC] #11140: add command-line option to GHC to dump raw parse trees of Haskell programs In-Reply-To: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> References: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> Message-ID: <059.8947efab779a49025402730d6c507f92@haskell.org> #11140: add command-line option to GHC to dump raw parse trees of Haskell programs -------------------------------------+------------------------------------- Reporter: bollu | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): None of those dump anything like "raw" format though (by this I assume you mean something like what the derived Show instance would produce if there was one). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 10:39:23 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 10:39:23 -0000 Subject: [GHC] #11758: Drop x86_64 binutils <2.17 hack In-Reply-To: <046.4526d91ede8d490bc5daf7dd1af1ee5c@haskell.org> References: <046.4526d91ede8d490bc5daf7dd1af1ee5c@haskell.org> Message-ID: <061.5d9d50a54dd4966a706ea66a57962481@haskell.org> #11758: Drop x86_64 binutils <2.17 hack -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1-rc2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer Comment: In https://phabricator.haskell.org/D1242#37057, kgardas says: W.r.t binutils < 2.17 I just signal that Solaris is using 2.23 and OpenBSD/amd64 is using 2.17 -- so from those two platforms it's safe to remove mentioned hack. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 10:40:19 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 10:40:19 -0000 Subject: [GHC] #11140: add command-line option to GHC to dump raw parse trees of Haskell programs In-Reply-To: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> References: <044.9ca7a94e52e643694da7336bc4c35d24@haskell.org> Message-ID: <059.7d0d12334312eb0bd19dc2e0404d8e90@haskell.org> #11140: add command-line option to GHC to dump raw parse trees of Haskell programs -------------------------------------+------------------------------------- Reporter: bollu | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): That is true but by them stages in the compilation pipeline you don't care about what the raw format looks like. When modifying the parser you need to know the precise structure of the AST rather than some pretty printed version produced by `Outputtable`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 10:45:39 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 10:45:39 -0000 Subject: [GHC] #11761: autoconf 2.69 breaks configure In-Reply-To: <046.026016968a0f00c4ea3dfc0c8c115a55@haskell.org> References: <046.026016968a0f00c4ea3dfc0c8c115a55@haskell.org> Message-ID: <061.8e7e041477ed19f493d48f87bce7a558@haskell.org> #11761: autoconf 2.69 breaks configure -------------------------------------+------------------------------------- Reporter: kgardas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.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: | -------------------------------------+------------------------------------- Comment (by thomie): I'm using autoconf 2.69 as shipped with Ubuntu, and everything works fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 11:44:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 11:44:22 -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.9469b4020b5f37b779846369e475b297@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 11:52:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 11:52:46 -0000 Subject: [GHC] #11761: autoconf 2.69 breaks configure In-Reply-To: <046.026016968a0f00c4ea3dfc0c8c115a55@haskell.org> References: <046.026016968a0f00c4ea3dfc0c8c115a55@haskell.org> Message-ID: <061.343b9aa7b7f4d93f9d367709344817dc@haskell.org> #11761: autoconf 2.69 breaks configure -------------------------------------+------------------------------------- Reporter: kgardas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.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: | -------------------------------------+------------------------------------- Comment (by kgardas): Hi, I've retested this and I'm no longer able to duplicate this on this host. So I'm closing for now... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 11:53:52 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 11:53:52 -0000 Subject: [GHC] #11761: autoconf 2.69 breaks configure In-Reply-To: <046.026016968a0f00c4ea3dfc0c8c115a55@haskell.org> References: <046.026016968a0f00c4ea3dfc0c8c115a55@haskell.org> Message-ID: <061.ba7d849df69e31d1e01f02478cfe8fc6@haskell.org> #11761: autoconf 2.69 breaks configure -------------------------------------+------------------------------------- Reporter: kgardas | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 8.1 Resolution: worksforme | 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 kgardas): * status: new => closed * resolution: => worksforme -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 11:57:19 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 11:57:19 -0000 Subject: [GHC] #5683: bug in signum function In-Reply-To: <053.26d0d3539f88a72f2e9c735fa6c69f54@haskell.org> References: <053.26d0d3539f88a72f2e9c735fa6c69f54@haskell.org> Message-ID: <068.cb5ce4de9cdf257027937b72a913cca9@haskell.org> #5683: bug in signum function -------------------------------------+------------------------------------- Reporter: tristes_tigres | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.6.1 Component: Prelude | Version: 7.0.3 Resolution: fixed | 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 thomie): This was fixed in commit d9a20573f473cc7389004470999b8a318aa6b3f2: {{{ Author: Alexander Berntsen Date: Mon Aug 18 21:43:33 2014 -0500 Make Prelude.signum handle -0.0 correctly (#7858) Summary: Make the `Float` and `Double` implementations of `signum` handle -0.0 correctly per IEEE-754. This, together with "Make Prelude.abs handle -0.0 correctly (#7858)", fixes Trac #7858. Depends on D145 Signed-off-by: Alexander Berntsen Test Plan: signum of (-0.0) should be (-0.0) not 0.0. Test program: main = putStrLn $ p ++ " " ++ n where f = show . signum p = f (-0.0 :: Double) n = f (0.0 :: Double) Reviewers: ekmett, hvr, rwbarton, austin Reviewed By: austin Subscribers: phaskell, simonmar, relrod, ezyang, carter Differential Revision: https://phabricator.haskell.org/D148 GHC Trac Issues: #7858 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 12:20:17 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 12:20:17 -0000 Subject: [GHC] #11962: Support induction recursion In-Reply-To: <047.045273ef2ac55a0385e215af795b4757@haskell.org> References: <047.045273ef2ac55a0385e215af795b4757@haskell.org> Message-ID: <062.fa2f71dd67bdb0faf36e72a6d5356a94@haskell.org> #11962: Support induction recursion -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: alexvieth (added) Comment: (@goldfire mentioned in ticket:11348#comment:17 that @alexvieth might be interested in working on this ticket, so I'm CC-ing him here) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 12:38:39 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 12:38:39 -0000 Subject: [GHC] #10840: Periodic alarm signals can cause a retry loop to get stuck In-Reply-To: <049.c792fb7fbab25e12997f6231b1f3472d@haskell.org> References: <049.c792fb7fbab25e12997f6231b1f3472d@haskell.org> Message-ID: <064.f060f64c36dcbe74d5cca1d27cedeac3@haskell.org> #10840: Periodic alarm signals can cause a retry loop to get stuck ---------------------------------+---------------------------------------- Reporter: Rufflewind | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.10.2 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 thomie): * os: Unknown/Multiple => MacOS X * milestone: 8.0.2 => 8.2.1 Comment: If I understand correctly, this is just an `OS X` issue now. And the commits for #11830, #11965 and this ticket have not been merged to the ghc-8.0 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 12:45:50 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 12:45:50 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.c06c49f1e65bdc79870c94c1f301ce41@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Szunti): Can I help more to get this fixed? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 12:51:44 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 12:51:44 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.9111f6993ad6828a01a18041f5ed940f@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"fffe3a25adab41d44943ed1be0191cf570d3e154/ghc" fffe3a25/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fffe3a25adab41d44943ed1be0191cf570d3e154" Make inert_model and inert_eqs deterministic sets The order inert_model and intert_eqs fold affects the order that the typechecker looks at things. I've been able to experimentally confirm that the order of equalities and the order of the model matter for determinism. This is just a straigthforward replacement of nondeterministic VarEnv for deterministic DVarEnv. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2232 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 13:25:29 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 13:25:29 -0000 Subject: [GHC] #11774: Regression on GHC 8 branch (vs 7.10.3) when using the GHC API to parse code that uses TH In-Reply-To: <050.40af602ae9a228b0dca3c0dd3ac155f0@haskell.org> References: <050.40af602ae9a228b0dca3c0dd3ac155f0@haskell.org> Message-ID: <065.3f4a74b0b7c3bfd910de871e0449c4fc@haskell.org> #11774: Regression on GHC 8 branch (vs 7.10.3) when using the GHC API to parse code that uses TH -------------------------------------+------------------------------------- Reporter: SimonHengel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHC API | Version: 8.0.1-rc2 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 thomie): * component: Compiler => GHC API Comment: Reproducible with HEAD (ghc-8.1.20160515). First run `cabal install ghc- paths syb`. Then run `ghci -package ghc Extract.hs` Solution / workaround: use `ghci -fexternal-interpreter`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 13:52:26 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 13:52:26 -0000 Subject: [GHC] #11777: RTS source code issues In-Reply-To: <046.3e69faecf0e4f69a5fcc7ec246409435@haskell.org> References: <046.3e69faecf0e4f69a5fcc7ec246409435@haskell.org> Message-ID: <061.ffab7f4c1b0adbc001a4409e09764caa@haskell.org> #11777: RTS source code issues -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer * cc: erikd (added) * component: Compiler => Runtime System @@ -2,1 +2,4 @@ - the C files used in GHC and noticed these issues: + the C files used in GHC and noticed these issues [edit: this list now + shows only those issues that haven't been fixed yet]: + + * driver/utils/dynwrapper.c: @@ -4,1 +7,4 @@ - /driver/utils/cwrapper.c : int main(int, char **); + int main(int argc, char *argv[]) { + void *p; + ... + } @@ -6,0 +12,1 @@ + @@ -9,0 +16,3 @@ + + + * rts/RetainerSet.c: @@ -10,7 +20,0 @@ - /rts/RetainerProfile.c : static nat sanityCheckHeapClosure(StgClosure *) - }}} - `StgInfoTable *info` has the same issue as above - - {{{ - /rts/RetainerSet.c - @@ -32,0 +35,1 @@ + * rts/win32/IOManager.c: @@ -33,14 +37,1 @@ - /rts/sm/MarkWeak.c : void markWeakPtrList (void); - - if (w->header.info == &stg_DEAD_WEAK_info) { - last_w = &(w->link); - } else { - last_w = &(w->link); - } - }}} - Not sure what's going on here. Regardless of the test the two branches do - the same thing. - {{{ - - /rts/win32/IOManager.c : AddIORequest, AddDelayRequest, AddProcRequest - functions + AddIORequest, AddDelayRequest, AddProcRequest functions New description: Tiago Silva writes: Last night I started looking at the C files used in GHC and noticed these issues [edit: this list now shows only those issues that haven't been fixed yet]: * driver/utils/dynwrapper.c: {{{ int main(int argc, char *argv[]) { void *p; ... } }}} `void *p` is apparently unused, even if the compiler optimizes it away.. you should check if something went missing. * rts/RetainerSet.c: {{{ #elif defined(RETAINER_SCHEME_CC) // Retainer scheme 3: retainer = cost centre void printRetainerSetShort(FILE *f, RetainerSet *rs, nat max_length) { char tmp[max_length + 1]; int size; nat j; } }}} Unlike the other functions around it, this function does nothing. Its variables are also not unused? * rts/win32/IOManager.c: {{{ AddIORequest, AddDelayRequest, AddProcRequest functions }}} If `(!ioMan || !wItem)` the functions either return 0 or FALSE, but they don't free `wItem` before. Is this optimized by the compiler? -- Comment: I removed some issues from the description that have since been fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 14:03:44 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 14:03:44 -0000 Subject: [GHC] #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure In-Reply-To: <046.d81887f1f82ecca81477b67bf0ea3214@haskell.org> References: <046.d81887f1f82ecca81477b67bf0ea3214@haskell.org> Message-ID: <061.2303639f25a0ab5e038d6220726859ef@haskell.org> #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 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 bgamari: @@ -1,3 +1,4 @@ - When characterizing bytestring's `Builder` interface[1] I noticed that - some benchmarks involving repeated appends (e.g. `Host endian/1MB of Word8 - in chunks of 16`) perform inexplicably much worse than others. A glance at + When characterizing `bytestring`'s `Builder` [[ + https://github.com/kolmodin/binary/pull/65|interface]] I noticed that some + benchmarks involving repeated appends (e.g. `Host endian/1MB of Word8 in + chunks of 16`) perform inexplicably much worse than others. A glance at @@ -53,2 +54,3 @@ - [1] https://github.com/kolmodin/binary/pull/65 - [2] https://www.haskell.org/pipermail/ghc-devs/2015-January/007997.html + + Also of interest, https://www.haskell.org/pipermail/ghc- + devs/2015-January/007997.html New description: When characterizing `bytestring`'s `Builder` [[ https://github.com/kolmodin/binary/pull/65|interface]] I noticed that some benchmarks involving repeated appends (e.g. `Host endian/1MB of Word8 in chunks of 16`) perform inexplicably much worse than others. A glance at the assembly revealed that a large number of `Word8`s are being evaluated and saved to registers, only to be later stored. E.g., {{{#!asm # First we evaluate a number of Word8s, saving them in registers movzbl %bl,%ebx leaq 1(%r14),%rcx movzbl %cl,%ecx leaq 2(%r14),%rdx movzbl %dl,%edx leaq 3(%r14),%rsi movzbl %sil,%esi leaq 4(%r14),%r9 movzbl %r9b,%r9d leaq 5(%r14),%r10 movzbl %r10b,%r10d ... # Eventually we run out of registers and start spilling to the stack movq %rax,64(%rsp) leaq 7(%r14),%rax movzbl %al,%eax movq %rbx,72(%rsp) ... # Only after evaluating all of the needed words do we actually consume # them movq %rax,-152(%r12) movq 72(%rsp),%rax movq %rax,-144(%r12) movq 80(%rsp),%rax movq %rax,-136(%r12) movq 88(%rsp),%rax movq %rax,-128(%r12) ... movq %rsi,-56(%r12) movq %r9,-48(%r12) movq %r10,-40(%r12) movq %r11,-32(%r12) movq %r14,-24(%r12) }}} This is due to the fact that the `Word`s are bound outside of a case analysis and GHC is reluctant to push them inside of the branches. The float-in pass will only float a binding into a case if the value is "small" and at least one branch doesn't use the binding. Unfortunately the case expression in question has only two branches. This is demonstrated in the attached testcase. Also of interest, https://www.haskell.org/pipermail/ghc- devs/2015-January/007997.html -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 14:04:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 14:04:14 -0000 Subject: [GHC] #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure In-Reply-To: <046.d81887f1f82ecca81477b67bf0ea3214@haskell.org> References: <046.d81887f1f82ecca81477b67bf0ea3214@haskell.org> Message-ID: <061.3ab9ca9517db93007e865532b39a4f3a@haskell.org> #10012: Cheap-to-compute values aren't pushed into case branches inducing unnecessary register pressure -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 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 bgamari: @@ -1,4 +1,4 @@ - When characterizing `bytestring`'s `Builder` [[ - https://github.com/kolmodin/binary/pull/65|interface]] I noticed that some - benchmarks involving repeated appends (e.g. `Host endian/1MB of Word8 in - chunks of 16`) perform inexplicably much worse than others. A glance at + When characterizing `bytestring`'s `Builder` + [[https://github.com/kolmodin/binary/pull/65|interface]] I noticed that + some benchmarks involving repeated appends (e.g. `Host endian/1MB of Word8 + in chunks of 16`) perform inexplicably much worse than others. A glance at New description: When characterizing `bytestring`'s `Builder` [[https://github.com/kolmodin/binary/pull/65|interface]] I noticed that some benchmarks involving repeated appends (e.g. `Host endian/1MB of Word8 in chunks of 16`) perform inexplicably much worse than others. A glance at the assembly revealed that a large number of `Word8`s are being evaluated and saved to registers, only to be later stored. E.g., {{{#!asm # First we evaluate a number of Word8s, saving them in registers movzbl %bl,%ebx leaq 1(%r14),%rcx movzbl %cl,%ecx leaq 2(%r14),%rdx movzbl %dl,%edx leaq 3(%r14),%rsi movzbl %sil,%esi leaq 4(%r14),%r9 movzbl %r9b,%r9d leaq 5(%r14),%r10 movzbl %r10b,%r10d ... # Eventually we run out of registers and start spilling to the stack movq %rax,64(%rsp) leaq 7(%r14),%rax movzbl %al,%eax movq %rbx,72(%rsp) ... # Only after evaluating all of the needed words do we actually consume # them movq %rax,-152(%r12) movq 72(%rsp),%rax movq %rax,-144(%r12) movq 80(%rsp),%rax movq %rax,-136(%r12) movq 88(%rsp),%rax movq %rax,-128(%r12) ... movq %rsi,-56(%r12) movq %r9,-48(%r12) movq %r10,-40(%r12) movq %r11,-32(%r12) movq %r14,-24(%r12) }}} This is due to the fact that the `Word`s are bound outside of a case analysis and GHC is reluctant to push them inside of the branches. The float-in pass will only float a binding into a case if the value is "small" and at least one branch doesn't use the binding. Unfortunately the case expression in question has only two branches. This is demonstrated in the attached testcase. Also of interest, https://www.haskell.org/pipermail/ghc- devs/2015-January/007997.html -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 14:44:27 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 14:44:27 -0000 Subject: [GHC] #9214: UNPACK support for sum types In-Reply-To: <047.5213ff1d75a2abd5ff04d6c7bb79813f@haskell.org> References: <047.5213ff1d75a2abd5ff04d6c7bb79813f@haskell.org> Message-ID: <062.f787d992644768b593bf1adc77da7f27@haskell.org> #9214: UNPACK support for sum types -------------------------------------+------------------------------------- Reporter: mojojojo | Owner: osa1 Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1540 Wiki Page: UnpackedSumTypes | Phab:D1559 -------------------------------------+------------------------------------- Comment (by dfeuer): One special case is a GADT with one constructor that takes one argument without any class context. For instance {{{#!hs data Foo a = This a | That a a data Bar a b where Bar :: !(Foo a) -> Bar a a data Baz where Baz :: !(Foo a) -> Baz }}} It would be great to be able to unpack `Foo` into `Bar` and `Baz`. Matching on the `Bar` or `Baz` constructor would force its contents to WHNF and reveal the evidence/open the existential. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 15:06:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 15:06:40 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.ba64e7a5f4b44fee90090b3a737b622f@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): For the record, the unsafe foreign call in Cmm after sink assignments: {{{#!C (_s3N3::I64) = call "ccall" arg hints: [, , ,] result hints: [] third_arg(0, 0, 7457, %MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(%MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(%MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(%MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(I64[Sp + 16] * _s3MA::I64)) / 255 + %MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(%MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(%MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(I64[Sp + 24] * _s3MA::I64)) / 255 + %MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(%MO_UU_Conv_W32_W64(%MO_UU_Conv_W64_W32(I64[R1 + 7] * _s3MA::I64)) / 255 << 8)))) << 8)))) << 8)) + 255))); }}} Indeed edx doesn't seem to be in the clobber list when the code for the fourth argument is generated and we obtain: {{{#!asm 405dc9: ba 21 1d 00 00 mov $0x1d21,%edx ; 0x1d21 is the third arg 405dce: b9 ff 00 00 00 mov $0xff,%ecx 405dd3: 48 8b 5b 07 mov 0x7(%rbx),%rbx 405dd7: 48 0f af d8 imul %rax,%rbx 405ddb: 48 89 c2 mov %rax,%rdx ; problem ... 405e43: e8 82 03 00 00 callq 4061ca }}} The following note in compiler/cmm/CmmNode.hs seems to be relevant: {{{#!hs {- Note [Register parameter passing] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ On certain architectures, some registers are utilized for parameter passing in the C calling convention. For example, in x86-64 Linux convention, rdi, rsi, rdx and rcx (as well as r8 and r9) may be used for argument passing. These are registers R3-R6, which our generated code may also be using; as a result, it's necessary to save these values before doing a foreign call. This is done during initial code generation in callerSaveVolatileRegs in StgCmmUtils.hs. However, one result of doing this is that the contents of these registers may mysteriously change if referenced inside the arguments. This is dangerous, so you'll need to disable inlining much in the same way is done in cmm/CmmOpt.hs currently. We should fix this! -} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 15:57:02 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 15:57:02 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.89f25a10ea5c9b78b96f52c3dcb91b28@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Good catch. Shouldn't `nlHsIf` always use builtin syntax? Do we really need a new function? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 16:00:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 16:00:22 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.2f362e6c2fcb0b83bc5e02aaf6b1d132@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): > The `PprFlags` change might be easier if these functions took `PlatformConstants` as an argument (which would then become part of the `PprFlags` structure). Surely if the functions take `PlatformConstants` as an argument, then the Cmm stuff becomes independent of choices of `DynFlags` and `PprFlags`? So why would this flag make `PlatformConstants` part of `PprFlags`? And more generally, is that a good place for `PlatformContants`? Doesn't sound like a place I'd look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 16:44:58 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 16:44:58 -0000 Subject: [GHC] #11727: Allow one type signature for multiple pattern synonyms In-Reply-To: <049.0fba9aba358ebb714117eb166e00090c@haskell.org> References: <049.0fba9aba358ebb714117eb166e00090c@haskell.org> Message-ID: <064.e65055169532d1db62ae00e6b57d5567@haskell.org> #11727: Allow one type signature for multiple pattern synonyms -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | patsyn/should_compile/T11727 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2083 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => patsyn/should_compile/T11727 * differential: => Phab:D2083 * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 16:47:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 16:47:40 -0000 Subject: [GHC] #11062: Type families + hs-boot files = panic In-Reply-To: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> References: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> Message-ID: <062.0d62c1fe12e634437383d4906af83899@haskell.org> #11062: Type families + hs-boot files = panic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeFamilies | hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2215 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm going to respond here to the comments on Phab:D2215 because I think Trac comments are more likely to survive long term than Phab discussion. The question is: ''where should we check for consistency of imported type- family axioms?'' Currently it's done right after processing the import declarations of a module; but that's too early when we are concerned about consistency of axioms for a type family declared in this module. The patch does it late, after type checking all the local declarations. That's bad too, because all that type checking could be done with bogus overlapping family instances. I can think of two solutions. 1. Check for consistency of axioms for `F` ''right after `F` is defined''. That is, somewhere in `TcTyClsDecls.tcTyClGroup`. Notes: * We'd still need to check consistency for ''imported'' families before we start typechecking anything. * With this more incremental behaviour it might be harder to optimise the number of pairs compared (see `checkFamInstConsistency` module-pair stuff). But that doesn't matter since it is vanishingly rare for a type family defined in this module to have any imported instances whatsoever. 2. Make family-instance lookup complain if it finds two matching instances. * That would means we'd never make use of inconsistent instances, which would prevent strange error messages * We'd still need to do an aggressive `checkFamInstConsistency` check after type checking, to ensure consistency of instances that we didn't actually need when compiling this module (see the comments above `FamInst.checkFamInstConsistency`. I'm not sure which is best. I think (2) looks a bit easier, and is quite close to the proposed patch; just needs an overlap check on lookup. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 18:10:03 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 18:10:03 -0000 Subject: [GHC] #9577: String literals are wasting space In-Reply-To: <045.ae4d47715fdd8321ed459b0edd946522@haskell.org> References: <045.ae4d47715fdd8321ed459b0edd946522@haskell.org> Message-ID: <060.764bc26ea47dfc0488616fa4540e8073@haskell.org> #9577: String literals are wasting space -------------------------------------+------------------------------------- Reporter: xnyhps | Owner: xnyhps Type: bug | Status: patch Priority: low | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | codeGen/should_run/T9577 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1290 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * testcase: => codeGen/should_run/T9577 * differential: => Phab:D1290 * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 18:10:10 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 18:10:10 -0000 Subject: [GHC] #12081: TypeInType Compile-time Panic Message-ID: <047.ceeb8e791a978943694d6a174084488b@haskell.org> #12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I've been playing around with GHC 8.0.1-rc4 release and got a panic from the following (stripped down) code: {{{#!hs {-# LANGUAGE TypeInType #-} data Nat = Z | S Nat class C (n :: Nat) where type T n :: Nat f :: (a :: T n) }}} {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-apple-darwin): isInjectiveTyCon sees a TcTyCon T }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 18:20:43 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 18:20:43 -0000 Subject: [GHC] #1262: RecursiveDo in Template Haskell In-Reply-To: <062.2857e038d8ba06eaa6e83d19ada8ff7e@haskell.org> References: <062.2857e038d8ba06eaa6e83d19ada8ff7e@haskell.org> Message-ID: <077.d81ae5034b6a19a7ab46b941be8b4203@haskell.org> #1262: RecursiveDo in Template Haskell -------------------------------------+------------------------------------- Reporter: philip.weaver@? | Owner: mgsloan Type: feature request | Status: new Priority: normal | Milestone: ? Component: Template Haskell | Version: 6.6 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | th/TH_recursiveDo Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1979 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * owner: => mgsloan * testcase: => th/TH_recursiveDo * differential: => Phab:D1979 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 18:38:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 18:38:22 -0000 Subject: [GHC] #12079: segmentation fault in both ghci and compiled program involves gtk library In-Reply-To: <045.95402382996132bdb463dfe148e7d190@haskell.org> References: <045.95402382996132bdb463dfe148e7d190@haskell.org> Message-ID: <060.dafcd4988bf4761e61e204684c0f546d@haskell.org> #12079: segmentation fault in both ghci and compiled program involves gtk library ----------------------------------+-------------------------------------- Reporter: doofin | Owner: doofin Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Comment (by osa1): What are the dependencies of this program? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 18:44:13 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 18:44:13 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails Message-ID: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This, {{{#!hs import GHC.Prim import Data.Typeable main = print $ typeRep (Proxy :: Proxy RealWorld) }}} fails with, {{{ ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-unknown-linux): tyConRep RealWorld Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 18:48:52 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 18:48:52 -0000 Subject: [GHC] #10117: Change the scheme for reporting redundant imports In-Reply-To: <046.c9fe94ada7957e35dfd23f2313543a1b@haskell.org> References: <046.c9fe94ada7957e35dfd23f2313543a1b@haskell.org> Message-ID: <061.84dfb7abe58f8262eb91d9055d330efb@haskell.org> #10117: Change the scheme for reporting redundant imports -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: deprecate | warning Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Hello, I wrote a proposal and put it here: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/RelaxedUnusedImports -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:19:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:19:00 -0000 Subject: [GHC] #10117: Change the scheme for reporting redundant imports In-Reply-To: <046.c9fe94ada7957e35dfd23f2313543a1b@haskell.org> References: <046.c9fe94ada7957e35dfd23f2313543a1b@haskell.org> Message-ID: <061.21ae09d48fd79f499fec145c492118a6@haskell.org> #10117: Change the scheme for reporting redundant imports -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: deprecate | warning Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): A blogpost: http://www.yesodweb.com/blog/2016/05/are-unused-import- warnings-harmful And discussion: https://www.reddit.com/r/haskell/comments/4jvtmh/are_unused_import_warnings_harmful/ -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:26:33 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:26:33 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.e2fbc54ef1cb99e51e3f9f32fd5bafcb@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Sadly this is issue isn't quite fixed. See #12082. Happily the fix is quite simple. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:30:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:30:40 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.20917575664ffb78bf9d5bad606341c3@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_run/TypeOf, typecheck/should_run/TypeRep -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:31:13 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:31:13 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.85db29338f83c56e937abe47cfd13100@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by afarmer): Ah good point. I thought `nlHsIf` was used in more places. I'll just change it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:32:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:32:48 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.a3f8499a39109d2aff53e7110ecba845@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_run/TypeRep * priority: normal => high * differential: => Phab:D2240, Phab:D2239 * status: new => patch * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:56 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.52afdcc98887d33bc12f6e943feaeb03@haskell.org> #8308: Resurrect ticky code for counting constructor arity -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: mlen Type: task | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f0f0ac859257a0b528815adb61d3f024c8bafa16/ghc" f0f0ac8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f0f0ac859257a0b528815adb61d3f024c8bafa16" Fix histograms for ticky code This patch fixes Cmm generation required to produce histograms when compiling with -ticky flag, strips dead code from rts/Ticky.c and reworks it to use a shared constant in both C and Haskell code. Fixes #8308. Test Plan: T8308 Reviewers: jstolarek, simonpj, austin Reviewed By: simonpj Subscribers: mpickering, simonpj, bgamari, mlen, thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D931 GHC Trac Issues: #8308 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:56 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.4ce501f1d734d4f85b98a3ba4408e95b@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: akio Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"ba3e1fd37dc5004c4307ed205f6701b16faceb59/ghc" ba3e1fd/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ba3e1fd37dc5004c4307ed205f6701b16faceb59" Add a test for #11108 Reviewers: austin, simonmar, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2196 GHC Trac Issues: #11108 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:56 -0000 Subject: [GHC] #11555: catch _|_ breaks at -O1 In-Reply-To: <045.f4f0ac6dcd2c99c5fed8e1a116742666@haskell.org> References: <045.f4f0ac6dcd2c99c5fed8e1a116742666@haskell.org> Message-ID: <060.de97d068d4f407402b2e281e1aef91c6@haskell.org> #11555: catch _|_ breaks at -O1 -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc2 Resolution: fixed | 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:D1973 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f091218ae14a24f9dbd991794c2da6377364578b/ghc" f091218/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f091218ae14a24f9dbd991794c2da6377364578b" CLabel: Catch #11155 during C-- pretty-printing In #11555 we ended up generating references to the non-existence stg_ap_0_upd. Here we add asserts to verify that we don't generate references to non-existent selector or application symbols. It would likely also make sense to add further asserts during code generation, so we can catch the issue even closer to its source. Test Plan: Validate Reviewers: simonmar, austin, ezyang Reviewed By: simonmar, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2230 GHC Trac Issues: #11155 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:56 -0000 Subject: [GHC] #12059: Add primop to query for pinned-ness of a ByteArray In-Reply-To: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> References: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> Message-ID: <061.6a295bd589f4807ecf4b6501fe6013c5@haskell.org> #12059: Add primop to query for pinned-ness of a ByteArray -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2217 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"310371ff2d5b73cdcb2439b67170ca5e613541c0/ghc" 310371f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="310371ff2d5b73cdcb2439b67170ca5e613541c0" rts: Add isPinnedByteArray# primop Adds a primitive operation to determine whether a particular `MutableByteArray#` is backed by a pinned buffer. Test Plan: Validate with included testcase Reviewers: austin, simonmar Reviewed By: austin, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2217 GHC Trac Issues: #12059 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:56 -0000 Subject: [GHC] #10961: Make it possible to purely use the parser In-Reply-To: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> References: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> Message-ID: <064.42df7168df7cf59e0cf8d249f358f0c0@haskell.org> #10961: Make it possible to purely use the parser -------------------------------------+------------------------------------- Reporter: mpickering | Owner: dalaing Type: task | Status: patch Priority: low | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10143 | Differential Rev(s): D2208 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"39a2faa05fbbdb4a5ef0682afc42b5809cbd86ce/ghc" 39a2faa0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="39a2faa05fbbdb4a5ef0682afc42b5809cbd86ce" Rework parser to allow use with DynFlags Split out the options needed by the parser from DynFlags, making the parser more friendly to standalone usage. Test Plan: validate Reviewers: simonmar, alanz, bgamari, austin, thomie Reviewed By: simonmar, alanz, bgamari, thomie Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2208 GHC Trac Issues: #10961 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:57 -0000 Subject: [GHC] #11155: Trivial thunk gives "undefined reference to stg_ap_0_upd_info" In-Reply-To: <046.d8196c999608fededc5ef9d4e2e29843@haskell.org> References: <046.d8196c999608fededc5ef9d4e2e29843@haskell.org> Message-ID: <061.8718b266398bb44e384e3972de153edd@haskell.org> #11155: Trivial thunk gives "undefined reference to stg_ap_0_upd_info" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T11155 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f091218ae14a24f9dbd991794c2da6377364578b/ghc" f091218/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f091218ae14a24f9dbd991794c2da6377364578b" CLabel: Catch #11155 during C-- pretty-printing In #11555 we ended up generating references to the non-existence stg_ap_0_upd. Here we add asserts to verify that we don't generate references to non-existent selector or application symbols. It would likely also make sense to add further asserts during code generation, so we can catch the issue even closer to its source. Test Plan: Validate Reviewers: simonmar, austin, ezyang Reviewed By: simonmar, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2230 GHC Trac Issues: #11155 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:57 -0000 Subject: [GHC] #12063: Knot-tying failure when type-synonym refers to non-existent data In-Reply-To: <045.5d0eb098fb5e4585a85062e98ec9f2c1@haskell.org> References: <045.5d0eb098fb5e4585a85062e98ec9f2c1@haskell.org> Message-ID: <060.755fec1e4f78851a8793a5ffd3a0a674@haskell.org> #12063: Knot-tying failure when type-synonym refers to non-existent data -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: hs-boot Operating System: 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:"9dd04810b2ed51a5a4db9356858b7233329d6a45/ghc" 9dd0481/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9dd04810b2ed51a5a4db9356858b7233329d6a45" Add (broken) test for #12063. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2222 GHC Trac Issues: #12063 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 19:59:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 19:59:57 -0000 Subject: [GHC] #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' In-Reply-To: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> References: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> Message-ID: <060.a905326f0a9fc4c54b5343e6a5d24960@haskell.org> #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"5f1557eea2c1a5cf09321d9dc01070b6c068e2fa/ghc" 5f1557ee/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5f1557eea2c1a5cf09321d9dc01070b6c068e2fa" Failing test case for #12076. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2229 GHC Trac Issues: #12076 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 20:24:50 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 20:24:50 -0000 Subject: [GHC] #11777: RTS source code issues In-Reply-To: <046.3e69faecf0e4f69a5fcc7ec246409435@haskell.org> References: <046.3e69faecf0e4f69a5fcc7ec246409435@haskell.org> Message-ID: <061.7a3d694df5ba49ef739ddd46000c5fd3@haskell.org> #11777: RTS source code issues -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): I am in the process of cleaning up and generally improving the quality of the C code throughtout the RTS. At some point I intend to turn on more C compiler warning flags and that will undoubtedly turn up stuff like this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 20:44:55 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 20:44:55 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.1ae96a069b8220d326e6168900838ce8@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK. Please comment `nHsIf` to point out the significance of the `Nothing` and explain why that choice is important. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 20:50:52 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 20:50:52 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon Message-ID: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: Yes. | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnicodeSyntax #-} import Prelude.Unicode type Constrd a = Num a ? a data ADT a = ADT (Constrd a) ExistentiallyLost data ExistentiallyLost = ? u. TC u ? ExistentiallyLost u class u ~ (ATF1 u, ATF2 u) ? TC u where type ATF1 u ? * type ATF2 u ? * uie_handlers ? ADT Int -- Loop: -- - ADT depends on ExistentiallyLost (also the Constrd appendage) -- - ExistentiallyLost depends on TC -- - TC depends on ADT }}} --> {{{ [1 of 1] Compiling Main ( /home/deepfire/src/ghc-testcases /tyconroles-sees-a-tctycon-tyalias.hs, interpreted ) <- ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-unknown-linux): tyConRoles sees a TcTyCon Constrd Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 20:51:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 20:51:14 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.ad1dede4aeb905541e028891e285d857@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * Attachment "tyconroles-sees-a-tctycon-tyalias.hs" added. Test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 20:57:54 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 20:57:54 -0000 Subject: [GHC] #12081: TypeInType Compile-time Panic In-Reply-To: <047.ceeb8e791a978943694d6a174084488b@haskell.org> References: <047.ceeb8e791a978943694d6a174084488b@haskell.org> Message-ID: <062.07bcc18d9e2d960ed4ee818328620c72@haskell.org> #12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType Comment: GHC should never panic, so this is certainly a bug. However, your program is not type-correct: any type that classifies a runtime value must have kind `Type` (same as `*`). The type of `f` is given as `(a :: T n)`, which has kind `T n`, not `Type`. I'm not sure what your goal is here, but even without the panic, this program would be rejected by GHC. Thanks for reporting! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 21:12:58 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 21:12:58 -0000 Subject: [GHC] #11819: Full validation issues for 8.0.1 In-Reply-To: <046.98f1b24d795b2e584c0708ff1e99ff8b@haskell.org> References: <046.98f1b24d795b2e584c0708ff1e99ff8b@haskell.org> Message-ID: <061.d3766b8bd38050f377d5085e20a8c62e@haskell.org> #11819: Full validation issues for 8.0.1 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * milestone: 8.0.1 => 8.0.2 Comment: e02b8c8dadcc77c0c40d5346246f6a3b548258c2 should take care of a bunch of them -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 22:00:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 22:00:41 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.35bd75e202362392f4742226702a8424@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * owner: akio => * status: closed => new * resolution: fixed => Comment: That test is failing on Travis. Set `DYNAMIC_GHC_PROGRAMS=NO` in `mk/build.mk` to reproduce. Maybe somebody could have a look? {{{ =====> T11108(normal) 3321 of 5160 [0, 0, 0] +++ /tmp/ghctest/hXSuXa/1/2/3/./rts/T11108/T11108.run.stdout.normalised 2016-05-18 21:08:22.862178964 +0000 @@ -0,0 +1,10 @@ +1001 +1002 +1003 +1004 +1005 +1006 +1007 +1008 +1009 +1010 *** unexpected failure for T11108(normal) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 22:37:12 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 22:37:12 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.4c776d3b361981bf6ef89a9802172468@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dalaing): I've just been bringing everything used by the the pretty printer across from `DynFlags` into `PprFlags` up to this point. I agree that `PprFlags` isn't a great place for `PlatformConstants`, but at the moment the pretty printing code uses `PlatformConstants` (via the Outputable instances for Cmm, amongst others), so it seems like it is needed for this kind of direct translation (unless I'm misssing something here). At the moment the Cmm code in questions takes a `DynFlags` as an argument, solely to use the `PlatformConstants` contained within `DynFlags`. I've recently been playing with a `HasPlatformConstants` typeclass, with instances for `DynFlags` and `PprFlags`, since there are a few utility functions around the place that make of `PlatformConstants` via a `DynFlags` and may not be so easy to change. If `targetPlatform` joins that class it would open some other doors. Although that might be digging too far down the wrong rabbit hole. The separation of `PprFlags` from `DynFlags` also means that `sdocWithDynFlags` becomes `sdocWtihPprFlags`, and for some of the `Outputable` instances those flags are the only way they have access to certain kinds of information. That makes `PprFlags` into a bottleneck by which various Outputable instances gather information they need (including which of certain flags are on, which of certains extensions are enabled). It'd be nice to be able to address that. @ezyang mentioned in IRC that it might be easier to add another typeclass like `Outputable` but with access to `DynFlags`. I'll probably have a look at that next, but I'm worried that the work required to thread the `DynFlags` to where they are needed might be a neutral or net negative move. It would be nice to not have a random handful of flags and extensions in `PprFlags` though, so I'll definitely give it a go. In the short-term I'm focusing on getting everything but the Cmm code working, after which I'll give `OutputableWithDyn` a go. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 22:51:19 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 22:51:19 -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.606558ab5c3f919ef511cfafa4bb2316@haskell.org> #11143: Feature request: Add index/read/write primops with byte offset for ByteArray# -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.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 Mathnerd314): Can we instead have primops which take both an offset measured in bytes and an offset measured in terms of the type? {{{#!hs indexTYPEArray# :: ByteArray# -> Int# {-byte offset-} -> Int# {-type offset-} -> TYPE# readTYPEArray# :: MutableByteArray# s -> Int# {-byte offset-} -> Int# {-type offset-} -> State# s -> (#State# s, TYPE##) writeTYPEArray# :: MutableByteArray# s -> Int# {-byte offset-} -> Int# {-type offset-} -> TYPE# -> State# s -> State# s indexTYPEOffAddr# :: Addr# -> Int# {-byte offset-} -> Int# {-type offset-} -> TYPE readTYPEOffAddr# :: Addr# -> Int# {-byte offset-} -> Int# {-type offset-} -> State# s -> (#State# s, TYPE ##) writeTYPEOffAddr# :: Addr# -> Int# {-byte offset-} -> Int# {-type offset-} -> TYPE -> State# s -> State# s }}} All of these go through the `mkBasicIndexed{Read,Write}` functions, which take both a byte offset and a type offset, so it seems reasonable to expose that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 22:53:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 22:53:56 -0000 Subject: [GHC] #12081: TypeInType Compile-time Panic In-Reply-To: <047.ceeb8e791a978943694d6a174084488b@haskell.org> References: <047.ceeb8e791a978943694d6a174084488b@haskell.org> Message-ID: <062.cee8bcc6fba254cc78b4539750081a86@haskell.org> #12081: TypeInType Compile-time Panic -------------------------------------+------------------------------------- Reporter: MichaelK | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by MichaelK): goldfire, Thanks for the explanation. For background, I've been trying to make a 'good' wrapper type for `Natural` whose type is effectively `Nat`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 23:17:08 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 23:17:08 -0000 Subject: [GHC] #5556: Support pin-changing on ByteArray#s In-Reply-To: <046.1b81478cf84dfba9336774f0fe7553f1@haskell.org> References: <046.1b81478cf84dfba9336774f0fe7553f1@haskell.org> Message-ID: <061.bda081997a3cf9b33b641a6656c56d07@haskell.org> #5556: Support pin-changing on ByteArray#s -------------------------------------+------------------------------------- Reporter: pumpkin | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.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 Mathnerd314): #12059 adds an `isPinnedByteArray#` primop, but there is still no zero- copy method of pinning / unpinning. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 18 23:42:04 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 18 May 2016 23:42:04 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.ceb8b8c94afa240faee5e622a6880a35@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"6282bc31808e335cd8386dd20d469bc2457f84de/ghc" 6282bc31/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6282bc31808e335cd8386dd20d469bc2457f84de" Kill varSetElems in tidyFreeTyCoVars I haven't observed this to have an effect on nondeterminism, but tidyOccName appears to modify the TidyOccEnv in a way dependent on the order of inputs. It's easy enough to change it to be deterministic to be on the safe side. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2238 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 00:19:55 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 00:19:55 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.19cd05bda2b327a3d6eca2eafdd5fbe3@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"13e40f998e15a626a4212bde0987ddbc98b3f56f/ghc" 13e40f99/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="13e40f998e15a626a4212bde0987ddbc98b3f56f" Kill varEnvElts in tcPragExpr I had to refactor some things to take VarSet instead of [Var], but I think it's more precise this way. Test Plan: ./validate Reviewers: simonmar, simonpj, austin, bgamari, goldfire Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2227 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 03:55:48 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 03:55:48 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto Message-ID: <045.6138befcdfe66be8ab592f178622610b@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Documentation Unknown/Multiple | bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- 'ghc --help' suggests the use of -auto-all (see below), but according to [#r1 [1]], "-fprof-auto was known as -auto-all prior to GHC 7.4.1." I assume this means that GHC >= 7.4.1 should not mention -auto-all, and that -fprof-auto should be suggested instead. {{{ $ ghc --help ... -prof Compile for cost-centre profiling (add -auto-all for automagic cost-centres on all top-level functions) ... }}} [=#r1 [1]] https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/profiling.html#ftn.idp46686521726064 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 06:16:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 06:16:21 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.c4d9486e9ab3bf583a41618c9a7fdb81@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:03:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:03:18 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.a37cf284f2d354904f9595025a4f1bbb@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Just fooling around {{{#!hs pattern Mempty :: Monoid a => b -> forall x. a -> b pattern Mempty b <- (($ mempty) -> b) where Mempty b _ = b }}} {{{#!hs pattern Mempty :: b -> forall a. (Eq a, Monoid a) => a -> b pattern Mempty b <- (($ mempty @String) -> b) where Mempty b _ = b foo :: (forall a. (Eq a, Monoid a) => a -> b) -> b foo (Mempty x) = x }}} {{{ ghci> foo (== mempty) True ghci> :t Mempty 'a' Mempty 'a' :: forall {a}. (Monoid a, Eq a) => a -> Char ghci> :t foo (Mempty 'a') foo (Mempty 'a') :: Char ghci> foo (Mempty 'a') 'a' }}} or {{{#!hs type MEMPTY b = forall a. (Eq a, Monoid a) => a -> b pattern Mempty :: b -> MEMPTY b }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:37:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:37:45 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.1a456a3d58f5da5321542d97b935699f@haskell.org> #8308: Resurrect ticky code for counting constructor arity -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: mlen Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.7 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 Comment: This is now fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:41:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:41:25 -0000 Subject: [GHC] #12085: Premature defaulting and variable not in scope Message-ID: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> #12085: Premature defaulting and variable not in scope -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# Language RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UnboxedTuples, UnicodeSyntax, ViewPatterns, QuasiQuotes, TypeInType, ApplicativeDo, TypeApplications, AllowAmbiguousTypes #-} import Data.Kind todo :: forall (a::Type). (Read a, Show a) => String todo = show @a (read @a "42") }}} there are two things I notice, even with `AllowAmbiguousTypes` the `a` gets defaulted prematurely {{{ $ ghci -ignore-dot-ghci -fwarn-type-defaults /tmp/tl0z.hs GHCi, version 8.0.0.20160511: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tl0z.hs, interpreted ) Ok, modules loaded: Main. *Main> :t todo :1:1: warning: [-Wtype-defaults] Defaulting the following constraints to type ?()? (Read a0) arising from a use of ?it? at :1:1 (Show a0) arising from a use of ?it? at :1:1 foo :: String *Main> }}} instead of something like `todo :: forall a. (Read a, Show a) => String`, it can be applied to types {{{ *Main> foo @Int "42" *Main> foo @Float "42.0" }}} ---- The second thing is that if you want to add an argument independent of `a` {{{#!hs -- ghci> foo @Int False -- "100" -- ghci> foo @Float True -- "42.0" foo :: forall (a::Type). (Read a, Show a) => Bool -> String foo b = show @a (read @a (if b then "42" else "100")) }}} I found no way to define it as {{{#!hs -- ghci> foo False @Int -- "100" -- ghci> foo True @Float -- "42.0" foo :: Bool -> forall (a::Type). (Read a, Show a) => String foo b = show @a (read @a (if b then "42" else "100")) }}} to which GHC persists {{{ $ ghci -ignore-dot-ghci -fwarn-type-defaults /tmp/tl0z.hs GHCi, version 8.0.0.20160511: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tl0z.hs, interpreted ) /tmp/tl0z.hs:10:15: error: Not in scope: type variable ?a? /tmp/tl0z.hs:10:24: error: Not in scope: type variable ?a? Failed, modules loaded: none. Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:41:40 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:41:40 -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.1dd5841e9e21f7d30b93048c0833020e@haskell.org> #11827: InteractiveEval error handling gets a boot ModSummary instead of normal ModSummary -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 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: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.0.1 => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:42:58 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:42:58 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly In-Reply-To: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> References: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> Message-ID: <062.7a657eeeacb0c5143b3b2311d580025f@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly ----------------------------------------+------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+------------------------------- Changes (by bgamari): * cc: Trommler (added) * milestone: => 8.2.1 Comment: CCing Peter Trommler, who has done a great deal of work on PPC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:43:31 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:43:31 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.6b5867657726f8d6f3f7dee30431a7b9@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): No quantification needed if returning a type synonym: {{{#!hs type Arr = (->) pattern App :: b -> Arr Char b pattern App b <- (($ 'a') -> b) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 07:45:30 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 07:45:30 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" In-Reply-To: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> References: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> Message-ID: <066.8337653f3aab250438dca2fbddaa64d4@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * version: 8.1 => 8.0.1 * milestone: => 8.0.2 Comment: This also happens in 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 08:07:50 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 08:07:50 -0000 Subject: [GHC] #10424: Build path leaks into ABI hashes In-Reply-To: <046.a66bd75799cab79a67d2ea94ef806de6@haskell.org> References: <046.a66bd75799cab79a67d2ea94ef806de6@haskell.org> Message-ID: <061.6b450e17690286547b5200419860df8b@haskell.org> #10424: Build path leaks into ABI hashes -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #4012 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: niteria (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 08:16:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 08:16:19 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" In-Reply-To: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> References: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> Message-ID: <066.bb231f21e556002494765f933138671d@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:1 Iceland_jack]: > Doesn't happen if > > {{{#!hs > data I (a :: Type) (b :: k) > }}} also doesn't happen if {{{#!hs data I (a :: k) (b :: Type) }}} ---- Also test whether it panics on the `:kind!` command: {{{#!hs data I (a :: Type) (b :: Type) instance Category I where type Ob I = (~) Int }}} {{{ ghci> :kind! Ob I ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160511 for x86_64-unknown-linux): print_equality ~ Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 08:32:46 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 08:32:46 -0000 Subject: [GHC] #11780: GHC stage-2 build fails with "relocation R_X86_64_PC32 against `exitStaticPtrTable' can not be used when making a shared object" In-Reply-To: <050.f473e323a42852f79ac16c8258da73cc@haskell.org> References: <050.f473e323a42852f79ac16c8258da73cc@haskell.org> Message-ID: <065.5d610dce40bd9d3a0669dff68562b27c@haskell.org> #11780: GHC stage-2 build fails with "relocation R_X86_64_PC32 against `exitStaticPtrTable' can not be used when making a shared object" -------------------------------------+------------------------------------- Reporter: zadarnowski | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: #10671 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #10671 Comment: How did you figure out it has anything to do with `pragma GCC visibility push(hidden)`? Maybe you could submit a patch to [wiki:Phabricator], so others can test it? Please include a source comment, explaining the situation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 08:33:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 08:33:18 -0000 Subject: [GHC] #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override In-Reply-To: <043.3dbf7fc0356f7f2fdf48023120606ded@haskell.org> References: <043.3dbf7fc0356f7f2fdf48023120606ded@haskell.org> Message-ID: <058.da9eff987f740d298f18c0619b81f041@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Linking) | Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11780 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #11780 Comment: The submitter of #11780 may have found a solution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 08:40:38 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 08:40:38 -0000 Subject: [GHC] #11782: Teach ghc-pkg to read multiple registrations from command line In-Reply-To: <045.ebc2c49d6acd2454350338cc0cabaa8a@haskell.org> References: <045.ebc2c49d6acd2454350338cc0cabaa8a@haskell.org> Message-ID: <060.80ce120a6aef594fb4a5e8f10b2d7ea6@haskell.org> #11782: Teach ghc-pkg to read multiple registrations from command line -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: ghc-pkg | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => new * differential: Phab:D2080 => Comment: The patch was abandoned. I'm not sure if this ticket should stay open or not. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 09:04:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 09:04:49 -0000 Subject: [GHC] #11784: panic "hscCmmFile: no_mod" with `-v2 and above In-Reply-To: <044.29a67b6904270a19ef7b34462d19062e@haskell.org> References: <044.29a67b6904270a19ef7b34462d19062e@haskell.org> Message-ID: <059.0607fd75dae9b094240f53ab0b8e49b0@haskell.org> #11784: panic "hscCmmFile: no_mod" with `-v2 and above -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high Comment: This is a regression from 7.10.3. To reproduce, create an empty file called `Test.cmm`. Then run: {{{ $ ghc-8.0.1 -c -dcmm-lint Test.cmm -v2 ... ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160511 for x86_64-unknown-linux): hscCmmFile: no_mod }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 09:27:28 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 09:27:28 -0000 Subject: [GHC] #11062: Type families + hs-boot files = panic In-Reply-To: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> References: <047.7c49c2177d004f32c0696dfdb91a7434@haskell.org> Message-ID: <062.ed4650fc3b3cf5b1911fbbbba4ecd016@haskell.org> #11062: Type families + hs-boot files = panic -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: TypeFamilies | hs-boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2215 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Another minor advantage of (2) is that we could remove the {{{ ; no_conflict <- checkForConflicts inst_envs fam_inst }}} check in `FamINst.addLocalFamInsts`, because inconsistency would be caught by the later aggressive check, and would not cause a problem meanwhile. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 09:49:42 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 09:49:42 -0000 Subject: [GHC] #11429: Make unrecognised `-W` flags a warning rather than an error In-Reply-To: <042.40e6ba51faf91f5384d7881fa490aec2@haskell.org> References: <042.40e6ba51faf91f5384d7881fa490aec2@haskell.org> Message-ID: <057.a39fa7ef0253481b5456dd92852719d8@haskell.org> #11429: Make unrecognised `-W` flags a warning rather than an error -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature request | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 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: | Differential Rev(s): Phab:D1830, Wiki Page: Design/Warnings | Phab:D1942 -------------------------------------+------------------------------------- Comment (by thomie): Is it by design that `-Wno-unrecognised-warning-flags` should come first on the command line? {{{ $ ghc-8.0.1 Test.hs -Wno-unrecognised-warning-flags -Wfoo # no warning, as expected $ ghc-8.0.1 Test.hs -Wfoo -Wno-unrecognised-warning-flags on the commandline: warning: unrecognised warning flag: -Wfoo }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 09:59:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 09:59:25 -0000 Subject: [GHC] #11789: Flag suggestion does not always work In-Reply-To: <046.8956aee4cb2b3d361b8607128f32a5f4@haskell.org> References: <046.8956aee4cb2b3d361b8607128f32a5f4@haskell.org> Message-ID: <061.16be266fc477039bf90dcc1f6504414c@haskell.org> #11789: Flag suggestion does not always work -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Driver | 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: #11429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * version: 8.1 => 8.0.1 * related: => #11429 Comment: ghc-8.0.1 never suggests alternative spellings for misspelled //warning// flags. This should be fixed as well. With `-Wno-unrecognised-warning-flags` (#11429), unknown warning flags on the command line are now reported as warnings instead of errors, so they never reach the `unknownFlagsErr` function in `ghc/Main.hs`. The issue with `-fppr-cols=1000` vs `-dppr-cols=1000` is that the edit distance is too large. The flag passed to the fuzzy matcher should probably break at the `'='` character. From `fuzzyLookup` in `compiler/utils/Util.hs`: {{{ -- Work out an approriate match threshold: -- We report a candidate if its edit distance is <= the threshold, -- The threshhold is set to about a quarter of the # of characters the user entered -- Length Threshold -- 1 0 -- Don't suggest *any* candidates -- 2 1 -- for single-char identifiers -- 3 1 -- 4 1 -- 5 1 -- 6 2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:00:48 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:00:48 -0000 Subject: [GHC] #11429: Make unrecognised `-W` flags a warning rather than an error In-Reply-To: <042.40e6ba51faf91f5384d7881fa490aec2@haskell.org> References: <042.40e6ba51faf91f5384d7881fa490aec2@haskell.org> Message-ID: <057.622e46b46857c3a4a1e0718fcf0de6c1@haskell.org> #11429: Make unrecognised `-W` flags a warning rather than an error -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature request | Status: closed Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 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: | Differential Rev(s): Phab:D1830, Wiki Page: Design/Warnings | Phab:D1942 -------------------------------------+------------------------------------- Comment (by thomie): This feature broke the alternative spelling suggestions for misspelled warning flags, see #11789. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:06:00 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:06:00 -0000 Subject: [GHC] #11799: Legend for hpc markup colors In-Reply-To: <047.314ffbb861201aff98726d88b5f478b7@haskell.org> References: <047.314ffbb861201aff98726d88b5f478b7@haskell.org> Message-ID: <062.f2b781b06779394b10cc31fb43927773@haskell.org> #11799: Legend for hpc markup colors -------------------------------------+------------------------------------- Reporter: drathier | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Code Coverage | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer * component: Test Suite => Code Coverage Comment: Would you or somebody else like to submit a patch? The code is `utils/hpc` and `libraries/hpc`. Make sure the tests in `libraries/hpc/tests` and `testsuite/tests/hpc` still pass. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:08:28 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:08:28 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.d964e2f04b96d60eb17ff8c36687542f@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't understand all the details here but * I'm cautious about putting `PlatformConstants` into `PprFlags`. The latter should really just be about rendering. Perhaps the platform- constant info should be used when ''generating'' Cmm rather than when ''printing'' it? Or, if it absolutely must be done when printing it, maybe it should be an explicit argument to the printing code, which will make more apparent that something strange is going on. * Let's try to avoid a proliferation of type classes, especially if we always know which one we are in. e.g if all the calls to `(+)` were at a known type (like `Int`), then we could use `plusInt`, `plusDouble` etc, and all the type class gives us is some notational convenience. That's not true for `(+)` because we want `foo :: Num a => a -> a; foo x = x+x`, but it may be here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:09:57 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:09:57 -0000 Subject: [GHC] #11789: Flag suggestion does not always work In-Reply-To: <046.8956aee4cb2b3d361b8607128f32a5f4@haskell.org> References: <046.8956aee4cb2b3d361b8607128f32a5f4@haskell.org> Message-ID: <061.e66a0374330efaaaeb3e824e41f179d0@haskell.org> #11789: Flag suggestion does not always work -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Driver | 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: #11429 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * type: feature request => bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:15:18 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:15:18 -0000 Subject: [GHC] #11805: Ability to use record fields for automatic derivation of user-defined classes. In-Reply-To: <048.a8bf80140dcd34cf9bcb7b67908c1fa7@haskell.org> References: <048.a8bf80140dcd34cf9bcb7b67908c1fa7@haskell.org> Message-ID: <063.936e46e83209ba4fd7ea8337a0d6ec26@haskell.org> #11805: Ability to use record fields for automatic derivation of user-defined classes. -------------------------------------+------------------------------------- Reporter: Tientuine | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: Replying to [comment:2 Tientuine]: > It seems that Parts 1 and 3 of OverloadedRecords together accomplish everything I was looking for > I suppose this Ticket can be closed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:22:58 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:22:58 -0000 Subject: [GHC] #11808: nofib's cryptarithm1 regresses due to deferred inlining of Int's Ord operations In-Reply-To: <046.0de81d906e12dbb6e83ee1dc28c4efa9@haskell.org> References: <046.0de81d906e12dbb6e83ee1dc28c4efa9@haskell.org> Message-ID: <061.381446bf22ba320135fa24a3122a2c39@haskell.org> #11808: nofib's cryptarithm1 regresses due to deferred inlining of Int's Ord operations -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: task | Status: closed Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc3 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 thomie): * status: new => closed * resolution: => worksforme Comment: This was the change that perf.h.o reported: {{{ nofib/time/cryptarithm1 0.401 + 4.99% 0.421 seconds }}} Since cryptarithm1's runtime is currently under 0.4 seconds again on perf.h.o, I think it's safe to close this ticket, and call it an anomaly. {{{ nofib/time/cryptarithm1 0.397 = 0.397 seconds }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:27:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:27:29 -0000 Subject: [GHC] #11815: Data.List: Add a function to get consecutive elements (mapConsecutives) In-Reply-To: <047.a500f487fe67f459851db750fa12afab@haskell.org> References: <047.a500f487fe67f459851db750fa12afab@haskell.org> Message-ID: <062.61ee0c27484b72df6663e8bb084116b9@haskell.org> #11815: Data.List: Add a function to get consecutive elements (mapConsecutives) -------------------------------------+------------------------------------- Reporter: holmisen | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: libraries/base | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Libraries discussion: * https://mail.haskell.org/pipermail/libraries/2016-April/026899.html * https://mail.haskell.org/pipermail/libraries/2016-May/026994.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:44:24 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:44:24 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311825=3A_Pretty_printer_doesn=27t_d?= =?utf-8?q?isplay_functional_dependency_with_=E2=80=98=E2=86=92?= =?utf-8?b?4oCZ?= In-Reply-To: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> References: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> Message-ID: <066.8b31a956f8b347b52370cd007599a9b5@haskell.org> #11825: Pretty printer doesn't display functional dependency with ??? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: invalid | Keywords: unicode, | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * keywords: => unicode, UnicodeSyntax * resolution: => invalid Comment: Use `-fprint-unicode-syntax`. See #8959 for details. {{{ $ ghci GHCi, version 8.0.0.20160511: http://www.haskell.org/ghc/ :? for help Prelude> import Control.Monad.Free Prelude Control.Monad.Free> :set -fprint-unicode-syntax Prelude Control.Monad.Free> :i MonadFree class Monad m ? MonadFree (f ? * ? *) (m ? * ? *) | m -> f where wrap ? f (m a) ? m a default wrap ? (m ~ t n, Control.Monad.Trans.Class.MonadTrans t, MonadFree f n, Functor f) ? f (m a) ? m a -- Defined in ?Control.Monad.Free.Class? instance [safe] Functor f ? MonadFree f (Free f) -- Defined in ?Control.Monad.Free? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:52:08 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:52:08 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311825=3A_Pretty_printer_doesn=27t_d?= =?utf-8?q?isplay_functional_dependency_with_=E2=80=98=E2=86=92?= =?utf-8?b?4oCZ?= In-Reply-To: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> References: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> Message-ID: <066.597970586f3e4bcaad3af7a662da1d3a@haskell.org> #11825: Pretty printer doesn't display functional dependency with ??? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: unicode, | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: invalid => Comment: Hmm, I guess it should print: {{{ class Monad m ? MonadFree (f :: * ? *) (m :: * ? *) | m ? f where }}} Note the last arrow is a unicode symbol as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 10:53:28 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 10:53:28 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.e624352e5dc11eb810e140386d65c581@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dalaing): If `PprFlags` is to be strictly about rendering, then `SDocContext` either needs to continue to have `DynFlags` in it, or needs to carry around the `PlatformConstants`, the general flags, and a whole heap of other stuff from `DynFlags`. That's just to handle the existing use cases, where folks have used `sdocWithDynFlags` to get hold of info they need for pretty printing where that information isn't plumbed in from anywhere. We could shift the non-rendering information from `PprFlags` into `SDocContext` - but since `PprFlags` is only being used via an `SDocContext`, it wouldn't be much of a change from the way things are now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:03:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:03:52 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.875d71ff678ada5cc6e341e46269f724@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I am confused about the goal here. I thought the point of speparating out `PprFlags` is because pretty-printing only needs them, not lots of other `DynFlags` stuff. The Descipriotn says "At the moment, SDoc computations have full access to the entirety of DynFlags, despite only a minusculely small amount of the data structure being relevant to them." But if pretty printing ''does'' require a "whole heap of other stuff from `DynFlags`", why not leave it all the way it is? Perhaps it would be worth elaborating the Description to explain a bit more about goal and motivation? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:16:39 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:16:39 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.6ad451c702256224a44a8a9ae3ebfc07@haskell.org> #8308: Resurrect ticky code for counting constructor arity -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * owner: mlen => * resolution: fixed => Comment: It's failing on Linux, when validating. I have {{{ GhcLibHcOpts += -ticky }}} if it makes a difference. {{{ --- /tmp/ghctest/0MzM7D/1/2/3/./rts/T8308/T8308/T8308.stdout.normalised 2016-05-19 11:44:19.368052973 +0100 +++ /tmp/ghctest/0MzM7D/1/2/3/./rts/T8308/T8308/T8308.run.stdout.normalised 2016-05-19 11:44:19.368052973 +0100 @@ -1 +1 @@ -1 +8 *** unexpected failure for T8308(normal) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:23:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:23:21 -0000 Subject: [GHC] #12051: -.-> is accepted as a data constructor In-Reply-To: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> References: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> Message-ID: <064.26aeae7fa65bbcf8f5b3c1087f6c5cae@haskell.org> #12051: -.-> is accepted as a data constructor -------------------------------------+------------------------------------- Reporter: mpickering | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"72b677d31e39f417e4403b1b151f02913f483d32/ghc" 72b677d3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="72b677d31e39f417e4403b1b151f02913f483d32" Fix Trac #12051 A minor parser issue, allowing a mal-formed data constructor through. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:23:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:23:21 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" In-Reply-To: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> References: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> Message-ID: <066.02fdfd08fbd1a731da58eb9590c15c2a@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"ad7f12260e227e849b815f4959df0f886ecbe807/ghc" ad7f1226/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ad7f12260e227e849b815f4959df0f886ecbe807" Improve pretty-printing of equalities The previous pretty-printer didn't account for partially applied equalities, causing Trac #12041 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:23:21 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:23:21 -0000 Subject: [GHC] #12072: GHC panic on type wildcard in left-hand side of data family In-Reply-To: <047.e584aa3b910eba55b26f4ea236a6c9a5@haskell.org> References: <047.e584aa3b910eba55b26f4ea236a6c9a5@haskell.org> Message-ID: <062.c8cde80d9733e7fc613895a229cb0641@haskell.org> #12072: GHC panic on type wildcard in left-hand side of data family -------------------------------------+------------------------------------- Reporter: andreash | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"f9e90bcb202b164189d71535eafbb39577682ff2/ghc" f9e90bcb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f9e90bcb202b164189d71535eafbb39577682ff2" Improve documentation for type wildcards This docmentation improvement was triggered by Trac #12072 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:24:02 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:24:02 -0000 Subject: [GHC] #12041: GHC panics on "print_equality ~" In-Reply-To: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> References: <051.f878e9e3434ca62afd20bb52b1f57643@haskell.org> Message-ID: <066.524673f2ac28017266f0f7363a8338c3@haskell.org> #12041: GHC panics on "print_equality ~" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: indexed- | types/should_fail/T12041 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed-types/should_fail/T12041 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:24:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:24:44 -0000 Subject: [GHC] #12051: -.-> is accepted as a data constructor In-Reply-To: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> References: <049.0d8d1acd71f78d6ef22c8bcb91ac3c97@haskell.org> Message-ID: <064.31bb34cd6c6e3ae28553624f0c43d790@haskell.org> #12051: -.-> is accepted as a data constructor -------------------------------------+------------------------------------- Reporter: mpickering | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | parser/should_fail/T12051 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => parser/should_fail/T12051 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 11:55:22 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 11:55:22 -0000 Subject: [GHC] #10117: Change the scheme for reporting redundant imports In-Reply-To: <046.c9fe94ada7957e35dfd23f2313543a1b@haskell.org> References: <046.c9fe94ada7957e35dfd23f2313543a1b@haskell.org> Message-ID: <061.4862f18c78863b87053ee898122580cc@haskell.org> #10117: Change the scheme for reporting redundant imports -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: deprecate | warning Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I'm fine with making a change like this, if there's user consensus that it's a step forward. The wiki page says things like "arguably the 'redundant' import here is not a big deal, and we shouldn't complain too much about it". **But what is the ''principle'' here?** Is is this? * **Existing principle**: an import item should be reported as redundant if it can be deleted without changing the meaning of the program. * **New principle**: add "...unless it is the last explicit by-name import of an entity." Is that the intent? (It's not quite what the wiki page says because of subsumption... but try re-stating the principle, or modify subsumption.) I'd rather not try to support two different import-warning plans, controlled by a flag. That feels like overkill. I don't think anyone is suggesting that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:03:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:03:52 -0000 Subject: [GHC] #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer In-Reply-To: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> References: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> Message-ID: <060.eca82d19052e46360c3468d7b057cb7e@haskell.org> #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Template Haskell | Version: 8.0.1-rc2 Resolution: | Keywords: backpack hs- | boot Operating System: 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): Or alternatively re-typecheck the interface produced from the bit before the splice, just as we would do if the bit before the splice was in another module. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:14:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:14:03 -0000 Subject: [GHC] #11108: Weak references related crash In-Reply-To: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> References: <046.1b25661a2ebf5aa23d3a93aae541239e@haskell.org> Message-ID: <061.caf0a3161bc8285a796d804556c63ad2@haskell.org> #11108: Weak references related crash -------------------------------------+------------------------------------- Reporter: Saulzar | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Runtime System | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11746,#11972 | Differential Rev(s): Phab:D2189 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: I believe the issue was merely a missing expected output file. Sorry about that! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:27:36 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:27:36 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.76d5d7693e880947923c60d45ee5f31d@haskell.org> #8308: Resurrect ticky code for counting constructor arity -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I suspect the issue here is the fact that you built your libraries with ticky. The testcase is expecting to see a count of 1 in the `RET_NEW_hst_1` ticker, since it expects only the testcase itself to be instrumented. However, since you have also instrumented the libraries, the count is larger. In this sense the testcase as-written may be a bit fragile, although I can't think of any great way to fix this without compromising the precision of the check in the "normal" case (where the user has instrumented their libraries, which is by far more common). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:32:13 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:32:13 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.825b55b384a34f7c8e11f401e3d6e6da@haskell.org> #8308: Resurrect ticky code for counting constructor arity -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK. I can live with that. Can you put a comment in the source file or the all.T file to mention this point? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:36:48 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:36:48 -0000 Subject: [GHC] #11829: C++ does not catch exceptions when used with Haskell-main and linked by ghc In-Reply-To: <041.08b08e181b7a4c97ec0ab8f67992afaf@haskell.org> References: <041.08b08e181b7a4c97ec0ab8f67992afaf@haskell.org> Message-ID: <056.a325cf756e4d48e4672d4ed71d67397d@haskell.org> #11829: C++ does not catch exceptions when used with Haskell-main and linked by ghc -------------------------------------+------------------------------------- Reporter: pl | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: c++ | exceptions Operating System: MacOS X | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * os: Unknown/Multiple => MacOS X Comment: Nice testcase. Works fine on Linux though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:49:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:49:05 -0000 Subject: [GHC] #11831: Illegal Instruction when running byte operations in ghci In-Reply-To: <049.a982c5549fef96b96f64ffed229de453@haskell.org> References: <049.a982c5549fef96b96f64ffed229de453@haskell.org> Message-ID: <064.0aa1532b93a899adf039c5eaf9568937@haskell.org> #11831: Illegal Instruction when running byte operations in ghci -------------------------------------+------------------------------------- Reporter: Kritzefitz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #10375, #8896, | Differential Rev(s): #10863, #10969 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: erikd (added) * related: => #10375, #8896, #10863, #10969 Comment: Which version of llvm do you have installed? llvm-3.5.0 is known to be broken, and llvm-3.5.2 is known to be working. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:50:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:50:45 -0000 Subject: [GHC] #11832: Allow reify to yield types in the current declaration group In-Reply-To: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> References: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> Message-ID: <071.bdd2e4f70daf8e00c22df0c1ec54a018@haskell.org> #11832: Allow reify to yield types in the current declaration group -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: | Keywords: reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | TemplateHaskell/Reify | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: template-haskell reify => reify * component: Compiler => Template Haskell -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:51:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:51:23 -0000 Subject: [GHC] #11832: Allow reify to yield types in the current declaration group In-Reply-To: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> References: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> Message-ID: <071.a17d8177a6118dc24d0d235a2bb672c0@haskell.org> #11832: Allow reify to yield types in the current declaration group -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: | Keywords: reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | TemplateHaskell/Reify | -------------------------------------+------------------------------------- Changes (by thomie): * type: bug => feature request -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 12:58:45 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 12:58:45 -0000 Subject: [GHC] #11946: Provide a `make uninstall` target In-Reply-To: <047.5aaa45c0af37779f8ed9cbbdddf9b3be@haskell.org> References: <047.5aaa45c0af37779f8ed9cbbdddf9b3be@haskell.org> Message-ID: <062.82d6d4b343bab29f9f4437b13768888a@haskell.org> #11946: Provide a `make uninstall` target -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11191 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #11191 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 13:18:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 13:18:33 -0000 Subject: [GHC] #11950: Eventlog should include delimiters showing when the process writes to the .eventlog file In-Reply-To: <050.f7b767a40aed547dddf7eb969d5bbc90@haskell.org> References: <050.f7b767a40aed547dddf7eb969d5bbc90@haskell.org> Message-ID: <065.9e7eb325096c487dbf8e0c3335b8f716@haskell.org> #11950: Eventlog should include delimiters showing when the process writes to the .eventlog file -------------------------------------+------------------------------------- Reporter: JamesFisher | Owner: Type: feature request | 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Sounds reasonable. See [wiki:Newcomers], [wiki:WorkingConventions/FixingBugs] and [wiki:Phabricator] if you'd like to submit a patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 13:31:09 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 13:31:09 -0000 Subject: [GHC] #11956: on osx 10.11 haddock --hyperlinked-source on ghc source fails with file resource exhausted In-Reply-To: <045.fee2087a290e6aaf014fc48496728b47@haskell.org> References: <045.fee2087a290e6aaf014fc48496728b47@haskell.org> Message-ID: <060.1a75e589b80bba1f1a087ab4aec0c529@haskell.org> #11956: on osx 10.11 haddock --hyperlinked-source on ghc source fails with file resource exhausted ---------------------------------+-------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: duplicate | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: A solution is being worked on in https://github.com/haskell/haddock/issues/495. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 13:49:39 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 13:49:39 -0000 Subject: [GHC] #11967: Custom message when showing functions, comparing functions, ... In-Reply-To: <051.2df31b020a6410a714945f3799f1d6ad@haskell.org> References: <051.2df31b020a6410a714945f3799f1d6ad@haskell.org> Message-ID: <066.6a0f50238426439693bab8095fdf0e73@haskell.org> #11967: Custom message when showing functions, comparing functions, ... -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => CustomTypeErrors * cc: ekmett (added) * component: Compiler => Core Libraries Comment: Maybe the Core Libraries Committee can answer your question. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:04:56 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:04:56 -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.d526c0cd2a1d63ffe98306a5992b807d@haskell.org> #11827: InteractiveEval error handling gets a boot ModSummary instead of normal ModSummary -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 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: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"470def9a98a89ead3d162af9ea4dabb28a58dfed/ghc" 470def9a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="470def9a98a89ead3d162af9ea4dabb28a58dfed" Testsuite: fix T11827 (#11827) It didn't trigger the bug before. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:18:50 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:18:50 -0000 Subject: [GHC] #11980: Testsuite: run each test in its own /tmp directory, after copying required files In-Reply-To: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> References: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> Message-ID: <060.9b33c833396e6d80447e6c7bcaed5813@haskell.org> #11980: Testsuite: run each test in its own /tmp directory, after copying required files -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | 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:D1187 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:32:44 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:32:44 -0000 Subject: [GHC] #11988: All ghc-compiled binaries seg-fault (on Windows) In-Reply-To: <046.238ed052ab9f92c55320cffd9643fede@haskell.org> References: <046.238ed052ab9f92c55320cffd9643fede@haskell.org> Message-ID: <061.05d50dbe38a3aac6c053b1429cdc59bb@haskell.org> #11988: All ghc-compiled binaries seg-fault (on Windows) ---------------------------------+---------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: infoneeded Priority: highest | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by thomie): * cc: Phyx- (added) * status: new => infoneeded * os: Unknown/Multiple => Windows Comment: Is this still a problem? Which version of msys2 do you use (copy-paste the output of `uname -a`), and which version of Windows? I did a validate on Windows a few days ago, and everything worked fine. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:44:00 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:44:00 -0000 Subject: [GHC] #11988: All ghc-compiled binaries seg-fault (on Windows) In-Reply-To: <046.238ed052ab9f92c55320cffd9643fede@haskell.org> References: <046.238ed052ab9f92c55320cffd9643fede@haskell.org> Message-ID: <061.d28af4e256446e761393744751fa96fe@haskell.org> #11988: All ghc-compiled binaries seg-fault (on Windows) ---------------------------------+---------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: highest | Milestone: Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by simonpj): * status: infoneeded => closed * resolution: => fixed Comment: Ah... I think it turned out to be a bad patch which we rolled back. (I think simonmar then fixed it.) I'll close this Simon I think the revert was this {{{ commit 546f24e4f8a7c086b1e5afcdda624176610cbcf8 Author: Simon Peyton Jones Date: Thu Apr 28 15:20:43 2016 +0100 Revert "Use __builtin_clz() to implement log_2()" This reverts commit 24864ba5587c1a0447beabae90529e8bb4fa117a. rts/sm/BlockAlloc.c | 32 +++++++++++--------------------- 1 file changed, 11 insertions(+), 21 deletions(-) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:45:42 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:45:42 -0000 Subject: [GHC] #11989: Performance bug reading large-exponent float without explicit type In-Reply-To: <051.b1652ea713a69c873f7c28b572efbdef@haskell.org> References: <051.b1652ea713a69c873f7c28b572efbdef@haskell.org> Message-ID: <066.9c70e425f58dd560ce5a506dbb6fa04b@haskell.org> #11989: Performance bug reading large-exponent float without explicit type -------------------------------------+------------------------------------- Reporter: bpearlmutter | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Runtime | Test Case: 1e1000000 :: performance bug | (RealFloat a => a) Blocked By: | Blocking: Related Tickets: #9059, #5688, | Differential Rev(s): #5692, #7044 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #9059, #5688, #5692, #7044 Comment: This is a real problem, but reported before as #9059 and others. Not much has been done in recent times to try to solve it. I'm closing this ticket, to not let discussion spread over multiple tickets. Please reopen if you disagree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:47:46 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:47:46 -0000 Subject: [GHC] #9059: Excessive space usage while generating code for fractional literals with big exponents In-Reply-To: <049.6d8f94befa1b5f7c36b68d142aab3d6d@haskell.org> References: <049.6d8f94befa1b5f7c36b68d142aab3d6d@haskell.org> Message-ID: <064.007ba1f5778984eefb3886c582fb1b2c@haskell.org> #9059: Excessive space usage while generating code for fractional literals with big exponents -------------------------------------+------------------------------------- Reporter: basvandijk | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5688, #5692, | Differential Rev(s): #7044, #11989 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: j.waldmann (added) * related: #5688, #7044 => #5688, #5692, #7044, #11989 Comment: Also reported as #11989. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 14:51:23 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 14:51:23 -0000 Subject: [GHC] #11992: RFC, add Suc to base In-Reply-To: <051.4a66b63f2092688496d35b0af74a94d4@haskell.org> References: <051.4a66b63f2092688496d35b0af74a94d4@haskell.org> Message-ID: <066.f4d5eec28206d0ffafef953be553ccc4@haskell.org> #11992: RFC, add Suc to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 8.1 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 thomie): * status: new => closed * resolution: => wontfix Comment: Closing as wontfix, since the consensus seems to be to not add `Suc` to base. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:00:37 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:00:37 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.a88d0833b6fe2b78eed38299efd92e03@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I have a fix in the works -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:10:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:10:05 -0000 Subject: [GHC] #11995: Can't infer type In-Reply-To: <051.ecd85ed869df953db3456994d5047fa3@haskell.org> References: <051.ecd85ed869df953db3456994d5047fa3@haskell.org> Message-ID: <066.72eaee01a48e3ed708cc6470c565ec47@haskell.org> #11995: Can't infer type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | 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 thomie): * keywords: => TypeInType @@ -2,0 +2,5 @@ + {-# LANGUAGE RankNTypes, LambdaCase, TypeOperators, + TypeInType, UnicodeSyntax, GADTs #-} + + module T11995 where + New description: {{{#!hs {-# LANGUAGE RankNTypes, LambdaCase, TypeOperators, TypeInType, UnicodeSyntax, GADTs #-} module T11995 where import Data.Kind data NP :: forall k. (? ? Type) ? ([k] ? Type) where Nil :: NP f '[] (:*) :: f x ? NP f xs ? NP f (x:xs) newtype K a b = K a deriving Show unK (K a) = a h'collapse :: NP (K a) xs -> [a] h'collapse = \case Nil -> [] K x:*xs -> x : h'collapse xs }}} if we replace `xs` by an underscore: {{{ tJN0.hs:13:29-30: error: ? ? Could not deduce: (xs :: [?]) ~~ ((':) ? x xs :: [?]) from the context: ((k :: *) ~~ (? :: *), (t :: [k]) ~~ ((':) ? x xs :: [?])) bound by a pattern with constructor: :* :: forall k (f :: k -> *) (x :: k) (xs :: [k]). f x -> NP k k f xs -> NP k k f ((':) k x xs), in a case alternative at /tmp/tJN0.hs:13:3-9 ?xs? is a rigid type variable bound by a pattern with constructor: :* :: forall k (f :: k -> *) (x :: k) (xs :: [k]). f x -> NP k k f xs -> NP k k f ((':) k x xs), in a case alternative at /tmp/tJN0.hs:13:3 Expected type: NP ? k (K ? a) t Actual type: NP ? ? (K ? a) xs ? In the first argument of ?h'collapse?, namely ?xs? In the second argument of ?(:)?, namely ?h'collapse xs? In the expression: x : h'collapse xs ? Relevant bindings include xs :: NP ? ? (K ? a) xs (bound at /tmp/tJN0.hs:13:8) h'collapse :: NP ? k (K ? a) t -> [a] (bound at /tmp/tJN0.hs:11:1) Compilation failed. }}} Should it not be able to infer that? The Glorious Glasgow Haskell Compilation System, version 8.1.20160419 -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:12:08 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:12:08 -0000 Subject: [GHC] #11996: coverage checker iteration flag isn't documented outside of release notes! In-Reply-To: <045.ec2941f7f4396967d5f2e67aea7c3568@haskell.org> References: <045.ec2941f7f4396967d5f2e67aea7c3568@haskell.org> Message-ID: <060.77187217f8354a8fe07e1dae024f0a44@haskell.org> #11996: coverage checker iteration flag isn't documented outside of release notes! -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Documentation | 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 thomie): * status: new => closed * version: 8.0.1 => 8.0.1-rc1 * resolution: => fixed * milestone: => 8.0.1 Comment: Fixed in commit 5adf8f3b74a4ee11d594b9993493bed4e3521ce2: {{{ Author: Ben Gamari Date: Wed Apr 27 09:57:41 2016 +0200 Document -fmax-pmcheck-iterations a bit better }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:17:38 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:17:38 -0000 Subject: [GHC] #12085: Premature defaulting and variable not in scope In-Reply-To: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> References: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> Message-ID: <066.4495a54cb1f40b7128aa053fc957991b@haskell.org> #12085: Premature defaulting and variable not in scope -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): For the first part, `:type` instantiates, defaults, and re-generalises, because `:type ` works on an arbitrary expression ``. You may want `:info`. See the extensive debate on #11376. So I think everything is behaving as designed there. (You may want to propose a design change.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:23:24 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:23:24 -0000 Subject: [GHC] #12085: Premature defaulting and variable not in scope In-Reply-To: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> References: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> Message-ID: <066.155af635be0977b5a038e4ba54a598b4@haskell.org> #12085: Premature defaulting and variable not in scope -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): For the second, a type signature brings into scope ''only'' the type variables in the ''leading'' or top-level `forall`. So in {{{ foo :: forall (a::Type). (Read a, Show a) => Bool -> String foo b = ...type variable 'a' is in scope here... }}} But for ''non-top-level'' foralls, nothing is brought into scope {{{ bar :: Bool -> forall (a::Type). (Read a, Show a) => Bool -> String bar b = ...type variable 'a' is NOT NOT in scope here... }}} This is again by design, and I think it's documented. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:23:59 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:23:59 -0000 Subject: [GHC] #12000: static pointer in ghci In-Reply-To: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> References: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> Message-ID: <066.2cae8d44304a8bb485539a614348b02c@haskell.org> #12000: static pointer in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: facundo.dominguez (added) * keywords: => StaticPointers * component: Compiler => Documentation * related: => #9878 * type: bug => feature request Comment: From ticket:9878#comment:2: > The current StaticPointers implementation is not intended to be supported in GHCi. @facundo.dominguez (off-topic): `StaticPointers` is not listed in the [https://downloads.haskell.org/~ghc/master/users-guide/flags.html flag reference] of the User's Guide. You'd have to edit `utils/mkUserGuidePart/Options/Language.hs` to change that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:34:51 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:34:51 -0000 Subject: [GHC] #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? In-Reply-To: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> References: <045.c409ff477550f37962efe884c5d6ae24@haskell.org> Message-ID: <060.2897566d6b35c2d7202c5b054205fbba@haskell.org> #12011: should runRW# (of GHC.Magic) be reexported by GHC.Exts? -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: libraries/base | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: commit 763610e990207eaa143856fca411d5ad420651ed {{{ Author: Ben Gamari Date: Wed May 4 18:30:51 2016 +0200 base: Export runRW# from GHC.Exts Seems like this should be available in GHC.Exts. Thanks for @carter for pointing this out. Test Plan: Validate Reviewers: rwbarton, hvr, austin Reviewed By: austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D2171 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:36:07 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:36:07 -0000 Subject: [GHC] #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer In-Reply-To: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> References: <045.f36b0b7706a40f3b8c84a5fcb4001df6@haskell.org> Message-ID: <060.612f73d28894cf3480341843fcc29da4@haskell.org> #12034: Template Haskell + hs-boot = Not in scope during type checking, but it passed the renamer -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Template Haskell | Version: 8.0.1-rc2 Resolution: | Keywords: backpack hs- | boot Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): How do would you suggest we actually do the retypechecking? For example, in GhcMake we can retypecheck because we're responsible for managing the HPT; but the retypecheck would have to work within the typechecker code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:39:16 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:39:16 -0000 Subject: [GHC] #12013: CallStack is available from base 4.8, not 4.9 In-Reply-To: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> References: <044.aa556eb3429adeab29aed47f00c1d4e7@haskell.org> Message-ID: <059.e0c0c991818ee5cf0bbab7025ff71326@haskell.org> #12013: CallStack is available from base 4.8, not 4.9 -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: closed Priority: low | Milestone: 8.0.1 Component: Documentation | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.0.1 Comment: The @since annotation was fixed in 3ec8288a18d57fb856e257905897daae237a1d5d. Since there most likely won't be a 7.10.4, I'm closing this as fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 15:40:34 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 15:40:34 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.514fd7447a3cf4474b377bd50232c5e1@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): I think the more refined claim is something like, "SDoc computations only need a minusculely small amount of the data structure, EXCEPT for the use of pretty-printing in the code generator, which also needs access to platform constants." The code generation pretty-printing is a small part of the overall story, so it might be worth to somehow deal with it specially. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 16:04:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 16:04:25 -0000 Subject: [GHC] #11831: Illegal Instruction when running byte operations in ghci In-Reply-To: <049.a982c5549fef96b96f64ffed229de453@haskell.org> References: <049.a982c5549fef96b96f64ffed229de453@haskell.org> Message-ID: <064.d79aaab8b91819fc8a5c5d7e906fe0d0@haskell.org> #11831: Illegal Instruction when running byte operations in ghci -------------------------------------+------------------------------------- Reporter: Kritzefitz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #10375, #8896, | Differential Rev(s): #10863, #10969 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by Kritzefitz): According to the [https://buildd.debian.org/status/fetch.php?pkg=ghc&arch=armel&ver=7.10.3-7&stamp=1454152730 Debian buildd log] llvm-3.5.2 was used. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 16:32:04 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 16:32:04 -0000 Subject: [GHC] #11967: Custom message when showing functions, comparing functions, ... In-Reply-To: <051.2df31b020a6410a714945f3799f1d6ad@haskell.org> References: <051.2df31b020a6410a714945f3799f1d6ad@haskell.org> Message-ID: <066.ba3842896fca227ca7042df789509d48@haskell.org> #11967: Custom message when showing functions, comparing functions, ... -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): This can be considered a more general question: would any of the core libraries benefit from custom type errors? I doubt it is only useful for EDSLs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 16:39:07 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 16:39:07 -0000 Subject: [GHC] #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE In-Reply-To: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> References: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> Message-ID: <064.da207b4cb1f02a511fa5fcba9200b135@haskell.org> #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE -------------------------------------+------------------------------------- Reporter: Rufflewind | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: performance, | inline, bits 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 thomie): * failure: None/Unknown => Runtime performance bug Comment: I was confused at first. From `Data.Bits` in `libraries/base`, it is clear that `unsafeShiftL` and `unsafeShiftR` //are// marked `INLINE`: {{{ class Eq a => Bits a where ... unsafeShiftL :: a -> Int -> a {-# INLINE unsafeShiftL #-} x `unsafeShiftL` i = x `shiftL` i unsafeShiftR :: a -> Int -> a {-# INLINE unsafeShiftR #-} x `unsafeShiftR` i = x `shiftR` i .... }}} But I guess you're talking about these instances, which indeed aren't marked `INLINE`: {{{ instance Bits Int where ... (I# x#) `unsafeShiftL` (I# i#) = I# (x# `uncheckedIShiftL#` i#) (I# x#) `unsafeShiftR` (I# i#) = I# (x# `uncheckedIShiftRA#` i#) ... }}} {{{ instance Bits Word where ... (W# x#) `unsafeShiftL` (I# i#) = W# (x# `uncheckedShiftL#` i#) (W# x#) `unsafeShiftR` (I# i#) = W# (x# `uncheckedShiftRL#` i#) ... }}} There is a `Note` which suggests explicit `INLINE`s aren't necessary, except for `rotate`: {{{ {- Note [Constant folding for rotate] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The INLINE on the Int instance of rotate enables it to be constant folded. For example: ... All other Bits instances seem to inline well enough on their own to enable constant folding; for example 'shift': sumU . mapU (`shift` 3) . replicateU 10000000 $ (7 :: Int) goes to: Main.$wfold = \ (ww_sOb :: Int#) (ww1_sOf :: Int#) -> case ww1_sOf of wild_XM { __DEFAULT -> Main.$wfold (+# ww_sOb 56) (+# wild_XM 1); 10000000 -> ww_sOb } -} }}} But that `Note` is older (2008) than the commit that introduced `unsafeShiftL/R` (f1c593e01d740fde1202f84aa37ad4cc95ec7272, 2011). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 16:45:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 16:45:03 -0000 Subject: [GHC] #12037: Shutdown interacts badly with requestSync() In-Reply-To: <047.398f4a0ce014a24a50d904976ea2fe27@haskell.org> References: <047.398f4a0ce014a24a50d904976ea2fe27@haskell.org> Message-ID: <062.6189f3066bb36719549aa8fa78d05aef@haskell.org> #12037: Shutdown interacts badly with requestSync() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: Duplicate of #12038. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 16:45:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 16:45:27 -0000 Subject: [GHC] #12036: Shutdown interacts badly with requestSync() In-Reply-To: <047.45b4f7f4fb4a55030e0b3c5a109360b6@haskell.org> References: <047.45b4f7f4fb4a55030e0b3c5a109360b6@haskell.org> Message-ID: <062.36e0a3536de15dee3d30a4bef8a5d49e@haskell.org> #12036: Shutdown interacts badly with requestSync() -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 7.10.3 Resolution: duplicate | 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 thomie): * status: new => closed * resolution: => duplicate Comment: Duplicate of #12038. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 16:49:56 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 16:49:56 -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.de9abd832ad00bc9002cfd4c0216cacb@haskell.org> #12043: internal error: evacuate: strange closure type ----------------------------------+--------------------------------------- Reporter: mattchan | Owner: Type: bug | Status: new Priority: normal | Milestone: Research needed 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: | ----------------------------------+--------------------------------------- Comment (by thomie): Thank you for the report. If the problem is reproducible, please try to create a small testscase without dependencies. See [wiki:ReportABug#Fulldescription:whatinformationtoprovideinthebodyofyourbugreport]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 17:18:40 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 17:18:40 -0000 Subject: [GHC] #12085: Premature defaulting and variable not in scope In-Reply-To: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> References: <051.76fc7e40b6f054750b737970d17efed2@haskell.org> Message-ID: <066.db68f664463e7b13b6d9f9f2d8e22ddb@haskell.org> #12085: Premature defaulting and variable not in scope -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Ah they are both by design, interesting! Replying to [comment:1 simonpj]: > So I think everything is behaving as designed there. (You may want to propose a design change.) If I were to propose one, it would look something like this: {{{ ghci> :type todo todo :: String ghci> :set -XAllowAmbiguousTypes ghci> :type todo todo :: forall a. (Read a, Show a) => String }}} I haven't read #11376 (as well as being out of my depth) so I defer to the judgment of GHC developers. ---- Replying to [comment:2 simonpj]: > For the second, a type signature brings into scope ''only'' the type variables in the ''leading'' or top-level `forall`. So in I'm not familiar with the terminology, what is a ?''leading''? forall? > But for ''non-top-level'' foralls, nothing is brought into scope > > `[?]` > > This is again by design, and I think it's documented. Searching for ?''non-top-level'' foralls? only gives this thread, I guess there isn't a formal name for it. I found these references in the user guide > `[?]` it is possible to declare type arguments somewhere other than the beginning of a type? regarding `RankNTypes`. > That is, you can nest foralls arbitrarily deep in function arrows > The `-XRankNTypes` option is also required for any type with a forall or context to the right of an arrow (e.g. `f :: Int -> forall a. a->a`, or `g :: Int -> Ord a => a -> a`). but I didn't find information about scoping. Is there a fundamental reason this couldn't work: {{{#!hs one :: forall a. Int -> ... one in_scope = {- ?a? is in scope -} two :: Int -> forall a. ... two not_in_scope = {- ?a? is in scope -} }}} This is not a feature I desperately need -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 18:30:14 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 18:30:14 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.779cae1e2a45262b3c1be8190496d05f@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by carlostome): This bug seems to be solved in ghc version 8.1.20160519 (commit 296b8f1baef2e6c88a418bbc5ac8b1ced111c745). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:23:35 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:23:35 -0000 Subject: [GHC] #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 In-Reply-To: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> References: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> Message-ID: <062.800336bddfb5e9ddff37040feb891fa8@haskell.org> #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Compiler (Type checker) Comment: Here is a reduced testcase, without any dependencies. {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} module T12040 where import Data.Proxy -- src/Numeric/Units/Dimensional/Variant.hs data Variant = DQuantity -- src/Numeric/Units/Dimensional/Internal.hs class KnownVariant (v :: Variant) where data Dimensional v :: Dimension -> * -> * instance KnownVariant 'DQuantity where newtype Dimensional 'DQuantity d a = Quantity a type Quantity = Dimensional 'DQuantity -- ' -- src/Numeric/Units/Dimensional/Dimensions/TypeLevel.hs data Dimension = Dim -- TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt TypeInt class HasDynamicDimension a where class HasDynamicDimension a => HasDimension a where type KnownDimension (d :: Dimension) = HasDimension (Proxy d) -- src/Numeric/Units/Dimensional/Dynamic.hs class Demotable (q :: * -> *) where instance (KnownDimension d) => Demotable (Quantity d) where }}} {{{ $ ghc-7.10.3 T12040.hs -v0 # ok $ ghc-8.0.1 T12040.hs -v0 T12040.hs:45:10: error: ? The constraint ?KnownDimension d? is no smaller than the instance head (Use UndecidableInstances to permit this) ? In the instance declaration for ?Demotable (Quantity d)? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:31:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:31:27 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.bd3d893c419e12acafdb5d8cc2def166@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2e6433af56a97ad9c501648afa5e1d8c6c17f82a/ghc" 2e6433a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2e6433af56a97ad9c501648afa5e1d8c6c17f82a" testsuite: Add a TypeRep test Test Plan: Validate Reviewers: goldfire, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2239 GHC Trac Issues: #12082, #11120 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:31:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:31:27 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.6e20663155170e2eb60e408f7e1c7404@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2e6433af56a97ad9c501648afa5e1d8c6c17f82a/ghc" 2e6433a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2e6433af56a97ad9c501648afa5e1d8c6c17f82a" testsuite: Add a TypeRep test Test Plan: Validate Reviewers: goldfire, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2239 GHC Trac Issues: #12082, #11120 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:31:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:31:27 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.c63a8925365914172a33deb711d4dca3@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a88bb1b1518389817583290acaebfd6454aa3cec/ghc" a88bb1b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a88bb1b1518389817583290acaebfd6454aa3cec" Give lifted primitive types a representation As of D1774 everything in GHC.Prim has a representation generated for it by TcTypeable (see #11120). Unfortunately I evidently missed propagating this change to lifted primitive types. This patch fixes this (#12082). Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2240 GHC Trac Issues: #12082 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:31:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:31:27 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.5b9071d58e1223cba218dc999d0c3701@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a88bb1b1518389817583290acaebfd6454aa3cec/ghc" a88bb1b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a88bb1b1518389817583290acaebfd6454aa3cec" Give lifted primitive types a representation As of D1774 everything in GHC.Prim has a representation generated for it by TcTypeable (see #11120). Unfortunately I evidently missed propagating this change to lifted primitive types. This patch fixes this (#12082). Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2240 GHC Trac Issues: #12082 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:34:02 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:34:02 -0000 Subject: [GHC] #12044: Remove sortWith in favor of sortOn In-Reply-To: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> References: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> Message-ID: <058.13a99bc4525a47f5cb051bb6ef9e3146@haskell.org> #12044: Remove sortWith in favor of sortOn -------------------------------------+------------------------------------- Reporter: cblp | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #2659 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer * related: 2659 => #2659 Comment: Sure. Do something like this: * add a `DEPRECATED` pragma to `sortWith` * add an entry in the base release notes (`libraries/base/changelog.md`) that `sortWith` is deprecated * replace use of `sortWith` in the compiler, libraries, and testsuite by `sortOn` * replace the implementation of `sortWith` by a call to `sortOn` (optional) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:36:43 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:36:43 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.19d28d4e9a445a3d15621942e575fdb1@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:44:51 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:44:51 -0000 Subject: [GHC] #12044: Remove sortWith in favor of sortOn In-Reply-To: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> References: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> Message-ID: <058.c57799296e0e63fc594e69bc5fdc4afe@haskell.org> #12044: Remove sortWith in favor of sortOn -------------------------------------+------------------------------------- Reporter: cblp | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #2659 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): I don't understand what the "for good reasons" means in the following [https://mail.haskell.org/pipermail/libraries/2014-April/022502.html comment]: > that name just reminded me of GHC.Exts.sortWith: > http://hackage.haskell.org/package/base-4.6.0.1/docs/GHC- Exts.html#v:sortWith > > Which actually has the right type signature, but it's still implemented > as compare (f x) (f y), and for good reasons too in this case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:47:07 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:47:07 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows In-Reply-To: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> References: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> Message-ID: <060.cca7f0b3babe65e32f194b8c09be758b@haskell.org> #12010: Incorrect return types for recv() and send() on Windows -----------------------------------+-------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -----------------------------------+-------------------------------------- Comment (by Tamar Christina ): In [changeset:"1ee47c1bfa35c7be435adaec5c1fa9ec92cc776d/ghc" 1ee47c1b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1ee47c1bfa35c7be435adaec5c1fa9ec92cc776d" Use the correct return type for Windows' send()/recv() (Fix #12010) Summary: They return signed 32 bit ints on Windows, even on a 64 bit OS, rather than Linux's 64 bit ssize_t. This means when recv() returned -1 to signal an error we thought it was 4294967295. It was converted to an int, -1 and the buffer was memcpy'd which caused a segfault. Other bad stuff happened with send()s. See also note CSsize in System.Posix.Internals. Add a test for #12010 Test Plan: - GHC testsuite (T12010) - http-conduit test (https://github.com/snoyberg/http-client/issues/191) Reviewers: austin, hvr, bgamari, Phyx Reviewed By: Phyx Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2170 GHC Trac Issues: #12010 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:50:03 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:50:03 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows In-Reply-To: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> References: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> Message-ID: <060.8964a33f3414994dce5f503b4ddb3e70@haskell.org> #12010: Incorrect return types for recv() and send() on Windows -----------------------------------+-------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -----------------------------------+-------------------------------------- Changes (by Phyx-): * status: patch => closed * resolution: => fixed Comment: Thanks for the patch @enolan! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 19:51:36 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 19:51:36 -0000 Subject: [GHC] #12086: Allow omitting type family signature Message-ID: <051.4479e64a9c2f6df882fe56d59fa938bf@haskell.org> #12086: Allow omitting type family signature -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Syntactic issue. I find myself writing {{{#!hs type family Not a where Not False = True Not True = False }}} quite often, where the signature can be inferred it would be nice to be able to write ... to mean the same thing {{{#!hs type family Not False = True Not True = False }}} I know Richard has [https://www.reddit.com/r/haskell/comments/4amov2/the_future_of_dependent_haskell/d14xtjs a lot of things planned], I don't know how they mesh together ---- The desugaring is straightforward, for a type family with n-indexes, add a signature with n fresh type variables. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 21:27:35 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 21:27:35 -0000 Subject: [GHC] #12050: Allow haddock comments on non-record types In-Reply-To: <046.f6b7a2b632eb5ba65b0da9770c2d4b66@haskell.org> References: <046.f6b7a2b632eb5ba65b0da9770c2d4b66@haskell.org> Message-ID: <061.2e98d52e686072377c9f2e206a05fd1d@haskell.org> #12050: Allow haddock comments on non-record types -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8822 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #8822 Comment: Also mentioned in ticket:8822#comment:1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 21:27:55 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 21:27:55 -0000 Subject: [GHC] #8822: Allow -- ^ Haddock syntax on record constructors In-Reply-To: <047.9e31292a58062fe675a519afe89cb025@haskell.org> References: <047.9e31292a58062fe675a519afe89cb025@haskell.org> Message-ID: <062.faa0208aa8430e1227c12b12e7708908@haskell.org> #8822: Allow -- ^ Haddock syntax on record constructors -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9770, #12050 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: #9770 => #9770, #12050 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 21:42:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 21:42:05 -0000 Subject: [GHC] #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 In-Reply-To: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> References: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> Message-ID: <062.299b45d67a21a52f6b68615bf76b4ed1@haskell.org> #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dmcclean): Thanks thornie. Do you have a position on whether the issue is with 7.10.3 being too permissive or 8.0.1 being too restrictive? Beyond "it makes sense to me" and "it used to work", I don't have a good handle on how to go about deciding whether this code is actually in line with the rules. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 22:21:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 22:21:27 -0000 Subject: [GHC] #12087: Inconsistency in GADTs? Message-ID: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> #12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: GADTs | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs f :: Ord a => Eq a => a -> Bool f = ? }}} this is allowed but not in GADTs {{{#!hs data F a where MkF :: Ord a => Eq a => a -> F a -- :48:16: error: -- ? Data constructor ?MkF? returns type ?Eq a => a -> F a? -- instead of an instance of its parent type ?F a? -- ? In the definition of data constructor ?MkF? -- In the data type declaration for ?F? }}} not a big deal -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 22:36:27 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 22:36:27 -0000 Subject: [GHC] #12088: Promote data family instance constructors Message-ID: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> #12088: Promote data family instance constructors -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: #11348 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- In `TcEnv.hs` there is a note AFamDataCon: not promoting data family constructors. It states that we can't use a promoted data family instance constructor because we would have to interleave the checking of instances and data types. But with the fix of #11348, we now do exactly this. In the example from the note {{{#!hs data family T a data instance T Int = MkT data Proxy (a :: k) data S = MkS (Proxy 'MkT) }}} -ddump-rn-trace shows these groups {{{ rnTycl dependency analysis made groups [[data family T a_apG] [] [data instance T Int = MkT], [data Proxy (a_apF :: k_apE)] [] [], [data S = MkS (Proxy MkT)] [] []] }}} That's to say, the instance `T Int` will in fact be checked before `S`. So let's remove this restriction. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 19 22:55:36 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 19 May 2016 22:55:36 -0000 Subject: [GHC] #12000: static pointer in ghci In-Reply-To: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> References: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> Message-ID: <066.a6723adc5c16240576a3165878a70ed4@haskell.org> #12000: static pointer in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): I'm testing the master branch of GHC. I can reproduce this without using the static form. {{{ Prelude> c = 'a' Prelude> c :9:1: error: Variable not in scope: c }}} The crash reported later, I can't see. {{{ > let a = static id Prelude> a :6:1: error: ? No instance for (Data.Typeable.Internal.Typeable a0) arising from a use of ?it? ? In a stmt of an interactive GHCi command: print it }}} That said, the static pointers produced in GHCi can only be found later if they are created in compiled (and later loaded) modules. Entering a static form at the prompt won't make it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 01:09:14 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 01:09:14 -0000 Subject: [GHC] #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE In-Reply-To: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> References: <049.42a90b3c14f1511ae118c95e3415d83f@haskell.org> Message-ID: <064.5f8836500f6e3909fe4e79ccb3fdc908@haskell.org> #12022: unsafeShiftL and unsafeShiftR are not marked as INLINE -------------------------------------+------------------------------------- Reporter: Rufflewind | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: performance, | inline, bits 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 dfeuer): More importantly, the note is nonsense. Things not marked `INLINE` or (more strongly) `INLINE CONLIKE` sometimes won't be inlined even though they can be, once the code around them gets complicated enough. An operation like an unsafe shift, mask, etc., that's literally cheaper than a function call should *always* be inlined, unless I'm extremely confused. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 02:00:09 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 02:00:09 -0000 Subject: [GHC] #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 In-Reply-To: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> References: <047.3cd5b94812ad80cfce971203d7137096@haskell.org> Message-ID: <062.4b52d9946e32ef759f2b6d0cb9e09386@haskell.org> #12040: Code that builds on 7.8.4 and 7.10.3 but fails with requiring UndecidableInstances on 8.0.1-rc4 -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): It has something to do with the polykindedness of `Proxy`. This further- reduced version displays the same behavior but after replacing `Proxy` by `Maybe`, both versions of ghc accept the program. {{{ {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} module T12040 where import Data.Proxy newtype Dimensional c d a = Quantity a class HasDimension a class Demotable (q :: * -> *) instance (HasDimension (Proxy d)) => Demotable (Dimensional Int d) where }}} Maybe a consequence of kind and type arguments being treated uniformly in GHC's Core language now? Arguably neither behavior is wrong, since the instance termination checker is necessarily a conservative approximation. There's no real harm in just turning on UndecidableInstances. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 02:56:44 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 02:56:44 -0000 Subject: [GHC] #12089: :kind command allows unsaturated type family, Message-ID: <051.de4529f2a5c55440e217606da458c40d@haskell.org> #12089: :kind command allows unsaturated type family, -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs data A = B type family F a where F B = String infixr 9 `Compose` class (f (g x)) => (f `Compose` g) x instance (f (g x)) => (f `Compose` g) x }}} GHCi accepts {{{ ghci> :kind Compose Eq F Compose Eq F :: A -> Constraint }}} but when used in code it gets rejected {{{ -- tvI6.hs:13:8-33: error: ? -- ? The type family ?F? should have 1 argument, but has been given none -- ? In the type signature: -- foo :: (Eq `Compose` F) a => String -- Compilation failed. foo :: (Eq`Compose`F) a => String foo = undefined }}} Bug? Version 8.0.0.20160511 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 04:22:34 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 04:22:34 -0000 Subject: [GHC] #12079: segmentation fault in both ghci and compiled program involves gtk library In-Reply-To: <045.95402382996132bdb463dfe148e7d190@haskell.org> References: <045.95402382996132bdb463dfe148e7d190@haskell.org> Message-ID: <060.15b88a92a9d8c7300359cd42a06de5e0@haskell.org> #12079: segmentation fault in both ghci and compiled program involves gtk library ----------------------------------+-------------------------------------- Reporter: doofin | Owner: doofin Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Description changed by doofin: @@ -0,0 +1,8 @@ + dependency package: + + prelude + text + gtk + gtksourceview3 + fsnotify + @@ -2,0 +10,1 @@ + New description: dependency package: prelude text gtk gtksourceview3 fsnotify the simple source file: {{{#!hs {-# LANGUAGE OverloadedStrings #-} module Main where import Graphics.UI.Gtk import System.Glib.Signals import Graphics.UI.Gtk.SourceView import Graphics.UI.Gtk.SourceView.SourceGutter import Graphics.UI.Gtk.SourceView.SourceCompletion import Graphics.UI.Gtk.SourceView.SourceMark import Graphics.UI.Gtk.SourceView.SourceBuffer import Graphics.UI.Gtk.Multiline.TextBuffer import Graphics.UI.Gtk.Gdk.EventM import Control.Monad.Trans import System.FSNotify import System.Environment import Control.Concurrent (threadDelay) import Control.Monad (forever) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Tuple import Data.Tuple.HT import Control.Concurrent main=do args<-getArgs print args let filename=head args txt<-T.readFile filename gtk txt $ \srcbf->do notify $ \evt -> case evt of Modified fp _->if (T.unpack $ Prelude.last $ T.splitOn "/" $ T.pack fp)==filename then do txtnew<-T.readFile $ head args postGUIAsync $ textBufferSetText srcbf (txtnew::T.Text) else return () _->return () return () notify action=withManager $ \mgr-> do --mgr<-startManager watchTree mgr -- manager "." -- directory to watch (const True) -- predicate $ \evt->do print evt-- action action evt forever $ threadDelay 1000000 -- sleep forever (until interrupted) gtk inittext act= do initGUI window <- windowNew windowSetDefaultSize window 900 600 windowSetPosition window WinPosCenter srcbf<-sourceBufferNew Nothing sourceView <- sourceViewNewWithBuffer srcbf scrolledWindow <- scrolledWindowNew Nothing Nothing sourceViewSetShowLineNumbers sourceView True textViewSetWrapMode sourceView WrapWord textBufferInsertAtCursor srcbf ("fdsf"::String) textBufferSetText srcbf inittext scrolledWindow `containerAdd` sourceView window `containerAdd` scrolledWindow widgetShowAll window on sourceView keyPressEvent $ do kl<-eventKeyName liftIO $ putStr $ show $ kl liftIO $ mapM_ (\(x,y)->if x==kl then textBufferInsertAtCursor srcbf (y::String) else return ()) pairs return False on window deleteEvent $ liftIO mainQuit >> return False connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" forkIO $ do act srcbf --onDestroy window mainQuit mainGUI pairs=[("parenleft",")"),("[","]")] }}} the program runs ok before adding the line {{{#!hs connectGeneric "notify::cursor-position" False srcbf $ do print "adsfd" }}} it crashes both under ghc -make ,ghc -make -threaded and runhaskell then i run ghc thisfile.hs -debug gdb thisfile run somefile move the cursor inside the textview,then seg fault happened bt {{{ result: Program received signal SIGSEGV, Segmentation fault. 0x00007fffeea0f4f0 in ?? () (gdb) bt #0 0x00007fffeea0f4f0 in ?? () #1 0x00000000000002f5 in ?? () #2 0x0000000000000309 in ?? () #3 0x00007fffffff44f8 in ?? () #4 0x00007fffffff4458 in ?? () #5 0x00007fff04fe0101 in ?? () #6 0x0000000000000113 in ?? () #7 0x00000000000002e5 in ?? () #8 0x0000000001db00ac in ?? () #9 0x00007fffeea13a21 in ?? () #10 0x00007fffeeaf5010 in ?? () #11 0x0000000000a8d709 in base_GHCziIOziFD_zdfBufferedIOFD2_closure () #12 0x00007fffeea07942 in ?? () #13 0x0000000000a8593a in base_GHCziIOziBuffer_WriteBuffer_closure () #14 0x0000000000000800 in ?? () #15 0x0000000000000000 in ?? () }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 04:23:25 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 04:23:25 -0000 Subject: [GHC] #12079: segmentation fault in both ghci and compiled program involves gtk library In-Reply-To: <045.95402382996132bdb463dfe148e7d190@haskell.org> References: <045.95402382996132bdb463dfe148e7d190@haskell.org> Message-ID: <060.c96b73e08d8f070404d15adcf53f3bb6@haskell.org> #12079: segmentation fault in both ghci and compiled program involves gtk library ----------------------------------+-------------------------------------- Reporter: doofin | Owner: doofin Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Comment (by doofin): Replying to [comment:4 osa1]: > What are the dependencies of this program? I have added the dependent packages at the top -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 05:11:50 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 05:11:50 -0000 Subject: [GHC] #11740: RFC kind synonyms In-Reply-To: <051.0e72c4f1c3d54cad33a28cc5a9b7fcc3@haskell.org> References: <051.0e72c4f1c3d54cad33a28cc5a9b7fcc3@haskell.org> Message-ID: <066.e683306a401bfa9fc912941d9b44e1b2@haskell.org> #11740: RFC kind synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I'll jot down some [https://github.com/kylcarte/type- combinators/blob/master/src/Type/Family/Constraint.hs data points] for posteriority {{{#!hs -- | The empty 'Constraint'. type ?C = (() :: Constraint) type Fail = (True ~ False) }}} That library also has a lot of ideas -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 06:33:37 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 06:33:37 -0000 Subject: [GHC] #12090: Document Weverything/Wall/Wextra/Wdefault in user's guide Message-ID: <042.a992a290421e0ee585b6ffd4e20279f8@haskell.org> #12090: Document Weverything/Wall/Wextra/Wdefault in user's guide -------------------------------------+------------------------------------- Reporter: hvr | Owner: hvr Type: task | Status: new Priority: normal | Milestone: 8.0.2 Component: Documentation | Version: 8.0.1 Keywords: warnings | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: Design/Warnings -------------------------------------+------------------------------------- The user's guide needs to be updated to reflect the feature implemented in phab:D1850 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 07:56:52 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 07:56:52 -0000 Subject: [GHC] #12091: 'Variable not in scope" when using GHCi with `-fobject-code` Message-ID: <045.26ac03692a5d3a787c09461db77dd610@haskell.org> #12091: 'Variable not in scope" when using GHCi with `-fobject-code` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #7253 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Since b98ff3ccb14e36145404f075349c8689762a2913 was landed (#7253), you don't need `let` to define stuff in GHCi: {{{ $ ghci Prelude> x = 3 Prelude> x 3 }}} But when using `-fobject-code`, this results in an error: {{{ $ ghci -fobject-code Prelude> x = 3 Prelude> x :2:1: error: Variable not in scope: x }}} Very strange. CC @roshats, who implemented this feature, but the bug is probably in some part of the code he didn't touch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 07:58:07 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 07:58:07 -0000 Subject: [GHC] #12000: static pointer in ghci In-Reply-To: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> References: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> Message-ID: <066.41756980ff8028f2bd2d1c68b060728d@haskell.org> #12000: static pointer in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): I opened #12091 for the "Variable not in scope" issue, since it is not `-XStaticPointers` related. Is there anything left to do here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 08:32:17 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 08:32:17 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311825=3A_Pretty_printer_doesn=27t_d?= =?utf-8?q?isplay_functional_dependency_with_=E2=80=98=E2=86=92?= =?utf-8?b?4oCZ?= In-Reply-To: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> References: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> Message-ID: <066.6b773339e1bd83f76c28733399dd35f8@haskell.org> #11825: Pretty printer doesn't display functional dependency with ??? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: unicode, | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2243 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D2243 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 08:37:07 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 08:37:07 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311825=3A_Pretty_printer_doesn=27t_d?= =?utf-8?q?isplay_functional_dependency_with_=E2=80=98=E2=86=92?= =?utf-8?b?4oCZ?= In-Reply-To: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> References: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> Message-ID: <066.97a951ff792f560df7c00d0855fb9285@haskell.org> #11825: Pretty printer doesn't display functional dependency with ??? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: unicode, | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2243 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ?mer Sinan A?acan ): In [changeset:"08e47ca9849ab986d0367746a003754fcf0d4176/ghc" 08e47ca9/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="08e47ca9849ab986d0367746a003754fcf0d4176" FunDep printer: Fix unicode arrow The arrow should be printed in unicode arrow syntax when -fprint-unicode-syntax is used. Reviewers: austin, bgamari, thomie Reviewed By: thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2243 GHC Trac Issues: #11825 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 08:38:19 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 08:38:19 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2311825=3A_Pretty_printer_doesn=27t_d?= =?utf-8?q?isplay_functional_dependency_with_=E2=80=98=E2=86=92?= =?utf-8?b?4oCZ?= In-Reply-To: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> References: <051.0bf8a13abb59676639134e7a6349fbd1@haskell.org> Message-ID: <066.659cb6b43f9daf8ba32fbeff2f29f613@haskell.org> #11825: Pretty printer doesn't display functional dependency with ??? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: merge Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 Resolution: | Keywords: unicode, | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2243 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 11:32:44 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 11:32:44 -0000 Subject: [GHC] #12000: static pointer in ghci In-Reply-To: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> References: <051.df0580fca8642cac87b47bf4dfa5d3de@haskell.org> Message-ID: <066.e4bee4fead16c5ac516f1fbd76413670@haskell.org> #12000: static pointer in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: invalid | Keywords: | StaticPointers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9878 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * status: new => closed * resolution: => invalid Comment: Probably not. If the crash persisted after upgrading GHC, it would deserve another ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 11:55:23 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 11:55:23 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.6b8a354bdce0e6dec3e62a7cb9ee8686@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Rafbill): The bug is still present in this slightly modified example : {{{#!hs {-# LANGUAGE GADTs, TypeInType, RankNTypes #-} import Data.Kind data P (x :: k) = Q data A :: Type where B :: forall (a :: A). P a -> A }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 14:45:44 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 14:45:44 -0000 Subject: [GHC] #6135: Unboxed Booleans In-Reply-To: <043.cd549fe6606c2420e878b67f7f91b738@haskell.org> References: <043.cd549fe6606c2420e878b67f7f91b738@haskell.org> Message-ID: <058.a93d49195be479e0e4205ca0b78bea27@haskell.org> #6135: Unboxed Booleans -------------------------------------+------------------------------------- Reporter: benl | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.4.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | primops/should_run/T6135 Blocked By: 8103, 8103 | Blocking: Related Tickets: #605 | Differential Rev(s): Wiki Page: PrimBool | -------------------------------------+------------------------------------- Changes (by jstolarek): * wikipage: => PrimBool -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 15:23:40 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 15:23:40 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.5ad17bbeb5af0baec39c060969e7a891@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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): Here's a crazy idea, associate every pattern synonym with a data type (this could also be a new ?form? of pattern synonyms). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 15:27:43 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 15:27:43 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.6adda8c0a1b84c44da362b10f30dceed@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:22 Iceland_jack]: > Here's a crazy idea, associate every pattern synonym with a data type (this could also be a new ?form? of pattern synonyms). Yes, sometimes, but when pattern synonyms overlap (e.g., left and right views, with empty), life sucks again. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 16:04:14 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 16:04:14 -0000 Subject: [GHC] #12092: Wrong error message with TypeApplications Message-ID: <042.23e7528a6587761bdab9893e3f2305c4@haskell.org> #12092: Wrong error message with TypeApplications -------------------------------------+------------------------------------- Reporter: kwf | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I write the following: {{{#!hs {-# language TypeApplications #-} module Bug where huh = spam @Int }}} I expect to get the error: {{{ ? Variable not in scope: spam ? Perhaps you meant ?span? (imported from Prelude) }}} But instead, I get the error: {{{ ? Cannot apply expression of type ?t0? to a visible type argument ?Int? ? In the expression: spam @Int In an equation for ?huh?: huh = spam @Int }}} While it is //technically// true that I cannot apply an out-of-scope identifier to a visible type argument, this is probably the less useful error to receive. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 16:09:01 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 16:09:01 -0000 Subject: [GHC] #12093: Wrong argument count in error message with TypeApplications Message-ID: <042.a2f0b0d456bcb1b521ee22a5876338d5@haskell.org> #12093: Wrong argument count in error message with TypeApplications -------------------------------------+------------------------------------- Reporter: kwf | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I write: {{{#!hs {-# language TypeApplications #-} module Bug where wrong = id @Bool True False }}} I get the error: {{{ ? Couldn't match expected type ?Bool -> t? with actual type ?Bool? ? The function ?id? is applied to three arguments, but its type ?Bool -> Bool? has only one In the expression: id @Bool True False In an equation for ?bad?: bad = id @Bool True False ? Relevant bindings include bad :: t (bound at Bug.hs:8:1) }}} This seems to tell me that I ought to get rid of //two// of the arguments given to `id`, when in fact I only ought to remove //one//. In particular, the issue seems to be that GHC includes visibly applied type parameters in the count of "how many arguments is it applied to?" but does not include them in the count of "how many arguments does it have?" Suggested fix: in cases of this error with visible type application, report something akin to, "The function ?id? is applied to two type arguments and two value arguments, but its type has only one value argument." -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 17:22:30 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 17:22:30 -0000 Subject: [GHC] #12026: Pattern match failure in RnNames.hs In-Reply-To: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> References: <045.d07f9d8741d68e74ac677773a1b56b31@haskell.org> Message-ID: <060.8a70e5eb2a1f2d12f4035c8269d90d64@haskell.org> #12026: Pattern match failure in RnNames.hs -------------------------------------+------------------------------------- Reporter: davean | Owner: mpickering Type: bug | Status: merge Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2181 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 17:33:14 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 17:33:14 -0000 Subject: [GHC] #12052: Split ghc-boot so we have better dependency hygiene In-Reply-To: <045.061983f99253ceb1981e41093fe365b7@haskell.org> References: <045.061983f99253ceb1981e41093fe365b7@haskell.org> Message-ID: <060.b24d40d2776c0c8eb65056462135812c@haskell.org> #12052: Split ghc-boot so we have better dependency hygiene -------------------------------------+------------------------------------- Reporter: ezyang | Owner: bgamari Type: bug | Status: closed Priority: highest | Milestone: 8.0.1 Component: Core Libraries | Version: 8.0.1-rc4 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: Explained this a bit in [[https://ghc.haskell.org/trac/ghc/wiki/Commentary/Libraries#GHC- internallibrariesghc-boot-]] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 18:04:47 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 18:04:47 -0000 Subject: [GHC] #12092: Wrong error message with TypeApplications In-Reply-To: <042.23e7528a6587761bdab9893e3f2305c4@haskell.org> References: <042.23e7528a6587761bdab9893e3f2305c4@haskell.org> Message-ID: <057.87c402734dad8e526a22014cfb13afb1@haskell.org> #12092: Wrong error message with TypeApplications -------------------------------------+------------------------------------- Reporter: kwf | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): This is actually representative of a class of suboptimal errors that I've seen while working with GHC 8, in that an out-of-scope identifier can cause a cascade of obscure type errors. Perhaps we should prioritize out- of-scope identifiers above other type errors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 18:06:15 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 18:06:15 -0000 Subject: [GHC] #12093: Wrong argument count in error message with TypeApplications In-Reply-To: <042.a2f0b0d456bcb1b521ee22a5876338d5@haskell.org> References: <042.a2f0b0d456bcb1b521ee22a5876338d5@haskell.org> Message-ID: <057.69bc85c15810cac85c745fc600318a5f@haskell.org> #12093: Wrong argument count in error message with TypeApplications -------------------------------------+------------------------------------- Reporter: kwf | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeApplications -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 18:28:12 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 18:28:12 -0000 Subject: [GHC] #12091: 'Variable not in scope" when using GHCi with `-fobject-code` In-Reply-To: <045.26ac03692a5d3a787c09461db77dd610@haskell.org> References: <045.26ac03692a5d3a787c09461db77dd610@haskell.org> Message-ID: <060.f3ec4e9291a86015d6b77a09fe0d6ebd@haskell.org> #12091: 'Variable not in scope" when using GHCi with `-fobject-code` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | 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: #7253 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I know the problem but I don't know how to fix it. `let x = ...` is compiled as a statement, `x = ...` is compiled as a declaration. Desugarer dumps unused declarations if the target is not `HscInterpreted` or `HscNothing` (see `DynFlags.targetRetainsAllBindings`), but nothing like that is done for statements. Since `-fobject-code` sets target something other than `HscInterpreted` and `HscNothing`, `x` gets dumped. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 18:32:01 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 18:32:01 -0000 Subject: [GHC] #12091: 'Variable not in scope" when using GHCi with `-fobject-code` In-Reply-To: <045.26ac03692a5d3a787c09461db77dd610@haskell.org> References: <045.26ac03692a5d3a787c09461db77dd610@haskell.org> Message-ID: <060.ccb02deb07baff76f5e0c8c9d1144b8c@haskell.org> #12091: 'Variable not in scope" when using GHCi with `-fobject-code` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | 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: #7253 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): This is related with @roshats's patch as that's where we choose to compile `x = ...` as a statement instead of declaration (by "desugaring" it into `let x = ...`). Maybe we can do that now, unless someone has a better idea. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 20:57:59 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 20:57:59 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.25b211d080d96bc0005472129302673b@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2226 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Austin Seipp ): In [changeset:"43589f5cad0926ec077214e7a21a27ef7a8cfe25/ghc" 43589f5c/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="43589f5cad0926ec077214e7a21a27ef7a8cfe25" testsuite: add CmmSwitchTest for 32-bit platforms Move CmmSwitchTest to CmmSwitchTest64, because it's broken on 32-bit platforms. Create CmmSwitchTest32 that repeats CmmSwitchTest64 for platforms with 32-bit wordsize. Reviewed By: nomeata, austin, bgamari, thomie Differential Revision: https://phabricator.haskell.org/D2226 GHC Trac Issues: #11297 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 20 22:47:53 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 20 May 2016 22:47:53 -0000 Subject: [GHC] #11297: CmmSwitchTest is broken on 32-bit platforms In-Reply-To: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> References: <046.bbf13a9102a88aa01c80eb4863e3217f@haskell.org> Message-ID: <061.ec4bc8922688f02a12d01c1491772fd5@haskell.org> #11297: CmmSwitchTest is broken on 32-bit platforms -------------------------------------+------------------------------------- Reporter: bgamari | Owner: avd Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 7.10.3 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: CmmSwitchTest Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2226 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Thanks Alex! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 01:00:27 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 01:00:27 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.507f360013c0c4dd425d5a5867147c57@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Phab:D2247 Wiki Page: | -------------------------------------+------------------------------------- Changes (by afarmer): * differential: => Phab:D2247 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 02:04:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 02:04:46 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.aaa9915b32cfbe64baef50fc5b0e5128@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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): Replying to [comment:23 dfeuer]: > Yes, sometimes, but when pattern synonyms overlap (e.g., left and right views, with empty), life sucks again. `MINIMAL` pragmas allow conjunction as well as disjunction {{{#!hs {-# MINIMAL fromRational, (recip | (/)) #-} }}} If you want to express that `Empty` and `(:<|)` form a complete pattern but so does `Empty` and `(:|>)` {{{#!hs pattern Empty :: Seq.Seq a pattern Empty <- (Seq.viewl -> Seq.EmptyL) where Empty = Seq.empty pattern (:<|) :: a -> Seq.Seq a -> Seq.Seq a pattern x :<| xs <- (Seq.viewl -> x Seq.:< xs) where x :<| xs = x Seq.<| xs pattern (:|>) :: Seq.Seq a -> a -> Seq.Seq a pattern xs :|> x <- (Seq.viewr -> xs Seq.:> x) where xs :|> x = xs Seq.|> x }}} so what's stopping us from writing {{{#!hs {-# COMPLETE_PATTERNS (Empty, (:<|)) | (Empty, (:|>)) #-} }}} to mean just that? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 02:20:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 02:20:28 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.12d1326206a36a76c3f03b447c5da802@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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): The ticket mentions > Multiple pragmas are obviously combined with `||`, and there is an implicit `{-# COMPLETE_PATTERNS [] && (:) #-}` listing all real data constructors. which sounds like {{{#!hs {-# COMPLETE_PATTERNS Empty, (:<|) #-} {-# COMPLETE_PATTERNS Empty, (:|>) #-} }}} would equal what I proposed (if I got the precedence right) {{{#!hs {-# COMPLETE_PATTERNS Empty, (:<|) | Empty, (:|>) #-} }}} ---- Tangent: The second part (?there is an implicit `{-# COMPLETE_PATTERNS [] && (:) #-}` listing all real data constructors.?) sounds awful similar to this part of the [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/pragmas.html users guide]: > If no MINIMAL pragma is given in the class declaration, it is just as if a pragma > {{{#!hs > {-# MINIMAL op1, op2, ..., opn #-} > }}} > was given, where the `opi` are the methods > a. that lack a default method in the class declaration, and > b. whose name that does not start with an underscore (c.f. -fwarn- missing-methods, Section 4.8, ?Warnings and sanity-checking?). As I understand it means that when the user defines {{{#!hs data ABC = A | B | C }}} it is as if the she had also written `{-# COMPLETE_PATTERNS A, B, C #-}`. Would this work with GADTs? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 03:46:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 03:46:32 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures Message-ID: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: pattern | Operating System: Unknown/Multiple synonyms | Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following program is rejected by ghc-8.0.1: {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE PatternSynonyms #-} module Foo where import GHC.Exts (Int#) pattern Zero :: Int# -- commenting out this line works pattern Zero <- 0# }}} {{{ % ghc-stage2 unlifted-pattern-synonym.hs [1 of 1] Compiling Foo ( unlifted-pattern-synonym.hs, unlifted-pattern-synonym.o ) unlifted-pattern-synonym.hs:7:17: error: ? Expecting a lifted type, but ?Int#? is unlifted ? In the type ?Int#? }}} Commenting out the type signature removes the error. GHC 7.10.3 accepts this program, with and without the type signature. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 05:17:42 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 05:17:42 -0000 Subject: [GHC] #12095: GHC and LLVM don't agree on what to do with byteSwap16# Message-ID: <052.819038532472d3051449ad4890ff8793@haskell.org> #12095: GHC and LLVM don't agree on what to do with byteSwap16# -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 (LLVM) | Keywords: codegen, llvm | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider this test case (taken from [https://github.com/well-typed/binary- serialise-cbor/issues/67 here] and lightly modified to work on big/little endian machines): {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE CPP #-} module Main ( main -- :: IO () ) where #include "ghcconfig.h" import GHC.Prim import GHC.Word data T = T !Addr# t :: T #ifndef WORDS_BIGENDIAN t = T "\xcf\xb1"# #else t = T "\xb1\xcf"# #endif grabWord16 :: T -> Word64 grabWord16 (T addr#) = W64# (byteSwap16# (indexWord16OffAddr# addr# 0#)) trip :: Int trip = fromIntegral (grabWord16 t) main :: IO () main = print trip }}} With GHC 7.10.3 using the NCG, the results given are correct: {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.10.3 $ ghc -Wall -fforce-recomp -O2 Issue67.hs && ./Issue67 [1 of 1] Compiling Main ( Issue67.hs, Issue67.o ) Linking Issue67 ... 53169 }}} This also is the same on GHC 8.0.1 using the NCG, on both PowerPC and AMD64 as well. This answer is correct: `53169` is `0xCFB1` in hex, so the `byteSwap16#` primitive correctly works to decode the swapped-endian number. However, the story is not the same with GHC 7.10.3+LLVM 3.5, or GHC 8.0.1+LLVM 3.7: {{{ $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.10.3 $ llc --version | head -2 LLVM (http://llvm.org/): LLVM version 3.5.2 $ ghc -Wall -fforce-recomp -O2 Issue67.hs -fllvm && ./Issue67 [1 of 1] Compiling Main ( Issue67.hs, Issue67.o ) Linking Issue67 ... -12367 }}} Note: {{{#!hs -12367 == (fromIntegral (53169 :: Word16) :: Int16) }}} The relevant snippet looks like this at the CMM level (GHC 7.10.3): {{{ ==================== Output Cmm ==================== [section "data" { Main.main2_closure: const Main.main2_info; const 0; const 0; const 0; }, section "readonly" { c3rq_str: I8[] [207,177] }, section "readonly" { c3rr_str: I8[] [207,177] }, Main.main2_entry() // [R1] { info_tbl: [(c3ru, label: Main.main2_info rep:HeapRep static { Thunk }), (c3rD, label: block_c3rD_info rep:StackRep [])] stack_info: arg_space: 8 updfr_space: Just 8 } {offset c3ru: ... c3ro: I64[Sp - 16] = stg_bh_upd_frame_info; I64[Sp - 8] = _c3rn::I64; (_c3rw::I64) = call MO_BSwap W16(%MO_UU_Conv_W16_W64(I16[c3rr_str])); I64[Sp - 24] = c3rD; R4 = GHC.Types.[]_closure+1; R3 = _c3rw::I64; R2 = 0; Sp = Sp - 24; call GHC.Show.$wshowSignedInt_info(R4, R3, R2) returns to c3rD, args: 8, res: 8, upd: 24; ... }}} Pre-optimized LLVM basic block: {{{ c3rB: %ln3sc = ptrtoint i8* @stg_bh_upd_frame_info to i64 %ln3sb = load i64** %Sp_Var %ln3sd = getelementptr inbounds i64* %ln3sb, i32 -2 store i64 %ln3sc, i64* %ln3sd, !tbaa !1 %ln3sf = load i64* %lc3rA %ln3se = load i64** %Sp_Var %ln3sg = getelementptr inbounds i64* %ln3se, i32 -1 store i64 %ln3sf, i64* %ln3sg, !tbaa !1 %ln3sh = ptrtoint %c3rE_str_struct* @c3rE_str$def to i64 %ln3si = inttoptr i64 %ln3sh to i16* %ln3sj = load i16* %ln3si, !tbaa !5 %ln3sk = zext i16 %ln3sj to i64 %ln3sl = trunc i64 %ln3sk to i16 %ln3sm = call ccc i16 (i16)* @llvm.bswap.i16( i16 %ln3sl ) %ln3sn = sext i16 %ln3sm to i64 store i64 %ln3sn, i64* %lc3rJ %ln3sp = ptrtoint void (i64*, i64*, i64*, i64, i64, i64, i64, i64, i64, i64)* @c3rQ_info$def to i64 %ln3so = load i64** %Sp_Var %ln3sq = getelementptr inbounds i64* %ln3so, i32 -3 store i64 %ln3sp, i64* %ln3sq, !tbaa !1 %ln3sr = ptrtoint i8* @ghczmprim_GHCziTypes_ZMZN_closure to i64 %ln3ss = add i64 %ln3sr, 1 store i64 %ln3ss, i64* %R4_Var %ln3st = load i64* %lc3rJ store i64 %ln3st, i64* %R3_Var store i64 0, i64* %R2_Var %ln3su = load i64** %Sp_Var %ln3sv = getelementptr inbounds i64* %ln3su, i32 -3 %ln3sw = ptrtoint i64* %ln3sv to i64 %ln3sx = inttoptr i64 %ln3sw to i64* store i64* %ln3sx, i64** %Sp_Var %ln3sy = bitcast i8* @base_GHCziShow_zdwshowSignedInt_info to void (i64*, i64*, i64*, i64, i64, i64, i64, i64, i64, i64)* }}} Post-optimized block (`opt --enable-tbaa=true -O2 out-llvm-orig.ll -o out- llvm.bc`): {{{ c3rB: ; preds = %c3rU %ln3s8 = ptrtoint i8* %ln3s7 to i64 %ln3sd = getelementptr inbounds i64* %Sp_Arg, i64 -2 store i64 ptrtoint (i8* @stg_bh_upd_frame_info to i64), i64* %ln3sd, align 8, !tbaa !5 %ln3sg = getelementptr inbounds i64* %Sp_Arg, i64 -1 store i64 %ln3s8, i64* %ln3sg, align 8, !tbaa !5 store i64 ptrtoint (void (i64*, i64*, i64*, i64, i64, i64, i64, i64, i64, i64)* @"c3rQ_info$def" to i64), i64* %ln3rZ, align 8, !tbaa !5 tail call cc10 void bitcast (i8* @base_GHCziShow_zdwshowSignedInt_info to void (i64*, i64*, i64*, i64, i64, i64, i64, i64, i64, i64)*)(i64* %Base_Arg, i64* %ln3rZ, i64* %Hp_Arg, i64 %R1_Arg, i64 0, i64 -12367, i64 add (i64 ptrtoint (i8* @ghczmprim_GHCziTypes_ZMZN_closure to i64), i64 1), i64 undef, i64 undef, i64 %SpLim_Arg) #0 ret void }}} Folds it right into a constant! I haven't spent time diagnosing this much further, yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 07:01:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 07:01:48 -0000 Subject: [GHC] #4370: Bring back monad comprehensions In-Reply-To: <046.49abdb223a4732cf8eac6690239b5924@haskell.org> References: <046.49abdb223a4732cf8eac6690239b5924@haskell.org> Message-ID: <061.5f866eb97c4adbd0c11cfac6972f3454@haskell.org> #4370: Bring back monad comprehensions -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: patch Priority: normal | Milestone: ? Component: Compiler | Version: 6.12.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:D2247 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2247 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 08:54:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 08:54:29 -0000 Subject: [GHC] #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' In-Reply-To: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> References: <045.45bfd5a6dee62b13780515de863d4289@haskell.org> Message-ID: <060.db3bb3a7b214f02e4277971babba7b76@haskell.org> #12076: "lazy" leads to undefined reference to `stg_ap_0_upd_info' -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ezyang): * owner: => ezyang -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 09:31:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 09:31:37 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures In-Reply-To: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> References: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> Message-ID: <058.0f1e3d2701ed1795f193b2912a025b4b@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: mpickering (added) * keywords: pattern synonyms => PatternSynonyms Comment: Also fails in HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 10:54:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 10:54:35 -0000 Subject: [GHC] #9298: ghc.exe: internal error: evacuate: strange closure type 365488164 In-Reply-To: <049.d765684266b06afdaa0f98beceafc02b@haskell.org> References: <049.d765684266b06afdaa0f98beceafc02b@haskell.org> Message-ID: <064.90c6b70c54f8fb840996614bef5316e0@haskell.org> #9298: ghc.exe: internal error: evacuate: strange closure type 365488164 ---------------------------------------+------------------------------ Reporter: Tominator2 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: worksforme | Keywords: Operating System: Windows | Architecture: x86 Type of failure: Compile-time crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------------+------------------------------ Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme Comment: Bug not reproducible, and hopefully fixed already. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 11:01:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 11:01:36 -0000 Subject: [GHC] #3333: GHCi doesn't load weak symbols In-Reply-To: <047.f7df20b3080234226b9f5744151738a8@haskell.org> References: <047.f7df20b3080234226b9f5744151738a8@haskell.org> Message-ID: <062.5681492ad5e22e45326fe03a26784151@haskell.org> #3333: GHCi doesn't load weak symbols -------------------------------------+------------------------------------- Reporter: heatsink | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 6.10.4 Resolution: fixed | Keywords: weak, dynamic | loading Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: This is now tracked in #11817. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 11:02:09 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 11:02:09 -0000 Subject: [GHC] #11817: Add proper support for weak symbols to the runtime linker In-Reply-To: <044.9d336eb495121fb8a216ccf15f54097a@haskell.org> References: <044.9d336eb495121fb8a216ccf15f54097a@haskell.org> Message-ID: <059.0d2537c7dc20863e58ddcc8a3937c6ef@haskell.org> #11817: Add proper support for weak symbols to the runtime linker -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/linking/T3333, | rts/T11223/T11223_weak* Blocked By: | Blocking: Related Tickets: #11223, #3333 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => ghci/linking/T3333, rts/T11223/T11223_weak* * related: #11223 => #11223, #3333 Comment: Previous discussion in #3333. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 11:19:30 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 11:19:30 -0000 Subject: [GHC] #12077: T8761 (Make pattern synonyms work with Template Haskell) is failing on Travis In-Reply-To: <045.60294a744526480b093ee47fef543bec@haskell.org> References: <045.60294a744526480b093ee47fef543bec@haskell.org> Message-ID: <060.455492b8f7f915501d236fa3c918bd14@haskell.org> #12077: T8761 (Make pattern synonyms work with Template Haskell) is failing on Travis -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8761 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"8e929744eb332eed878aa2b334beea435d30ddfd/ghc" 8e92974/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8e929744eb332eed878aa2b334beea435d30ddfd" Testsuite: mark T8761 expect_broken #12077 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 11:21:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 11:21:43 -0000 Subject: [GHC] #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) (was: T8761 (Make pattern synonyms work with Template Haskell) is failing on Travis) In-Reply-To: <045.60294a744526480b093ee47fef543bec@haskell.org> References: <045.60294a744526480b093ee47fef543bec@haskell.org> Message-ID: <060.4a1fb96cf68a619684f4875c3d9a0529@haskell.org> #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8761 Blocked By: | Blocking: Related Tickets: #8761 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => th/T8761 @@ -1,2 +1,0 @@ - Note that Travis uses `DYNAMIC_GHC_PROGRAMS=NO`. - New description: First failure: https://travis-ci.org/ghc/ghc/builds/129738012 {{{ Actual stderr output differs from expected: --- ./th/T8761.stderr.normalised 2016-05-12 15:08:16.512921981 +0000 +++ ./th/T8761.comp.stderr.normalised 2016-05-12 15:08:16.512921981 +0000 @@ -1,7 +1,3 @@ -pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _) -pattern x1_0 Q2 x2_1 = ((x1_0, x2_1)) -pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where - Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3]) T8761.hs:(15,1)-(38,13): Splicing declarations do { [qx1, qy1, qz1] <- mapM (/ i -> newName $ "x" ++ show i) [1, 2, 3]; @@ -123,30 +119,6 @@ pattern Pup x <- MkUnivProv x pattern Puep :: forall a. forall b. Show b => a -> b -> (ExProv, a) pattern Puep x y <- (MkExProv y, x) -pattern T8761.P :: GHC.Types.Bool -pattern T8761.Pe :: () => forall (a0_0 :: *) . a0_0 -> T8761.Ex -pattern T8761.Pu :: forall (a0_0 :: *) . a0_0 -> a0_0 -pattern T8761.Pue :: forall (a0_0 :: *) . () => forall (b0_1 :: *) . - a0_0 -> b0_1 -> (a0_0, T8761.Ex) -pattern T8761.Pur :: forall (a0_0 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - a0_0 -> [a0_0] -pattern T8761.Purp :: forall (a0_0 :: *) (b0_1 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - GHC.Show.Show b0_1 => a0_0 -> b0_1 -> ([a0_0], T8761.UnivProv b0_1) -pattern T8761.Pure :: forall (a0_0 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - forall (b0_1 :: *) . a0_0 -> b0_1 -> ([a0_0], T8761.Ex) -pattern T8761.Purep :: forall (a0_0 :: *) . (GHC.Num.Num a0_0, - GHC.Classes.Eq a0_0) => - forall (b0_1 :: *) . GHC.Show.Show b0_1 => - a0_0 -> b0_1 -> ([a0_0], T8761.ExProv) -pattern T8761.Pep :: () => forall (a0_0 :: *) . GHC.Show.Show a0_0 => - a0_0 -> T8761.ExProv -pattern T8761.Pup :: forall (a0_0 :: *) . () => GHC.Show.Show a0_0 => - a0_0 -> T8761.UnivProv a0_0 -pattern T8761.Puep :: forall (a0_0 :: *) . () => forall (b0_1 :: *) . GHC.Show.Show b0_1 => - a0_0 -> b0_1 -> (T8761.ExProv, a0_0) T8761.hs:(107,1)-(111,25): Splicing declarations do { infos <- mapM reify *** unexpected failure for T8761(normal) }}} @bollmann added the test in c079de3c43704ea88f592e441389e520313e30ad. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 12:20:21 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 12:20:21 -0000 Subject: [GHC] #12095: GHC and LLVM don't agree on what to do with byteSwap16# In-Reply-To: <052.819038532472d3051449ad4890ff8793@haskell.org> References: <052.819038532472d3051449ad4890ff8793@haskell.org> Message-ID: <067.c0a6e7c7ffaf49bbf4e2b6d1d3194865@haskell.org> #12095: GHC and LLVM don't agree on what to do with byteSwap16# -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: codegen, llvm Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): `byteSwap16#` is defined in `primops.txt.pp` as {{{ primop BSwap16Op "byteSwap16#" Monadic Word# -> Word# {Swap bytes in the lower 16 bits of a word. The higher bytes are undefined. } }}} So, I don't see the problem. Writing `W64# (byteSwap16# (...))` is wrong. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 12:28:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 12:28:15 -0000 Subject: [GHC] #11817: Add proper support for weak symbols to the runtime linker In-Reply-To: <044.9d336eb495121fb8a216ccf15f54097a@haskell.org> References: <044.9d336eb495121fb8a216ccf15f54097a@haskell.org> Message-ID: <059.e262687659854f4e05286be697a72ba6@haskell.org> #11817: Add proper support for weak symbols to the runtime linker -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Runtime System | Version: 8.1 (Linker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/linking/T3333, | rts/T11223/T11223_weak* Blocked By: | Blocking: Related Tickets: #11223, #3333 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by chetant): * cc: chetant@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 12:56:47 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 12:56:47 -0000 Subject: [GHC] #4370: Bring back monad comprehensions In-Reply-To: <046.49abdb223a4732cf8eac6690239b5924@haskell.org> References: <046.49abdb223a4732cf8eac6690239b5924@haskell.org> Message-ID: <061.1986a3f5a52d4a7c05132ec421ae23f7@haskell.org> #4370: Bring back monad comprehensions -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: patch Priority: normal | Milestone: ? Component: Compiler | Version: 6.12.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:D2247 Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): bgamari, is this the right ticket? Also, I wish we wouldn't reopen issues with mega-threads like this one. Monad comprehensions were indeed added and you have to get to comment:62 to find out what the open part of this ticket is. Much easier for posterity if the remaining piece is split out into its own ticket once the comment thread has become very long. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 14:21:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 14:21:13 -0000 Subject: [GHC] #12096: Attach stacktrace information to SomeException Message-ID: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> #12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: | Version: 8.0.1 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Now (base 4.9.0.0) ErrorCall contain field for stacktrace information and error fills it. If you add field for stacktrace information to SomeException {{{#!hs data SomeException where SomeExceptionWithLocation :: Exception e => String -> e -> SomeException pattern SomeException :: () => Exception e => e -> SomeException pattern SomeException err <- SomeExceptionWithLocation _ err where SomeException err = SomeExceptionWithLocation "" err }}} and will fills it in throw {{{#!hs throw :: (HasCallStack, Exception e) => e -> a throw e = unsafeDupablePerformIO $ do stack <- currentCallStack raise# (CallStackException e $ if stack /= [] then prettyCallStack ?callStack ++ "\n" ++ renderStack stack else prettyCallStack ?callStack) }}} it will be more useful for ghci users. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 15:58:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 15:58:48 -0000 Subject: [GHC] #12097: DuplicateRecordFields appears not to work in Message-ID: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> #12097: DuplicateRecordFields appears not to work in -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This was [[https://www.reddit.com/r/haskell/comments/4kdzp2/announce_its_official_ghc_801_has_been_released/d3e6syc|noticed]] shortly after the 8.0.1 announcement, {{{ $ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/ben/.ghci ?> :set -XDuplicateRecordFields ?> data A = A {test :: String} ?> data B = B {test :: Int} ?> print $ test (A 42) :4:9: error: Ambiguous occurrence ?test? It could refer to either the field ?test?, defined at :2:13 or the field ?test?, defined at :3:13 }}} The equivalent program compiled as a module works as expected, {{{#!hs {-# LANGUAGE DuplicateRecordFields #-} module Hi where data A = A { test :: Int } deriving Show data B = B { test :: String } deriving Show x :: A x = A 42 main = do print x print (A 42) }}} {{{ $ runghc Hi.hs A {test = 42} A {test = 42} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 15:58:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 15:58:58 -0000 Subject: [GHC] #12097: DuplicateRecordFields appears not to work in GHCi (was: DuplicateRecordFields appears not to work in) In-Reply-To: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> References: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> Message-ID: <061.7808b6fab0927ee98061ee6e9a649605@haskell.org> #12097: DuplicateRecordFields appears not to work in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 16:00:01 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 16:00:01 -0000 Subject: [GHC] #8779: Exhaustiveness checks for pattern synonyms In-Reply-To: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> References: <046.b910d807e2ecf5838df4d05d7ec88278@haskell.org> Message-ID: <061.b94c1209209f5f80e912c0019f4a2a8f@haskell.org> #8779: Exhaustiveness checks for pattern synonyms -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.1 checker) | Keywords: Resolution: | 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): Keeping in mind that the patterns `Empty`, `(:<|)`, `(:|>)` may be defined in separate modules. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 16:03:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 16:03:28 -0000 Subject: [GHC] #12097: DuplicateRecordFields appears not to work in GHCi In-Reply-To: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> References: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> Message-ID: <061.ae4cf7ad88db67d7fa6388a298124b04@haskell.org> #12097: DuplicateRecordFields appears not to work in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | 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 bgamari): * status: new => closed * resolution: => invalid Comment: Never mind; in my haste I completed butchered the example. If one adds a `test` in the expressions being printed above typechecking fails in when compiled as a module as well. This is likely due to the typechecking limitations of `DuplicateRecordFields`, although I don't know for certain. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 16:10:03 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 16:10:03 -0000 Subject: [GHC] Batch modify: #10547 Message-ID: <20160521161003.CF42D3A2FF@ghc.haskell.org> Batch modification to #10547 by bgamari: milestone to 8.0.2 Comment: Ticket retargeted after milestone closed -- Tickets URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 16:44:57 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 16:44:57 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows In-Reply-To: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> References: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> Message-ID: <060.0e723110909204f8416e64cf77a96b79@haskell.org> #12010: Incorrect return types for recv() and send() on Windows -----------------------------------+-------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -----------------------------------+-------------------------------------- Comment (by Tamar Christina ): In [changeset:"a1f3bb8ca454f05fa35cb6b5c64e92f640380802/ghc" a1f3bb8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a1f3bb8ca454f05fa35cb6b5c64e92f640380802" Fix failing T12010 Summary: T12010 seems to be failing because it can't find the correct paths. This gives the test some more qualified paths. Test Plan: make TEST=12010 Reviewers: hvr, bgamari, austin, thomie Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D2252 GHC Trac Issues: #12010 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 17:12:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 17:12:11 -0000 Subject: [GHC] #12095: GHC and LLVM don't agree on what to do with byteSwap16# In-Reply-To: <052.819038532472d3051449ad4890ff8793@haskell.org> References: <052.819038532472d3051449ad4890ff8793@haskell.org> Message-ID: <067.de6430d5fd26f350c2b60a57aee6f9a7@haskell.org> #12095: GHC and LLVM don't agree on what to do with byteSwap16# -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (LLVM) | Version: 8.0.1 Resolution: | Keywords: codegen, llvm Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thoughtpolice): So you're right, and the answer with a little more detail is outlined in this commit in `binary-serialise-cbor`: https://github.com/well-typed /binary-serialise-cbor/commit/d419bdeae39e56531a86d8208e059967863cffb5 if you want to read the novel about the LLVM view of things. But something about this ticket still makes me feel uneasy. In particular, is there ever any reason why the `byteSwap#` primitives do not imply such narrowing themselves? Are the high bits always undefined even if they were set before? Why does it imply that - because it can't be guaranteed on every platform? (e.g. on x86 I believe should be able to do a 16-byte swap with simply `xchg ah, al` which should not modify the high 16 bits, that's legitimate). Obviously not every primitive can be safe (if it pokes memory or whatever), but I'm strongly in favor of having sensible behavior for operators like this which are merely 'bit fiddling' wrapped up in a single MachOp, as opposed to leaving them to have 'undefined behavior' like in C which is just a cue for clever compilers to torment me more than they need to. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 17:50:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 17:50:45 -0000 Subject: [GHC] #12098: Typechecker regression in 8.0.1 Message-ID: <048.fc96fa58e363f2cf0ea88f15909e8d50@haskell.org> #12098: Typechecker regression in 8.0.1 -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Windows Architecture: x86 | Type of failure: GHC rejects | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code: {{{#!hs {-# LANGUAGE IncoherentInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE RoleAnnotations #-} module Bug where import Data.Proxy (Proxy(..)) import GHC.Prim (coerce) class Throws e where {} type role Throws representational newtype Wrap e a = Wrap { unWrap :: Throws e => a } coerceWrap :: Wrap e a -> Wrap (Catch e) a coerceWrap = coerce newtype Catch a = Catch a instance Throws (Catch e) where {} unthrow :: Proxy e -> (Throws e => a) -> a unthrow _ = unWrap . coerceWrap . Wrap }}} compiles fine with ghc 7.10.2 but fails with ghc 8.0.1 with error: {{{ Bug.hs:25:13: error: * Could not deduce (Throws e) from the context: Throws e0 bound by a type expected by the context: Throws e0 => a at Bug.hs:25:13-38 Possible fix: add (Throws e) to the context of the type signature for: unthrow :: Proxy e -> (Throws e => a) -> a * In the expression: unWrap . coerceWrap . Wrap In an equation for `unthrow': unthrow _ = unWrap . coerceWrap . Wrap }}} This code is extracted from blog post http://www.well- typed.com/blog/2015/07/checked-exceptions/ and gist https://gist.github.com/edsko/f1f566f77422398fba7d -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 18:14:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 18:14:35 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.5a58395881542446b6612fb4e77cef0f@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Phab:D2247 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"527ed7246a35fe8bab89c7c582084cd20661018a/ghc" 527ed72/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="527ed7246a35fe8bab89c7c582084cd20661018a" Fix deriving Ord when RebindableSyntax is enabled Deriving clauses (Ord especially) generated if-expressions with nlHsIf which were subject to RebindableSyntax. This changes nlHsIf to generate concrete if-expressions. There was also an error about calling tagToEnum# at a polymorphic type, which is not allowed. Fixing nlHsIf didn't fix this for some reason, so I generated a type ascription around the call to tagToEnum#. Not sure why the typechecker could not figure this out. Test Plan: Added a test, ran validate. Reviewers: simonpj, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2247 GHC Trac Issues: #12080 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 21:37:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 21:37:28 -0000 Subject: [GHC] #12080: RebindableSyntax breaks deriving Ord In-Reply-To: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> References: <046.7713328ee376d4dd3d58a4520e76a2fb@haskell.org> Message-ID: <061.8e16700af57a415b2ff945192255f154@haskell.org> #12080: RebindableSyntax breaks deriving Ord -------------------------------------+------------------------------------- Reporter: afarmer | Owner: afarmer Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11396 | Differential Rev(s): Phab:D2247 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 21:43:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 21:43:43 -0000 Subject: [GHC] #10961: Make it possible to purely use the parser In-Reply-To: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> References: <049.fcc8c76168c1ad7ed5e00c80467dcc18@haskell.org> Message-ID: <064.39873b113836d4c725792ab2c72010ff@haskell.org> #10961: Make it possible to purely use the parser -------------------------------------+------------------------------------- Reporter: mpickering | Owner: dalaing Type: task | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10143 | Differential Rev(s): Phab:D2208 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: patch => closed * differential: D2208 => Phab:D2208 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 21:44:50 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 21:44:50 -0000 Subject: [GHC] #11727: Allow one type signature for multiple pattern synonyms In-Reply-To: <049.0fba9aba358ebb714117eb166e00090c@haskell.org> References: <049.0fba9aba358ebb714117eb166e00090c@haskell.org> Message-ID: <064.bb03f26bc486767024ba0bda2d629a3f@haskell.org> #11727: Allow one type signature for multiple pattern synonyms -------------------------------------+------------------------------------- Reporter: mpickering | Owner: mpickering Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | patsyn/should_compile/T11727 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2083 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * owner: => mpickering -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 21:46:14 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 21:46:14 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.16707e7a8127944b857dd4c6a7b52bb1@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by seraphime): I can do it tomorrow. Should the message suggest also that -auto-all is deprecated ? If it is so, maybe ghc should emit a warning message if -auto-all is used. The latest docs don't mention the -auto-all flag [1]. Older docs on the other hand describe it in the same terms as the newer -fprof-auto flag.[2] [1] https://downloads.haskell.org/~ghc/7.2-latest/docs/html/users_guide /prof-compiler-options.html [2] https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/prof- compiler-options.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 22:03:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 22:03:45 -0000 Subject: [GHC] #12099: ghc --show-options lists invalid flags Message-ID: <046.f661034fd1c4aa2ec7129aadde9e360e@haskell.org> #12099: ghc --show-options lists invalid flags -------------------------------------+------------------------------------- Reporter: DanielG | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- While porting ghc-mod to GHC 8 I noticed that all `-fwarn` flags are missing from `flagsForCompletion` instead only `-fwarn-` and `-fno-warn-` appear. This also shows up in the front-end when running `ghc --show- options`. Looking at the code this turned out to be because the old `-fwarn` flags were marked as hidden using `hideFlag` and hidden flags are explicitly filtered out in `flagsForCompletion` but for some reason the `-fwarn-` and `-fno-warn-` prefixes still show up in the list. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 22:11:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 22:11:02 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.cc195c89d1d5f9de16877d2b212350a5@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): `ghc --help` doesn't need to mention `-auto-all` Deprecating `-auto-all`, `-auto` and `-caf-all` is ok, but you'll have to mention it in the release notes (`docs/users_guide/8.2.1-notes.rst`), and update all places where they are used in the `testsuite`, `docs` and `nofib`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 22:17:15 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 22:17:15 -0000 Subject: [GHC] #12099: ghc --show-options lists invalid flags In-Reply-To: <046.f661034fd1c4aa2ec7129aadde9e360e@haskell.org> References: <046.f661034fd1c4aa2ec7129aadde9e360e@haskell.org> Message-ID: <061.1bcc99ce6fc2f33c8109790db35b55e1@haskell.org> #12099: ghc --show-options lists invalid flags -------------------------------------+------------------------------------- Reporter: DanielG | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer Comment: > all -fwarn flags are missing from flagsForCompletion That is intended behavior I think. Those flags are deprecated, ad replaced by equivalent `-W` flags. `-fwarn-`, `-fno-warn` and `-W` probably show up in the output of `--show- options` because of this code from `compiler/main/DynFlags.hs`: {{{ ++ [ (NotDeprecated, unrecognisedWarning "W") , (NotDeprecated, unrecognisedWarning "fwarn-") , (NotDeprecated, unrecognisedWarning "fno-warn-") ] }}} For a newcomer. Adding a test is optional. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 21 22:17:30 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 21 May 2016 22:17:30 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows In-Reply-To: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> References: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> Message-ID: <060.127aca896ca94646be7226ced91dbcac@haskell.org> #12010: Incorrect return types for recv() and send() on Windows -----------------------------------+-------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -----------------------------------+-------------------------------------- Comment (by mpickering): This test fails for me on OSX because {{{ Wrong exit code (expected 0 , actual 2 ) Stdout: Stderr: T12010.hsc:12:10: fatal error: 'HsBase.h' file not found #include "HsBase.h" ^ 1 error generated. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 05:16:05 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 05:16:05 -0000 Subject: [GHC] #6077: Respect XDG_CONFIG_HOME In-Reply-To: <045.4be78870b39bed231ff23249aec382c8@haskell.org> References: <045.4be78870b39bed231ff23249aec382c8@haskell.org> Message-ID: <060.027ef30ff450beeb08076d91a4bb8e8f@haskell.org> #6077: Respect XDG_CONFIG_HOME -------------------------------------+------------------------------------- Reporter: So8res | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: None | Version: 7.4.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 5966 | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by siddhanathan): The GHCi configuration file would clearly be in `$XDG_CONFIG_HOME/ghc/ghci.conf`. Where exactly the GHCi history should be placed is debatable. [https://wiki.debian.org/XDGBaseDirectorySpecification Debian] argues for an additional state directory. But for now, I think `$XDG_DATA_HOME/ghc/ghci_history` would be best. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 06:37:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 06:37:29 -0000 Subject: [GHC] #4370: Bring back monad comprehensions In-Reply-To: <046.49abdb223a4732cf8eac6690239b5924@haskell.org> References: <046.49abdb223a4732cf8eac6690239b5924@haskell.org> Message-ID: <061.319ce7e57950b0e471ee2f123e2b938d@haskell.org> #4370: Bring back monad comprehensions -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ? Component: Compiler | Version: 6.12.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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * differential: Phab:D2247 => * resolution: => fixed Comment: Of dear, indeed it isn't; sorry for the noise. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 07:08:34 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 07:08:34 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.e5929171e747add8c7b9d2d85fe9bff3@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1-rc3 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 ilovezfs): Unfortunately, this still happens in the 8.0.1 release version. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 07:52:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 07:52:10 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.4e9dfa16a43503c9d76aac57777bdc7f@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1-rc3 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 thomie): We're unlikely to put a lot of time in to investigate this bug, since you seem to be the only one running into it, and the current build system is being retired. Could you please try https://github.com/snowleopard/hadrian, and see if you can reproduce the problem. Please provide the following details: * which OS * which command do you run? (`make -j`) * is there anything "weird" about your system. Slow disk? * after the failure, does the build continue successfully if you run `make` again? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 07:57:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 07:57:37 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.5542910b328752329f485def70a81751@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1-rc3 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 ilovezfs): What's weird is the number of make jobs is set to 100 to turn up build systems that have parallelization bugs. CPU: 8-core 64-bit skylake OS X: 10.11.5-x86_64 SSD 32G of RAM. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 08:04:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 08:04:28 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.1c72b6471c95137973097a67a0f38a61@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1-rc3 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 ilovezfs): I doubt there's any reason for anyone to spend time hunting down the "real" bug. As I mentioned calling sync or adding a little sleep where I said works around it, so that would be a sufficient solution probably if you're switching build systems anyway. It would be great if you could throw that workaround into "libffi/ghc.mk" so I don't have to patch this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 08:07:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 08:07:31 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.28e2e379c34649f541606c8262361d14@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: seraphime Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by seraphime): * owner: => seraphime -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 08:12:07 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 08:12:07 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.811672032d2d9c39960ec26582907a91@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1-rc3 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 Thomas Miedema ): In [changeset:"c81e7b2014e284774eecf5e48e42aab31892cec1/ghc" c81e7b20/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c81e7b2014e284774eecf5e48e42aab31892cec1" Build system: temp solution for parallelisation bug (#11960) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 08:15:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 08:15:59 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.f85c25b8eb68e5c5dea47cded5e8cbb3@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.1-rc3 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 thomie): * milestone: => 8.0.2 Comment: > make jobs is set to 100 Nice :) Ok, the above patch will be in 8.0.2. Thank you for the report and suggested fix. If you have some time, please try out the new build system! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 08:16:09 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 08:16:09 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.be2d7be6cd46eee9ed97913dc0379ae0@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.1-rc3 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 thomie): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 08:22:22 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 08:22:22 -0000 Subject: [GHC] #11960: GHC parallel build failure during "make" In-Reply-To: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> References: <047.ec2cf2a2fa93a6c771ea2f164f8f5768@haskell.org> Message-ID: <062.bea377f7dcff7363b0afbe39e4f0d880@haskell.org> #11960: GHC parallel build failure during "make" -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.1-rc3 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 ilovezfs): Cool, thanks a lot! Yes, I will definitely try it out. If I can get it working, I'll add it to https://github.com/ilovezfs/homebrew-ghc and possibly also to Homebrew core's devel and/or head spec for ghc. Right now I'm preparing the ghc 8.0.1 Homebrew release. Unfortunately, just hit a segfault using my old workaround (https://github.com/Homebrew /homebrew-core/blob/master/Formula/ghc.rb#L53-L72) for the nm bug, which was to put a shim pointing to nm-classic earlier in the PATH than /usr/bin/nm. That old workaround has worked fine for 7.10.3b and 8.0 RCs, so I'm not sure if this is a new bug or not. Now I'm re-trying with "--with-nm=#{`xcrun --find nm-classic`}" to see if that also hits the segfault or not. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 10:13:25 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 10:13:25 -0000 Subject: [GHC] #12100: GHC 8.0.1 build segmentation fault in haddock Message-ID: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> #12100: GHC 8.0.1 build segmentation fault in haddock -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: MacOS X Architecture: | Type of failure: Building GHC Unknown/Multiple | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Skylake iMac OS X 10.11.5. Xcode 7.3.1. march=native. This happens each time I attempt to build 8.0.1. The release candidates were not affected: {{{ "inplace/bin/ghc-stage2" -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -H32m -O -Wall -hide-all-packages -i -iutils/haddock/driver -iutils/haddock/haddock-api/src -iutils/haddock/haddock- library/vendor/attoparsec-0.12.1.1 -iutils/haddock/haddock-library/src -iutils/haddock/dist/build -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build -Iutils/haddock/dist/build/autogen -optP- DIN_GHC_TREE -optP-include -optPutils/haddock/dist/build/autogen/cabal_macros.h -package-id Cabal-1.24.0.0 -package-id array-0.5.1.1 -package-id base-4.9.0.0 -package-id bytestring-0.10.8.1 -package-id containers-0.5.7.1 -package-id deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id filepath-1.4.1.0 -package-id ghc-8.0.1 -package-id ghc-boot-8.0.1 -package-id transformers-0.5.2.0 -package-id xhtml-3000.2.1 -funbox-strict-fields -Wall -fwarn-tabs -O2 -threaded -XHaskell2010 -no-user-package-db -rtsopts -Wno-unused-imports -Wno-deprecations -Wnoncanonical-monad- instances -odir utils/haddock/dist/build -hidir utils/haddock/dist/build -stubdir utils/haddock/dist/build -c utils/haddock/haddock- library/src/Documentation/Haddock/Types.hs -o utils/haddock/dist/build/Documentation/Haddock/Types.dyn_o "inplace/bin/ghc-stage2" -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -H32m -O -Wall -hide-all-packages -i -iutils/haddock/driver -iutils/haddock/haddock-api/src -iutils/haddock/haddock- library/vendor/attoparsec-0.12.1.1 -iutils/haddock/haddock-library/src -iutils/haddock/dist/build -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build -Iutils/haddock/dist/build/autogen -optP- DIN_GHC_TREE -optP-include -optPutils/haddock/dist/build/autogen/cabal_macros.h -package-id Cabal-1.24.0.0 -package-id array-0.5.1.1 -package-id base-4.9.0.0 -package-id bytestring-0.10.8.1 -package-id containers-0.5.7.1 -package-id deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id filepath-1.4.1.0 -package-id ghc-8.0.1 -package-id ghc-boot-8.0.1 -package-id transformers-0.5.2.0 -package-id xhtml-3000.2.1 -funbox-strict-fields -Wall -fwarn-tabs -O2 -threaded -XHaskell2010 -no-user-package-db -rtsopts -Wno-unused-imports -Wno-deprecations -Wnoncanonical-monad- instances -odir utils/haddock/dist/build -hidir utils/haddock/dist/build -stubdir utils/haddock/dist/build -c utils/haddock/dist/build/autogen/Paths_haddock.hs -o utils/haddock/dist/build/Paths_haddock.dyn_o "inplace/bin/ghc-stage2" -hisuf dyn_hi -osuf dyn_o -hcsuf dyn_hc -fPIC -dynamic -H32m -O -Wall -hide-all-packages -i -iutils/haddock/driver -iutils/haddock/haddock-api/src -iutils/haddock/haddock- library/vendor/attoparsec-0.12.1.1 -iutils/haddock/haddock-library/src -iutils/haddock/dist/build -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build -Iutils/haddock/dist/build/autogen -optP- DIN_GHC_TREE -optP-include -optPutils/haddock/dist/build/autogen/cabal_macros.h -package-id Cabal-1.24.0.0 -package-id array-0.5.1.1 -package-id base-4.9.0.0 -package-id bytestring-0.10.8.1 -package-id containers-0.5.7.1 -package-id deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id filepath-1.4.1.0 -package-id ghc-8.0.1 -package-id ghc-boot-8.0.1 -package-id transformers-0.5.2.0 -package-id xhtml-3000.2.1 -funbox-strict-fields -Wall -fwarn-tabs -O2 -threaded -XHaskell2010 -no-user-package-db -rtsopts -Wno-unused-imports -Wno-deprecations -Wnoncanonical-monad- instances -odir utils/haddock/dist/build -hidir utils/haddock/dist/build -stubdir utils/haddock/dist/build -c utils/haddock/haddock- library/src/Documentation/Haddock/Utf8.hs -o utils/haddock/dist/build/Documentation/Haddock/Utf8.dyn_o make[1]: *** [utils/haddock/dist/build/Haddock/Backends/Hyperlinker/Types.dyn_o] Segmentation fault: 11 make[1]: *** Waiting for unfinished jobs.... make[1]: *** [utils/haddock/dist/build/Documentation/Haddock/Types.dyn_o] Segmentation fault: 11 make[1]: *** [utils/haddock/dist/build/Haddock/GhcUtils.dyn_o] Segmentation fault: 11 make[1]: *** [utils/haddock/dist/build/Paths_haddock.dyn_o] Segmentation fault: 11 make[1]: *** [utils/haddock/dist/build/ResponseFile.dyn_o] Segmentation fault: 11 make: *** [all] Error 2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 10:37:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 10:37:51 -0000 Subject: [GHC] #12100: GHC 8.0.1 build segmentation fault in haddock In-Reply-To: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> References: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> Message-ID: <062.7e6e50025de41805b320dd515a1a5f4f@haskell.org> #12100: GHC 8.0.1 build segmentation fault in haddock -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #11744, #11951 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => highest * cc: bgamari (added) * related: => #11744, #11951 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 10:39:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 10:39:35 -0000 Subject: [GHC] #12100: GHC 8.0.1 build segmentation fault in haddock In-Reply-To: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> References: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> Message-ID: <062.1f3aade036188d4b48c9306cbcc055a4@haskell.org> #12100: GHC 8.0.1 build segmentation fault in haddock -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #11744, #11951 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ilovezfs): This is using nm-classic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 10:51:53 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 10:51:53 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures In-Reply-To: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> References: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> Message-ID: <058.0c56b4dade9f31a51663fccbb973b5a4@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2255 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => patch * differential: => Phab:D2255 Comment: Easy fix. Thanks for reporting the bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 11:18:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 11:18:29 -0000 Subject: [GHC] #12100: GHC 8.0.1 build segmentation fault in haddock In-Reply-To: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> References: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> Message-ID: <062.ac93a1c53f44b7a1c2538a0693df75ca@haskell.org> #12100: GHC 8.0.1 build segmentation fault in haddock -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #11744, #11951 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ilovezfs): Setting -march=core2 instead of -march=native worked around it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 11:50:37 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 11:50:37 -0000 Subject: [GHC] #12101: Regression: Pattern synonyms make GHCi 8.0.1 crash Message-ID: <048.1e0263af742efb43df32b1251feac2b5@haskell.org> #12101: Regression: Pattern synonyms make GHCi 8.0.1 crash -------------------------------------+------------------------------------- Reporter: int-index | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: GHCi crash Unknown/Multiple | Test Case: | Blocked By: https://gist.githubusercontent.com | /int- | index/17dfb68fd97f724aef2849d0defae0d6/raw/3dab71756bbafa197b93170310ccabfea8c92120/M.hs| Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code: {{{ {-# LANGUAGE PatternSynonyms #-} data T = C pattern P :: T pattern P = C pattern P' :: T pattern P' = P }}} compiles fine with both GHC 7.10.3 and 8.0.1. However, if you try to load it into GHCi 8.0.1, it panics: {{{ GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Prelude> :l M.hs [1 of 1] Compiling Main ( M.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): kindPrimRep.go rep_a18a Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} GHCi 7.10.3 does not crash, therefore it's a regression: {{{ GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help Prelude> :l M.hs [1 of 1] Compiling Main ( M.hs, interpreted ) Ok, modules loaded: Main. *Main> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 13:45:14 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 13:45:14 -0000 Subject: [GHC] #11574: schedule: re-entered unsafely on minimal hello world program on arm In-Reply-To: <051.5f65ae7b7de5c2aba500f9eaf01974c1@haskell.org> References: <051.5f65ae7b7de5c2aba500f9eaf01974c1@haskell.org> Message-ID: <066.631f09c05f36508d246c06ca64e8c41d@haskell.org> #11574: schedule: re-entered unsafely on minimal hello world program on arm ----------------------------------+------------------------------ Reporter: andrewufrank | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: arm Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #11190 | Differential Rev(s): Wiki Page: | ----------------------------------+------------------------------ Changes (by thomie): * status: infoneeded => closed * resolution: => duplicate * related: => #11190 Comment: Replying to [comment:9 andrewufrank]: > now things work nicely! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 14:11:24 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 14:11:24 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.235be4334ea43393a2ea205fc42ef936@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer Comment: It looks like this only happens when `-w` is combined with `-Wunrecognised-warning-flags`. GHC seems to do the right thing when using `-w` and some other warning flag (make sure to use `-fforce-recomp` during testing). For a newcomer. The code to change is in `compiler/main/DynFlags.hs`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 14:13:11 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 14:13:11 -0000 Subject: [GHC] #12056: Too aggressive `-w` option In-Reply-To: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> References: <042.615977cbd760a0223c1133d5e2a0fac1@haskell.org> Message-ID: <057.2f0317e8b711c11735b3541d327ab28a@haskell.org> #12056: Too aggressive `-w` option -------------------------------------+------------------------------------- Reporter: asr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11429, #11789 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #11429, #11789 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 14:15:01 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 14:15:01 -0000 Subject: [GHC] #12059: Add primop to query for pinned-ness of a ByteArray In-Reply-To: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> References: <046.5ad385bf515e30a1a94e73ae24d714e2@haskell.org> Message-ID: <061.fb6304415ae63843cadb4c08f78b32b5@haskell.org> #12059: Add primop to query for pinned-ness of a ByteArray -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codeGen/should_run/T12059 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2217 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * testcase: => codeGen/should_run/T12059 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 14:36:49 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 14:36:49 -0000 Subject: [GHC] #9095: make sdist picks up test files In-Reply-To: <045.5bc6b697ad76318e7d59aba1132cfee1@haskell.org> References: <045.5bc6b697ad76318e7d59aba1132cfee1@haskell.org> Message-ID: <060.c2b1f4fe01ba0c913ebe475ce9eac03e@haskell.org> #9095: make sdist picks up test files -------------------------------------+------------------------------------- Reporter: ezyang | Owner: thomie Type: bug | Status: closed Priority: low | Milestone: 8.2.1 Component: Build System | Version: 7.9 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Fixed by running tests in /tmp (#11980). Although not perfect (if you yourself create some temporary files in the `testsuite/` directory, they //will// still be included in the sdist. So just don't do that if you care about this issue.), I think it's good enough for now. Maybe Hadrian will do better. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 14:39:08 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 14:39:08 -0000 Subject: [GHC] #11427: superclasses aren't considered because context is no smaller than the instance head In-Reply-To: <045.5bbd322743d829f91b935ee5364b27b3@haskell.org> References: <045.5bbd322743d829f91b935ee5364b27b3@haskell.org> Message-ID: <060.5db5f411de97aae4591dbf2391628c20@haskell.org> #11427: superclasses aren't considered because context is no smaller than the instance head -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vagarenko): * cc: vagarenko (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 14:55:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 14:55:46 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named In-Reply-To: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> References: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> Message-ID: <063.5c3787af915d1c5f2e3e2e059439aa05@haskell.org> #12060: GHC panic depending on what a Haskell module is named ----------------------------------+-------------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: | ----------------------------------+-------------------------------------- Comment (by thomie): Could you try to reduce your testcase a bit? Ideally you'd slim it down to a simple .cpp file, without any external libraries. Also please provide detailed instructions for how to reproduce the problem. Assume only tools and libraries mentioned on [wiki:Building/Preparation/Windows] are installed. Thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 15:11:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 15:11:59 -0000 Subject: [GHC] #12065: there is a way to override the .tix path with HPCTIXFILE In-Reply-To: <045.acf890da63effd264c753e4e22e0c6f2@haskell.org> References: <045.acf890da63effd264c753e4e22e0c6f2@haskell.org> Message-ID: <060.e08244c37ad3c8161f67ab8c0361361d@haskell.org> #12065: there is a way to override the .tix path with HPCTIXFILE -------------------------------------+------------------------------------- Reporter: kostmo | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Code Coverage | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Documentation => Code Coverage Comment: Thanks. It seems `HPCTIXDIR` isn't documented either. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 15:12:06 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 15:12:06 -0000 Subject: [GHC] #1853: hpc mix files for Main modules overwrite each other In-Reply-To: <044.9b946ad54a9a35d3915c7a74c107b816@haskell.org> References: <044.9b946ad54a9a35d3915c7a74c107b816@haskell.org> Message-ID: <059.ea2e7e2f62cb9cacc8cc9011f7f04382@haskell.org> #1853: hpc mix files for Main modules overwrite each other ----------------------------------+-------------------------------------- Reporter: guest | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Code Coverage | Version: 6.8.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+-------------------------------------- Changes (by thomie): * cc: kostmo (added) Comment: Perhaps relevant to the discussion here, @kostmo points out in #12065: > specifying `HPCTIXFILE` as an environment variable when running the executable program does change the output path of the .tix file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 15:16:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 15:16:48 -0000 Subject: [GHC] #12066: Symbol not found: _stg_ap_0_upd_info In-Reply-To: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> References: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> Message-ID: <062.e42c73f8fae78d1364210b3d534405bf@haskell.org> #12066: Symbol not found: _stg_ap_0_upd_info -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: Can you reproduce this problem? If so, please provide instructions that don't include Nix(os). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 15:53:07 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 15:53:07 -0000 Subject: [GHC] #12067: warn-unused-imports does not detect coersions In-Reply-To: <047.e234196f4d28c1786926628389b4a6f1@haskell.org> References: <047.e234196f4d28c1786926628389b4a6f1@haskell.org> Message-ID: <062.de1241a93392f917c654f1d5af621f6d@haskell.org> #12067: warn-unused-imports does not detect coersions -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #10347 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: => #10347 Comment: Also happens with 8.0. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 16:15:28 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 16:15:28 -0000 Subject: [GHC] #12066: Symbol not found: _stg_ap_0_upd_info In-Reply-To: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> References: <047.acb085228fe7253ed07d0786e97ac00b@haskell.org> Message-ID: <062.e55c81093a3a897382d7588ddd75946b@haskell.org> #12066: Symbol not found: _stg_ap_0_upd_info -------------------------------------+------------------------------------- Reporter: pikajude | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): Given that #12076 is outstanding I wouldn't try reproducing/minimizing yet. Easy way to test if it is that one is to recompile GHC without lazy removal optimization in CorePrep. On vacation so hard to say more. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 17:20:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 17:20:36 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.fa510479f79033e3f2c5fa764fd6bcfe@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: seraphime Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"35fc121fc8cc501ea2713c579a053be7ea65b16e/nofib" 35fc121/nofib]: {{{ #!CommitTicketReference repository="nofib" revision="35fc121fc8cc501ea2713c579a053be7ea65b16e" Fix: #12084 deprecate old profiling flags }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 17:36:54 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 17:36:54 -0000 Subject: [GHC] #12068: RULE too complicated to desugar when using constraint synonyms In-Reply-To: <047.446f8f83cd16c15c289d2bf01aaa7058@haskell.org> References: <047.446f8f83cd16c15c289d2bf01aaa7058@haskell.org> Message-ID: <062.bb12e9e51b57c7e133c91a90964bf38d@haskell.org> #12068: RULE too complicated to desugar when using constraint synonyms -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: commit a6f0f5ab45b2643b561e0a0a54a4f14745ab2152 {{{ Author: Simon Peyton Jones Date: Tue Dec 23 15:39:50 2014 +0000 Eliminate so-called "silent superclass parameters" }}} > It works in HEAD ... I'm not sure if it's worth adding a regression test. Closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 17:45:49 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 17:45:49 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly In-Reply-To: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> References: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> Message-ID: <062.a3f2878cd237eb951931e5e8ae425585@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly ----------------------------------------+------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+------------------------------- Changes (by thomie): * cc: Trommler (removed) * cc: trommler, slyfox (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:04:04 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:04:04 -0000 Subject: [GHC] #12101: Regression: Pattern synonyms make GHCi 8.0.1 crash In-Reply-To: <048.1e0263af742efb43df32b1251feac2b5@haskell.org> References: <048.1e0263af742efb43df32b1251feac2b5@haskell.org> Message-ID: <063.659fca89b2cba7e97624d0da54e2b926@haskell.org> #12101: Regression: Pattern synonyms make GHCi 8.0.1 crash -------------------------------------+------------------------------------- Reporter: int-index | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: #12007 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * testcase: https://gist.githubusercontent.com/int- index/17dfb68fd97f724aef2849d0defae0d6/raw/3dab71756bbafa197b93170310ccabfea8c92120/M.hs => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:10:59 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:10:59 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.acb5426cdf6167283ceca856fc34d482@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): @_deepfire: Could you please change your testcase to not depend on `base- unicode-symbols`? That would make it easier to include it in the testsuite later. Thanks. Note to others: you can uncomment `import Prelude.Unicode` and still reproduce the bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:25:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:25:32 -0000 Subject: [GHC] #12087: Inconsistency in GADTs? In-Reply-To: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> References: <051.271b252c8ff7e6b4a86908e0694bb2a9@haskell.org> Message-ID: <066.9bbc96cbd01b0ba192a855045b23fa31@haskell.org> #12087: Inconsistency in GADTs? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | Keywords: GADTs Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => invalid Comment: > f :: Ord a => Eq a => a -> Bool This is not valid Haskell. See #11540. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:33:39 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:33:39 -0000 Subject: [GHC] #12096: Attach stacktrace information to SomeException In-Reply-To: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> References: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> Message-ID: <064.43ce44253289c085fd537091565ce5a1@haskell.org> #12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: gridaphobe, ekmett (added) * component: libraries/base => Core Libraries -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:43:17 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:43:17 -0000 Subject: [GHC] #12098: Typechecker regression in 8.0.1 In-Reply-To: <048.fc96fa58e363f2cf0ea88f15909e8d50@haskell.org> References: <048.fc96fa58e363f2cf0ea88f15909e8d50@haskell.org> Message-ID: <063.4e03969f8d47647e27f34b57b80fbe49@haskell.org> #12098: Typechecker regression in 8.0.1 -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11364 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #11364 * priority: highest => normal * architecture: x86 => Unknown/Multiple * os: Windows => Unknown/Multiple Comment: Duplicate of #11364. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:48:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:48:26 -0000 Subject: [GHC] #11980: Testsuite: run each test in its own /tmp directory, after copying required files In-Reply-To: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> References: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> Message-ID: <060.81e13208f6cd2aa352946fc219531a63@haskell.org> #11980: Testsuite: run each test in its own /tmp directory, after copying required files -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | 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:D1187 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"2230c8822233d6d68f930170cd51d96169649056/ghc" 2230c882/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2230c8822233d6d68f930170cd51d96169649056" Testsuite: fix T12010 for real * Use `extra_files` instead of (the deprecated) `extra_clean` (#11980). * Don't depend on generated files from build tree (libraries/base/include/HsBaseConfig.h). Running 'make test TEST=T12010' should work, even without building GHC first (it will use the system installed ghc). Test Plan: 'make test TEST=T12010' on Linux and Windows. Reviewed by: Phyx Differential Revision: https://phabricator.haskell.org/D2256 GHC Trac Issues: #12010 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:48:26 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:48:26 -0000 Subject: [GHC] #12010: Incorrect return types for recv() and send() on Windows In-Reply-To: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> References: <045.cd7d6e8e5a2d9e9b7b83c726e2bb2436@haskell.org> Message-ID: <060.e683e828430ad914da76a7eb3bc6a9e5@haskell.org> #12010: Incorrect return types for recv() and send() on Windows -----------------------------------+-------------------------------------- Reporter: enolan | Owner: enolan Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2170 Wiki Page: | -----------------------------------+-------------------------------------- Comment (by Thomas Miedema ): In [changeset:"2230c8822233d6d68f930170cd51d96169649056/ghc" 2230c882/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2230c8822233d6d68f930170cd51d96169649056" Testsuite: fix T12010 for real * Use `extra_files` instead of (the deprecated) `extra_clean` (#11980). * Don't depend on generated files from build tree (libraries/base/include/HsBaseConfig.h). Running 'make test TEST=T12010' should work, even without building GHC first (it will use the system installed ghc). Test Plan: 'make test TEST=T12010' on Linux and Windows. Reviewed by: Phyx Differential Revision: https://phabricator.haskell.org/D2256 GHC Trac Issues: #12010 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 18:57:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 18:57:36 -0000 Subject: [GHC] #12096: Attach stacktrace information to SomeException In-Reply-To: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> References: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> Message-ID: <064.536e29f5f21b0af9b90657ec8d8ee6f2@haskell.org> #12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by gridaphobe): I'm generally in favor of adding `CallStack`s to exceptions (I've often cursed myself for using exceptions and having no clue where they were thrown). I'm not sure this is the best API though. A few thoughts: 1. I would prefer to not serialize the `CallStack`, i.e. get rid of `prettyCallStack`. Clients might want to inspect the `CallStack` when they catch an exception. 2. I wonder if adding the `CallStack` to `SomeException` is the best move. If we do this, we're kinda limited to adding the stack to `SomeException`s `Show` instance. People (AFAIK) don't usually operate directly on `SomeException`, they use `catch` and co. to unwrap the exception, which means giving up the `CallStack`. On the other hand, expecting users to add `CallStack`s to each exception type is not practical, nor is it clear how we'd wire that into `throw`. Perhaps (2) can be solved by keeping the `CallStack` in `SomeException` and adding a few helper functions, e.g. {{{#!haskell catchWithCallStack :: Exception e => IO a -> (e -> CallStack -> IO a) -> IO a }}} Thanks for the suggestion! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:00:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:00:43 -0000 Subject: [GHC] #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) In-Reply-To: <045.60294a744526480b093ee47fef543bec@haskell.org> References: <045.60294a744526480b093ee47fef543bec@haskell.org> Message-ID: <060.d170cdf104f52dfc8efb506accdb6ebb@haskell.org> #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8761 Blocked By: | Blocking: Related Tickets: #8761 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bollmann): hmm, it seems as if doing IO during compilation isn't supported with DYNAMIC_GHC_PROGRAMS=NO enabled? Where do I set this option to be able to verify this behavior on my local machine? Is it in `mk/build.mk` somewhere? It'd be great if anyone could tell me so, that I can take a deeper look at a fix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:17:16 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:17:16 -0000 Subject: [GHC] #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) In-Reply-To: <045.60294a744526480b093ee47fef543bec@haskell.org> References: <045.60294a744526480b093ee47fef543bec@haskell.org> Message-ID: <060.565d6fac21d42612bec6e303053964a6@haskell.org> #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8761 Blocked By: | Blocking: Related Tickets: #8761 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): > Where do I set this option to be able to verify this behavior on my local machine? Is it in mk/build.mk somewhere? Yes. When `DYNAMIC_GHC_PROGRAMS=NO`, GHCi uses the Runtime System linker (rts/Linker.c) instead of the system installed dynamic linker. Thanks for looking into it. It might be a [https://ghc.haskell.org/trac/ghc/query?status=!closed&component=Runtime+System+(Linker) known issue with the Runtime System Linker], I'm not sure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:31:54 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:31:54 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.7d139aa7c6548b48d3516a41c3912c9b@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics 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): * owner: => RyanGlScott Comment: I'm working on this now. Before I get too far, I wanted to ask about a potential design choice for this feature. I like just about everything in comment:19 except for one thing: I don't think we should introduce pragmas for explicitly requesting a "deriving strategy" (the phrase I coined to describe this), if only because it unnecessarily changes the syntax. I think we could just as effectively use type synonyms to denote which deriving strategy you want: {{{#!hs -- | Derive a type class instance using GHC's default behavior. type Builtin (a :: k) = a -- | Derive a type class instance by generating an instance with no -- implementations for any class methods or associated types. This requires the -- @-XDeriveAnyClass@ extension. type DAC (a :: k) = a -- | Derive a type class instance for a newtype by using the underlying type's -- instance for that class. This requires the @-XGeneralizedNewtypeDeriving@ -- extension. type GND (a :: k) = a }}} Then we can specify a deriving strategy (for both `deriving` clauses and standalone `deriving`) without any new syntax: {{{#!hs data Foo a = Foo a deriving ( Builtin Show , DAC (Bar Int) ) deriving instance Quux a => GND (Quux (Foo a)) }}} Then GHC simply has to check for the presence of one of these magical types before deciding which deriving mechanism to actually use. Does this sound agreeable? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:43:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:43:32 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.ad1dede4aeb905541e028891e285d857@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * Attachment "tyconroles-sees-a-tctycon-tyalias.hs" removed. Test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:43:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:43:32 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.c39e62c4511baf2408f8d44ae0b3f386@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * Attachment "tyconroles-sees-a-tctycon-tyalias.hs" added. a testcase not depending on base-unicode-symbols -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:44:20 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:44:20 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.75f62bfc608fff42c3f7f709eeef2f28@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by _deepfire): @thomie, done! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 19:45:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 19:45:02 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.076049fa12fe351dd454dd72bae20970@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by _deepfire: @@ -4,2 +4,0 @@ - - import Prelude.Unicode New description: {{{#!hs {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnicodeSyntax #-} type Constrd a = Num a ? a data ADT a = ADT (Constrd a) ExistentiallyLost data ExistentiallyLost = ? u. TC u ? ExistentiallyLost u class u ~ (ATF1 u, ATF2 u) ? TC u where type ATF1 u ? * type ATF2 u ? * uie_handlers ? ADT Int -- Loop: -- - ADT depends on ExistentiallyLost (also the Constrd appendage) -- - ExistentiallyLost depends on TC -- - TC depends on ADT }}} --> {{{ [1 of 1] Compiling Main ( /home/deepfire/src/ghc-testcases /tyconroles-sees-a-tctycon-tyalias.hs, interpreted ) <- ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160421 for x86_64-unknown-linux): tyConRoles sees a TcTyCon Constrd Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 20:30:07 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 20:30:07 -0000 Subject: =?utf-8?q?=5BGHC=5D_=2312102=3A_=E2=80=9CConstraints_in_kinds?= =?utf-8?q?=E2=80=9D_illegal_family_application_in_instance_=28+_?= =?utf-8?q?documentation_issues=3F=29?= Message-ID: <051.c1413ffcad4dfaf42160b6c05930b934@haskell.org> #12102: ?Constraints in kinds? illegal family application in instance (+ documentation issues?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: TypeInType | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- GHC 8.0.0.20160511. Example from the user guide: [https://downloads.haskell.org/~ghc/8.0.1/docs/html/users_guide/glasgow_exts.html #constraints-in-kinds Constraints in kinds] {{{#!hs type family IsTypeLit a where IsTypeLit Nat = 'True IsTypeLit Symbol = 'True IsTypeLit a = 'False data T :: forall a. (IsTypeLit a ~ 'True) => a -> * where MkNat :: T 42 MkSymbol :: T "Don't panic!" }}} Deriving a standalone `Show` instance *without* the constraint works fine {{{#!hs deriving instance Show (T a) }}} but I couldn't define a `Show` instance given the constraints: {{{#!hs -- ? Couldn't match expected kind ?'True? -- with actual kind ?IsTypeLit a0? -- The type variable ?a0? is ambiguous -- ? In the first argument of ?Show?, namely ?T a? -- In the stand-alone deriving instance for ?Show (T a)? deriving instance Show (T a) }}} let's add constraints {{{#!hs -- ? Couldn't match expected kind ?'True? -- with actual kind ?IsTypeLit lit? -- ? In the first argument of ?Show?, namely ?T (a :: lit)? -- In the instance declaration for ?Show (T (a :: lit))? instance IsTypeLit lit ~ 'True => Show (T (a :: lit)) where }}} let's derive for a single literal {{{#!hs -- ? Illegal type synonym family application in instance: -- T Nat -- ('Data.Type.Equality.C:~ -- Bool -- (IsTypeLit Nat) -- 'True -- ('GHC.Types.Eq# Bool Bool (IsTypeLit Nat) 'True <>)) -- 42 -- ? In the stand-alone deriving instance for ?Show (T (42 :: Nat))? deriving instance Show (T (42 :: Nat)) }}} same happens with {{{#!hs instance Show (T 42) where }}} ---- The documentation > Note that explicitly quantifying with `forall a` is not necessary here. seems to be wrong since removing it results in {{{ tVDv.hs:10:17-18: error: ? ? Expected kind ?a?, but ?42? has kind ?Nat? ? In the first argument of ?T?, namely ?42? In the type ?T 42? In the definition of data constructor ?MkNat? Compilation failed. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 23:15:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 23:15:36 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.42ee149d663f4ce2692ccf414e6880b6@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by oerjan): That magic somewhat disturbs me, especially since it means a type synonym is not equivalent to its expansion. But if you think it's better than (backwards-compatibly) extending the parser to reuse keywords... (I guess `default` is a bit of a stretch anyway.) In any case, you should also decide how to annotate a `class` definition, which is where I actually suggested a pragma. (I think this feature is an important part of this: E.g. I think `mtl` classes are almost always used with newtype deriving while `aeson` uses generics, and the libraries should be able to specify this.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 22 23:37:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 22 May 2016 23:37:51 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.f6165dea93fec4594fa934c73836124a@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: 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 magic somewhat disturbs me, especially since it means a type synonym is not equivalent to its expansion. I'm not proposing making these type synonyms expand to something different than what they're defined as above. The only magic comes when it's used in a `deriving` statement?that would cause its underlying (expanded) type to have a different derived //instance//, but the types are honest. > But if you think it's better than (backwards-compatibly) extending the parser to reuse keywords... (I guess `default` is a bit of a stretch anyway.) It's not quite backwards-compatible?we'd also have to make a breaking change to `template-haskell` in order to accommodate the presence of these new pragmas. The type synonym approach, however, is only backportable to GHC 7.6. (It should be noted that many uses of this feature would not be usable on older GHCs in the first place, so perhaps this isn't a huge concern.) > In any case, you should also decide how to annotate a `class` definition, which is where I actually suggested a pragma. I'm not sure what you mean. Are talking about annotating when you should use `DeriveAnyClass` (`DAC`)? Or something else? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 00:50:38 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 00:50:38 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.4c888993748025c2ff2332203fc5726b@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by oerjan): Replying to [comment:25 RyanGlScott]: > It's not quite backwards-compatible?we'd also have to make a breaking change to `template-haskell` in order to accommodate the presence of these new pragmas. The type synonym approach, however, is only backportable to GHC 7.6. Ah, there's always something. Which reminds me, Haddock might possibly want to know about the distinctions, too. > > In any case, you should also decide how to annotate a `class` definition, which is where I actually suggested a pragma. > > I'm not sure what you mean. Are talking about annotating when you should use `DeriveAnyClass` (`DAC`)? Or something else? DAC or GND, both should be possible to specify. Neither is equivalent to having no annotation. The annotations on the class not only tell what you normally ''should'' use, but also guide the compiler's selection for a newtype if the deriving clause does not itself have an annotation. Also, annotating the class removes the possibility of a warning if GHC must choose between DAC and GND because a module enables both as language extensions. To re-summarize my suggested system, when choosing what mechanism to use for deriving a class for a newtype: 1. Annotations on the deriving clause take top precedence (with the exception of some builtin classes at least including, for safety, `Typeable`). 2. Then builtin derivable status of the class. 3. Then annotations on the class declaration. 4. Only if none of the above exists are the module's enabled relevant language extensions (GND or DAC) used to choose. If both GND and DAC are enabled, a warning is given, and DAC is chosen. 5. No matter what is chosen in the above, the module must have enabled any relevant language extensions. The guiding principles here being backwards compatibility (2,4), the ability to state intended usage at both class declaration and deriving sites (1,2,3), and reducing undetected surprises from irrelevant changes (4,5). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 08:38:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 08:38:08 -0000 Subject: [GHC] #12097: DuplicateRecordFields appears not to work in GHCi In-Reply-To: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> References: <046.8a0bdb4a33d6339dac7ae933c185ede1@haskell.org> Message-ID: <061.ff125742c43939ee0803e3bbff136f70@haskell.org> #12097: DuplicateRecordFields appears not to work in GHCi -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: invalid | Keywords: ORF Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by adamgundry): * keywords: => ORF Comment: This is indeed expected behaviour. See #11343. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 08:58:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 08:58:17 -0000 Subject: [GHC] #11540: ghc accepts non-standard type without language extension In-Reply-To: <047.4af844a129b268095ee1a782d708bfe8@haskell.org> References: <047.4af844a129b268095ee1a782d708bfe8@haskell.org> Message-ID: <062.5533261a6d9bec0ed58955c33b04179c@haskell.org> #11540: ghc accepts non-standard type without language extension -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Moreover, the current treatment (allowing nested contexts) is inconsistent with GADTs (#12087), which is undesirable. Nothing hard here; just gotta decide what we want and implement it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 09:13:37 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 09:13:37 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.21af01461fd6944be4d9efaed9a40a5d@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: 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): An alternative would be to require an instance declaration for DAD, thus {{{ instance C a => C (T a) }}} That's all that is required, provided `C` has suitable generic default methods and `T` is an instance of `Generic`. And if DAC always used this route, there'd be less ambiguity in the `deriving` clause of a data type declaration. I think (but I am not sure) that we don't allow standalone deriving for DAC; thus {{{ deriving instance C a => C (T a) }}} would not work for DAC. Is that right? It seems reasonable to disallow it, because it's one word longer than the ordinary instance declaration. And if it is disallowed, then builtin and GND are already treated differently to DAC. So we'd get * GND/builtin: `deriving` clauses and `deriving instance` declarations * DAC: always a plain `instance` decl I know that's not backward compatible.. On Ryan's synonym thing, like oerjan I'm uncomfortable with pressing synonyms into service like this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 10:40:43 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 10:40:43 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.5285f62dceef2035979a175d2c07f3fc@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:27 simonpj]: > An alternative would be to require an instance declaration for DAD, thus > {{{ > instance C a => C (T a) > }}} > That's all that is required, provided `C` has suitable generic default methods and `T` is an instance of `Generic`. And if DAC always used this route, there'd be less ambiguity in the `deriving` clause of a data type declaration. I would strongly object to this! Literally the whole reason why I want this feature in the first place is so I can combine `GeneralizedNewtypeDeriving` with `DeriveAnyClass` in the presence of `deriving` clauses (which very conveniently don't require providing context). And moreover, if type out an instance manually like that, it's no longer `DeriveAnyClass`, it's pure Haskell 98! So imposing this "requirement" for `DeriveAnyClass` is tantamount to completely losing its utility, in my opinion. > I think (but I am not sure) that we don't allow standalone deriving for DAC; thus > {{{ > deriving instance C a => C (T a) > }}} > would not work for DAC. Is that right? It seems reasonable to disallow it, because it's one word longer than the ordinary instance declaration. And if it is disallowed, then builtin and GND are already treated differently to DAC. So we'd get > * GND/builtin: `deriving` clauses and `deriving instance` declarations > * DAC: always a plain `instance` decl > > I know that's not backward compatible.. We do currently allow `StandaloneDeriving` to be used with any deriving strategy in existence, including `DeriveAnyClass`. You're right that using `DeriveAnyClass` in this fashion is a tad redundant (you can just as well drop the `deriving` part and get the same thing), but I don't think there's any reason to explicitly disallow it?after all, that would be another breaking change, and it does seem a bit //ad hoc// to disallow one form of `deriving` here when it could easily work with the ideas proposed in this ticket. > On Ryan's synonym thing, like oerjan I'm uncomfortable with pressing synonyms into service like this. OK, that's two votes against that idea, so I'll stop pursuing it :) In that case, pragmas looks like the path forward. Do the following names sound reasonable for pragmas? * `{-# BUILTIN #-}` * `{-# GND #-}` * `{-# DAC #-}` (goldfire proposed `{-# ANY #-}` above, but I'd argue that is a bit too ambiguous) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 10:56:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 10:56:17 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.39fb80f6be001c6e4d16d938da208bf2@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: 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): Let me also address oerjan's proposal to annotate class definitions with these pragmas as well to guide which deriving mechanism is chosen. I'll admit the idea makes me a bit uncomfortable, since it's not backwards compatible. For example, if there's a `class ToJSON` in use with current GHCs that becomes annotated with `classs {-# DAC #-} ToJSON`, then the following code: {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving #-} newtype Foo = Foo Bar deriving ToJSON }}} would do two different things depending on which GHC is used! If an older GHC is used, it'll pick `GeneralizedNewtypeDeriving`, but if a more recent GHC is used, it'll pick `DeriveAnyClass`. Not to mention GHC will now complain that you need to enable `DeriveAnyClass` for that code to compile in the first place, which would be a pretty confusing breakage. This seems deeply wrong to me?in my opinion, one should be able to tell from the module in which the `deriving` statement is in which mechanism will be picked. Also, I'm not sure what would happen if you have `class {-# GND #-} Baz` and tried to do `data Quux = Quux deriving Baz`. When you explicitly annotate a `deriving` statement for a `data` type with `{-# GND #-}`, that's an obvious error. But when the pragma is tucked away in a class definition (possibly in a far-flung module), it might not be intuitive as why that code would error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 10:59:28 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 10:59:28 -0000 Subject: [GHC] #12103: Typed Template Haskell missing many utilities provided by untyped variant Message-ID: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> #12103: Typed Template Haskell missing many utilities provided by untyped variant -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Currently typed TH feels a bit second-class as it lacks a number of handy utilities which are provided in the untyped case. In my brief look at this I encountered the following, {{{#!hs type TExpQ a = Q (TExp a) stringT :: String -> TExpQ String trueT, false :: TExpQ Bool }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 10:59:36 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 10:59:36 -0000 Subject: [GHC] #12103: Typed Template Haskell missing utilities provided by untyped variant (was: Typed Template Haskell missing many utilities provided by untyped variant) In-Reply-To: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> References: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> Message-ID: <061.5574e440e14ae343e0d616c17d74d421@haskell.org> #12103: Typed Template Haskell missing utilities provided by untyped variant -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 11:04:26 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 11:04:26 -0000 Subject: [GHC] #12103: Typed Template Haskell missing utilities provided by untyped variant In-Reply-To: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> References: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> Message-ID: <061.33f6175b517e4315bdf3cea397845867@haskell.org> #12103: Typed Template Haskell missing utilities provided by untyped variant -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -9,1 +9,1 @@ - trueT, false :: TExpQ Bool + trueT, falseT :: TExpQ Bool @@ -11,0 +11,5 @@ + + Names still need bike-shedded. + + Of course, another reasonable option would just be to rather push users to + instead use quotes. New description: Currently typed TH feels a bit second-class as it lacks a number of handy utilities which are provided in the untyped case. In my brief look at this I encountered the following, {{{#!hs type TExpQ a = Q (TExp a) stringT :: String -> TExpQ String trueT, falseT :: TExpQ Bool }}} Names still need bike-shedded. Of course, another reasonable option would just be to rather push users to instead use quotes. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 11:29:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 11:29:16 -0000 Subject: [GHC] #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) In-Reply-To: <045.60294a744526480b093ee47fef543bec@haskell.org> References: <045.60294a744526480b093ee47fef543bec@haskell.org> Message-ID: <060.95ac5d742fbf72472329bf041a35a6aa@haskell.org> #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8761 Blocked By: | Blocking: Related Tickets: #8761 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bollmann): hmm, putting `DYNAMIC_GHC_PROGRAMS=NO` into `mk/build.mk` and then running `./boot && ./configure && make` results in an error: {{{ Configuring ghc-prim-0.5.0.0... ghc-cabal: Cannot find the program 'ghc'. User-specified path '/home/dominik/ghc/inplace/bin/ghc-stage1' does not refer to an executable and the program is not on the system path. libraries/ghc-prim/ghc.mk:4: recipe for target 'libraries/ghc-prim/dist- install/package-data.mk' failed make[1]: *** [libraries/ghc-prim/dist-install/package-data.mk] Error 1 Makefile:129: recipe for target 'all' failed make: *** [all] Error 2 }}} I don't really understand what's happening here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 12:19:30 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 12:19:30 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures In-Reply-To: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> References: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> Message-ID: <058.803e71cb85eb97c3a99b2b505d1d1503@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2255 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Matthew Pickering ): In [changeset:"8c9b8a31dd9e085704ecac3361a64f196a0bc09d/ghc" 8c9b8a31/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8c9b8a31dd9e085704ecac3361a64f196a0bc09d" Allow unlifted types in pattern synonym result type Fixes #12094 Test Plan: ./validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2255 GHC Trac Issues: #12094 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 12:20:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 12:20:29 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures In-Reply-To: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> References: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> Message-ID: <058.597f7fb4413cd4a5fce052eb033139f5@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2255 Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 12:54:54 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 12:54:54 -0000 Subject: [GHC] #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) In-Reply-To: <045.60294a744526480b093ee47fef543bec@haskell.org> References: <045.60294a744526480b093ee47fef543bec@haskell.org> Message-ID: <060.831f8a43f830428fe377e054f3ec1807@haskell.org> #12077: DYNAMIC_GHC_PROGRAMS=NO: T8761 is failing (Make pattern synonyms work with Template Haskell) -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T8761 Blocked By: | Blocking: Related Tickets: #8761 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Remove `stage=2` from `mk/build.mk`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 14:08:48 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 14:08:48 -0000 Subject: [GHC] #12094: Unlifted types and pattern synonym signatures In-Reply-To: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> References: <043.12e14a4dec3cc62adda5e9a020766697@haskell.org> Message-ID: <058.60509379fc34924a79c92a35525b9276@haskell.org> #12094: Unlifted types and pattern synonym signatures -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2255 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Bidirectional form also works {{{#!hs -- ghci> let a@(I# Zero) = I# Zero in a -- 0 pattern Zero = 0# }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 14:13:19 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 14:13:19 -0000 Subject: [GHC] #11219: Implement fine-grained `-Werror=...` facility In-Reply-To: <042.5bdc58470a03f2bc4f044a0a96cc781d@haskell.org> References: <042.5bdc58470a03f2bc4f044a0a96cc781d@haskell.org> Message-ID: <057.49dcdb6b1c1b5b5061e7da114f75f59f@haskell.org> #11219: Implement fine-grained `-Werror=...` facility -------------------------------------+------------------------------------- Reporter: hvr | Owner: quchen Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11218, #9037 | Differential Rev(s): Wiki Page: Design/Warnings | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 14:21:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 14:21:29 -0000 Subject: [GHC] #10827: GHCi should support interpeting multiple packages/units with separate DynFlags In-Reply-To: <045.56917c0b2dd940e5429ceefba9639e36@haskell.org> References: <045.56917c0b2dd940e5429ceefba9639e36@haskell.org> Message-ID: <060.4bcfe179994ea451c8ec713de718cd8f@haskell.org> #10827: GHCi should support interpeting multiple packages/units with separate DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: GHC API | Version: 7.11 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 DanielG): * cc: DanielG (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 15:09:27 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 15:09:27 -0000 Subject: [GHC] #1851: "make install-strip" should work In-Reply-To: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> References: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> Message-ID: <059.3695b7b1c02a35d2532657cd582726c0@haskell.org> #1851: "make install-strip" should work -------------------------------------+------------------------------------- Reporter: igloo | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.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 gidyn): * owner: thomie => * status: closed => new * version: 7.10.1-rc1 => 8.0.1 * resolution: fixed => * milestone: 8.0.1 => 8.0.2 Comment: `make install-strip` doesn't strip anything from the source distribution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 15:26:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 15:26:29 -0000 Subject: [GHC] #1851: "make install-strip" should work In-Reply-To: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> References: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> Message-ID: <059.2cc16793747dd3ac3f6357eb738fd40a@haskell.org> #1851: "make install-strip" should work -------------------------------------+------------------------------------- Reporter: igloo | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.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: | -------------------------------------+------------------------------------- Comment (by thomie): Can you give instructions to reproduce the problem. What do you mean precisely with "anything from the source distribution"? I tried the following (using HEAD), and it seems to work as expected: {{{ $ DESTDIR=/tmp/install make install $ DESTDIR=/tmp/install-strip make install-strip }}} {{{ $ file /tmp/install/usr/local/lib/ghc-8.1.20160521/bin/ghc ... ELF 64-bit LSB executable ... not stripped $ file /tmp/install-strip/usr/local/lib/ghc-8.1.20160521/bin/ghc ... ELF 64-bit LSB executable ... stripped }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 15:59:16 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 15:59:16 -0000 Subject: [GHC] #12044: Remove sortWith in favor of sortOn In-Reply-To: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> References: <043.a68fedd475aea8c3d9f6732a967a3997@haskell.org> Message-ID: <058.d3725d49c41f511a028c75e86eec423a@haskell.org> #12044: Remove sortWith in favor of sortOn -------------------------------------+------------------------------------- Reporter: cblp | Owner: vkonton Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #2659 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by vkonton): * owner: => vkonton -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 16:54:51 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 16:54:51 -0000 Subject: [GHC] #11796: Warn about unwanted instances in a modular way In-Reply-To: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> References: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> Message-ID: <061.746a88a2da969fc97772ab2f9ab041a4@haskell.org> #11796: Warn about unwanted instances in a modular way -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11219 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #11219 New description: I like to propose the following way to warn about instances that are unwanted by some programmers. First step is to mark the instances at their definition site like so: {{{#!hs {-# WARN_INSTANCE tuple #-} instance Foldable ((,) a) where ... {-# WARN_INSTANCE tuple #-} instance Functor ((,) a) where ... {-# WARN_INSTANCE tuple #-} instance Foldable ((,,) a b) where ... {-# WARN_INSTANCE tuple #-} instance Functor ((,,) a b) where ... }}} This way, all the above instances are collected in an instance group labelled `tuple`. At the use sites we introduce a GHC warning option like `-fwarn-instance=tuple`. This warns about any place where any of the `tuple` instances is used. We can either place {{{ GHC-Options: -fwarn-instance=tuple }}} in a Cabal package description in order to issue warnings in a whole package or we can put {{{ {-# OPTIONS_GHC -fwarn-instance=tuple #-} }}} at the top of a module in order to enable the warning per module. Another candidate for an instance group might be `numeric` for numeric instances of functions and tuples in the `NumInstances` package. What does it mean to use an instance? I would say, if omitting an `instance X Y` would lead to a "missing instance" type error at place Z in a module, then `instance X Y` is used at place Z. There might be an even more restrictive option like `-fforbid- instance=tuple`. This would not only warn about an instance usage, but it would cause a type error. Essentially it should treat all `tuple` instances as if they were not defined. (Other instances might depend on `tuple` instances and if the `tuple` instances weren't there the compiler would not even reach the current module. I do not know, whether this case needs special treatment. We might require that any instance depending on `tuple` must be added to the `tuple` group as well or it might be added automatically.) The advantage of a type error is that we see all problems from `tuple` instances also in the presence of other type errors. Warnings would only show up after a module is otherwise type correct. This solution requires cooperation of the instance implementor. Would that work in practice? Otherwise we must think about ways to declare instance groups independently from the instance declaration and we get the problem of bringing the instance group names into the scope of the importing module. A separate discussion must be held on whether `-fwarn-instance=tuple` should be part of `-Wall`. I think that people should be warned about `tuple` instances early because they won't expect that there is a trap when using `length` and `maximum` and so on. One might also think about generalizations, e.g. whether {{{ {-# WARN_INSTANCE tuple, functor #-} }}} should be allowed in order to put an instance in several groups or whether there should be a way to compose a group from subgroups. Another topic would be a form of instance group disambiguation. Instance groups might be qualified with module or package names. I think package names are more appropriate, like so `-fwarn-instance=base:tuple`. -- Comment: I think I could get on board with this proposal, but I have some suggestions: * We currently have `WARNING` and `DEPRECATED` pragmas ([http://downloads.haskell.org/~ghc/8.0.1/docs/html/users_guide/glasgow_exts.html #warning-and-deprecated-pragmas link]) that serve a very similar role to what you're proposing. I think the key ingredient in your proposal that you're lacking is the ability to toggle their severity with separate flags. For example, we currently have: {{{#!hs {-# WARNING unsafePerformIO "Be careful" #-} }}} This always emits a warning. But we could envision a flags like `-Wpragma-error="unsafePerformIO"` or `-Wpragma- suppress="unsafePerformIO"` that would either elevate a `WARNING` pragma to an error or suppress its warning altogether, respectively. (We'd also need `-Wpragma-warn` for when we want to explicitly request a warning, rather than an error). So implementing `-Wpragma-error`, `-Wpragma-warn`, and `-Wpragma-suppress` seems like an important step. * Then we'd need to extend `WARNING`/`DEPRECATED` to be able to attach them to instances. Syntactically, I think this would make the most sense: {{{#!hs instance Foo Int where {-# WARNING instance FooInt "Beware of this instance" #-} ... }}} I think you'd need to put the pragma within the instance like so, because otherwise GHC would have a hard time figuring out which `WARNING` corresponds to which instance. We'd also need to give a unique string (e.g., `FooInt`) for the reason above. * We'd need a variation of `WARNING` that allows you to give it a unique string, but doesn't emit a warning by default when used (`SILENT` or `SILENT_WARNING`, perhaps?) * Lastly, we'd need some form of conflict resolution for unique strings. I could certainly see a scenario where a package has multiple `FooInt` strings floating around. Perhaps we could use a representation of `-Wpragma-warn=::`, where `` and `` are optional. Would this accomplish what you want? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 17:42:03 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 17:42:03 -0000 Subject: [GHC] #11796: Warn about unwanted instances in a modular way In-Reply-To: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> References: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> Message-ID: <061.9b1c05960f02a71c57188aef0b6f8e06@haskell.org> #11796: Warn about unwanted instances in a modular way -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11219 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Lemming): Replying to [comment:3 RyanGlScott]: > * We currently have `WARNING` and `DEPRECATED` pragmas ([http://downloads.haskell.org/~ghc/8.0.1/docs/html/users_guide/glasgow_exts.html #warning-and-deprecated-pragmas link]) that serve a very similar role to what you're proposing. A unification with the WARNING pragma looks like a good idea to me. I think I did not consider it, because currently warnings cannot be grouped. But if WARNINGs can be grouped we could re-use this capability for `instance` warnings. > This always emits a warning. But we could envision a flags like `-Wpragma-error="unsafePerformIO"` or `-Wpragma- suppress="unsafePerformIO"` that would either elevate a `WARNING` pragma to an error or suppress its warning altogether, respectively. (We'd also need `-Wpragma-warn` for when we want to explicitly request a warning, rather than an error). So implementing `-Wpragma-error`, `-Wpragma-warn`, and `-Wpragma-suppress` seems like an important step. The machinery sketched in #11219 seems like a good way to switch between the effect of hitting a warning. > * Lastly, we'd need some form of conflict resolution for unique strings. I could certainly see a scenario where a package has multiple `FooInt` strings floating around. Perhaps we could use a representation of `-Wpragma-warn=::`, where `` and `` are optional. For `instance`s the module name should not be part of the identifier. The definition of the instance can be anywhere in the package in a private module. This module can be renamed without even a minor version bump. But when I think about it, the same is true for function identifiers. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 17:57:17 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 17:57:17 -0000 Subject: [GHC] #11219: Implement fine-grained `-Werror=...` facility In-Reply-To: <042.5bdc58470a03f2bc4f044a0a96cc781d@haskell.org> References: <042.5bdc58470a03f2bc4f044a0a96cc781d@haskell.org> Message-ID: <057.58bcf7211f61a5880f875ccb05823e2d@haskell.org> #11219: Implement fine-grained `-Werror=...` facility -------------------------------------+------------------------------------- Reporter: hvr | Owner: quchen Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11796 | Differential Rev(s): Wiki Page: Design/Warnings | -------------------------------------+------------------------------------- Changes (by thomie): * related: #11218, #9037 => #11796 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 17:58:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 17:58:22 -0000 Subject: [GHC] #11618: Supporting echoing the C compiler invocation instead of the GHC invocation when building the RTS In-Reply-To: <047.24e0c6d5f3a78d3251b196d72b6dc0e8@haskell.org> References: <047.24e0c6d5f3a78d3251b196d72b6dc0e8@haskell.org> Message-ID: <062.2062fec0ca6ba6705912a1331d973d27@haskell.org> #11618: Supporting echoing the C compiler invocation instead of the GHC invocation when building the RTS -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Build System | Version: 7.10.3 Resolution: invalid | Keywords: ide Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => invalid Comment: No response from submitter. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 18:01:03 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 18:01:03 -0000 Subject: [GHC] #11796: Warn about unwanted instances in a modular way In-Reply-To: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> References: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> Message-ID: <061.58074e3467b23b5c2be6a3e580403ff0@haskell.org> #11796: Warn about unwanted instances in a modular way -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11219 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: hvr (added) Comment: Replying to [comment:4 Lemming]: > A unification with the WARNING pragma looks like a good idea to me. I think I did not consider it, because currently warnings cannot be grouped. But if WARNINGs can be grouped we could re-use this capability for `instance` warnings. `WARNING`s can be grouped, actually: {{{#!hs hello = "hello" world = "world" {-# WARNING hello, world "Beware" #-} }}} But this is much easier for top-level identifiers, since they have clearly defined names. Instances, on the other hand, don't have a convenient shorthand for referring to them, so it's not clear to me how you could group them together at the top-level. I believe that due to the way GHC parses pragmas, it cannot know that a pragma is "next" to an instance, so you have to nest it inside the instance to make it clear that this pragma belongs to that particular instance. An alternative would perhaps be to specify the unique string for an instance with a separate pragma, e.g., {{{#!hs instance Foo Int where {-# INSTANCE_TAG FooInt #-} ... instance Foo Char where {-# INSTANCE_TAG FooChar #-} ... {-# WARNING FooInt, FooChar "Watch out" #-} }}} Then you could group together multiple instances within a single `WARNING` at the top level. > The machinery sketched in #11219 seems like a good way to switch between the effect of hitting a warning. I agree! The difference here is that we're not elevating/suppressing warnings wholesale in this case, but rather configuring them on a tag-by- tag basis. Nonetheless, we'd need similar machinery to what #11219 needs. > For `instance`s the module name should not be part of the identifier. The definition of the instance can be anywhere in the package in a private module. This module can be renamed without even a minor version bump. But when I think about it, the same is true for function identifiers. Indeed. In fact, there could be two different private modules in the same package that export two functions with the same name, or two instances with the same tag. I can't think of a better way to tell them apart, can you? Relying on the exact location is a bit dangerous, admittedly, but it's the best form of disambiguation I know of. Ideally, you wouldn't have to use `:` very much in the first place, but it'd be nice to have for the few cases where it matters. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 18:05:02 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 18:05:02 -0000 Subject: [GHC] #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" Message-ID: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: TypeFamilies, | Operating System: MacOS X CustomTypeErrors | Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If I create a type family ? open or closed ? with a case that evaluates to a `TypeError`, and define a top-level binding with this type, loading the file with `-fdefer-type-errors` enabled (or via `:load!`/`:reload!`) panics GHC with "opt_univ fell into a hole". (And if I used `:load!` or `:reload!`, `-fdefer-type-errors` doesn't get unset.) A minimal example: {{{#!hs {-# LANGUAGE TypeFamilies, DataKinds, UndecidableInstances #-} import GHC.TypeLits type family F a where F a = TypeError (Text "error") err :: F () err = () }}} results in the panic {{{ ?.hs:9:7: warning: [-Wdeferred-type-errors] ? error ? In the expression: () In an equation for ?err?: err = () ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-apple-darwin): opt_univ fell into a hole {a4Va} }}} Adding more cases to the type family, or making it open, still cause the crash. This holds whether the error case is a final catch-all case, or something more like {{{#!hs type family F a where F () = TypeError (Text "error") F a = () }}} Just using a type synonym for `F` doesn't cause a panic, however, and nor does giving `err` the type `TypeError (Text "error")` directly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 18:05:47 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 18:05:47 -0000 Subject: [GHC] #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" In-Reply-To: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> References: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> Message-ID: <061.06dada802914d9304776f56986270a59@haskell.org> #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | CustomTypeErrors Operating System: MacOS X | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by antalsz): * Attachment "type-families-TypeError-defer-type-errors-opt_univ-bug.hs" added. The minimal example contained in the text of the ticket -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 18:23:58 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 18:23:58 -0000 Subject: [GHC] #12105: merge MatchFixity and HsMatchContext Message-ID: <044.0d136ec1e3b0b0304a6895a0a48280ac@haskell.org> #12105: merge MatchFixity and HsMatchContext -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- `MatchFixity` was introduced to facilitate use of API Annotations. `HsMatchContext` does the same thing with more detail, but is chased through all over the place to provide context when processing a `Match`. Since we already have `MatchFixity` in the AST, it may as well provide the full context. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:25:46 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:25:46 -0000 Subject: [GHC] #12106: Wrong type inferenced for locally defined function Message-ID: <042.655cd1f59022552be9f3be83f49a21ea@haskell.org> #12106: Wrong type inferenced for locally defined function -------------------------------------+------------------------------------- Reporter: syd | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following example. {{{#!hs data A = A deriving Show data B = B -- deriving Show is missing here. main :: IO () main = do let myPrint = putStrLn . show myPrint A myPrint B }}} The {{{Show}}} instance for {{{B}}} is missing and the most general type for {{{myPrint}}} is {{{Show a => a -> IO ()}}}. Ghc, however, reports the following error: {{{ file.hs:10:13: error: ? Couldn't match expected type ?A? with actual type ?B? ? In the first argument of ?myPrint?, namely ?B? In a stmt of a 'do' block: myPrint B In the expression: do { let myPrint = putStrLn . show; myPrint A; myPrint B } }}} This error won't help the programmer find the missing {{{deriving Show}}} declaration. Instead, the error should read something like {{{No instance for (Show B) arising from a use of ?myPrint?}}}. Weirdly, when I type this {{{main}}} function into ghci, the error is 'correct'. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:26:08 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:26:08 -0000 Subject: [GHC] #11796: Warn about unwanted instances in a modular way In-Reply-To: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> References: <046.91e31cdcc0e901faacb417cf9f6c616f@haskell.org> Message-ID: <061.de95ae2cdf98dc9faf38b6cb9767b886@haskell.org> #11796: Warn about unwanted instances in a modular way -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11219 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Lemming): Replying to [comment:5 RyanGlScott]: > Replying to [comment:4 Lemming]: > > A unification with the WARNING pragma looks like a good idea to me. I think I did not consider it, because currently warnings cannot be grouped. But if WARNINGs can be grouped we could re-use this capability for `instance` warnings. > > `WARNING`s can be grouped, actually: > > {{{#!hs > hello = "hello" > world = "world" > > {-# WARNING hello, world "Beware" #-} > }}} I see, the grouping works the other way round to what I had in mind. See below. > Indeed. In fact, there could be two different private modules in the same package that export two functions with the same name, or two instances with the same tag. I can't think of a better way to tell them apart, can you? I would consider it a feature, not a bug. Every warning tag should represent a group not a single object. If multiple objects get the same tag, you can enable and disable and error-convert multiple warnings via one tag. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:31:53 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:31:53 -0000 Subject: [GHC] #12106: Wrong type inferenced for locally defined function In-Reply-To: <042.655cd1f59022552be9f3be83f49a21ea@haskell.org> References: <042.655cd1f59022552be9f3be83f49a21ea@haskell.org> Message-ID: <057.8fdbfec9d8d467173f3dfef3fb686337@haskell.org> #12106: Wrong type inferenced for locally defined function -------------------------------------+------------------------------------- Reporter: syd | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => invalid Comment: The [http://stackoverflow.com/questions/32496864/what-is-the-monomorphism- restriction monomorphism restriction] applies to `myPrint`, so its inferred type cannot be `Show a => a -> IO ()`. It has nothing to do with the absense of a `Show` instance for `B` (as you can check by adding that instance). In GHCi the monomorphism restriction is disabled by default (as of a recent version of GHC). You can also turn it off for a module with `{-# LANGUAGE NoMonomorphismRestriction #-}`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:34:25 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:34:25 -0000 Subject: [GHC] #10594: the ghc-7.10.1-x86_64-apple-darwin.tar.bz2 doesn't install /sw/lib/ghc-7.10.1/ghcpr_8TmvWUcS1U1IKHT0levwg3/GHC In-Reply-To: <046.69b85de5f279bc6fd8a3f5ec62466a80@haskell.org> References: <046.69b85de5f279bc6fd8a3f5ec62466a80@haskell.org> Message-ID: <061.60eb0db7cc45509c2444eed48bb947ee@haskell.org> #10594: the ghc-7.10.1-x86_64-apple-darwin.tar.bz2 doesn't install /sw/lib/ghc-7.10.1/ghcpr_8TmvWUcS1U1IKHT0levwg3/GHC -------------------------------------+------------------------------------- Reporter: howarth | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: worksforme | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Installing GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme Comment: Closing, with the excuse that nobody else reported this problem. So it either had some external cause (disk full?), or it has since been fixed. Please reopen if you can reproduce the problem with the ghc-8.0.1 release. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:36:31 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:36:31 -0000 Subject: [GHC] #12106: Wrong type inferenced for locally defined function In-Reply-To: <042.655cd1f59022552be9f3be83f49a21ea@haskell.org> References: <042.655cd1f59022552be9f3be83f49a21ea@haskell.org> Message-ID: <057.154e4633c4d369095e4551dd76823b20@haskell.org> #12106: Wrong type inferenced for locally defined function -------------------------------------+------------------------------------- Reporter: syd | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by syd): Replying to [comment:1 rwbarton]: > The [http://stackoverflow.com/questions/32496864/what-is-the- monomorphism-restriction monomorphism restriction] applies to `myPrint`, so its inferred type cannot be `Show a => a -> IO ()`. It has nothing to do with the absense of a `Show` instance for `B` (as you can check by adding that instance). > > In GHCi the monomorphism restriction is disabled by default (as of a recent version of GHC). You can also turn it off for a module with `{-# LANGUAGE NoMonomorphismRestriction #-}`. Woops, did not know about this. Sorry to bother you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:50:51 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:50:51 -0000 Subject: [GHC] #11033: ghc 7.10.2 testsuite: "DoParamM(normal)" test fails In-Reply-To: <048.1c7db3aeebf6a66b725d369df661d4e5@haskell.org> References: <048.1c7db3aeebf6a66b725d369df661d4e5@haskell.org> Message-ID: <063.3ee2c48f73a519468e3574ba04b5e39d@haskell.org> #11033: ghc 7.10.2 testsuite: "DoParamM(normal)" test fails ---------------------------------+-------------------------------------- Reporter: dtonhofer | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 7.10.2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: commit dadf82d61f3cced61e9ccc35a5219e0b32cfee9e {{{ Author: Thomas Miedema Date: Mon Apr 25 16:58:34 2016 +0200 Testsuite: fixup lots of tests These aren't run very often, because they require external libraries. https://ghc.haskell.org/trac/ghc/wiki/Building/RunningTests/Running#AdditionalPackages maessen-hashtab still doesn't compile, QuickCheck api changed. Update submodule hpc. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 19:57:50 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 19:57:50 -0000 Subject: [GHC] #8990: Performance tests behave differently depending on presence of .hi file (even with -fforce-recomp) In-Reply-To: <045.abd2027873a2b9d9a2bc9aa2b4b749ea@haskell.org> References: <045.abd2027873a2b9d9a2bc9aa2b4b749ea@haskell.org> Message-ID: <060.e53d356219bd411ca60e590fce70d649@haskell.org> #8990: Performance tests behave differently depending on presence of .hi file (even with -fforce-recomp) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: thomie Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 7.9 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:D1187 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Fixed by running each test in a fresh `/tmp` directory (#11980). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 20:08:48 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 20:08:48 -0000 Subject: [GHC] #11081: Implement Introspective Template Haskell In-Reply-To: <047.67eb7661a40be634ed16872d272a44ca@haskell.org> References: <047.67eb7661a40be634ed16872d272a44ca@haskell.org> Message-ID: <062.706541c25c6ecbb89bd4c64e486d364e@haskell.org> #11081: Implement Introspective Template Haskell -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: ? Component: Template Haskell | 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: | TemplateHaskell/Introspective | -------------------------------------+------------------------------------- Changes (by alanz): * cc: alanz (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 20:27:13 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 20:27:13 -0000 Subject: [GHC] #11034: ghc 7.10.2 testsuite: "T367(normal)" test compilation fails In-Reply-To: <048.7bcba4146771a0fa18b97c4cde40ecf0@haskell.org> References: <048.7bcba4146771a0fa18b97c4cde40ecf0@haskell.org> Message-ID: <063.925303a0670bbe80925ab79e0a0c4558@haskell.org> #11034: ghc 7.10.2 testsuite: "T367(normal)" test compilation fails ---------------------------------+---------------------------------------- Reporter: dtonhofer | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: Component: Test Suite | Version: 7.10.2 Resolution: worksforme | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by thomie): * status: new => closed * resolution: => worksforme Comment: `T367` seems fine now. Tested with `vector-0.11` (the missing library) and ghc-7.10.3, ghc-8.0.1 and HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 20:55:23 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 20:55:23 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named In-Reply-To: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> References: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> Message-ID: <063.4901bacf6d8acfb44f8d6228100c4c43@haskell.org> #12060: GHC panic depending on what a Haskell module is named ----------------------------------+-------------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: | ----------------------------------+-------------------------------------- Comment (by Phyx-): At the very least, a version that uses cabal instead of Stack would be useful. As the extra level of abstraction makes it harder to debug GHC failures :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 21:48:04 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 21:48:04 -0000 Subject: [GHC] #11967: Custom message when showing functions, comparing functions, ... In-Reply-To: <051.2df31b020a6410a714945f3799f1d6ad@haskell.org> References: <051.2df31b020a6410a714945f3799f1d6ad@haskell.org> Message-ID: <066.64b2f3d2168815032e913bf62b105571@haskell.org> #11967: Custom message when showing functions, comparing functions, ... -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.3 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): I'll put this here, from a [https://twitter.com/paf31/status/734566028483657729 tweet] {{{#!hs instance TypeError (Text "Lists are not numbers!" :$$: Text "Use (++) or (Data.Monoid.<>) instead!") => Num [a] }}} {{{ ghci> "Hello" + " " + "World!" :91:1: error: ? Lists are not numbers! Use (++) or (Data.Monoid.<>) instead! ? In the expression: "Hello" + " " + "World!" In an equation for ?it?: it = "Hello" + " " + "World!" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 22:01:41 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 22:01:41 -0000 Subject: [GHC] #12060: GHC panic depending on what a Haskell module is named In-Reply-To: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> References: <048.9792be5fee2d5107059a1c21188af3f0@haskell.org> Message-ID: <063.b7dc45dbedc9e6b46587bdd1fb92dfe5@haskell.org> #12060: GHC panic depending on what a Haskell module is named ----------------------------------+-------------------------------------- Reporter: Darwin226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.3 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: | ----------------------------------+-------------------------------------- Comment (by Darwin226): I will try to shrink the problem a bit if I can, but I feel like this might be pretty pointless since the bug might not exist with GHC 8.0 It's a bit impractical for me to test if the same thing happens on the newer version at the moment, though maybe if I get a better example someone else can try it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 23:09:29 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 23:09:29 -0000 Subject: [GHC] #12107: Strange behavior of Foldable (,) a Message-ID: <046.a4aec5006e96c36a7e67ad6ab5610e05@haskell.org> #12107: Strange behavior of Foldable (,) a -------------------------------------+------------------------------------- Reporter: polarke | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core | Version: 8.0.1 Libraries | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The definion of ''Foldable (,) a'' is as follows. {{{#!hs instance Foldable ((,) a) where foldMap f (_, y) = f y foldr f z (_, y) = f y z }}} I am very confused with this definition. As a consequence, we have {{{#!hs maximum (1,0) == 0 }}} I believe this is not something we want. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 23:20:01 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 23:20:01 -0000 Subject: [GHC] #12107: Strange behavior of Foldable (,) a In-Reply-To: <046.a4aec5006e96c36a7e67ad6ab5610e05@haskell.org> References: <046.a4aec5006e96c36a7e67ad6ab5610e05@haskell.org> Message-ID: <061.282fa9ed23be208af28ed40d398c8036@haskell.org> #12107: Strange behavior of Foldable (,) a -------------------------------------+------------------------------------- Reporter: polarke | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => wontfix Comment: This has been discussed to death already: * https://mail.haskell.org/pipermail/libraries/2016-February/026678.html * https://mail.haskell.org/pipermail/libraries/2016-March/026851.html * https://www.reddit.com/r/haskell/comments/3oq0kd/proposal_eliminate_the_monad_implementation_on/ * https://www.reddit.com/r/haskell/comments/3pfg7x/either_and_in_haskell_are_not_arbitrary/ Closing as wontfix, until there is consensus to remove the instance from the libraries list or the Core Libraries Committee. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 23 23:24:01 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 23 May 2016 23:24:01 -0000 Subject: [GHC] #12107: Strange behavior of Foldable (,) a In-Reply-To: <046.a4aec5006e96c36a7e67ad6ab5610e05@haskell.org> References: <046.a4aec5006e96c36a7e67ad6ab5610e05@haskell.org> Message-ID: <061.a9fb901d5adf9d70e064d29950538038@haskell.org> #12107: Strange behavior of Foldable (,) a -------------------------------------+------------------------------------- Reporter: polarke | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by polarke): Thx for clearing! Replying to [comment:1 thomie]: > > This has been discussed to death already: > * https://mail.haskell.org/pipermail/libraries/2016-February/026678.html > * https://mail.haskell.org/pipermail/libraries/2016-March/026851.html > * https://www.reddit.com/r/haskell/comments/3oq0kd/proposal_eliminate_the_monad_implementation_on/ > * https://www.reddit.com/r/haskell/comments/3pfg7x/either_and_in_haskell_are_not_arbitrary/ > > Closing as wontfix, until there is consensus to remove the instance from the libraries list or the Core Libraries Committee. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 00:14:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 00:14:31 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.1f8a26dd68250c8515b0076bd66c4960@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by oerjan): As Ryan implies, Simon's suggestion seems precisely equivalent to abolishing `DeriveAnyClass` altogether. And the entire point of that extension is to extend `deriving` clauses to allow user-defined classes. OK, so the class annotation idea is not backwards compatible across actually adding those annotations. At least that would seem to need a major version change. Maybe they could still be useful to enable warnings if the program is implicitly using the non-recommended derivation type. This could easily happen if a module lists the wrong GND/DAC language extension. Your `ToJSON` example is instructive, in that a programmer might very well want either version, and in that there's already a problem ''today'' if the module lists the wrong language extensions. As for your last example, I meant for all of this to have no effect at all on `data` types. But on the other hand, an annotation of `{-# GND #-}` might strongly imply that a class is ''not'' designed to support DAC, and so suggest a warning. Which now makes me realize that it may be reasonable for some classes to support both, at least if they are equivalent in result (and then, probably more efficient with GND.) It's getting pretty obvious here that some of my design goals are inconsistent with each other. I'd suggest erring on the side of giving warnings unless the user is being explicit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 00:20:54 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 00:20:54 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.35ccd267a4c28b00fc9b7f64cb52891e@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: 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 would propose making the class-annotation stuff its own ticket?I think there's further discussion that would need to be had before considering such a change. In any case, I'm getting close to having a Diff ready for this. I originally implemented it using the type synonyms approach, but since that was shot down, I'll need to do some refactoring to use pragmas instead (hopefully just plumbing). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 01:20:25 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 01:20:25 -0000 Subject: [GHC] #12108: Function type synonym fails in pattern synonym Message-ID: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> #12108: Function type synonym fails in pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: 11977 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs pattern Id :: a -> a pattern Id x = x }}} works but {{{#!hs -- ? Pattern synonym ?Id? has one argument -- but its type signature has none -- ? In the declaration for pattern synonym ?Id? type Endo a = a -> a pattern Id :: Endo a pattern Id x = x }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 01:24:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 01:24:58 -0000 Subject: [GHC] #12108: Function type synonym fails in pattern synonym In-Reply-To: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> References: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> Message-ID: <066.9648c4db801deee88abe18d4f6e00d21@haskell.org> #12108: Function type synonym fails in pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11977 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: mpickering (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 01:32:21 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 01:32:21 -0000 Subject: [GHC] #12109: Matching on pattern synonym succeeds compiled with ghc, fails with ghci Message-ID: <051.866ade8c6398614612551f8239372ccc@haskell.org> #12109: Matching on pattern synonym succeeds compiled with ghc, fails with ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- A file `/tmp/test.hs` {{{#!hs {-# Language PatternSynonyms, ViewPatterns #-} pattern Parsed x = [(x, "")] pattern Read a <- (reads -> Parsed a) main = do let Read x = "420" print (x::Int) }}} {{{ $ ghc -ignore-dot-ghci /tmp/test.hs && /tmp/test 420 }}} fails with ghci {{{#!hs $ ghci -ignore-dot-ghci /tmp/test.hs GHCi, version 8.0.0.20160511: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/test.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.0.20160511 for x86_64-unknown-linux): kindPrimRep.go rep_a1XC Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 01:34:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 01:34:55 -0000 Subject: [GHC] #12109: Matching on pattern synonym succeeds compiled with ghc, fails with ghci In-Reply-To: <051.866ade8c6398614612551f8239372ccc@haskell.org> References: <051.866ade8c6398614612551f8239372ccc@haskell.org> Message-ID: <066.d760a74443da1fbbc90d2917527f8442@haskell.org> #12109: Matching on pattern synonym succeeds compiled with ghc, fails with ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): {{{#!hs $ ghci -ignore-dot-ghci GHCi, version 8.0.0.20160511: http://www.haskell.org/ghc/ :? for help Prelude> :set -XPatternSynonyms Prelude> :set -XViewPatterns Prelude> pattern Parsed x = [(x, "")] Prelude> pattern Read a <- (reads -> Parsed a) Prelude> let Read x = "420" in (x::Int) 420 }}} works -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 02:18:31 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 02:18:31 -0000 Subject: [GHC] #1965: Allow unconstrained existential contexts in newtypes In-Reply-To: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> References: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> Message-ID: <059.2df35c901468f3566f6f5e9f98acd71b@haskell.org> #1965: Allow unconstrained existential contexts in newtypes -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | 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: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 05:45:03 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 05:45:03 -0000 Subject: [GHC] #1965: Allow unconstrained existential contexts in newtypes In-Reply-To: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> References: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> Message-ID: <059.5c5b0457d18426f0d2174b29b440f60d@haskell.org> #1965: Allow unconstrained existential contexts in newtypes -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | 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 dfeuer): Replying to [comment:9 simonpj]: > Anything involving existentials is going to be hard to implement using newtype directly. But as 'mokus' says, it might be possible to make a guarantee, right in the code generator, that certain sorts of data types do not allocate a box. The conditions are, I think, very nearly as 'mokus' says: > 1. Only one constructor > 2. Only one field with nonzero width in that constructor (counting constraints as fields) > 3. That field is marked strict > 4. That field has a boxed (or polymorphic) type > I think this'd be do-able. The question is how important it is in practice; it's one more thing to maintain. I would like to have something like this very much! Among other things, it's one possible way to make `IntMap` nicer. One potential extension: I think constraints only need to count as fields if any of them are classes that have methods, or whose superclasses have methods. In particular, it could be very useful to have equality constraints involving type families. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 06:26:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 06:26:12 -0000 Subject: [GHC] #12110: Windows exception handler change causes segfault with API Monitor Message-ID: <045.d4b936e5e562932ebd0d335c0535752d@haskell.org> #12110: Windows exception handler change causes segfault with API Monitor ----------------------------------------+---------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Keywords: | Operating System: Windows Architecture: Unknown/Multiple | Type of failure: Runtime crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: ----------------------------------------+---------------------------------- [http://www.rohitab.com/apimonitor API Monitor] is a debugging tool that intercepts and logs calls to DLLs. It was extremely helpful with debugging #12010 and is broken in recent GHCs. Attaching it to a GHC compiled executable causes the message `Segmentation fault/access violation in generated code` to be printed. Launching one from inside API Monitor doesn't work either, though I can't read the console output before the window closes. Bisect shows the offending commit is 5200bdeb26 - "Replaced SEH handles with VEH handlers which should work uniformly across x86 and x64". I know this is somewhat outside of "standard usage", but there are very few useful debugging tools for stuff like this and I'd really like to not lose this one. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 07:01:20 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 07:01:20 -0000 Subject: [GHC] #9678: Warning about __sync_fetch_and_nand semantics from gcc In-Reply-To: <045.23b8870530d0cafb1b87a515eec9fc0e@haskell.org> References: <045.23b8870530d0cafb1b87a515eec9fc0e@haskell.org> Message-ID: <060.e6858086c315083e43d94cd55c429d0b@haskell.org> #9678: Warning about __sync_fetch_and_nand semantics from gcc -------------------------------------+------------------------------------- Reporter: gintas | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Build System | Version: 7.9 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): -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"4f5b33529b9e13b49a3ee00e9116b0edc9df1234/ghc" 4f5b3352/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4f5b33529b9e13b49a3ee00e9116b0edc9df1234" Suppress the warning about __sync_fetch_and_nand (#9678) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 07:04:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 07:04:07 -0000 Subject: [GHC] #9678: Warning about __sync_fetch_and_nand semantics from gcc In-Reply-To: <045.23b8870530d0cafb1b87a515eec9fc0e@haskell.org> References: <045.23b8870530d0cafb1b87a515eec9fc0e@haskell.org> Message-ID: <060.bc1835418e7954486b287a2c7e7d8e8a@haskell.org> #9678: Warning about __sync_fetch_and_nand semantics from gcc -------------------------------------+------------------------------------- Reporter: gintas | Owner: Type: bug | Status: closed Priority: low | Milestone: 8.2.1 Component: Build System | Version: 7.9 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: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 07:06:32 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 07:06:32 -0000 Subject: [GHC] #12110: Windows exception handler change causes segfault with API Monitor In-Reply-To: <045.d4b936e5e562932ebd0d335c0535752d@haskell.org> References: <045.d4b936e5e562932ebd0d335c0535752d@haskell.org> Message-ID: <060.09eaa64365b410310c729c27b9b951eb@haskell.org> #12110: Windows exception handler change causes segfault with API Monitor -------------------------------------+------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Phyx-): The Exception handlers shouldn't be the issue. The don't cause the segfault. It only handles them when they happen. It likely has to do with how API monitoring does API hooking. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 07:25:28 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 07:25:28 -0000 Subject: [GHC] #12108: Function type synonym fails in pattern synonym In-Reply-To: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> References: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> Message-ID: <066.f794c424d1d29c7f4f3fc9686db9ce21@haskell.org> #12108: Function type synonym fails in pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11977 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj Comment: Similar to #11977, which I am fixing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:00:57 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:00:57 -0000 Subject: [GHC] #1851: "make install-strip" should work In-Reply-To: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> References: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> Message-ID: <059.1f097b1e6690b6de9363d5c8db241052@haskell.org> #1851: "make install-strip" should work -------------------------------------+------------------------------------- Reporter: igloo | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.1 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 gidyn): * status: new => closed * resolution: => fixed Comment: I seem to be having a problem with gcc. I'll re-open if it turns out that there was an issue in ghc after all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:19:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:19:37 -0000 Subject: [GHC] #1851: "make install-strip" should work In-Reply-To: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> References: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> Message-ID: <059.e0f9fe9e9ed5b0add2f08141ad8d70ea@haskell.org> #1851: "make install-strip" should work -------------------------------------+------------------------------------- Reporter: igloo | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.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 gidyn): * status: closed => new * resolution: fixed => Comment: OK, I think I've found the libraries which aren't stripped. (Apologies for the earlier comment, a problem with my gcc installation had led me to think that nothing is stripped.) {{{ # cd /usr/local/lib/ghc-8.0.1/rts # du -h * 3.1M libHSrts.a 3.9M libHSrts_thr.a # strip --strip-unneeded * # du -h * 736K libHSrts.a 848K libHSrts_thr.a }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:22:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:22:47 -0000 Subject: [GHC] #11011: Add type-indexed type representations (`TypeRep a`) In-Reply-To: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> References: <047.c73f466ae3b4d7fe3bfc6781e66855ef@haskell.org> Message-ID: <062.194e07b4e4eedb45030624f7c355a4a4@haskell.org> #11011: Add type-indexed type representations (`TypeRep a`) -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2010 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:43 Iceland_jack]: > Bikeshedding. > > Base already has the existentials `SomeSymbol` and `SomeNat` so one wonders if `SomeTypeRep` is a more consistent name for `TypeRepX`. Very true. I do like this proposal despite the name being a bit longer. Really, the length isn't even such a big deal given that users can always use the `Data.Typeable.TypeRep` synonym. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:27:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:27:07 -0000 Subject: [GHC] #1851: "make install-strip" should work In-Reply-To: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> References: <044.55b2dd35d7abad74f0ebfed90c4f828d@haskell.org> Message-ID: <059.0790cbf6d260636cd0e5c9f63aea8564@haskell.org> #1851: "make install-strip" should work -------------------------------------+------------------------------------- Reporter: igloo | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Build System | Version: 8.0.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: | -------------------------------------+------------------------------------- Comment (by thomie): Ack. Maybe the new build system (https://github.com/snowleopard/hadrian) will do better, although it doesn't know how to install GHC at all yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:47:05 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:47:05 -0000 Subject: [GHC] #12108: Function type synonym fails in pattern synonym In-Reply-To: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> References: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> Message-ID: <066.6b199a71674b84a03b5d924089eb24c6@haskell.org> #12108: Function type synonym fails in pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: 11977 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"03d8960388d64f5d5c9617dd0e21555e9e987e26/ghc" 03d89603/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="03d8960388d64f5d5c9617dd0e21555e9e987e26" Don't split the arg types in a PatSyn signature This patch fixes Trac #11977, and #12108, rather satisfactorily maily by deleting code! pattern P :: Eq a => a -> a -> Int The idea is simply /not/ to split the bit after the '=>' into the pattern argument types, but to keep the (a->a->Int) part un-decomposed, in the patsig_body_ty field of a TcPatSynInfo. There is one awkward wrinkle, which is that we can't split the implicitly-bound type variables into existential and universal until we know which types are arguments and which are part of the result. So we postpone the decision until we have the declaration in hand. See TcPatSyn Note [The pattern-synonym signature splitting rule] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:47:05 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:47:05 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.3818be9edb3618d40fc351153cc6a615@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"03d8960388d64f5d5c9617dd0e21555e9e987e26/ghc" 03d89603/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="03d8960388d64f5d5c9617dd0e21555e9e987e26" Don't split the arg types in a PatSyn signature This patch fixes Trac #11977, and #12108, rather satisfactorily maily by deleting code! pattern P :: Eq a => a -> a -> Int The idea is simply /not/ to split the bit after the '=>' into the pattern argument types, but to keep the (a->a->Int) part un-decomposed, in the patsig_body_ty field of a TcPatSynInfo. There is one awkward wrinkle, which is that we can't split the implicitly-bound type variables into existential and universal until we know which types are arguments and which are part of the result. So we postpone the decision until we have the declaration in hand. See TcPatSyn Note [The pattern-synonym signature splitting rule] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:56:43 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:56:43 -0000 Subject: [GHC] #10832: Generalize injective type families In-Reply-To: <048.1487f224b00112fe37d31a1812a748a4@haskell.org> References: <048.1487f224b00112fe37d31a1812a748a4@haskell.org> Message-ID: <063.3b732857892d50aefbaf66f556fe48f9@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) | Resolution: | Keywords: TypeFamilies 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 jstolarek): Carter, can you upload a self-contained piece of code? When we were working on injective type families we had a really hard time finding real- world examples where injectivity was necessary. Many people in the past claimed that they needed it but when we finally had the feature implemented few people could remember their use cases from the past. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 08:58:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 08:58:30 -0000 Subject: [GHC] #10016: UNPACK support for existentials In-Reply-To: <046.c8a66a042094ff097eced717a1d59a97@haskell.org> References: <046.c8a66a042094ff097eced717a1d59a97@haskell.org> Message-ID: <061.a19b20d7b474b2a11c95c2db13cf0b01@haskell.org> #10016: UNPACK support for existentials -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 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): See also #1965 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 09:00:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 09:00:06 -0000 Subject: [GHC] #12108: Function type synonym fails in pattern synonym In-Reply-To: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> References: <051.c961edc0b6315fc46eb10fe81ebe225a@haskell.org> Message-ID: <066.98c5817df047727c0280f02438f2648f@haskell.org> #12108: Function type synonym fails in pattern synonym -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | patsyn/should_compile/T12108 Blocked By: | Blocking: Related Tickets: 11977 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => patsyn/should_compile/T12108 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 09:00:35 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 09:00:35 -0000 Subject: [GHC] #11977: ghc doesn't agree with its own inferred pattern type In-Reply-To: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> References: <051.890e2a0ef534fc631508076f831baaf7@haskell.org> Message-ID: <066.1e0e652332ea97032b0a62c71e6e3e11@haskell.org> #11977: ghc doesn't agree with its own inferred pattern type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | patsyn/should_compile/T11977 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => patsyn/should_compile/T11977 * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 09:47:34 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 09:47:34 -0000 Subject: [GHC] #11980: Testsuite: run each test in its own /tmp directory, after copying required files In-Reply-To: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> References: <045.666c00e2d5978d6e6851add98af62b04@haskell.org> Message-ID: <060.49d8b590e50ec3d7ff784f57ab06dec8@haskell.org> #11980: Testsuite: run each test in its own /tmp directory, after copying required files -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: task | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | 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:D1187 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"35053eb6c3f9058020f9818bf0de672aef6894c9/ghc" 35053eb6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="35053eb6c3f9058020f9818bf0de672aef6894c9" Testsuite: delete check_files_written The CHECK_FILES_WRITTEN feature is no longer necessary, since tests don't write to the source directory anymore (#11980). Reviewed by: bgamari Differential Revision: https://phabricator.haskell.org/D2162 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 10:10:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 10:10:37 -0000 Subject: [GHC] #12109: Matching on pattern synonym succeeds compiled with ghc, fails with ghci In-Reply-To: <051.866ade8c6398614612551f8239372ccc@haskell.org> References: <051.866ade8c6398614612551f8239372ccc@haskell.org> Message-ID: <066.2e8460a098466aeb8856a22c2ee6e50d@haskell.org> #12109: Matching on pattern synonym succeeds compiled with ghc, fails with ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: duplicate | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12007 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => closed * resolution: => duplicate * related: => #12007 Comment: This is the same as #12007 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 10:12:09 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 10:12:09 -0000 Subject: [GHC] #11993: RFC, allow local bindings in pattern synonyms In-Reply-To: <051.8c746ee9d0f7bcf6a2764a5c20344e08@haskell.org> References: <051.8c746ee9d0f7bcf6a2764a5c20344e08@haskell.org> Message-ID: <066.2d15d436e76e4d0d35b00c432e56bee1@haskell.org> #11993: RFC, allow local bindings in pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I don't think this is a terrible idea but it does mean that the overloaded `where` could also be used in a non-overloaded way. I'm inclined to say that we should leave things as they are for now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 10:27:18 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 10:27:18 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.6ac282679c4e964c53942c4f6dc6103e@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * priority: normal => high * cc: hsyl20 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 10:59:18 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 10:59:18 -0000 Subject: [GHC] #12096: Attach stacktrace information to SomeException In-Reply-To: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> References: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> Message-ID: <064.057b216c09672dad36d5fe0177758932@haskell.org> #12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ndtimofeev): 1. I just copy `ErrorCall` API and implementation. Also I would like to see both stacktrace (`CallStack` and `CostCentreStack`, not only `CallStack`). 2. Yep, stacktrace information is lost when we catch unwraped exception. It looks like a problem. First: {{{#!hs f = throw (CustomException False) g = f `catch` \err@(CustomException fixable) -> if fixable then makeGood else throw err }}} We only rethrow exception and? change it stacktrace. Now it start from `throw` in `g`, not in `f`. Second: {{{#!hs onException eval handler = eval `catch` (\e@(SomeException _) -> handler >> throw e) f = throw (CustomException False) g = f `onException` makeGood }}} Now exception has to stacktrace. Third: {{{#!hs loop = forever $ threadDelay maxBound main = do tid <- forkIO $ loop `onException` putStrLn "Bang!" threadDelay 1000000 throwTo tid UserException }}} Now `UserException` has absolutely irrelevant stacktrace. I don't know how fix first problem. The second can be fixed something like that: {{{#!hs throw :: (HasCallStack, Exception e) => e -> a throw e | Just (SomeException _) <- cast e = raise# e | otherwise = unsafeDupablePerformIO $ do stack <- currentCallStack raise# (CallStackException e $ if stack /= [] then prettyCallStack ?callStack ++ "\n" ++ renderStack stack else prettyCallStack ?callStack) }}} The third is more complicated. For example we can skip stacktrace information for asynchronous exceptions. But in general, we can't determine this exception synchronous or asynchronous. Perhaps `throwTo` can add to exception extra information. But I do not understand how. {{{#!hs throwTo' :: Exception e => ThreadId -> e -> IO a throwTo' tid = throwTo tid . SomeAsyncException catch' :: Exception e => IO a -> (e -> IO a) -> IO a catch' eval handler = eval `catch` \err@(SomeException _) -> go err handler err where go :: (Exception e, Exception a) => e -> (a -> IO b) -> SomeException -> IO b go ex f origErr | Just v <- cast ex = f v | Just (SomeException inner) <- cast ex = go inner f origErr | Just (SomeAsyncException inner) <- cast ex = go inner f origErr | otherwise = throw origErr }}} Also it will be useful in situation like that: {{{#!hs processCmd = timeout 20000 . postDataAndWaitResponce main = do tasks <- newChan :: IO (Chan (String, MVar (Either SomeEception (Maybe String)))) tid <- forkIO $ forever $ do (cmd, ret) <- readChan tasks try (processCmd cmd) >>= putMVar ret threadDelay 1000000 throwTo tid UserException }}} `UserException` can't kill forked thread because it try catch all (synchronous) exception. If `try (processCmd cmd) >>= putMVar ret` will be masked `timeout` will be broken. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 10:59:39 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 10:59:39 -0000 Subject: [GHC] #11743: Add unicode support for TH quotes (`[| |]`) In-Reply-To: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> References: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> Message-ID: <066.49cabecfc2617617a82c28947fcfed3e@haskell.org> #11743: Add unicode support for TH quotes (`[| |]`) -------------------------------------+------------------------------------- Reporter: JoshPrice247 | Owner: JoshPrice247 Type: feature request | Status: patch Priority: low | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 (Parser) | Keywords: unicode, Resolution: | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2878, #10162 | Differential Rev(s): Phab:D2185 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"8f7d01632cd79957fe42ea37103ca9b91a1c54f5/ghc" 8f7d0163/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8f7d01632cd79957fe42ea37103ca9b91a1c54f5" Add support for unicode TH quotes (#11743) I've also added cases for `IToparenbar` and `ITcparenbar` (aka banana brackets) to `isUnicode`. Document unicode TH quote alternatives (#11743) Test Plan: ./validate Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2185 GHC Trac Issues: #11743 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 11:00:41 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 11:00:41 -0000 Subject: [GHC] #11743: Add unicode support for TH quotes (`[| |]`) In-Reply-To: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> References: <051.4e3f659fb72a6cab53dcc41b17807208@haskell.org> Message-ID: <066.8cb8f5e6ff67a9f1e6f3b19003ee994a@haskell.org> #11743: Add unicode support for TH quotes (`[| |]`) -------------------------------------+------------------------------------- Reporter: JoshPrice247 | Owner: JoshPrice247 Type: feature request | Status: closed Priority: low | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 (Parser) | Keywords: unicode, Resolution: fixed | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2878, #10162 | Differential Rev(s): Phab:D2185 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 11:31:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 11:31:11 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.59037de625de305c2316f684b9049b54@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"4c6e69d58a300d6ef440d326a3fd29b58b284fa1/ghc" 4c6e69d5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4c6e69d58a300d6ef440d326a3fd29b58b284fa1" Document some benign nondeterminism I've changed the functions to their nonDet equivalents and explained why they're OK there. This allowed me to remove foldNameSet, foldVarEnv, foldVarEnv_Directly, foldVarSet and foldUFM_Directly. Test Plan: ./validate, there should be no change in behavior Reviewers: simonpj, simonmar, austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2244 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 12:41:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 12:41:30 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.56e367aada5fa31946539653e3659019@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: 11362 | Blocking: Related Tickets: #10424 | Differential Rev(s): Phab:D910, | Phab:D1073, Phab:D1133, Phab:D1192, | Phab:D1268, Phab:D1360, Phab:D1373, Wiki Page: | Phab:D1396, Phab:D1457, Phab:D1468, DeterministicBuilds | Phab:D1487, Phab:D1504, Phab:D1508 -------------------------------------+------------------------------------- Comment (by Bartosz Nitka ): In [changeset:"9d06ef1ae451a145607301dc7556931b537a7d83/ghc" 9d06ef1a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9d06ef1ae451a145607301dc7556931b537a7d83" Make Arrow desugaring deterministic This kills two instances of varSetElems that turned out to be nondeterministic. I've tried to untangle this before, but it's a bit hard with the fixDs in the middle. Fortunately I now have a test case that proves that we need determinism here. Test Plan: ./validate, new testcase Reviewers: simonpj, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2258 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 12:59:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 12:59:12 -0000 Subject: [GHC] #12105: merge MatchFixity and HsMatchContext In-Reply-To: <044.0d136ec1e3b0b0304a6895a0a48280ac@haskell.org> References: <044.0d136ec1e3b0b0304a6895a0a48280ac@haskell.org> Message-ID: <059.1d8b50aa6a9ba332e470c0f9494d7ece@haskell.org> #12105: merge MatchFixity and HsMatchContext -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Sounds good to me! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 13:27:58 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 13:27:58 -0000 Subject: [GHC] #12096: Attach stacktrace information to SomeException In-Reply-To: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> References: <049.d8705f5da8c3125826af35f329bd903a@haskell.org> Message-ID: <064.dbd55d1bf2d0938cb883ea8b35bfc024@haskell.org> #12096: Attach stacktrace information to SomeException -------------------------------------+------------------------------------- Reporter: ndtimofeev | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ndtimofeev): * Attachment "Exception.hs" added. proof of concept -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 15:13:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 15:13:26 -0000 Subject: [GHC] #9249: Link to "latest" user's guide In-Reply-To: <047.de05e08954a03649b76e01617284c75d@haskell.org> References: <047.de05e08954a03649b76e01617284c75d@haskell.org> Message-ID: <062.5ad2d4be5565eb93ffb44c092e49998c@haskell.org> #9249: Link to "latest" user's guide -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Documentation | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 15:26:23 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 15:26:23 -0000 Subject: [GHC] #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection In-Reply-To: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> References: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> Message-ID: <061.d5816a3ee7675ac533141918aec62677@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Test Suite | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T8958a Blocked By: | Blocking: Related Tickets: #10298, #7695 | Differential Rev(s): Phab:D1059, Wiki Page: | Phab:D1085, Phab:D2262 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * differential: Phab:D1059, Phab:D1085 => Phab:D1059, Phab:D1085, Phab:D2262 Comment: I have another patch for this series. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 15:31:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 15:31:47 -0000 Subject: [GHC] #9249: Link to "latest" user's guide In-Reply-To: <047.de05e08954a03649b76e01617284c75d@haskell.org> References: <047.de05e08954a03649b76e01617284c75d@haskell.org> Message-ID: <062.fd82b42cc2891434e9ca799ac9d2834e@haskell.org> #9249: Link to "latest" user's guide -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: low | Milestone: 8.2.1 Component: Documentation | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.2.1 Comment: Hmm, alright, this will be a bit tricky but I think we can manage it. It will mean, however, that I'll need to rework the workflow for generating the documentation for downloads.haskell.org as currently is it simply extracted from the bindist. I'll try to have a look at doing this soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 15:49:19 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 15:49:19 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.3940844d560a0da571d2be0a5e6cb43f@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): Interestingly, these seem to fix this code: - Marking the FFI function "safe". - `-XStrict` May be helpful when debugging... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 16:26:38 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 16:26:38 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.e21fee9f8781fa32db453de980258bd0@haskell.org> #8308: Resurrect ticky code for counting constructor arity ------------------------------+---------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Windows | Architecture: Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Wiki Page: | ------------------------------+---------------------------------------- Changes (by thomie): * cc: Phyx- (added) * os: Unknown/Multiple => Windows Comment: On Windows, `T8308` fails with: {{{ Actual stdout output differs from expected: ... -1 +0 *** unexpected failure for T8308(normal) }}} After running `make test TEST=T8308 CLEANUP=0`, the `.ticky` file contains this fishy looking histogram (note the `4294967296` entry): {{{ The following table is explained by http://ghc.haskell.org/trac/ghc/wiki/Debugging/TickyTicky All allocation numbers are in bytes. ************************************************** Entries Alloc Alloc'd Non-void Arguments STG Name -------------------------------------------------------------------------------- 1 16 0 1 I f{v rpA} (main at main:Main) (fun) ************************************************** ... 0 RET_UNBOXED_TUP_ctr 4294967296 RET_NEW_hst_0 0 RET_NEW_hst_1 ... }}} @mlen: any idea? Perhaps a known issue with ticky on Windows? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 17:38:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 17:38:37 -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.fc3c23fe094e2d5956ee87835f112ad6@haskell.org> #10822: GHC inconsistently handles \\?\ for long paths on Windows ---------------------------------+---------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: 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): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by Phyx-): The problem is that we rely on ports of POSIX applications to work. e.g. GCC, binutils etc. So even if GHC supports UNC paths. It probably wouldn't help much unfortunately. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 18:21:10 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 18:21:10 -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.eaf0d75ff9f05ea6a2897e1580147c6c@haskell.org> #10822: GHC inconsistently handles \\?\ for long paths on Windows ---------------------------------+---------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: 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): Wiki Page: | ---------------------------------+---------------------------------------- Comment (by ezyang): But then the best thing to do is figure out exactly what the state of short path support is in the toolchain, lobby projects to fix this, and eventually get this fixed. upstream is broken is not an excuse to throw ones hands up and give up. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 19:06:05 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 19:06:05 -0000 Subject: [GHC] #12111: prof build flavour doesn't work Message-ID: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> #12111: prof build flavour doesn't work -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Building with `prof` flavour on a fresh build doesn't work. I'm currently getting {{{ compiler/utils/Outputable.hs-boot:1:8: error: Failed to load interface for ?Prelude? Perhaps you haven't installed the "p_dyn" libraries for package ?base-4.9.0.0?? Use -v to see a list of the files searched for. }}} In addition, I don't see any profiling flags passes to GHC in `prof.mk` (like `-fprof-auto`), so I'm not sure how effective default profiling build is. Am I missing something or do users need to add those manually to `GhcStage2HcOpts`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 19:40:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 19:40:07 -0000 Subject: [GHC] #12112: Testsuite driver links from /tmp directory to .hi and .o files in source directory Message-ID: <045.7d23a7a3cb4a7b7416891da2c643789a@haskell.org> #12112: Testsuite driver links from /tmp directory to .hi and .o files in source directory -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11980 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is a clear bug, but only shows up when the source directory is not clean. Perhaps from a validate run from before the `/tmp` testsuite patch. A user might also have been running some small sample programs in the source directory manually. The testsuite driver currently matches `*`. I'm not sure if a whitelist or blacklist solution is more future proof. These are all existing filetypes in the testsuite: {{{ $ find . -name tests | xargs dir | grep -v stderr | grep -v stdout Extension Files ==================================== .def (1) .tix (1) .hspp (2) .ghci (1) .primops (1) .mix (1) .gnp (2) .so (1) .md (2) .hx (1) .sh (1) .test (1) .cpp (2) .mm (1) .gitignore (7) .m (2) .asm (4) .conf (2) .h (19) .hsc (10) .lib (2) .pkg (14) .hs-boot (49) .txt (5) .hsig (14) .cabal (37) .gml (1) .cmm (46) .sample (14) .c (66) .dat (3) .pgn (1) .stdin (8) .lhs (23) .script (318) .plt (2) .T (311) (370) . (438) .hs (5343) Total: (10370) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 19:42:17 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 19:42:17 -0000 Subject: [GHC] #12112: Testsuite driver links from /tmp directory to .hi and .o files in source directory In-Reply-To: <045.7d23a7a3cb4a7b7416891da2c643789a@haskell.org> References: <045.7d23a7a3cb4a7b7416891da2c643789a@haskell.org> Message-ID: <060.d4aa38c9578af60595e208d1f353ff69@haskell.org> #12112: Testsuite driver links from /tmp directory to .hi and .o files in source directory -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | 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: #11980 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): After fixing this, I think it's save to reapply the iface compression patch: commit 9bb277269ec020f138fe70a65f5972466113ab61 {{{ Author: Ben Gamari Date: Mon May 23 15:32:12 2016 +0200 Revert "compiler/iface: compress .hi files" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 19:54:47 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 19:54:47 -0000 Subject: [GHC] #12113: ghc-8.0.1-rc4: unification false positive? Message-ID: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> #12113: ghc-8.0.1-rc4: unification false positive? -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnicodeSyntax #-} module Foo () where type family TF x ? * data ADT x type instance TF (ADT x) = x class (a ~ ADT (TF a)) ? TC2 a b | a ? b data Forget = ? a b. TC2 a b ? Forget a -- ~ Forget (ADT (TF a)) data PhantomF a b = Constr Forget -- ~ Constr (Forget (ADT (TF a))) f ? ? a b. TC2 a b ? ADT (TF a) ? [Forget] f _ = case ((undefined) ? (PhantomF a b)) of Constr m ? [Forget m] -- Here GHC 8.0.1-rc4 unifies, whereas GHC 7.10.3 (properly?) fails with: -- ghc8-unification-false-positive.hs:20:21: -- Couldn't match type ?Forget? with ?ADT (TF Forget)? -- In the expression: Forget m -- In the expression: [Forget m] -- In a case alternative: Constr m -> [Forget m] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 19:55:20 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 19:55:20 -0000 Subject: [GHC] #12113: ghc-8.0.1-rc4: unification false positive? In-Reply-To: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> References: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> Message-ID: <063.c05efc66d43f70ad0a933f40a19893ad@haskell.org> #12113: ghc-8.0.1-rc4: unification false positive? -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * Attachment "ghc8-unification-false-positive.hs" added. Test case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 19:56:36 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 19:56:36 -0000 Subject: [GHC] #12113: ghc-8.0.1-rc4: unification false positive? In-Reply-To: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> References: <048.c95bd6fbcccb5a650cdc8ab8ee561a4e@haskell.org> Message-ID: <063.219e82032df0df54c6c09fbbc259d239@haskell.org> #12113: ghc-8.0.1-rc4: unification false positive? -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by _deepfire): * testcase: => Yes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 20:16:12 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 20:16:12 -0000 Subject: [GHC] #12114: GHC rejects injective type family Message-ID: <050.2ff02132b5faa0737de73fd83ef430b0@haskell.org> #12114: GHC rejects injective type family -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following injective type family fails to compile in GHC 8.0 {{{ type family Snoc (xs :: [k]) (y::k) = r | r -> xs y where Snoc '[] y = '[y] Snoc (x ': xs) y = x ': (Snoc xs y) }}} The error message is {{{ ? Type family equations violate injectivity annotation: forall k (y :: k). Snoc '[] y = '[y] -- Defined at FAlgebra.hs:49:5 forall k (xs :: [k]) (x :: k) (y :: k). Snoc (x : xs) y = x : Snoc xs y -- Defined at FAlgebra.hs:52:5 ? In the equations for closed type family ?Snoc? In the type family declaration for ?Snoc? }}} I think the problem is related to injectivity rule 5 from [this page](https://ghc.haskell.org/trac/ghc/wiki/InjectiveTypeFamilies) being too conservative. In particular, if you substitute `'[]` for `Snoc xs y` in the RHS of the second rule, then the two rules will unify but have different LHSs. This substitution is invalid, however, because the `Snoc` type family will never result in an empty list. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:09:06 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:09:06 -0000 Subject: [GHC] #12110: Windows exception handler change causes segfault with API Monitor In-Reply-To: <045.d4b936e5e562932ebd0d335c0535752d@haskell.org> References: <045.d4b936e5e562932ebd0d335c0535752d@haskell.org> Message-ID: <060.e6015d2eccae2fd00f60f5b9bcf1fb1e@haskell.org> #12110: Windows exception handler change causes segfault with API Monitor -------------------------------------+------------------------------------- Reporter: enolan | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 8.0.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by enolan): It works before the commit and doesn't after. It may be fair to blame API Monitor's developer, but the exception handlers are definitely involved. Maybe API Monitor method of hooking triggers the exception handler and it's incorrectly interpreted as a segfault? You definitely know more about this than me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:41:42 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:41:42 -0000 Subject: [GHC] #11700: pattern match bug In-Reply-To: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> References: <050.22a2b2ee064f088d52261b2a9d8c72b0@haskell.org> Message-ID: <065.2e5b3ef38690686c8694068d8f5e63e8@haskell.org> #11700: pattern match bug -------------------------------------+------------------------------------- Reporter: TobyGoodwin | Owner: Type: bug | 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 thomie): * testcase: https://github.com/TobyGoodwin/odd-ghc-pattern-bug => * component: Compiler => Compiler (Type checker) Comment: @simonpj: like TobyGoodwin said, the example from comment:4 doesn't have any dependencies. This bug goes back to at least ghc-7.8. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:45:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:45:55 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.847ad7eada85a4f8641e96c1830cfe03@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: seraphime Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"1956cbf13bd2138500daebd5f1f0a4931d8710ec/ghc" 1956cbf1/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1956cbf13bd2138500daebd5f1f0a4931d8710ec" Fix: #12084 deprecate old profiling flags Change help message so it doesn't specify -auto-all. Make old profiling flags deprecated as they are no longer documented. Update Makefile and documentation accordingly. Update release notes for ghc 8.2 Test Plan: ./verify; `ghc --help` shouldn't specify the -auto-all flag. Furthermore `ghc -fprof -auto-all` should emit a warning Reviewed By: thomie, austin Differential Revision: https://phabricator.haskell.org/D2257 GHC Trac Issues: #12084 Update submodule nofib }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:45:55 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:45:55 -0000 Subject: [GHC] #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection In-Reply-To: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> References: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> Message-ID: <061.8d5041bf642b5f2af8bc2e51744f47da@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Test Suite | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T8958a Blocked By: | Blocking: Related Tickets: #10298, #7695 | Differential Rev(s): Phab:D1059, Wiki Page: | Phab:D1085, Phab:D2262 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"1319363f7633c441bdb1f659616d71ecd700076d/ghc" 1319363f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="1319363f7633c441bdb1f659616d71ecd700076d" Always use native-Haskell de/encoders for ASCII and latin1 This fixes test encoding005 on Windows (#10623). Reviewed by: austin, bgamari Differential Revision: https://phabricator.haskell.org/D2262 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:48:44 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:48:44 -0000 Subject: [GHC] #12084: ghc --help suggests -auto-all instead of -fprof-auto In-Reply-To: <045.6138befcdfe66be8ab592f178622610b@haskell.org> References: <045.6138befcdfe66be8ab592f178622610b@haskell.org> Message-ID: <060.5311a1b39e6cdd0b81ecb601e7b5075e@haskell.org> #12084: ghc --help suggests -auto-all instead of -fprof-auto -------------------------------------+------------------------------------- Reporter: kjslag | Owner: seraphime Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 Comment: seraphime: congratulations with your first GHC patch. kjslag: thank you for the report. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:52:07 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:52:07 -0000 Subject: [GHC] #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection In-Reply-To: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> References: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> Message-ID: <061.a0a39024efba534b7c69b9ca3d7cb87f@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T8958a, | libraries/base/tests/IO/encoding005 Blocked By: | Blocking: Related Tickets: #10298, #7695 | Differential Rev(s): Phab:D1059, Wiki Page: | Phab:D1085, Phab:D2262 -------------------------------------+------------------------------------- Changes (by thomie): * testcase: T8958a => T8958a, libraries/base/tests/IO/encoding005 * status: patch => closed * resolution: => fixed * milestone: 8.0.2 => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 21:54:44 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 21:54:44 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.730ca1227ae72f6ca362e9a273ff0b33@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I spent some time debugging this. Here are codes for FFI function arguments (before register allocation): {{{ first arg: [ xorl %edi,%edi] second arg: [ xorl %esi,%esi] third arg: [ movl $7457,%edx] fourth arg: [ movl $255,%vI_n4I8, movq 7(%rbx),%vI_n4Ia, imulq %vI_s4pW,%vI_n4Ia, movl %vI_n4Ia,%eax, xorq %rdx,%rdx, divq %vI_n4I8, movq %rax,%vI_n4Ib, shlq $8,%vI_n4Ib, movl %vI_n4Ib,%vI_n4Ic, movl $255,%vI_n4Id, movq 24(%rbp),%vI_n4If, imulq %vI_s4pW,%vI_n4If, movl %vI_n4If,%eax, xorq %rdx,%rdx, divq %vI_n4Id, movq %rax,%vI_n4Ih, addq %vI_n4Ic,%vI_n4Ih, movl %vI_n4Ih,%vI_n4Ii, shlq $8,%vI_n4Ii, movl %vI_n4Ii,%vI_n4Ij, movl $255,%vI_n4Ik, movq 16(%rbp),%vI_n4Im, imulq %vI_s4pW,%vI_n4Im, movl %vI_n4Im,%eax, xorq %rdx,%rdx, divq %vI_n4Ik, movq %rax,%vI_n4Io, addq %vI_n4Ij,%vI_n4Io, movl %vI_n4Io,%vI_n4Ip, shlq $8,%vI_n4Ip, movl %vI_n4Ip,%vI_n4Iq, leaq 255(%vI_n4Iq),%vI_n4Ir, movl %vI_n4Ir,%ecx] }}} These look correct to me. Since the code mostly uses virtual registers `%edx` isn't overridden at this point. So I think the problem may be in register allocation. I don't know how register allocation in GHC is working, but I looked at liveness information output, and it shows this for the `call third_arg` instruction: {{{ call third_arg # born: %r8 %r9 %r10 %r11 %r16 %r17 %r18 %r19 %r20 %r21 %r24 %r25 %r26 %r27 %r28 %r29 %r30 %r31 %r32 %r33 %r34 %r35 %r36 %r37 %r38 %r39 # w_dying: %r2 %r3 %r4 %r5 %r8 %r9 %r10 %r11 %r16 %r17 %r18 %r19 %r20 %r21 %r24 %r25 %r26 %r27 %r28 %r29 %r30 %r31 %r32 %r33 %r34 %r35 %r36 %r37 %r38 %r39 }}} I don't quite understand what's happening here (what are all those registers??), but I'd expect this instruction to "read" (or "use") `%edx`. So `%edx` would have to stay live between `third arg` and this call instruction, and so register allocation would have to generate some spill instructions when allocating registers for fourth argument if available registers are not enough. At least this is how my compiler is doing it. I may have another look tomorrow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 24 23:07:29 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 24 May 2016 23:07:29 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.afada8bd217e7a455c4d5d9ac0e69d7d@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): Replying to [comment:5 osa1]: > {{{ > third arg: [ movl $7457,%edx] > fourth arg: [ movl $255,%vI_n4I8, movq 7(%rbx),%vI_n4Ia, > imulq %vI_s4pW,%vI_n4Ia, movl %vI_n4Ia,%eax, xorq %rdx,%rdx, > }}} > > These look correct to me. Since the code mostly uses virtual registers `%edx` > isn't overridden at this point. It is overriden: `%rdx` is `xor`ed before each `divq`. With -ddump-asm- liveness, we can see that `%edx` (`%r3`) born in the `movl` is overwritten. {{{ movl $7457,%edx # born: %r3 # w_dying: %r3 movl $255,%vI_n413 # born: %vI_n413 movq 7(%rbx),%vI_n415 # born: %vI_n415 # r_dying: %r1 imulq %vI_s3Mw,%vI_n415 movl %vI_n415,%eax # born: %r0 # r_dying: %vI_n415 xorq %rdx,%rdx # born: %r3 divq %vI_n413 # r_dying: %vI_n413 # w_dying: %r3 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 01:52:01 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 01:52:01 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.4099c185884e0b1d77b74f9f37bba976@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): I have made a first patch: https://phabricator.haskell.org/D2263 The result looks better (even if a little bit suboptimal): {{{#!nasm movq 8(%rbp),%rax xorl %ecx,%ecx xorl %edx,%edx movl $7457,%esi movl $255,%edi ; inlined code not using %esi/%rsi ; ... movq %rcx,%rdi ; suboptimal (could be xorq %rdi, %rdi) movq %rsi,%rcx ; suboptimal (could be movq %rsi, %rdx directly) movq %rbx,%rsi ; suboptimal (could be xorq %rsi, %rsi) movq %rcx,%rdx movq %rax,%rcx subq $8,%rsp xorl %eax,%eax call third_arg }}} The patch doesn't handle pushed args yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 01:54:56 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 01:54:56 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.6a872ed0ca0d1e63dbe93829cb018fef@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2263 Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * differential: => Phab:D2263 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 04:14:02 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 04:14:02 -0000 Subject: [GHC] #10512: Generic instances missing for Int32, Word64 etc. In-Reply-To: <051.eb2fd15ce978c34ac9303293c51292d1@haskell.org> References: <051.eb2fd15ce978c34ac9303293c51292d1@haskell.org> Message-ID: <066.a8cce8e5849df5e016dcddf6432889eb@haskell.org> #10512: Generic instances missing for Int32, Word64 etc. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: wontfix | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9526 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Seems to break example from [https://hackage.haskell.org/package/Chart-1.1/docs/Generics-Deriving- Lens.html Generics.Deriving.Lens] {{{ ghci> allOf tinplate (=="Hello") (1::Int,2::Double,(),"Hello",["Hello"]) :85:7: error: ? No instance for (GHC.Generics.Generic Char) arising from a use of ?tinplate? ? In the first argument of ?allOf?, namely ?tinplate? In the expression: allOf tinplate (== "Hello") (1 :: Int, 2 :: Double, (), "Hello", ["Hello"]) In an equation for ?it?: it = allOf tinplate (== "Hello") (1 :: Int, 2 :: Double, (), "Hello", ["Hello"]) }}} {{{ ghci> mapMOf_ tinplate putStrLn ("hello",[(2 :: Int, "world!")]) :86:9: error: ? No instance for (GHC.Generics.Generic Char) arising from a use of ?tinplate? ? In the first argument of ?mapMOf_?, namely ?tinplate? In the expression: mapMOf_ tinplate putStrLn ("hello", [(2 :: Int, "world!")]) In an equation for ?it?: it = mapMOf_ tinplate putStrLn ("hello", [(2 :: Int, "world!")]) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 04:15:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 04:15:46 -0000 Subject: [GHC] #9526: Add missing Generic instances in base In-Reply-To: <042.36fe33d326f024375b013e70748f1e6c@haskell.org> References: <042.36fe33d326f024375b013e70748f1e6c@haskell.org> Message-ID: <057.634584a731a3aed6d0f0a1a84d4b8b74@haskell.org> #9526: Add missing Generic instances in base -------------------------------------+------------------------------------- Reporter: nh2 | Owner: dreixel Type: feature request | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 7.8.3 Resolution: wontfix | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10512 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): See ticket:10512#comment:12. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 07:18:08 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 07:18:08 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.371315e7958b80765896be02661fb212@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2263 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): Hmm, I'd like to find a way to fix this without making codegen worse for every unsafe call. The problem appears to be that the code for the fourth argument uses `divq` which clobbers `%rdx`. I need to refresh my memory about how this is supposed to work... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 07:56:37 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 07:56:37 -0000 Subject: [GHC] #1965: Allow unconstrained existential contexts in newtypes In-Reply-To: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> References: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> Message-ID: <059.f739b3bd6e0cac29b9d1761fbc7f4809@haskell.org> #1965: Allow unconstrained existential contexts in newtypes -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | 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 dfeuer): I've started a [https://ghc.haskell.org/trac/ghc/wiki/NewtypeOptimizationForGADTS wiki page] to give examples of why we want this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 08:00:27 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 08:00:27 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.65b2c1a03c6bad49bf8c17e5133e5c09@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2263 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I added a comment to the Phab ticket. I think we should fix the code gen so that if a register is written at some point A and read at point B, it should be kept alive no matter what. It'd be great if we could write some unit tests about that, but that needs a lot of infrastructure work... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 08:44:17 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 08:44:17 -0000 Subject: [GHC] #1965: Allow unconstrained existential contexts in newtypes In-Reply-To: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> References: <044.685803b9d3f1e49e57aaed63227984b8@haskell.org> Message-ID: <059.1f287c70e3841e88ff6dde3b9768ccdf@haskell.org> #1965: Allow unconstrained existential contexts in newtypes -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | 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: | -------------------------------------+------------------------------------- Description changed by simonpj: @@ -9,0 +9,2 @@ + + The wiki page [wiki:NewtypeOptimizationForGADTS] summarises the proposal New description: Declarations like {{{ newtype Bar = forall a. Bar (Foo a) }}} ought to be allowed so long as no typeclass constraints are added. Right now, this requires data rather than newtype. The wiki page [wiki:NewtypeOptimizationForGADTS] summarises the proposal -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 09:13:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 09:13:46 -0000 Subject: [GHC] #12111: prof build flavour doesn't work In-Reply-To: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> References: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> Message-ID: <058.58e55e5f7b79ff6c5bf960dc6e3dcdb7@haskell.org> #12111: prof build flavour doesn't work -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: I can not reproduce this problem, starting from commit ac38c025b99868d348e3797e85a4af9c6d6377ac. Here is what I tried: {{{ * git clone --recursive * cp mk/build.mk.sample mk/build.mk * uncomment `BuildFlavour = prof` in mk/build.mk * ./boot && ./configure && make }}} Test that it works: {{{ $ ./inplace/bin/ghc-stage2 -fforce-recomp Test.hs +RTS -p $ ls ghc-stage2.prof ghc-stage2.prof }}} Some things to check: * do you have other settings in `mk/build.mk` that might interfer? * make sure there isn't a leftover `mk/are-validating.mk` file * run `make show VALUE=ghc_stage2_PROGRAM_WAY`. It should show `ghc_stage2_PROGRAM_WAY="p"`. * look at the build command that failed. It probably contains `-dynamic`. Figure out why. `-fprof-auto` gets added in `compiler/ghc.mk`. You shouldn't have to manually fiddle with `GhcStage2HcOpts`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 09:16:58 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 09:16:58 -0000 Subject: [GHC] #12115: CoreLint error in safe program Message-ID: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This correct program is failing with a CoreLint error: {{{ {-# LANGUAGE MagicHash, UnboxedTuples #-} module Main where import GHC.Prim import GHC.Types showAlt0 :: (# Void#, (# #) #) -> String showAlt0 (# _, (# #) #) = "()" main :: IO () main = return () }}} Error: {{{ *** Core Lint errors : in result of Desugar (after optimization) *** : warning: In the type ?(# Void#, (# #) #) -> String? Kind application error in type ?(# Void#, (# #) #)? Function kind = * -> * -> TYPE 'UnboxedTupleRep Arg kinds = [('VoidRep, RuntimeRep), ('UnboxedTupleRep, RuntimeRep), (Void#, TYPE 'VoidRep), ((# #), TYPE 'VoidRep)] core_err.hs:13:1: warning: [RHS of showAlt0 :: (# Void#, (# #) #) -> String] The type of this binder doesn't match the type of its RHS: showAlt0 Binder's type: (# Void#, (# #) #) -> String Rhs type: (# Void#, (# #) #) -> String }}} Tried with: GHC HEAD, 8.0.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 09:28:51 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 09:28:51 -0000 Subject: [GHC] #12111: prof build flavour doesn't work In-Reply-To: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> References: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> Message-ID: <058.d9d3472f5c51cce6a872bcf47c157177@haskell.org> #12111: prof build flavour doesn't work -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): This commit message is informative (ce1f1607ed7f8fedd2f63c8610cafefd59baaf32): {{{ Author: Simon Marlow Date: Sat Nov 7 09:39:05 2015 +0000 Make GHCi & TH work when the compiler is built with -prof Summary: Amazingly, there were zero changes to the byte code generator and very few changes to the interpreter - mainly because we've used good abstractions that hide the differences between profiling and non-profiling. So that bit was pleasantly straightforward, but there were a pile of other wibbles to get the whole test suite through. Note that a compiler built with -prof is now like one built with -dynamic, in that to use TH you have to build the code the same way. For dynamic, we automatically enable -dynamic-too when TH is required, but we don't have anything equivalent for profiling, so you have to explicitly use -prof when building code that uses TH with a profiled compiler. For this reason Cabal won't work with TH. We don't expect to ship a profiled compiler, so I think that's OK. Test Plan: validate with GhcProfiled=YES in validate.mk Reviewers: goldfire, bgamari, rwbarton, austin, hvr, erikd, ezyang Reviewed By: ezyang Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1407 GHC Trac Issues: #4837, #545 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 09:33:13 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 09:33:13 -0000 Subject: [GHC] #11081: Implement Introspective Template Haskell In-Reply-To: <047.67eb7661a40be634ed16872d272a44ca@haskell.org> References: <047.67eb7661a40be634ed16872d272a44ca@haskell.org> Message-ID: <062.d39a25e2e175cceeeebf93385176edf2@haskell.org> #11081: Implement Introspective Template Haskell -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: ? Component: Template Haskell | 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: | TemplateHaskell/Introspective | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:5 simonpj]: > I'm very unsure about the back-compat shim, but maybe it's possible. Yay for pattern synonyms. Could they also be used for other [https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0?action=diff&version=42 migrations]? In [https://hackage.haskell.org/package/template- haskell-2.11.0.0/docs/Language-Haskell-TH-Lib.html#v:instanceD Language.Haskell.TH.Lib] another function `instanceWithOverlapD` was added to prevent breakage: {{{#!hs instanceD :: CxtQ -> TypeQ -> [DecQ] -> DecQ instanceWithOverlapD :: Maybe Overlap -> CxtQ -> TypeQ -> [DecQ] -> DecQ }}} The same could have been done with `InstanceD` {{{#!hs -- OLD: -- | InstanceD Cxt Type [Dec] | InstanceWithOverlapD (Maybe Overlap) Cxt Type [Dec] }}} and like `ErrorCall` defining {{{#!hs pattern InstanceD :: Ctx -> Type -> [Dec] -> Dec pattern InstanceD ctx ty decs = InstanceWithOverlapD Nothing ctx ty decs }}} which suffers from the [ticket:8779#comment:12 same problem] as `ErrorCall`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 09:44:53 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 09:44:53 -0000 Subject: [GHC] #11993: RFC, allow local bindings in pattern synonyms In-Reply-To: <051.8c746ee9d0f7bcf6a2764a5c20344e08@haskell.org> References: <051.8c746ee9d0f7bcf6a2764a5c20344e08@haskell.org> Message-ID: <066.5ef4feae434d347212ea80099e8735f7@haskell.org> #11993: RFC, allow local bindings in pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): It becomes a lot more worthwhile when you have local data ''and'' pattern synonym declarations because they interplay, I'll get back to this -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 10:31:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 10:31:30 -0000 Subject: [GHC] #12116: No easy way to add cost-centre to top-levels Message-ID: <043.6b04c4666f71935c9beabebf233c1a73@haskell.org> #12116: No easy way to add cost-centre to top-levels -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- As far as I can see from the user manual (I also tried placing some `SCC`s), there's no way to easily add cost-centres to top-level definitions. We can do things like: {{{ f x y z = ... => f = {-# SCC f #-} \x y z -> ... }}} but it becomes too much work once we have "equations" style definitions like {{{ head [] = {-# SCC head #-} Nothing head (x : _) = {-# SCC head #-} Just x }}} Also, `where` clauses work differently after the transformations. Example: {{{ f x y z = ... where => f = {-# SCC f #-} \x y z -> ... where }}} So it gets annoying real quick. It'd be really great if we could just add `{-# SCC ... #-}` just like `{-# INLINE ... #-}` pragmas. Any ideas/opinions? Looking at the code, it seems like `-fprof-auto` and similar flags are adding ticks to `FunBind.fun_tick`. We could do the same with this new `SCC` pragma. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 11:51:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 11:51:00 -0000 Subject: [GHC] #12103: Typed Template Haskell missing utilities provided by untyped variant In-Reply-To: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> References: <046.b18752b937f18b0d4fa594e84b29566e@haskell.org> Message-ID: <061.512b8126c73ec8c325ad9a74ed579d01@haskell.org> #12103: Typed Template Haskell missing utilities provided by untyped variant -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I, personally, favor the "push to use quotes" idea. There are fewer names to remember that way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 12:49:19 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 12:49:19 -0000 Subject: [GHC] #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option Message-ID: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option -----------------------------------------+--------------------------------- Reporter: wapxmas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: -threaded, freeze | Operating System: Windows Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -----------------------------------------+--------------------------------- I attached program to reproduce bug. While running you need type "abc" then "1": 1. if build with "ghc -threaded concbug.hs" - code after "threadDelay_ t" on 29 is never run. 2. if build as "ghc concbug.hs" - program work as expected -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 12:49:41 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 12:49:41 -0000 Subject: [GHC] #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option In-Reply-To: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> References: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> Message-ID: <061.f5bc41bcbce8a145773199b9b98ccbf2@haskell.org> #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option ---------------------------------+----------------------------------------- Reporter: wapxmas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: -threaded, freeze 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 wapxmas): * Attachment "concbug.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 12:51:38 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 12:51:38 -0000 Subject: [GHC] #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option In-Reply-To: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> References: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> Message-ID: <061.3d2efef9d179f9de8605fd14377d6d1d@haskell.org> #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option ---------------------------------+----------------------------------------- Reporter: wapxmas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: -threaded, freeze 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 wapxmas): If uncomment line 33 in "concbug.hs" and comment line 34 then with or without -threaded option promram works as expected without hangs and freezes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 13:19:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 13:19:49 -0000 Subject: [GHC] #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option In-Reply-To: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> References: <046.9477657f657f52380cdee1dfc3be4e48@haskell.org> Message-ID: <061.3fad461e54b41ebfbab89902d25f34de@haskell.org> #12117: Thread by forkIO freezes (while read :: Int if error appears) when compiled with -threaded option -------------------------------------+------------------------------------- Reporter: wapxmas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.3 Resolution: | Keywords: -threaded, | freeze 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 thomie): * cc: Phyx-, simonmar (added) * component: Compiler => Runtime System Comment: Sees like a Windows-only problem. Reproducible with GHC HEAD (9c3e55bd029447d9c2cac1c9ca1607a8a803cd79). > if build as "ghc concbug.hs" - program work as expected I'm not sure. For me, on Windows, it doesn't print the "seconds is up! BING!" line, until I enter some non-number string. It also never prints "Prelude.read: no parse", as it does on Linux. But the program doesn't freeze, as it does with `-threaded`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 13:25:06 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 13:25:06 -0000 Subject: [GHC] #12114: Make injectivity check less conservative (was: GHC rejects injective type family) In-Reply-To: <050.2ff02132b5faa0737de73fd83ef430b0@haskell.org> References: <050.2ff02132b5faa0737de73fd83ef430b0@haskell.org> Message-ID: <065.6c7b7864ea67710e2d63e912a4741d4f@haskell.org> #12114: Make injectivity check less conservative -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * type: bug => feature request Comment: I agree completely with your analysis. The problem here is that for GHC to perform this analysis, it would have to characterize the set of possible outputs from a function. While this may be possible, this pushes us into a much more involved injectivity check than we currently have. I am thus relabeling this ticket as a feature request. However, without a suggested algorithm, it's hard to know how to make progress here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 13:41:57 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 13:41:57 -0000 Subject: [GHC] #11468: testsuite should ignore config files In-Reply-To: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> References: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> Message-ID: <064.7905aad01a2097457564006ee27885dc@haskell.org> #11468: testsuite should ignore config files -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2265 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * owner: => thomie * keywords: newcomer => * differential: => Phab:D2265 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 13:50:45 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 13:50:45 -0000 Subject: [GHC] #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files Message-ID: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This change was made without explanation in commit 429f0099ab9adfadc779ca76f3aae1c9c160fb8c: {{{ Author: Esa Ilari Vuokko Date: Sun Aug 13 12:46:49 2006 +0000 Fix driver not to normalise output when using platform specific output files }}} I don't understand why that change was made. It makes `T11223_link_order_a_b_2_fail` and `T11223_simple_duplicate_lib` fail on Windows, when running with `BINDIST=YES` (or, after accepting the `BINDIST=YES` output, when running with `BINDIST=NO`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 14:20:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 14:20:30 -0000 Subject: [GHC] #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files In-Reply-To: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> References: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> Message-ID: <060.e5dd401ae415dd769963fb9f4a377b50@haskell.org> #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 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): Phab:D2267 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * differential: => Phab:D2267 * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 15:10:33 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 15:10:33 -0000 Subject: [GHC] #12088: Promote data family instance constructors In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.ab6a40719dedf4fde988d4b71480abd1@haskell.org> #12088: Promote data family instance constructors -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11348 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => TypeInType Comment: Looks reasonable to me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 15:25:46 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 15:25:46 -0000 Subject: [GHC] #11995: Can't infer type In-Reply-To: <051.ecd85ed869df953db3456994d5047fa3@haskell.org> References: <051.ecd85ed869df953db3456994d5047fa3@haskell.org> Message-ID: <066.8c463e5b4bcd31fcceba0630999ca3c0@haskell.org> #11995: Can't infer type -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | 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 goldfire): This is correct behavior. Though I failed to find a mention of the fact in either the user manual or in the Haskell 2010 report, a function can use polymorphic recursion only when given a type signature. The [https://en.wikipedia.org/wiki/Polymorphic_recursion Wikipedia page] on polymorphic recursion may be helpful. When you stub out the `xs` with an underscore, GHC considers the type signature to be incomplete and it does type inference -- not type checking -- on the function. Your function is polymorphically recursive, and so this fails. Still remaining to do: * improve the error message to mutter about polymorphic recursion (not sure if this is at all possible) * find and/or create documentation to this effect. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 15:40:01 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 15:40:01 -0000 Subject: [GHC] #12111: prof build flavour doesn't work In-Reply-To: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> References: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> Message-ID: <058.c0ca3cd0f77cf09256c9d603a4b74258@haskell.org> #12111: prof build flavour doesn't work -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: infoneeded => closed * resolution: => invalid Comment: OK; here what I think is happening: I can't pass `-fprof-auto` anything like that to `GhcStage2Opts` because I think it's also used when compiling some files that are supposed to be compiled in normal mode (as opposed to profiling mode). I'm still not sure if there's a way to do what I want, but at least profiling build works and I can add cost centers manually. Closing this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 15:41:24 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 15:41:24 -0000 Subject: [GHC] #7190: GHC's -fprof-auto does not work with LINE pragmas In-Reply-To: <049.b7337da5880f7d950e41894a88c70fc8@haskell.org> References: <049.b7337da5880f7d950e41894a88c70fc8@haskell.org> Message-ID: <064.b30b6ca365ce5cecb93fe44ce240d98d@haskell.org> #7190: GHC's -fprof-auto does not work with LINE pragmas -------------------------------------+------------------------------------- Reporter: timthelion | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.4.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 going over cost-center-related tickets -- does anyone know how do I test and close this? As far as I can see `.prof.sample` files are not good enough for testing purposes. For example, I created a `.prof.sample` for testing this, but if I remove a random line in that file the test is still accepted. What am I doing wrong? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 16:00:23 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 16:00:23 -0000 Subject: [GHC] #12111: prof build flavour doesn't work In-Reply-To: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> References: <043.a2ee22af65ac6cbf3ff355f26f1427f7@haskell.org> Message-ID: <058.ccadd608b37ff97142ac38c45cc3fe19@haskell.org> #12111: prof build flavour doesn't work -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 8.0.1 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Actually, you do need to fiddle with `-fprof-auto` a little. See this comment in `compiler/ghc.mk`: {{{ # If we're profiling GHC then we want SCCs. However, adding -auto-all # everywhere tends to give a hard-to-read profile, and adds lots of # overhead. A better approach is to proceed top-down; identify the # parts of the compiler of interest, and then add further cost centres # as necessary. Turn on -fprof-auto for individual modules like this: # compiler/main/DriverPipeline_HC_OPTS += -fprof-auto compiler/main/GhcMake_HC_OPTS += -fprof-auto compiler/main/GHC_HC_OPTS += -fprof-auto # or alternatively add {-# OPTIONS_GHC -fprof-auto #-} to the top of # modules you're interested in. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 16:05:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 16:05:30 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.c2aa7358d9b4bcf237a9c95763ea5dcf@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I wanted a break from dissertation-writing so I took a look. The problem is surely in the byte-code generator, which is opaque to me. The nub of the problem seems to be here: {{{#!hs -- introduce a let binding for a ticked case expression. This rule -- *should* only fire when the expression was not already let-bound -- (the code gen for let bindings should take care of that). Todo: we -- call exprFreeVars on a deAnnotated expression, this may not be the -- best way to calculate the free vars but it seemed like the least -- intrusive thing to do schemeE d s p exp@(AnnTick (Breakpoint _id _fvs) _rhs) = if isUnliftedType ty then do ... else do id <- newId ty ... where exp' = deAnnotate' exp ty = exprType exp' }}} The problem is that `ty :: TYPE rep` for a skolem `rep`. So we've created an abomination: a runtime variable (the `id`) whose type is representation polymorphic. Indeed, even the `isUnliftedType` query is bogus, because there is no way to know whether or not `ty` is unlifted at this point. How we've gotten here or what this code is doing, I don't know. But this is definitely the source of the problem! I'm afraid I won't have a chance to dig deeper here, but hopefully these bread crumbs can be picked up by the next traveler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 17:21:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 17:21:30 -0000 Subject: [GHC] #11468: testsuite should ignore config files In-Reply-To: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> References: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> Message-ID: <064.e435d5955c45ae79b61e0eb041a4ff40@haskell.org> #11468: testsuite should ignore config files -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2265 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"bdc555885b8898684549eca70053c9ce0ec7fa39/ghc" bdc55588/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bdc555885b8898684549eca70053c9ce0ec7fa39" Testsuite: introduce TEST_HC_OPTS_INTERACTIVE (#11468) Refactoring only. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 17:52:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 17:52:40 -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.2efcd392220d98d56ec2b0fdeaaedd1b@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: seraphime Type: task | Status: new Priority: normal | Milestone: 8.2.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): Wiki Page: | -------------------------------------+------------------------------------- Changes (by seraphime): * owner: => seraphime -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 18:23:40 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 18:23:40 -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.2d4c9392b228164426c5ea91d9f95de1@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: seraphime Type: task | Status: new Priority: normal | Milestone: 8.2.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Thanks for taking on this task, seraphime! Figuring out the GHC versions when instances were introduced can be pretty tiring sometimes (since it involves a lot of `git` archeology). I recommend looking at the source of `base-orphans`, since it categorizes all of the new instances added to GHC (dating back to GHC 7.0) by the `#if MIN_VERSION_base(x,y,z)` blocks they fall under. For example, here are all of the new instances introduced in `base-4.4` (GHC 7.2): https://github.com/haskell-compat/base- orphans/blob/cd918aef4915c5cc4051bb74a689d14ed1d2e233/src/Data/Orphans.hs#L86-L118 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:27:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:27:35 -0000 Subject: [GHC] #9399: CPP does not process test case enum01.hs correctly In-Reply-To: <042.8bd2b8ed84f95b67c9cae49884c4f662@haskell.org> References: <042.8bd2b8ed84f95b67c9cae49884c4f662@haskell.org> Message-ID: <057.0ea1179611e7d6b8edf52f763549006f@haskell.org> #9399: CPP does not process test case enum01.hs correctly -------------------------------------+------------------------------------- Reporter: jrp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.11 Resolution: | Keywords: cpp Operating System: Windows | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: enum01.hs Blocked By: | Blocking: Related Tickets: #365 | Differential Rev(s): Phab:D957 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"f07bf19ec49d25395dd47923ba5e6b525ce7e68f/ghc" f07bf19e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f07bf19ec49d25395dd47923ba5e6b525ce7e68f" Testsuite: fix enum01/02/03 on Windows (#9399) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:27:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:27:35 -0000 Subject: [GHC] #5522: mc03 -O -fliberate-case -fspec-constr runs out of memory In-Reply-To: <044.70b406220a8f6320743e1c51e2eba565@haskell.org> References: <044.70b406220a8f6320743e1c51e2eba565@haskell.org> Message-ID: <059.d28e156eb8c394a2a5bd83882b2675fa@haskell.org> #5522: mc03 -O -fliberate-case -fspec-constr runs out of memory -------------------------------------+------------------------------------- Reporter: btutt | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 7.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: mc03 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"5020bc8fd2a99a557f45ea5abf8240ac995cc03d/ghc" 5020bc8/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5020bc8fd2a99a557f45ea5abf8240ac995cc03d" Testsuite: add a test for #5522 (-fliberate-case -fspec-constr) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:27:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:27:35 -0000 Subject: [GHC] #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files In-Reply-To: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> References: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> Message-ID: <060.20a3cf1c07760361d561ddb200b7531c@haskell.org> #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 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): Phab:D2267 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"6a5bce14ffb8b10def150b185fc95d7b2ebab263/ghc" 6a5bce14/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6a5bce14ffb8b10def150b185fc95d7b2ebab263" Testsuite: also normalise platform-dependent .stdout/stderr This effectively reverses commit 429f0099ab9adfadc779ca76f3aae1c9c160fb8c (2006). I don't see why platform-dependent .stdout/stderr files should //not// get normalised. It fixes T11223_link_order_a_b_2_fail on Windows, by normalising `ghc-stage2.exe` to `ghc` when comparing stderr with .stderr-mingw32. Reviewed by: Phyx Differential Revision: https://phabricator.haskell.org/D2267 GHC Trac Issues: #12118 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:30:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:30:48 -0000 Subject: [GHC] #5522: mc03 -O -fliberate-case -fspec-constr runs out of memory In-Reply-To: <044.70b406220a8f6320743e1c51e2eba565@haskell.org> References: <044.70b406220a8f6320743e1c51e2eba565@haskell.org> Message-ID: <059.9ae4079b44a85eb4a913f74899bb8f5d@haskell.org> #5522: mc03 -O -fliberate-case -fspec-constr runs out of memory -------------------------------------+------------------------------------- Reporter: btutt | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: Component: Test Suite | Version: 7.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | deSugar/should_run/mc03, | deSugar/should_run/T5522 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: mc03 => deSugar/should_run/mc03, deSugar/should_run/T5522 * status: new => closed * resolution: => fixed Comment: I added the original report (`mc03 -O -fliberate-case -fspec-constr`) as test, with a memory limit of 1 gigabyte. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:31:25 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:31:25 -0000 Subject: [GHC] #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files In-Reply-To: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> References: <045.c01df6ed03b6b610e1e1edc82dace2e3@haskell.org> Message-ID: <060.12662360c3e7359ecc0a0b8f6e11151c@haskell.org> #12118: Testsuite driver does not normalise platform-dependent .stdout/stderr files -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 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): Phab:D2267 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:52:27 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:52:27 -0000 Subject: [GHC] #11581: TypeError requires UndecidableInstances unnecessarily In-Reply-To: <047.4c36e92acb669f967ff5258393f77106@haskell.org> References: <047.4c36e92acb669f967ff5258393f77106@haskell.org> Message-ID: <062.27d5f4519661117c16e45dbf2e419683@haskell.org> #11581: TypeError requires UndecidableInstances unnecessarily -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: indexed- valid program | types/should_compile/T11581 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 Wed May 25 19:54:13 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:54:13 -0000 Subject: [GHC] #12119: Can't create injective type family equation with TypeError as the RHS Message-ID: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> #12119: Can't create injective type family equation with TypeError as the RHS -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple CustomTypeErrors, TypeFamilies, | Injective | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- For the longest time, I've wanted to make a type family like this injective: {{{#!hs type family Foo (a :: *) :: * where Foo Bar = Int Foo Baz = Char }}} But the problem is that `Foo` is defined on //all// types of kind `*`, so the above definition is inherently non-injective. With the introduction of `TypeError`s, however, I thought I could rule out all other cases: {{{#!hs import GHC.TypeLits type family Foo (a :: *) = (r :: *) | r -> a where Foo Bar = Int Foo Baz = Char Foo _ = TypeError ('Text "boom") }}} But this doesn't work, sadly: {{{ Injective.hs:18:3: error: ? Type family equations violate injectivity annotation: Foo Bar = Int -- Defined at Injective.hs:18:3 Foo _ = (TypeError ...) -- Defined at Injective.hs:20:3 ? In the equations for closed type family ?Foo? In the type family declaration for ?Foo? Injective.hs:20:3: error: ? Type family equation violates injectivity annotation. Type variable ?_? cannot be inferred from the right-hand side. In the type family equation: Foo _ = (TypeError ...) -- Defined at Injective.hs:20:3 ? In the equations for closed type family ?Foo? In the type family declaration for ?Foo? Injective.hs:20:3: error: ? Type family equation violates injectivity annotation. RHS of injective type family equation cannot be a type family: Foo _ = (TypeError ...) -- Defined at Injective.hs:20:3 ? In the equations for closed type family ?Foo? In the type family declaration for ?Foo? }}} From GHC's perspective, `TypeError` is just another type family, so it thinks it violates injectivity. But should this be the case? After all, having the RHS of a type family equation being `TypeError` is, in my perspective, tantamount to making that type family undefined for those inputs. It seems like if we successfully conclude that `Foo a ~ Foo b` (and GHC hasn't blown up yet due to type erroring), we should be able to conclude that `a ~ b`. Could this be accomplished by simply adding a special case for `TypeError` in the injectivity checker? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 19:57:00 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 19:57:00 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on GHC.Generic's `Rep` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.03355dbcd71be1511ec270310c46ec85@haskell.org> #12057: TypeFamilyDependencies on GHC.Generic's `Rep` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective Operating System: 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): `Rep` definitely isn't injective. Counterexample: `Rep (Proxy Int)` = `Rep (Proxy Char)`, but `Int` is not `Char`. `Not` can certainly be made injective though, and this would be simple to do and useful. Would you care to make a patch for it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 20:03:27 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:03:27 -0000 Subject: [GHC] #12016: Allow wildcards in type synonyms and data declarations In-Reply-To: <051.25982c21d04ab8006e28de59d7da7e1e@haskell.org> References: <051.25982c21d04ab8006e28de59d7da7e1e@haskell.org> Message-ID: <066.4126346e195ab984283fbe96ce4a5c28@haskell.org> #12016: Allow wildcards in type synonyms and data declarations -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: lowest | Milestone: Component: Compiler | Version: (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 20:05:05 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:05:05 -0000 Subject: [GHC] #11350: Allow visible type application in patterns In-Reply-To: <051.b16517d65bfaaca2db1f23781a666611@haskell.org> References: <051.b16517d65bfaaca2db1f23781a666611@haskell.org> Message-ID: <066.2a12193a838631ebc1b698781a1de23e@haskell.org> #11350: Allow visible type application in patterns -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | TypeApplications PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 20:06:26 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:06:26 -0000 Subject: [GHC] #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) In-Reply-To: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> References: <051.f5a3bb82cbacb1093f08604448c52c48@haskell.org> Message-ID: <066.6620f63ae5796c70ea780b4687490215@haskell.org> #12048: Allow CustomTypeErrors in type synonyms (+ evaluate nested type family?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: diatchki Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 20:07:54 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:07:54 -0000 Subject: [GHC] #8914: Remove unnecessary constraints from MonadComprehensions and ParallelListComp In-Reply-To: <051.acde5e53d639cac227862a3e93262533@haskell.org> References: <051.acde5e53d639cac227862a3e93262533@haskell.org> Message-ID: <066.1c758470cb16e2990e6e8d83d2be6560@haskell.org> #8914: Remove unnecessary constraints from MonadComprehensions and ParallelListComp -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 10976 | 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 Wed May 25 20:08:12 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:08:12 -0000 Subject: [GHC] #10976: Applicative Comprehensions In-Reply-To: <046.b8fb42a1a67c05a5fd3b2ee681f1abcf@haskell.org> References: <046.b8fb42a1a67c05a5fd3b2ee681f1abcf@haskell.org> Message-ID: <061.a1dd5d499b06c70f0c3269f437a4afeb@haskell.org> #10976: Applicative Comprehensions -------------------------------------+------------------------------------- Reporter: davidar | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 8914 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 Wed May 25 20:09:11 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:09:11 -0000 Subject: [GHC] #11325: Type of hole does not get refined after pattern matching on [GADT] constructors In-Reply-To: <051.8ec42c0e7d97d5831a3b9d77051c9cfe@haskell.org> References: <051.8ec42c0e7d97d5831a3b9d77051c9cfe@haskell.org> Message-ID: <066.e4e4e15e07f7a24af884a19d86bab226@haskell.org> #11325: Type of hole does not get refined after pattern matching on [GADT] constructors -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Resolution: | Keywords: GADTs Operating System: Linux | Architecture: x86 Type of failure: Incorrect | Test Case: warning at compile-time | 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 Wed May 25 20:18:14 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:18:14 -0000 Subject: [GHC] #9399: CPP does not process test case enum01.hs correctly In-Reply-To: <042.8bd2b8ed84f95b67c9cae49884c4f662@haskell.org> References: <042.8bd2b8ed84f95b67c9cae49884c4f662@haskell.org> Message-ID: <057.4c61c50b24db13b3870a12c417b198af@haskell.org> #9399: CPP does not process test case enum01.hs correctly -------------------------------------+------------------------------------- Reporter: jrp | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 7.11 Resolution: fixed | Keywords: cpp Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: GHC rejects | Test Case: valid program | libraries/base/tests/enum01 Blocked By: | Blocking: Related Tickets: #365 | Differential Rev(s): Phab:D957 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * testcase: enum01.hs => libraries/base/tests/enum01 * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 20:23:08 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:23:08 -0000 Subject: [GHC] #8751: Show parenthesised output of expressions in ghci In-Reply-To: <051.64a3a6e4a9644c56cf4e2e987a774ebd@haskell.org> References: <051.64a3a6e4a9644c56cf4e2e987a774ebd@haskell.org> Message-ID: <066.3d2942a28a6d25aa4ce674d802a61eda@haskell.org> #8751: Show parenthesised output of expressions in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Iceland_jack, this patch looks wonderful! Do you mind submitting it as a Diff via Phabricator? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 20:54:30 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 20:54:30 -0000 Subject: [GHC] #12119: Can't create injective type family equation with TypeError as the RHS In-Reply-To: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> References: <050.21d4af732cea81fafcb58c894bb8137c@haskell.org> Message-ID: <065.0ae601190436089b2a2f1d9537fd7343@haskell.org> #12119: Can't create injective type family equation with TypeError as the RHS -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | CustomTypeErrors, TypeFamilies, | Injective Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That looks plausible to me. What is the consequences of declaring `Foo` to be injective? Answer, only that if we have {{{ [W] g1 : Foo t1 ~ Foo t2 }}} where `[W]` means "wanted", a constraint we are trying to solve, then we try to prove {{{ [W] g2: t1 ~ t2 }}} Assuming we succeed, binding `g2 = `, then we can prove the first constraint by binding `g1 = Foo g2`. If `F` is not injective, this proof strategy is no unsound; but it may be incomplete. Perhaps there are un-equal types `t1` and `t2` for which `Foo t1 ~ Foo t2`. In your example, it's true that `Foo Int ~ TypeError "boom" ~ Foo Bool`. So indeed there may be a solution to the constraint `Foo t1 ~ Foo t2` that does not require `t1 ~ t2`. But if the proof goes via `TypeError`, as here, perhaps that particular sort of incompleteness doesn't matter. So it sounds plausible. I don't really know how to formalise it though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 21:11:11 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 21:11:11 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?q?=3E_Num_Dollars=E2=80=9D?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.ed9a72d34370c93016bd2649faec2877@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 7.10.3 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 RyanGlScott): * component: Compiler => Documentation Comment: That section isn't saying that `newtype Dollars = Dollars Int deriving Num` literally derives an instance of the form `instance Num Int => Num Dollars`, but rather it generates an `instance Num Dollars` by starting with `Num Int` as the context, then simplifying as much as possible. In that example, since a `Num Int` instance exists, we can discharge that constraint and be left with `()`, giving us the `instance Num Dollars` that you actually get when you compile with `-ddump-deriv`. I agree that the wording in that section is a bit vague (it uses the phrase "Notationally" without going into much detail about what it really entails) and could stand to be clarified. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 21:13:24 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 21:13:24 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` (was: TypeFamilyDependencies on GHC.Generic's `Rep`) In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.0aa498f0e31333c9a9376ba38efc0f80@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: TypeFamilies, Injective => TypeFamilies, Injective, newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 21:15:21 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 21:15:21 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.91da967dd6166f5a2c86fb16b85d07c8@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:3 RyanGlScott]: > `Rep` definitely isn't injective. Counterexample: `Rep (Proxy Int)` = `Rep (Proxy Char)`, but `Int` is not `Char`. Interesting, thank you. Would this be covered by the weaker [https://ghc.haskell.org/trac/ghc/ticket/6018#comment:48 ?head?-injectivity]? Is there any benefit from adding this distinguishing information/kind information to the metadata (since `Proxy` is polykinded)? I am perversely working backwards from the perspective of injectivity but there may be a use for `TypeRep`s in the `Rep`. > `Not` can certainly be made injective though, and this would be simple to do and useful. Would you care to make a patch for it? Sure, it can be kept open for more injective type families in base. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 22:04:17 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 22:04:17 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.3cd8535bdde539a5c91df878d93d2489@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * owner: => Iceland_jack -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 22:06:35 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 22:06:35 -0000 Subject: [GHC] #8751: Show parenthesised output of expressions in ghci In-Reply-To: <051.64a3a6e4a9644c56cf4e2e987a774ebd@haskell.org> References: <051.64a3a6e4a9644c56cf4e2e987a774ebd@haskell.org> Message-ID: <066.d991e44baf70f4fbae9cbbfc99312390@haskell.org> #8751: Show parenthesised output of expressions in ghci -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:10 RyanGlScott]: > Iceland_jack, this patch looks wonderful! Do you mind submitting it as a Diff via Phabricator? I revisited it and some GHC internals had changed, I'll finish #12057 and #12045 and then get right on it :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 22:06:48 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 22:06:48 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.2132250f43f43aea72c085fa1c3bb8a8@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:5 Iceland_jack]: > Interesting, thank you. Would this be covered by the weaker [https://ghc.haskell.org/trac/ghc/ticket/6018#comment:48 ?head?-injectivity]? In principle, it should be. Ever since we added [https://ghc.haskell.org/trac/ghc/ticket/10030 packageName] to the generics metadata, every `Rep` instance should be uniquely identified by the package, module, and datatype name of the underlying datatype, so I think `Rep`s are unique modulo type variables. I say "in principle" because although most `Generic` instances (and hence `Rep` instances) are derived, a devilish programmer //could// handwrite a `Rep` instance that violates injectivity. However, it's strongly discouraged to do such a thing (for instance, you can't handwrite `Generic` instances in `Safe` code), so I don't know if that would even be an issue in practice. > Is there any benefit from adding this distinguishing information/kind information to the metadata (since `Proxy` is polykinded)? > > I am perversely working backwards from the perspective of injectivity but there may be a use for `TypeRep`s in the `Rep`. Well, I've never found myself wanting to put `TypeRep` in `Rep` precisely because `Typeable`'s a whole 'nother can of worms, and it does feel perverse to jam more stuff into an already cluttered `Rep`. Furthermore, I don't think this would solve the problem of making it injective, since `TypeRep` values represent monomorphic types. > Sure, it can be kept open for more injective type families in base. Out of curiosity, are there any other type families in `base` besides `Not` that can be injective? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 22:35:49 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 22:35:49 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?q?=3E_Num_Dollars=E2=80=9D?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.0504337bfb508c01ecceb9cdec9e9eeb@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 7.10.3 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 agree that the wording in that section is a bit vague (it uses the phrase "Notationally" without going into much detail about what it really entails) and could stand to be clarified. Agreed. Patch welcome! Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed May 25 22:43:22 2016 From: ghc-devs at haskell.org (GHC) Date: Wed, 25 May 2016 22:43:22 -0000 Subject: [GHC] #12088: Promote data family instance constructors In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.401f92e74a143ab5e5d672ffb4f5e67a@haskell.org> #12088: Promote data family instance constructors -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11348 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): And me. Maybe someone can offer a patch? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 00:35:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 00:35:25 -0000 Subject: [GHC] #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon In-Reply-To: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> References: <048.a4a2a5816a0aa4dfbaf2640f489bd6c3@haskell.org> Message-ID: <063.361d1bb5eaf23978c0fb79507745206e@haskell.org> #12083: ghc-8.0.1-rc4: tyConRoles sees a TcTyCon -------------------------------------+------------------------------------- Reporter: _deepfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1-rc4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Yes. Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Urgh. I know what is going on here. The problem is that `Constrd` is bogus because its right-hand side is constrained and we haven't enabled the right extensions. The validity check fails. Regardless, GHC tries to continue to check the remaining declarations. To do this, GHC replaces `Constrd` with a stubbed-out `TyCon`, as explained in this note: {{{ {- Note [Recover from validity error] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We recover from a validity error in a type or class, which allows us to report multiple validity errors. In the failure case we return a TyCon of the right kind, but with no interesting behaviour (makeTyConAbstract). Why? Suppose we have type T a = Fun where Fun is a type family of arity 1. The RHS is invalid, but we want to go on checking validity of subsequent type declarations. So we replace T with an abstract TyCon which will do no harm. See indexed-types/should_fail/BadSock and Trac #10896 Painfully, though, we *don't* want to do this for classes. Consider tcfail041: class (?x::Int) => C a where ... instance C Int The class is invalid because of the superclass constraint. But we still want it to look like a /class/, else the instance bleats that the instance is mal-formed because it hasn't got a class in the head. -} }}} Because of the changes caused by `TypeInType`, the solver now can run while checking type declarations, and the solver ends up seeing the stubbed-out `TyCon`, causing the panic. What should be done about this? Here are some ideas: 1. Some up with a way to deal with the problem described in the Note without fully stubbing out the `TyCon`. For example, the bogus `T` in the note could be transmuted to a `type family T a` with no instances. 2. If there is a validity error in one mutually-recursive group, don't proceed to the next group. This will reduce the number of errors reported in one go. 3. Enlarge the stubbed-out `TyCon`s to be able to make it through the solver without panicking. This shouldn't be too hard, but it seems like the wrong direction of travel. In any case, I'm not assigning the ticket to myself, because I make no guarantees about my ability to finish this work. I just saw that `TcTyCon` (which is the current form of a stubbed-out `TyCon`) was causing trouble so I thought I'd take a look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 01:58:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 01:58:19 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.b712bec864ef9c77e93f2f4fa9e61e30@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D2268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * differential: => D2268 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 01:58:31 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 01:58:31 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.a24fd9c3fefff4626bdb04d398d839ba@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): 2268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * differential: D2268 => 2268 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 01:59:26 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 01:59:26 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.4f5b1881b5ba1a4078592c761196df22@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2268 Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * differential: 2268 => Phab:D2268 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 02:05:25 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 02:05:25 -0000 Subject: [GHC] #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` In-Reply-To: <051.38c482983531342047bddb8add84ef15@haskell.org> References: <051.38c482983531342047bddb8add84ef15@haskell.org> Message-ID: <066.563d42eedee1afb639359df5974dcced@haskell.org> #12057: TypeFamilyDependencies on Data.Type.Bool's `Not` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Iceland_jack Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | Injective, newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2268 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:7 RyanGlScott]: > I say "in principle" because although most `Generic` instances (and hence `Rep` instances) are derived, a devilish programmer //could// handwrite a `Rep` instance that violates injectivity. That could be checked if GHC ends up adding support for head-injectivity, there may be use cases for an injective `Rep`. > Out of curiosity, are there any other type families in `base` besides `Not` that can be injective? I can sift through `base` and see if there are others, posting them here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 09:08:42 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 09:08:42 -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.93fa2881001a76f6013daf244c29e38a@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: seraphime Type: task | Status: new Priority: normal | Milestone: 8.2.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by seraphime): I have already written a script that seeks out the first commit in the git history where the instance appears, compares its timestamp to stamps which correspond to version bumps ( I found those by reading the commit history ). Comparison in the script is done on a single file, so files containing the same instance declaration will not disturb each other. However, I couldn't find any indications about the release dates of versions before 2.01. Should the annotation specify something like "<= 2.01" or there is some way to find out their respective release dates ? For instances I cannot check in the link you gave, can I trust the logs ? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 09:52:01 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 09:52:01 -0000 Subject: [GHC] #12120: GHC accepts invalid Haskell: `class Eq (a Int) => C a where` Message-ID: <045.6de5d9d63fecead5f74ef4c28335b676@haskell.org> #12120: GHC accepts invalid Haskell: `class Eq (a Int) => C a where` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Keywords: report-impact | Operating System: Unknown/Multiple Architecture: | Type of failure: Documentation Unknown/Multiple | bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- From the Haskell 2010 report [https://www.haskell.org/onlinereport/haskell2010/haskellch4.html chapter 4], * Class and instance declarations: {{{ | class [scontext =>] ... | instance [scontext =>] ... }}} * Normal type signatures: {{{ vars :: [context =>] ... }}} Notice the difference between `scontext` (//with// `s`) and `context` (without `s`). {{{ scontext ? simpleclass | ( simpleclass1 , ? , simpleclassn ) (n ? 0) simpleclass ? qtycls tyvar }}} {{{ context ? class | ( class1 , ? , classn ) (n ? 0) class ? qtycls tyvar | qtycls ( tyvar atype1 ? atypen ) (n ? 1) }}} GHC seems to ignore this difference, and happily accepts `class Eq (a Int) => C a where`. Hugs (Version: September 2006) reports for that same example: {{{ Illegal Haskell 98 class constraint in class declaration *** Constraint : Eq (a Int) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 09:56:42 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 09:56:42 -0000 Subject: [GHC] #12120: GHC accepts invalid Haskell: `class Eq (a Int) => C a where` In-Reply-To: <045.6de5d9d63fecead5f74ef4c28335b676@haskell.org> References: <045.6de5d9d63fecead5f74ef4c28335b676@haskell.org> Message-ID: <060.7386e8f8c7dc627e7d6b105a86f7bfd0@haskell.org> #12120: GHC accepts invalid Haskell: `class Eq (a Int) => C a where` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: report-impact Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): I didn't see this mentioned in https://downloads.haskell.org/~ghc/master /users-guide/bugs.html. It probably should be, so that the Haskell 2020 commitee sees it, and perhaps lifts this restriction on class and instance declarations. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 10:03:06 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 10:03:06 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.638f2286586655742b51d0de25373856@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2263 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I was doing some reading on Cmm and found something that may be relevant in [this wiki page](https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/CmmType): > Global Registers in Cmm currently have a problem with inlining: because neither compiler/cmm/PprC.hs nor the NCG are able to keep Global Registers from clashing with C argument passing registers, Cmm expressions that contain Global Registers cannot be inlined into an argument position of a foreign call. For more thorough notes on inlining, see the comments in compiler/cmm/CmmOpt.hs. The page is a bit out of date but this part sounded like the problem we're having here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 10:07:19 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 10:07:19 -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.b6a006f101153f3b0ec7aca2feb7b0c7@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: seraphime Type: task | Status: new Priority: normal | Milestone: 8.2.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): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Wow, that script sounds very useful! Replying to [comment:6 seraphime]: > However, I couldn't find any indications about the release dates of versions before 2.01. Should the annotation specify something like "<= 2.01" or there is some way to find out their respective release dates ? I'm not sure, but to be perfectly honest, I don't think anyone actually uses `base <= 2.01`, so I'd be OK with simply not giving `@since` annotations to things that are that old. > For instances I cannot check in the link you gave, can I trust the logs ? The `base-orphans` link is merely a suggestion. If your script works well for you, by all means feel free to use that exclusively. But if you do need another cross-reference, `base-orphans` is regularly tested against multiple GHC versions, so it should be pretty accurate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 10:26:49 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 10:26:49 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.e05e0a2559ee1d4b7e314f319d0339dc@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2263 Wiki Page: | -------------------------------------+------------------------------------- Comment (by osa1): I still don't know how the register allocator works, but I realized something interesting. `CmmCall` has a field `cml_args_regs :: [GlobalReg]` for the arguments that are passed to the function, but `CmmUnsafeForeignCall` doesn't have anything like that. Shouldn't it have the same thing to be used in register allocation? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 11:04:33 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 11:04:33 -0000 Subject: [GHC] #12121: FlexibleContexts is under specified Message-ID: <045.d85403886ed965b098b403fa737d3a40@haskell.org> #12121: FlexibleContexts is under specified -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Documentation Unknown/Multiple | bug Test Case: | Blocked By: Blocking: | Related Tickets: #12010 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I've been reading the documentation on `FlexibleContexts`. It's pretty confusing. === Structure The documentation is scattered around 3 different sections: * 9.8.1.2. The superclasses of a class declaration (this is where the [http://downloads.haskell.org/~ghc/8.0.1/docs/html/users_guide/glasgow_exts.html #ghc-flag--XFlexibleContexts link] from the flag reference takes you). * 9.8.3.3. Relaxed rules for instance contexts * 9.15.2. The context of a type signature Maybe it's ok to separate it like this, but it took me a while to figure out that there //are// actually three different sections. A simple solution would be to mention that there are 3 different sections, in each section (it already does so in the last section). === Specification > The -XFlexibleContexts flag lifts the Haskell 98 restriction that the type-class constraints in a type signature must have the form `(class type-variable)` or `(class (type-variable type1 type2 ... typen))`. That's all fine and well, but hardly teaches me anything. I would like to know which type-class constraints //are// allowed with `FlexibleContexts`. Or in other words: what is a definition of a "type- class constraint" with `FlexibleContexts`? This is the old grammar: {{{ context ? class | ( class1 , ? , classn ) (n ? 0) class ? qtycls tyvar | qtycls ( tyvar atype1 ? atypen ) (n ? 1) }}} What is the new one? === Examples * These are the example mentioned in the section on the context of a class declaration (9.8.1.2): {{{ class Functor (m k) => FiniteMap m k where class (Monad m, Monad (t m)) => Transform t m where lift :: m a -> (t m) a }}} Problem is, they neither require `FlexibleContexts`, nor do they compile with `FlexibleContexts`! Those examples require `MultiParamTypeClasses`. `MultiParamTypeClasses` doesn't enable `FlexibleContexts` automatically. * The section on instance contexts doesn't have any examples. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 11:24:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 11:24:29 -0000 Subject: [GHC] #12121: FlexibleContexts is under specified In-Reply-To: <045.d85403886ed965b098b403fa737d3a40@haskell.org> References: <045.d85403886ed965b098b403fa737d3a40@haskell.org> Message-ID: <060.608b66f04a82b5cc50d0ee034317b6b0@haskell.org> #12121: FlexibleContexts is under specified -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: #12020 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: #12010 => #12020 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 11:54:41 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 11:54:41 -0000 Subject: [GHC] #12121: FlexibleContexts is under specified In-Reply-To: <045.d85403886ed965b098b403fa737d3a40@haskell.org> References: <045.d85403886ed965b098b403fa737d3a40@haskell.org> Message-ID: <060.7bd1150db57b3bb7fcd7fdcf3c9a7e27@haskell.org> #12121: FlexibleContexts is under specified -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: #12020 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That's bad. Would you be willing to fix it if I tell you the specification? > I would like to know which type-class constraints are allowed with FlexibleContexts. Or in other words: what is a definition of a "type-class constraint" with FlexibleContexts? With `FlexibleContexts` you can put anything `Constraint`-kinded in the context. Except * For class decls, no implicit parameters * For instance decls, no implicit parameters, and must be smaller than the head unless `UndecidableInstances`. For contexts in type signatures Haskell 98 allowed `Functor (m k)`, or even `Functor (m [k])`; anything headed by a tyvar, as in the syntax for `context` above. But the Haskell 98 report is more restrictive for class decls; they are supposed to be `cls tyvar`. Alas, GHC does not do this; it treats them the same as type signatures. Henc, yes, {{{ class Functor (m k) => FiniteMap m k where }}} does not require `FlexibleContexts`. (It does compile with `FlexibleContexts` though, doesn't it?) I don't know whether it is worth tightening this up. Does that help? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 12:30:34 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 12:30:34 -0000 Subject: [GHC] #12120: GHC accepts invalid Haskell: `class Eq (a Int) => C a where` In-Reply-To: <045.6de5d9d63fecead5f74ef4c28335b676@haskell.org> References: <045.6de5d9d63fecead5f74ef4c28335b676@haskell.org> Message-ID: <060.68f2f5bbf7bbfa08524e83e32709228c@haskell.org> #12120: GHC accepts invalid Haskell: `class Eq (a Int) => C a where` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: report-impact 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): Yes, as mentioned in #12121, I think this is a bug in GHC. Fixing it will probably mean that some working programs break, which will make people upset. Maybe we should just document it as a bug that we don't propose to fix? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 13:22:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 13:22:05 -0000 Subject: [GHC] #12121: FlexibleContexts is under specified In-Reply-To: <045.d85403886ed965b098b403fa737d3a40@haskell.org> References: <045.d85403886ed965b098b403fa737d3a40@haskell.org> Message-ID: <060.c9a99530c926cad1e5e230813f265306@haskell.org> #12121: FlexibleContexts is under specified -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: #12020 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * owner: => thomie -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 13:23:35 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 13:23:35 -0000 Subject: [GHC] #12121: FlexibleContexts is under specified In-Reply-To: <045.d85403886ed965b098b403fa737d3a40@haskell.org> References: <045.d85403886ed965b098b403fa737d3a40@haskell.org> Message-ID: <060.67de8e6aa46182a2b4de76dda248f617@haskell.org> #12121: FlexibleContexts is under specified -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: #12120 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * related: #12020 => #12120 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 13:58:29 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 13:58:29 -0000 Subject: [GHC] #12122: User's guide (master): all links to libraries are broken Message-ID: <045.fbe31db504a07fe77cb07ff2ed5ecbcb@haskell.org> #12122: User's guide (master): all links to libraries are broken -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Documentation Unknown/Multiple | bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Example. The page http://downloads.haskell.org/~ghc/master/users- guide/glasgow_exts.html#generic-programming has a broken link to GHC.Generics: http://downloads.haskell.org/~ghc/master/libraries/base-4.9.0.0/GHC- Generics.html. It should instead link to http://downloads.haskell.org/~ghc/master/libraries/html/base/GHC- Generics.html It seems all such links to libraries are broken. The content is also over a month old (20160411). Preferably, a resource called `master` would be automatically updated every day. If that's not possible, maybe it should just be removed, and people can compile their own version. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 15:25:20 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 15:25:20 -0000 Subject: [GHC] #12105: merge MatchFixity and HsMatchContext In-Reply-To: <044.0d136ec1e3b0b0304a6895a0a48280ac@haskell.org> References: <044.0d136ec1e3b0b0304a6895a0a48280ac@haskell.org> Message-ID: <059.d77df4a91963cbaf52f184cc76534554@haskell.org> #12105: merge MatchFixity and HsMatchContext -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2271 Wiki Page: | -------------------------------------+------------------------------------- Changes (by alanz): * differential: => Phab:D2271 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:24:50 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:24:50 -0000 Subject: [GHC] #8308: Resurrect ticky code for counting constructor arity In-Reply-To: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> References: <048.881ed81a50f663ce5516d17888eb822c@haskell.org> Message-ID: <063.c85eaaa40ef369f39549f9865d73fee6@haskell.org> #8308: Resurrect ticky code for counting constructor arity ------------------------------+---------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: 8.2.1 Component: Profiling | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Windows | Architecture: Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D931 Wiki Page: | ------------------------------+---------------------------------------- Comment (by mlen): @Phyx-: nope, sorry. I don't have any windows experience. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:25:10 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:25:10 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.fb2766fefbf82624043eebdd69e75b5b@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"0f1e315b9274725c4a2c975f4d06a5c956cf5385/ghc" 0f1e315/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0f1e315b9274725c4a2c975f4d06a5c956cf5385" Fix bytecode gen to deal with rep-polymorphism When faced runtime-rep-polymorphic code from a pattern-synonym matcher, the bytecode generator was treating the result as lifted, which it isn't. The fix is just to treat those rep-polymorphic continuations like unlifted types, and add a dummy arg. Trac #12007 is a case in point. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:25:10 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:25:10 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.87850fe3cba345ed9efe3f1760728a53@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"e9e61f18a548b70693f4ccd245bc56335c94b498/ghc" e9e61f18/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e9e61f18a548b70693f4ccd245bc56335c94b498" Reduce special-casing for nullary unboxed tuple When we built the kind of a nullary unboxed tuple, we said, in TysWiredIn.mk_tuple: res_rep | arity == 0 = voidRepDataConTy -- See Note [Nullary unboxed tuple] in Type | otherwise = unboxedTupleRepDataConTy But this is bogus. The Note deals with what the 'unarise' transformation does, and up to that point it's simpler and more uniform to treat nullary unboxed tuples the same as all the others. Nicer now. And it fixes the Lint error in Trac #12115 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:29:02 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:29:02 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.c4f1a626ed6994647e5b53e9feacd400@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => codegen/should_compile/T12115 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:30:05 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:30:05 -0000 Subject: [GHC] #12007: Panic when loading file with nested pattern synonyms into ghci In-Reply-To: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> References: <050.6ea75b00ffb245107acfb719a89b7ff6@haskell.org> Message-ID: <065.f85e3395ac8add5ff18f06fb6e8c3f43@haskell.org> #12007: Panic when loading file with nested pattern synonyms into ghci -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/scripts/T12007 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => ghci/scripts/T12007 Comment: Maybe merge to 8.0 branch in due course -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:30:26 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:30:26 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.20b8d008a8b73612701d7c160d159afc@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => merge Comment: Maybe merge to 8.0 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 16:34:52 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 16:34:52 -0000 Subject: [GHC] #11792: Optimised unsafe FFI call can get wrong argument In-Reply-To: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> References: <045.c2134c5a0111e06b4c39b9b8cba0b1db@haskell.org> Message-ID: <060.73c3b687efe76e8a38913c36261fe930@haskell.org> #11792: Optimised unsafe FFI call can get wrong argument -------------------------------------+------------------------------------- Reporter: Szunti | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2263 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonmar): This is unrelated to global registers, in fact. There is a related issue with global registers which is described here: https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/cmm/CmmNode.hs;e9e61f18a548b70693f4ccd245bc56335c94b498$205-218 But the issue here is different: see my comment on the diff. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu May 26 23:17:26 2016 From: ghc-devs at haskell.org (GHC) Date: Thu, 26 May 2016 23:17:26 -0000 Subject: [GHC] #12088: Promote data family instance constructors In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.ae9879617d9657e61c8dfb879e0733ab@haskell.org> #12088: Promote data family instance constructors -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11348 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alexvieth): > Maybe someone can offer a patch? [https://phabricator.haskell.org/D2272 Here's my attempt.] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 00:10:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 00:10:00 -0000 Subject: [GHC] #12088: Promote data family instance constructors In-Reply-To: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> References: <048.155fdb7e7ce6e09c92258c376a6950ab@haskell.org> Message-ID: <063.88057deffb2faf73faaaf933d2895e48@haskell.org> #12088: Promote data family instance constructors -------------------------------------+------------------------------------- Reporter: alexvieth | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11348 | Differential Rev(s): Phab:D2272 Wiki Page: | -------------------------------------+------------------------------------- Changes (by goldfire): * differential: => Phab:D2272 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 00:59:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 00:59:58 -0000 Subject: [GHC] #12123: GHC crashes when calling typeRep on a promoted tuple Message-ID: <050.7224be05b7e58580597e49fc3f0142fe@haskell.org> #12123: GHC crashes when calling typeRep on a promoted tuple -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code (asking for the typeRep of a promoted tuple) causes GHC to crash. {{{ import Data.Typeable import Data.Proxy x = typeRep (Proxy::Proxy '(Int,Int)) }}} The error message is: {{{ [1 of 1] Compiling Main ( ../Bug.hs, interpreted ) GHC error in desugarer lookup in Main: Can't find interface-file declaration for variable $tc'(,) Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160518 for x86_64-unknown-linux): initDs IOEnv failure }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 02:11:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 02:11:26 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.04ef46aa1c0bcf7087200a1f3756128a@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dalaing): It's not clear to me if this change is wanted or not. I was mostly after this to clean up how #10961 deals with messages and also to help break a circular dependency. Beyond that I was only looking for a behaviour preserving split out of `PprFlags` - even containing things not strictly related to pretty printing - in order to place an upper bound on what information can be reached while pretty printing. The idea was that a) it'll make people stop and think about other ways of accessing non-printing information while pretty printing, so hopefully things won't get any worse and b) we can open tickets to try to clean up the code that accesses the platform constants or general flags from the pretty printer, so that things get better over time. If folks think that's a lateral move / change for the sake of change / a step back, I'm happy to work on something else instead :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 07:13:46 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 07:13:46 -0000 Subject: [GHC] #12124: Ambiguous type variable: it's a red herring! Message-ID: <045.3fef5c2d647c702c366f69de60e48a08@haskell.org> #12124: Ambiguous type variable: it's a red herring! -------------------------------------+------------------------------------- Reporter: drb226 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ module Ret where data Whoops = Whoops Int Int foo :: Maybe Int foo = return (case Whoops 1 2 of Whoops a -> a _ -> 0) }}} Note that there is a pattern match error in the case statement, which the compiler correctly reports. However, it first reports the following red herring: {{{ ret.hs:6:7: error: ? Ambiguous type variable ?m0? arising from a use of ?return? prevents the constraint ?(Monad m0)? from being solved. Probable fix: use a type annotation to specify what ?m0? should be. These potential instances exist: instance Monad IO -- Defined in ?GHC.Base? instance Monad Maybe -- Defined in ?GHC.Base? instance Monad ((->) r) -- Defined in ?GHC.Base? ...plus two others (use -fprint-potential-instances to see them all) ? In the expression: return (case Whoops 1 2 of { Whoops a -> a _ -> 0 }) In an equation for ?foo?: foo = return (case Whoops 1 2 of { Whoops a -> a _ -> 0 }) }}} One would think that the context `foo :: Maybe Int` is sufficient for the compiler to realize that `return (blah)` implies that m0 = Maybe, regardless of the errors involved in the expression `(blah)`. ghc 7.10.3 does not report this red herring. One can get a similar red- herring type error in ghc 7.10.3 by replacing `return (...)` with `return $ ...` in the example above. The red herring also does *not* appear, in ghc 7.10.3 or in ghc 8.0.1, if you name the broken case expression with a let binding. {{{ module Ret where data Whoops = Whoops Int Int foo :: Maybe Int foo = return boo where boo = case Whoops 1 2 of Whoops a -> a _ -> 0 }}} There seems to be something fishy going on here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 08:22:52 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 08:22:52 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.f15488d96abdfbae8b6ada04d9a2e4f2@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: 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: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by magesh.b): Does this fix the representation for lifted tuple as well? I'm getting following error when tried to typeOf with lifted tuple {{{ Prelude> :set -XDataKinds Prelude> import Data.Typeable as T Prelude T> import Data.Proxy as P Prelude T P> typeOf (Proxy :: Proxy '(1,2)) GHC error in desugarer lookup in Ghci1: Can't find interface-file declaration for variable $tc'(,) Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): initDs IOEnv failure Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 08:30:49 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 08:30:49 -0000 Subject: [GHC] #12125: Field accessors unnecessarily kept alive Message-ID: <043.0981b0708581432c190c561d66c8ba25@haskell.org> #12125: Field accessors unnecessarily kept alive -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): Phab:D2270 | Wiki Page: -------------------------------------+------------------------------------- Suppose you have a record with some non-exported field accessors, like so: {{{#!haskell module Lib (Rec) where data Rec = Rec { f1 :: Int , f2 :: Int , f3 :: Int , f4 :: Int , f5 :: Int } }}} Code for fields `f1`, `f2` ... are redundantly generated, optimized etc. and they made it to the object file, causing wasted compile times and bloated object files. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 10:24:13 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 10:24:13 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.4b9a3084c6dabfafa17146401588a258@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: RyanGlScott Type: feature request | Status: closed Priority: low | Milestone: 8.2.1 Component: Core Libraries | Version: 7.10.1 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | generics/T10604/T10604_* Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2168 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * testcase: => generics/T10604/T10604_* * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 10:53:47 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 10:53:47 -0000 Subject: [GHC] #12122: User's guide (master): all links to libraries are broken In-Reply-To: <045.fbe31db504a07fe77cb07ff2ed5ecbcb@haskell.org> References: <045.fbe31db504a07fe77cb07ff2ed5ecbcb@haskell.org> Message-ID: <060.2972c5b066905e1db68940082fda2033@haskell.org> #12122: User's guide (master): all links to libraries are broken -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed it seems like the cron job I set up to update this content never quite worked right. This is hopefully now fixed. I'm still working on fixing the library URLs in a non-hacky way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 11:36:32 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 11:36:32 -0000 Subject: [GHC] #11640: Panic because of "updateRole" In-Reply-To: <051.a2aa2f07407d8fdc661bf953d330894a@haskell.org> References: <051.a2aa2f07407d8fdc661bf953d330894a@haskell.org> Message-ID: <066.c7f3fa80bb8af8276d7d6c2418732f77@haskell.org> #11640: Panic because of "updateRole" -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | polykinds/T11640 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => polykinds/T11640 * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 11:49:14 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 11:49:14 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.adcf94030c7433bcdcd139a7cf208ef5@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): This patch is causing the following panic in `tcrun051` (on Linux): {{{ [1 of 1] Compiling Main ( tcrun051.hs, tcrun051.o ) 7907 ghc: panic! (the 'impossible' happened) 7908 (GHC version 8.1.20160527 for x86_64-unknown-linux): 7909 unboxed tuple PrimRep 7910 7911 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug 7912 7913 7914 *** unexpected failure for tcrun051(normal) 7915 }}} tcrun051.hs: {{{#!hs {-# LANGUAGE UnboxedTuples #-} module Main where -- Tests unboxed tuple slow calls {-# NOINLINE g #-} g :: Int -> (# Int, Int #) -> Int -> (# Int, (# Int #) #) -> (# #) -> Int g a (# b, c #) d (# e, (# f #) #) (# #) = a + b + c + d + e + f {-# NOINLINE h #-} h :: (Int -> (# Int, Int #) -> Int -> (# Int, (# Int #) #) -> (# #) -> Int) -> (Int, Int) h g = (g5, g5') where -- Apply all the arguments at once g5' = g 1 (# 2, 3 #) 4 (# 5, (# 6 #) #) (# #) -- Try to force argument-at-a-time application as a stress-test g1 = g 1 g2 = g1 `seq` g1 (# 2, 3 #) g3 = g2 `seq` g2 4 g4 = g3 `seq` g3 (# 5, (# 6 #) #) g5 = g4 `seq` g4 (# #) main = print $ h g }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 12:16:09 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 12:16:09 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.171aeb40b2a4ffc79f59ea08087994e2@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Yes thanks. I found that last night. (I didn't do 'slow' validate before pushing.) I have a fix; will push shortly. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 12:26:47 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 12:26:47 -0000 Subject: [GHC] #10143: Separate PprFlags (used by Outputable) from DynFlags In-Reply-To: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> References: <045.0c964cf0fdf539316860c6c8c56c5f9e@haskell.org> Message-ID: <060.554c75618e34390292b859a41c126eea@haskell.org> #10143: Separate PprFlags (used by Outputable) from DynFlags -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10961 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I think your goal is this (taken from the top of the ticket). > At the moment, SDoc computations have full access to the entirety of DynFlags, despite only a minusculely small amount of the data structure being relevant to them. This proposal is to split out a PprFlags structure which will be contained in a DynFlags, and contain dynamic flags JUST for pretty-printing. Is that your goal? If so,seems a good goal. But that seems to contradict your comment:11, where you say > If PprFlags is to be strictly about rendering, then SDocContext either needs to continue to have DynFlags in it, or needs to carry around the PlatformConstants, the general flags, and a **whole heap of other stuff from DynFlags**. My confusion is about whether it's true that `SDoc` computations need only a "miniscule" bit of `DynFlags`. If true, then this project seems worthwhile. If false, not so worthwhile. I think the reason no one is being clear about whether this change is wanted or not is that there is confusion about what "this change" actually is. Could you, for example, list exactly the things you propose to put in `PprFlags`? And what functions/data types change their signatures? Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 13:35:12 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 13:35:12 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.f616b1c9d0476456ea2ddf5bdf3ee1ff@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"b43a7936ebf77bce744d50a131d686c83f63e60b/ghc" b43a793/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b43a7936ebf77bce744d50a131d686c83f63e60b" More fixes for unboxed tuples This is a continuation of commit e9e61f18a548b70693f4ccd245bc56335c94b498 Date: Thu May 26 15:24:53 2016 +0100 Reduce special-casing for nullary unboxed tuple which related to Trac #12115. But typecheck/should_run/tcrun051 revealed that my patch was incomplete. This fixes it, by removing another special case in Type.repType. I had also missed a case in UnariseStg.unariseIdBinder. I took the opportunity to add explanatory notes Note [Unarisation] Note [Unarisation and nullary tuples] in UnariseStg }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 13:35:49 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 13:35:49 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.869aecfa1d79b67f7b00ec52aa331490@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Fixed now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 13:53:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 13:53:26 -0000 Subject: [GHC] #11415: pandoc-types fails to build on 4 GB machine In-Reply-To: <049.3f4a5adbe3ed958aec19c26d7f43bc21@haskell.org> References: <049.3f4a5adbe3ed958aec19c26d7f43bc21@haskell.org> Message-ID: <064.3e1de47c842bae8793ce37209025250c@haskell.org> #11415: pandoc-types fails to build on 4 GB machine -------------------------------------+------------------------------------- Reporter: pavolzetor | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Generics Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: In https://github.com/bos/aeson/pull/335#issue-127344930, RyanGlScott mentions: > To test out the improvments, I did a very fast-and-loose profiling of the time and memory it takes to compile `pandoc-types` (a package known to be affected badly by the aeson-0.10 compilation regressions). > The total wall time went from 10 minutes to under a minute, and it went from using 3 GB of RAM (and thrashing my laptop mercilessly) to about 500 MB of RAM. pavolzetor: make sure you upgrade to the latest version of `aeson` to get those improvements. The //real// problem with Generics compile-time performance it still tracked in #5642. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:06:45 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:06:45 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.02649d785ecf4795e7992262ca1d3a70@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * resolution: fixed => Comment: Fails in HEAD too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:08:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:08:58 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.274ca5bb1fc29159f63c15a0125acfa3@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:09:37 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:09:37 -0000 Subject: [GHC] #11736: Allow unsaturated uses of unlifted types in Core In-Reply-To: <046.58eb4ccf2c61eb23569b6021fe490e4a@haskell.org> References: <046.58eb4ccf2c61eb23569b6021fe490e4a@haskell.org> Message-ID: <061.3fa3b3055387a7b97a2f055a281d4942@haskell.org> #11736: Allow unsaturated uses of unlifted types in Core -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Typeable 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): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:09:48 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:09:48 -0000 Subject: [GHC] #11714: Kind of (->) type constructor is overly constrained In-Reply-To: <046.1c872034bd46f91c4f4aa91d607a8219@haskell.org> References: <046.1c872034bd46f91c4f4aa91d607a8219@haskell.org> Message-ID: <061.8a71e5d3394d7587298793df459301bf@haskell.org> #11714: Kind of (->) type constructor is overly constrained -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:10:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:10:00 -0000 Subject: [GHC] #11722: No TypeRep for unboxed tuples In-Reply-To: <047.62aa410ace38ef8cf0e4ab854da20597@haskell.org> References: <047.62aa410ace38ef8cf0e4ab854da20597@haskell.org> Message-ID: <062.c2fc886ab9ac0c390cab8ebccc96f620@haskell.org> #11722: No TypeRep for unboxed tuples -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:10:16 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:10:16 -0000 Subject: [GHC] #11715: Constraint vs * In-Reply-To: <046.907e6fb89981c8664a4e7309489f51fd@haskell.org> References: <046.907e6fb89981c8664a4e7309489f51fd@haskell.org> Message-ID: <061.8b1f8448bd5357d82dcd5a6e6d2a2256@haskell.org> #11715: Constraint vs * -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1-rc1 checker) | Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:11:25 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:11:25 -0000 Subject: [GHC] #12123: GHC crashes when calling typeRep on a promoted tuple In-Reply-To: <050.7224be05b7e58580597e49fc3f0142fe@haskell.org> References: <050.7224be05b7e58580597e49fc3f0142fe@haskell.org> Message-ID: <065.14e017273b6b23440e16e4d88966a0c3@haskell.org> #12123: GHC crashes when calling typeRep on a promoted tuple -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 14:12:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 14:12:26 -0000 Subject: [GHC] #12082: Typeable on RealWorld fails In-Reply-To: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> References: <046.e4ee4338a41502e1434038b393cfe130@haskell.org> Message-ID: <061.fac1120a03f86da8bc27bf41bca8749d@haskell.org> #12082: Typeable on RealWorld fails -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2240, Wiki Page: | Phab:D2239 -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 15:01:04 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 15:01:04 -0000 Subject: [GHC] #12125: Field accessors unnecessarily kept alive In-Reply-To: <043.0981b0708581432c190c561d66c8ba25@haskell.org> References: <043.0981b0708581432c190c561d66c8ba25@haskell.org> Message-ID: <058.6c9e8ec899f4cd008b619179f70224ea@haskell.org> #12125: Field accessors unnecessarily kept alive -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2270 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 15:15:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 15:15:00 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?q?=3E_Num_Dollars=E2=80=9D?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.afbfd17f642bf4946f793303d89ea13d@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 7.10.3 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:D2273 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2273 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 15:52:08 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 15:52:08 -0000 Subject: [GHC] #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults In-Reply-To: <044.e54e5ecad8d095611a80bfdfe4263626@haskell.org> References: <044.e54e5ecad8d095611a80bfdfe4263626@haskell.org> Message-ID: <059.34da9b300fbcc617a163436889ebd540@haskell.org> #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults ------------------------------------+-------------------------------------- Reporter: awson | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler (LLVM) | Version: 7.9 Resolution: worksforme | 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: | ------------------------------------+-------------------------------------- Comment (by GordonBGood): Replying to awson: and thomie: I don't think this should have been closed: Using GCH 64-bit 8.0.1 and the same binutils as always as version 2.5.1 (which is the one that comes with GHC both 7.10.3 and the new one) and LLVM 3.7, I still get segment faults for the compiled executable on Windows 7 64-bit. I think that just because the simple little test program runs doesn't mean the problem isn't still there, as Fanael: showed that the problem occurs when a page barrier is crossed; The compilation for GHC has changed significantly and it may well be that a little insignificant program no longer crosses a page barrier. My much larger application perhaps does and triggers the same problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 15:57:16 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 15:57:16 -0000 Subject: [GHC] #8971: Native Code Generator for 7.8 is not as optimized as 7.6.3... In-Reply-To: <050.c7fda5d49ea9b3871e29284bd1fa2f5f@haskell.org> References: <050.c7fda5d49ea9b3871e29284bd1fa2f5f@haskell.org> Message-ID: <065.1383ed47413c907bfce2980bc3624abe@haskell.org> #8971: Native Code Generator for 7.8 is not as optimized as 7.6.3... -------------------------------------+------------------------------------- Reporter: GordonBGood | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (NCG) | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by GordonBGood): This bug has not been assigned to GHC Milestone 8.2 so I don't suppose any action will be taken on it. I just checked with GHC 8.0.1 and the problem is still there, with the NCG produced code for these type of tight loops running about four times slower with x86 code than for x64 code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 15:59:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 15:59:00 -0000 Subject: [GHC] #8971: Native Code Generator for 7.8 is not as optimized as 7.6.3... In-Reply-To: <050.c7fda5d49ea9b3871e29284bd1fa2f5f@haskell.org> References: <050.c7fda5d49ea9b3871e29284bd1fa2f5f@haskell.org> Message-ID: <065.e75b237067fd7ed79809ab28b47591f9@haskell.org> #8971: Native Code Generator for 7.8 is not as optimized as 7.6.3... -------------------------------------+------------------------------------- Reporter: GordonBGood | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (NCG) | Version: 7.8.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by GordonBGood): Fortunately for x86 code we can use the LLVM back end, even though LLVM still doesn't work reliably for 64 bit code on Windows. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 16:56:02 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 16:56:02 -0000 Subject: [GHC] #10852: ghc 7.8.4 on arm - panic: Simplifier ticks exhausted In-Reply-To: <051.6de3bb6380bb073196bb38e7623ede92@haskell.org> References: <051.6de3bb6380bb073196bb38e7623ede92@haskell.org> Message-ID: <066.4246f6cc14720bbce39b8cba741721c8@haskell.org> #10852: ghc 7.8.4 on arm - panic: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: andrewufrank | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5642, #9675 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high Comment: I made two changes to my test setup, to compile `InstanceSerialize.hs`: * use `cereal` commit [https://github.com/GaloisInc/cereal/commit/7092614cdea80ab08c225c7a5c74f7ae1608e0bb 7092614cdea80ab08c225c7a5c74f7ae1608e0bb] instead of cereal-0.4.1 This includes a [https://github.com/GaloisInc/cereal/pull/54 pull request] that @thoughpolice made recently, to split up the `GSerialize` class in two. (same trick as ticket:9630#comment:23). I'd hoped this would reduce memory consumption and compile time. * use ghc-8.0.1 instead of ghc-7.10.3. Result: {{{ Simplifier ticks exhausted When trying UnfoldingDone unGet }}} `-fsimpl-tick-factor=400` made it go through (and `300` did not), but it still uses 2GB RAM and takes 4-5 minutes to complete. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 16:59:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 16:59:42 -0000 Subject: [GHC] #12100: GHC 8.0.1 build segmentation fault in haddock In-Reply-To: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> References: <047.3b49389b21e0a29c007c4ece13b83eaf@haskell.org> Message-ID: <062.4349ff02f989b737f187332aee5fd1c0@haskell.org> #12100: GHC 8.0.1 build segmentation fault in haddock -------------------------------------+------------------------------------- Reporter: ilovezfs | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: #11744, #11951 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * milestone: => 8.0.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 17:16:42 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 17:16:42 -0000 Subject: [GHC] #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" In-Reply-To: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> References: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> Message-ID: <061.77b28e0a668a07ca8cf261cf74f11676@haskell.org> #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeFamilies, | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high * os: MacOS X => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple @@ -11,0 +11,2 @@ + + module T12104 where New description: If I create a type family ? open or closed ? with a case that evaluates to a `TypeError`, and define a top-level binding with this type, loading the file with `-fdefer-type-errors` enabled (or via `:load!`/`:reload!`) panics GHC with "opt_univ fell into a hole". (And if I used `:load!` or `:reload!`, `-fdefer-type-errors` doesn't get unset.) A minimal example: {{{#!hs {-# LANGUAGE TypeFamilies, DataKinds, UndecidableInstances #-} module T12104 where import GHC.TypeLits type family F a where F a = TypeError (Text "error") err :: F () err = () }}} results in the panic {{{ ?.hs:9:7: warning: [-Wdeferred-type-errors] ? error ? In the expression: () In an equation for ?err?: err = () ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-apple-darwin): opt_univ fell into a hole {a4Va} }}} Adding more cases to the type family, or making it open, still cause the crash. This holds whether the error case is a final catch-all case, or something more like {{{#!hs type family F a where F () = TypeError (Text "error") F a = () }}} Just using a type synonym for `F` doesn't cause a panic, however, and nor does giving `err` the type `TypeError (Text "error")` directly. -- Comment: Confirmed with HEAD (8.1.20160520). Also reproducible by running just {{{ ghc -fdefer-type-errors type-families-TypeError-defer-type-errors- opt_univ-bug.hs }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 17:32:29 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 17:32:29 -0000 Subject: [GHC] #11094: Cost-center heap profiler should be able to emit samples to eventlog In-Reply-To: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> References: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> Message-ID: <061.0b86a57dbf2ad2b83185923c4368ad27@haskell.org> #11094: Cost-center heap profiler should be able to emit samples to eventlog -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1722 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * differential: => Phab:D1722 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 17:33:12 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 17:33:12 -0000 Subject: [GHC] #11094: Cost-center heap profiler should be able to emit samples to eventlog In-Reply-To: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> References: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> Message-ID: <061.421c6108db35a68e39f652db518dfe6c@haskell.org> #11094: Cost-center heap profiler should be able to emit samples to eventlog -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1722 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Profiling -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 17:33:33 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 17:33:33 -0000 Subject: [GHC] #9051: Report heap profile data in eventlog In-Reply-To: <045.3c63a8138228d719761c7f929bb060c2@haskell.org> References: <045.3c63a8138228d719761c7f929bb060c2@haskell.org> Message-ID: <060.5c7ee077ea5c547f94e856a30c6bbf39@haskell.org> #9051: Report heap profile data in eventlog -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Profiling | Version: 7.9 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11094 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #11094 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 17:35:47 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 17:35:47 -0000 Subject: [GHC] #3021: A way to programmatically insert marks into heap profiling output In-Reply-To: <043.8f6f7af4d3cf139bc012e761a76247cb@haskell.org> References: <043.8f6f7af4d3cf139bc012e761a76247cb@haskell.org> Message-ID: <058.eeb9f702f32eadd96c597d284aacce8c@haskell.org> #3021: A way to programmatically insert marks into heap profiling output -------------------------------------+------------------------------------- Reporter: SamB | Owner: Type: feature request | Status: new Priority: normal | Milestone: ? Component: Profiling | Version: 6.10.1 Resolution: | Keywords: profiling Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11094 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: bgamari (added) * related: => #11094 Comment: > in the long run profiling data should also go to the eventlog bgamari is working on that in #11094. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 17:43:54 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 17:43:54 -0000 Subject: [GHC] #12122: User's guide (master): all links to libraries are broken In-Reply-To: <045.fbe31db504a07fe77cb07ff2ed5ecbcb@haskell.org> References: <045.fbe31db504a07fe77cb07ff2ed5ecbcb@haskell.org> Message-ID: <060.d3758077244ece28a158ee1b32387d40@haskell.org> #12122: User's guide (master): all links to libraries are broken -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by thomie): Replying to [comment:1 bgamari]: > Indeed it seems like the cron job I set up to update this content never quite worked right. This is hopefully now fixed. > Thanks! > I'm still working on fixing the library URLs in a non-hacky way. Putting the docs in the directories where the URLs point to might be easier than changing the URLs themselves. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 18:10:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 18:10:00 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?q?=3E_Num_Dollars=E2=80=9D?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.1b2b795202933dd1b448c4f47fbfac93@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: patch Priority: normal | Milestone: Component: Documentation | Version: 7.10.3 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:D2273 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Ryan Scott ): In [changeset:"d0dd572b707631a104e060711faf9bd169bdc968/ghc" d0dd572b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d0dd572b707631a104e060711faf9bd169bdc968" Clarify users' guide section on GeneralizedNewtypeDeriving Summary: It seemed to imply that GHC was generating infelicitous code when it actually wasn't. Fixes #12047. Reviewers: hvr, bgamari, austin Reviewed By: austin Subscribers: thomie, Iceland_jack Differential Revision: https://phabricator.haskell.org/D2273 GHC Trac Issues: #12047 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 18:10:39 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 18:10:39 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2312047=3A_Users_Guide=3A_Generalized?= =?utf-8?q?NewtypeDeriving_derives_=E2=80=9Cinstance_Num_Int_=3D?= =?utf-8?q?=3E_Num_Dollars=E2=80=9D?= In-Reply-To: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> References: <051.cf1f9ecab3a9860fedb7bc090a009357@haskell.org> Message-ID: <066.a14f89a9d2be63ba396d0c9c0320778a@haskell.org> #12047: Users Guide: GeneralizedNewtypeDeriving derives ?instance Num Int => Num Dollars? -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: task | Status: closed Priority: normal | Milestone: Component: Documentation | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2273 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 18:14:57 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 18:14:57 -0000 Subject: [GHC] #12126: Bad error messages for SPECIALIZE pragmas Message-ID: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> #12126: Bad error messages for SPECIALIZE pragmas -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: Specialize, | Operating System: Unknown/Multiple ErrorMessages | Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When playing with SPECIALIZE pragmas, I've encountered one large problem with the error messages, and two minor ones. 1. Given a function with a `Num` constraint, applying `SPECIALIZE` at a non-function type triggers defaulting incorrectly; the code {{{#!hs f1 :: Num a => a -> a f1 x = x + x {-# SPECIALIZE f1 :: Bool #-} }}} produces the error {{{ ?/Test1.hs:5:1: error: ? Couldn't match expected type ?Integer -> Integer? with actual type ?Bool? ? In the SPECIALISE pragma {-# SPECIALIZE f1 :: Bool #-} }}} (This is in the attached file `Test1.hs`.) 2. Given a function, applying `SPECIALIZE` at a well-formed type without the looked-for instance produces an error with some extra text (the first line ends with "a SPECIALISE pragma for ?f2?", even though this is repeated on the next line); the code {{{#!hs f2 :: Num a => a -> a f2 x = x + x {-# SPECIALIZE f2 :: Bool -> Bool #-} }}} produces the error {{{ ?/Test2.hs:5:1: error: ? No instance for (Num Bool) a SPECIALISE pragma for ?f2? ? In the SPECIALISE pragma {-# SPECIALIZE f2 :: Bool -> Bool #-} }}} (This is in the attached file `Test2.hs`.) 3. This is minor, but: both of these error messages talk about a `SPECIALISE` pragma when I wrote a `SPECIALIZE` pragma. Even more so, case is not preserved in the quoted pragma; if I provide a {{{#!hs {-# specialize ? #-} }}} pragma, the error message ends with {{{ ? In the SPECIALISE pragma {-# SPECIALIZE ? #-}`. }}} even though that isn't what I wrote. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 18:15:32 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 18:15:32 -0000 Subject: [GHC] #12126: Bad error messages for SPECIALIZE pragmas In-Reply-To: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> References: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> Message-ID: <061.6c4842c2ed2974eb5be52388997cd0ec@haskell.org> #12126: Bad error messages for SPECIALIZE pragmas -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Specialize, | ErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by antalsz): * Attachment "Test1.hs" added. Incorrect defaulting in a `SPECIALIZE` error message -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 18:15:49 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 18:15:49 -0000 Subject: [GHC] #12126: Bad error messages for SPECIALIZE pragmas In-Reply-To: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> References: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> Message-ID: <061.8482f586aaa59d6581283c6ad67cb16c@haskell.org> #12126: Bad error messages for SPECIALIZE pragmas -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Specialize, | ErrorMessages Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by antalsz): * Attachment "Test2.hs" added. Extra text in a `SPECIALIZE` error message -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 18:40:00 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 18:40:00 -0000 Subject: [GHC] #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" In-Reply-To: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> References: <046.3aa229b1c93bff66ccc48ab6d0e3a13c@haskell.org> Message-ID: <061.241435a32167c4d3a9d80ceb8af8cdc8@haskell.org> #12104: Type families, `TypeError`, and `-fdefer-type-errors` cause "opt_univ fell into a hole" -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: TypeFamilies, Resolution: | CustomTypeErrors Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: conal (added) * component: Compiler => Compiler (Type checker) Comment: Conal Elliott reported the same panic in https://mail.haskell.org/pipermail/ghc-devs/2016-April/011687.html, when writing a custom GHC plugin. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 19:41:01 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 19:41:01 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.b1184a2c1c387da7a75b4aefc23201ab@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alexvieth): I have a patch which will reject the example in comment:7 and give this error {{{ ? Type constructor ?A? cannot be used here (it is defined and used in the same recursive group) ? In the kind ?A? In the definition of data constructor ?B? In the data declaration for ?A? }}} The details: - `ATcTyThing` has a new variant `ATcTyConUnpromoted TyCon` meaning the `TyCon` can't be used as a kind. - `tcTyVar` will give a promotion error (`TyConPE`) whenever an `ATcTyConUnpromoted` is encountered and the `TcTyMode` is kind level. - When checking the constructors of a `DataDecl`, the name of the type is associated with an `ATcTyConUnpromoted`, rather than `ATcTyCon` as it is now. Think this is a sane thing to do? If so I'll upload it to phab. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 20:27:32 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 20:27:32 -0000 Subject: [GHC] #9224: Add support for binary integer literals In-Reply-To: <042.1a89d47aeeec7e7c411448001a06492c@haskell.org> References: <042.1a89d47aeeec7e7c411448001a06492c@haskell.org> Message-ID: <057.f1b7799bd56d3b527091ddd48098f6e6@haskell.org> #9224: Add support for binary integer literals -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: (Parser) | Resolution: fixed | Keywords: literals Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Lemming): That's pretty useful for bit manipulation! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 20:46:26 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 20:46:26 -0000 Subject: [GHC] #11468: testsuite should ignore config files In-Reply-To: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> References: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> Message-ID: <064.6f8c098c3f7bc8080b1a5f832f8028c4@haskell.org> #11468: testsuite should ignore config files -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: Component: Test Suite | Version: 8.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2265 Wiki Page: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"d40682ec74d802376d7cf50f2d3612b3292b29c5/ghc" d40682e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d40682ec74d802376d7cf50f2d3612b3292b29c5" Testsuite: don't use --interactive in Makefiles Add a linter to encourage the use of `$(TEST_HC_OPTS_INTERACTIVE)` instead of `$(TEST_HC_OPTS) --interactive -ignore-dot-ghci -v0`. It's too easy to forget one of those flags when adding a new test. Update submodule hpc. Reviewed by: austin Differential Revision: https://phabricator.haskell.org/D2265 GHC Trac Issues: #11468 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 20:47:45 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 20:47:45 -0000 Subject: [GHC] #11468: testsuite should ignore config files In-Reply-To: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> References: <049.de2320dee7569d2d6851ff576589c50b@haskell.org> Message-ID: <064.75a473c4ac7a9b19cb6af2a82250b7a3@haskell.org> #11468: testsuite should ignore config files -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: thomie Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Test Suite | Version: 8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2265 Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 21:06:58 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 21:06:58 -0000 Subject: [GHC] #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults In-Reply-To: <044.e54e5ecad8d095611a80bfdfe4263626@haskell.org> References: <044.e54e5ecad8d095611a80bfdfe4263626@haskell.org> Message-ID: <059.aa8e0969ca062b07c6ea463e45666f8d@haskell.org> #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults ------------------------------------+-------------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (LLVM) | Version: 7.9 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 Fanael): * status: closed => new * resolution: worksforme => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri May 27 21:46:03 2016 From: ghc-devs at haskell.org (GHC) Date: Fri, 27 May 2016 21:46:03 -0000 Subject: [GHC] #12126: Bad error messages for SPECIALIZE pragmas In-Reply-To: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> References: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> Message-ID: <061.5eb14c915c31c45b8c620301dfd0e0e1@haskell.org> #12126: Bad error messages for SPECIALIZE pragmas -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Specialize, | ErrorMessages, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: Specialize, ErrorMessages => Specialize, ErrorMessages, newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 00:06:52 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 00:06:52 -0000 Subject: [GHC] #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults In-Reply-To: <044.e54e5ecad8d095611a80bfdfe4263626@haskell.org> References: <044.e54e5ecad8d095611a80bfdfe4263626@haskell.org> Message-ID: <059.d5e276a9dd76495bfa82af1408055528@haskell.org> #8974: 64 bit windows executable built with ghc-7.9.20140405+LLVM segfaults ------------------------------------+-------------------------------------- Reporter: awson | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler (LLVM) | Version: 7.9 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: | ------------------------------------+-------------------------------------- Comment (by GordonBGood): Replying to [comment:36 Fanael]: > Precisely *nothing* changed in the code generated by GHC and the binutils bug is still open, so the idea that GHC HEAD doesn't have this bug is [REDACTED]. Thanks, Fanael, I tried binutils version 2.26.2 to the mix of GHC version 8.0.1 and LLVM 3.7 and there is still no resolution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 10:37:32 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 10:37:32 -0000 Subject: [GHC] #12126: Bad error messages for SPECIALIZE pragmas In-Reply-To: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> References: <046.46f61e5c8784dffd3faa2d7de26366e6@haskell.org> Message-ID: <061.3aab6afb5e3ccf953446bc97f486ecf1@haskell.org> #12126: Bad error messages for SPECIALIZE pragmas -------------------------------------+------------------------------------- Reporter: antalsz | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Specialize, | ErrorMessages, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Thanks, this is a good bug report and something good for a newcomer to get started with. I think that fixing at least (2) and (3) should be easy. Here are my investigations so far: 1. Specialisation signatures are handled in `TcBinds.tcSpecPrags`. 2. `unifyType` fails to solve `Bool ~ (Num a => a -> a)` so it gets deferred to later on in the constraint solving process. At which point it is defaulted for some reason. 1. The outer error context is added in `tcSpecPrag`. 2. The inner error context is added as a result of `hsSigDoc`. Suggestion: Modify the outer context added in `tcSpecPrag`. 1. The actual text that a user used can be found in the `inl_src` field of the `InlinePragma` field of `SpecSig`. Suggestion: There should be a few places to change where you can use this value rather than hard-coding `SPECIALISE`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 12:26:19 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 12:26:19 -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.6f578adf47348117684a2f373982a61e@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: seraphime Type: task | Status: patch Priority: normal | Milestone: 8.2.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: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2277 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 15:00:31 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 15:00:31 -0000 Subject: [GHC] #12127: ghc-8.0.1: panic! (the 'impossible' happened) filterImports/combine (double import) Message-ID: <045.ae5844a0544b94191ee992f204e3d334@haskell.org> #12127: ghc-8.0.1: panic! (the 'impossible' happened) filterImports/combine (double import) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- It's a distilled example or repa-devil-0.3.2.6 build failure: {{{#!hs -- Cursored.hs: {-# LANGUAGE TypeFamilies #-} module Cursored where class Source r where data Array r instance Source () where data Array () = F { f :: Int } }}} {{{#!hs -- Bug.hs: module DevIL () where import Cursored (Array(..), Source(..)) }}} {{{ [1 of 2] Compiling Cursored ( Cursored.hs, Cursored.o ) [2 of 2] Compiling DevIL ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): filterImports/combine (Array, Array{Array, F, f}, Nothing) (Array, Source{Source, Array}, Nothing) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The error is the same as #11959 but involved entities are slightly different. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 16:50:21 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 16:50:21 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly In-Reply-To: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> References: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> Message-ID: <062.2ae8adb9f9b6356ab704c09a3f688b90@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly ----------------------------------------+---------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+---------------------------------- Changes (by trommler): * status: new => infoneeded * component: Compiler => Compiler (NCG) Comment: I think we need to be more specific when we parse the host triple in `configure.ac` and introduce instruction set variants. Right now `powerpc` (`ArchPPC` in Haskell code) refers to a server (not embedded) PowerPC. Could you please attach the output of `./configure` to this ticket so we can fix architecture detection in `configure.ac`. The native code generator assumes a server PPC with FPU so your proposed fix would only be a first step to support e500 CPUs . That is where you see your second failure. I don't have access to e500 hardware but I could help with coaching and code reviews if you would like to add support for embedded PPCs. Meanwhile you could also build an unregisterised compiler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 17:42:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 17:42:18 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly In-Reply-To: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> References: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> Message-ID: <062.8b616807c8149364ae74c6321220c36c@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly ----------------------------------------+---------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+---------------------------------- Changes (by glaubitz): * Attachment "config.log" added. Output of configure without options on a e500v2 machine -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 17:42:36 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 17:42:36 -0000 Subject: [GHC] #12075: Fails to build on powerpcspe because of inline assembly In-Reply-To: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> References: <047.7799711340d17162ce82b5c7159b8d72@haskell.org> Message-ID: <062.c7f0620f9a633cdb032b8aab332a03c5@haskell.org> #12075: Fails to build on powerpcspe because of inline assembly ----------------------------------------+---------------------------------- Reporter: glaubitz | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 8.2.1 Component: Compiler (NCG) | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------------+---------------------------------- Comment (by glaubitz): Replying to [comment:4 trommler]: > I think we need to be more specific when we parse the host triple in `configure.ac` and introduce instruction set variants. Right now `powerpc` (`ArchPPC` in Haskell code) refers to a server (not embedded) PowerPC. Could you please attach the output of `./configure` to this ticket so we can fix architecture detection in `configure.ac`. > > The native code generator assumes a server PPC with FPU so your proposed fix would only be a first step to support e500 CPUs . That is where you see your second failure. > > I don't have access to e500 hardware but I could help with coaching and code reviews if you would like to add support for embedded PPCs. Meanwhile you could also build an unregisterised compiler. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 21:04:12 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 21:04:12 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.e5ca056b6b081bb373fa525be71d34f0@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): By the way, I have been slowly chipping away at this one. I suspect I'll have a fix tomorrow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat May 28 22:38:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sat, 28 May 2016 22:38:51 -0000 Subject: [GHC] #487: powerpc/linux segfaulting binaries In-Reply-To: <043.e4c96af6f7160fcdea6756f17c3ec89f@haskell.org> References: <043.e4c96af6f7160fcdea6756f17c3ec89f@haskell.org> Message-ID: <058.1788641fab42e98b193ddec5223d6180@haskell.org> #487: powerpc/linux segfaulting binaries ----------------------------------+------------------------------- Reporter: dons | Owner: erikd Type: bug | Status: closed Priority: normal | Milestone: ? Component: Compiler | Version: 6.4.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Runtime crash | Test Case: N/A Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ----------------------------------+------------------------------- Changes (by erikd): * status: new => closed * resolution: None => fixed Comment: Yep, builds fine with 7.10.3. Closing this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 02:11:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 02:11:13 -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.36b3e762c72baa91b6381f605d61d7bb@haskell.org> #11767: Add @since annotations for base instances -------------------------------------+------------------------------------- Reporter: bgamari | Owner: seraphime Type: task | Status: patch Priority: normal | Milestone: 8.2.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 Iceland_jack): Replying to [comment:6 seraphime]: > I have already written a script [...] Hm, have you tried running it on instances with existing `@since` and verifying the output? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 02:43:45 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 02:43:45 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 Message-ID: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> #12128: ghci cause panic on 8.0.1 -------------------------------------+------------------------------------- Reporter: zxtx | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code panics when called with ghci: {{{#!hs module Foo where import GHC.TypeLits (Symbol) import Unsafe.Coerce instance Read Symbol where readsPrec = unsafeCoerce (readsPrec :: Int -> ReadS String) data Bar = TyCon !Symbol deriving (Read) }}} {{{ % ghci foo.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/zv/.ghc/ghci.conf [1 of 1] Compiling Foo ( foo.hs, interpreted ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): atomPrimRep case a1_s2AG of _ [Occ=Dead] { } }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 02:44:35 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 02:44:35 -0000 Subject: [GHC] #12128: ghci cause panic on 8.0.1 In-Reply-To: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> References: <043.d0d8e98d01cc863c9b0e7ff6db6baf83@haskell.org> Message-ID: <058.2fe8c4a3be8bd74d261a375a0058494b@haskell.org> #12128: ghci cause panic on 8.0.1 ---------------------------------+---------------------------------------- Reporter: zxtx | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by zxtx): * os: Unknown/Multiple => Linux -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 06:02:47 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 06:02:47 -0000 Subject: [GHC] #12129: Optimize the implementation of minusInteger in the integer-gmp package Message-ID: <045.2163dd10a25b10afe0356071e88b814b@haskell.org> #12129: Optimize the implementation of minusInteger in the integer-gmp package -------------------------------------+------------------------------------- Reporter: admock | Owner: Type: task | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | 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: -------------------------------------+------------------------------------- As mentioned in [https://www.fpcomplete.com/blog/2016/05/weigh-package], the current implementation of `minusInteger` is {{{#!hs minusInteger x y = inline plusInteger x (inline negateInteger y) }}} which always allocates an additional integer. This could be improved by not always calling `negateInteger` and instead having an implementation more like `plusInteger`'s. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 06:16:43 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 06:16:43 -0000 Subject: [GHC] #12130: ghc: panic! (the 'impossible' happened): find_tycon Block [] Message-ID: <044.523b434f5130bcce5d2e71f45a4abdd5@haskell.org> #12130: ghc: panic! (the 'impossible' happened): find_tycon Block [] -------------------------------------+------------------------------------- Reporter: jeiea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I just tried building yesod-simple template project with nightly-2016-05-29 snapshot and some extra-deps package, and it seems to fail due to {{{$(widgetFile ...)}}} yesod template haskell clause. It was same on linux and windows, and when I remove handler ghc fails at Application module (and seems also due to template haskell). {{{ ~/yt> stack build ... yt-0.0.0: configure Configuring yt-0.0.0... yt-0.0.0: build Preprocessing library yt-0.0.0... [1 of 9] Compiling Settings ( Settings.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Settings.o ) [2 of 9] Compiling Settings.StaticFiles ( Settings/StaticFiles.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Settings/StaticFiles.o ) [3 of 9] Compiling Import.NoFoundation ( Import/NoFoundation.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Import/NoFoundation.o ) [4 of 9] Compiling Foundation ( Foundation.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Foundation.o ) [5 of 9] Compiling Import ( Import.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Import.o ) [6 of 9] Compiling Handler.Common ( Handler/Common.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Handler/Common.o ) [7 of 9] Compiling Handler.Home ( Handler/Home.hs, .stack- work/dist/x86_64-linux/Cabal-1.24.0.0/build/Handler/Home.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): find_tycon Block [] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Completed 179 action(s). -- While building package yt-0.0.0 using: /home/jeiea/.stack/setup-exe-cache/x86_64-linux/setup-Simple- Cabal-1.24.0.0-ghc-8.0.1 --builddir=.stack- work/dist/x86_64-linux/Cabal-1.24.0.0 build lib:yt exe:yt --ghc-options " -ddump-hi -ddump-to-file" Process exited with code: ExitFailure 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 06:19:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 06:19:58 -0000 Subject: [GHC] #12130: ghc: panic! (the 'impossible' happened): find_tycon Block [] In-Reply-To: <044.523b434f5130bcce5d2e71f45a4abdd5@haskell.org> References: <044.523b434f5130bcce5d2e71f45a4abdd5@haskell.org> Message-ID: <059.ce202f9c9e9d8f338f877577d5d94a7e@haskell.org> #12130: ghc: panic! (the 'impossible' happened): find_tycon Block [] -------------------------------------+------------------------------------- Reporter: jeiea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by jeiea): * Attachment "yesod-simple.zip" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 07:15:48 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 07:15:48 -0000 Subject: [GHC] #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) Message-ID: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple UndecidableSuperClasses | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #11480 #12025 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The Glorious Glasgow Haskell Compilation System, version 8.0.1. Code taken from [https://gist.github.com/ekmett/b26363fc0f38777a637d gist] with {{{#!hs fmap :: p a b -> q (f a) (f b) }}} replaced by {{{#!hs fmap :: Dom f a b -> Cod f (f a) (f b) }}} If you enable `DataKinds` and `TypeInType` `:kind` will happily tell you its kind: {{{ ghci> :kind 'Main.Nat 'Main.Nat :: forall j i (p :: Cat i) (q :: Cat j) (f :: i -> j) (g :: i -> j). (FunctorOf p q f, FunctorOf p q g) => (forall (a :: i). Ob p a => q (f a) (g a)) -> Main.Nat p q f g }}} but if you try `:type Nat` it spits out a long list of unsolved constraints {{{ ghci> :type Nat :1:1: error: solveWanteds: too many iterations (limit = 1) Unsolved: WC {wc_simple = [W] $dFunctor_ag3Y :: Main.Functor f_ag3S (CDictCan) [W] $dFunctor_ag4d :: Main.Functor g_ag3T (CDictCan) [D] _ :: Main.Functor s_ag51 (CDictCan) [D] _ :: Main.Functor s_ag5a (CDictCan) [D] _ :: Main.Functor s_ag4W (CDictCan) [D] _ :: Main.Functor s_ag55 (CDictCan) [D] _ :: Category s_ag51 (CDictCan) [D] _ :: Category s_ag5a (CDictCan) [D] _ :: Category s_ag4W (CDictCan) [D] _ :: Category s_ag55 (CDictCan) [W] hole{ag4Y} :: Dom g_ag3T ~ Dom f_ag3S (CNonCanonical) [W] hole{ag53} :: Cod g_ag3T ~ Cod f_ag3S (CNonCanonical) [D] _ :: Dom (Dom f_ag3S) ~ Op (Dom f_ag3S) (CNonCanonical) [D] _ :: Cod (Dom f_ag3S) }}} This seems like #11480. This makes undecidable superclasses a harsh master and raises two questions that I'll bundle together: 1. Why can the `:kind` be inferred but not the `:type`? It works when given extra information: {{{ ghci> :type Nat @_ @_ @(->) @(->) Nat @_ @_ @(->) @(->) :: (Cod g ~ (->), Dom g ~ (->), Cod f ~ (->), Dom f ~ (->), Main.Functor g, Main.Functor f) => (forall a. Vacuous (->) a => f a -> g a) -> Main.Nat (->) (->) f g }}} {{{ ghci> :type Nat @_ @_ @_ @_ @[] @Maybe Nat @_ @_ @_ @_ @[] @Maybe :: (forall a. Vacuous (->) a => [a] -> Maybe a) -> Main.Nat (->) (->) [] Maybe }}} {{{ ghci> :type Nat @_ @_ @_ @_ @[] @Maybe listToMaybe Nat @_ @_ @_ @_ @[] @Maybe listToMaybe :: Main.Nat (->) (->) [] Maybe }}} 2. Why is `j` positioned before `i` (most likely because of `forall a. ...` but I tried tinkering without success? Is there any trick to ordering it as you'd expect `forall i j (p :: Cat i) (q :: Cat j)` or is it not possible per #12025? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 07:16:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 07:16:58 -0000 Subject: [GHC] #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) In-Reply-To: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> References: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> Message-ID: <066.51409c0089046c7ad774e2f0c61dfa0f@haskell.org> #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11480 #12025 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * Attachment "Testcase.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 08:33:07 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 08:33:07 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples Message-ID: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is a continuation of #11120. It seems there is something odd happening with type representations for boxed tuples, {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.1.20160528: http://www.haskell.org/ghc/ :? for help Prelude> :set -XDataKinds Prelude> :m + Data.Typeable Data.Proxy Prelude Data.Typeable Data.Proxy> typeOf (Proxy :: Proxy (Int,Int)) Proxy * (Int,Int) Prelude Data.Typeable Data.Proxy> typeOf (Proxy :: Proxy '(Int,Int)) GHC error in desugarer lookup in Ghci2: Can't find interface-file declaration for variable $tc'(,) Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160528 for x86_64-unknown-linux): initDs IOEnv failure Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude Data.Typeable Data.Proxy> }}} This is odd since the `$tc'(,)` binding is present in the interface file for `GHC.Tuple`, {{{ $ inplace/bin/ghc-stage2 --show-iface libraries/ghc-prim/dist- install/build/GHC/Tuple.dyn_hi |less ... 14e44400752f4580e52ed2a760b9633f $tc'(,) :: TyCon {- HasNoCafRefs, Strictness: m, Unfolding: (TyCon 14407099369839560749## 10712746223293009168## $trModule $tc'(,)1) -} 543be63d698612591d2e75b0b60ad643 $tc'(,)1 :: TrName {- HasNoCafRefs, Strictness: m1, Unfolding: (TrNameS "'(,)"#) -} 469b4ffe716da12a5be1f5ab03864791 $tc'(,,) :: TyCon {- HasNoCafRefs, Strictness: m, Unfolding: (TyCon 3540448346642256323## 9150387332266490903## $trModule $tc'(,,)1) -} ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 08:34:13 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 08:34:13 -0000 Subject: [GHC] #11120: Missing type representations In-Reply-To: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> References: <047.ed7038f9e6faf469d425a225b8ecbabe@haskell.org> Message-ID: <062.9bb9de65007b54677dfc2cc3d5bb037e@haskell.org> #11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: #12132 | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * related: => #12132 Comment: I've opened up #12132 to track the issue in comment:52 so we can keep these issues distinct. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 08:35:01 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 08:35:01 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.2c25a2f205d352eb1a77aa68a60daae1@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: @@ -40,8 +40,0 @@ - 469b4ffe716da12a5be1f5ab03864791 - $tc'(,,) :: TyCon - {- HasNoCafRefs, Strictness: m, - Unfolding: (TyCon - 3540448346642256323## - 9150387332266490903## - $trModule - $tc'(,,)1) -} New description: This is a continuation of #11120. It seems there is something odd happening with type representations for boxed tuples, {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.1.20160528: http://www.haskell.org/ghc/ :? for help Prelude> :set -XDataKinds Prelude> :m + Data.Typeable Data.Proxy Prelude Data.Typeable Data.Proxy> typeOf (Proxy :: Proxy (Int,Int)) Proxy * (Int,Int) Prelude Data.Typeable Data.Proxy> typeOf (Proxy :: Proxy '(Int,Int)) GHC error in desugarer lookup in Ghci2: Can't find interface-file declaration for variable $tc'(,) Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160528 for x86_64-unknown-linux): initDs IOEnv failure Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude Data.Typeable Data.Proxy> }}} This is odd since the `$tc'(,)` binding is present in the interface file for `GHC.Tuple`, {{{ $ inplace/bin/ghc-stage2 --show-iface libraries/ghc-prim/dist- install/build/GHC/Tuple.dyn_hi |less ... 14e44400752f4580e52ed2a760b9633f $tc'(,) :: TyCon {- HasNoCafRefs, Strictness: m, Unfolding: (TyCon 14407099369839560749## 10712746223293009168## $trModule $tc'(,)1) -} 543be63d698612591d2e75b0b60ad643 $tc'(,)1 :: TrName {- HasNoCafRefs, Strictness: m1, Unfolding: (TrNameS "'(,)"#) -} ... }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 08:37:46 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 08:37:46 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.824842ff15a70e962ae97667002db7ac@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Sadly `-ddump-if-trace` doesn't appear to be so helpful here, {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.1.20160528: http://www.haskell.org/ghc/ :? for help Prelude> :set -XDataKinds Prelude> :m + Data.Typeable Data.Proxy Prelude Data.Typeable Data.Proxy> typeOf (Proxy :: Proxy (Int,Int)) Proxy * (Int,Int) Prelude Data.Typeable Data.Proxy> typeOf (Proxy :: Proxy '(Int,Int)) GHC error in desugarer lookup in Ghci2: Can't find interface-file declaration for variable $tc'(,) Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160528 for x86_64-unknown-linux): initDs IOEnv failure Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Prelude Data.Typeable Data.Proxy> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 09:17:24 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 09:17:24 -0000 Subject: [GHC] #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) In-Reply-To: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> References: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> Message-ID: <066.19fc9cac4ae87244440d7aa5425f638f@haskell.org> #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11480 #12025 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Also true for {{{#!hs data Product (p :: Cat i) (q :: Cat j) :: Cat (i, j) where Product :: p (Fst a) (Fst b) -> q (Snd a) (Snd b) -> Product p q a b }}} with code from [https://github.com/ekmett/hask/blob/master/src/Hask/Category/Polynomial.hs Polynomial.hs] and [https://github.com/ekmett/hask/blob/master/src/Hask/Category.hs Category.hs] adapted: {{{#!hs type family Fst (p :: (i,j)) :: i where Fst '(a, _) = a type family Snd (q :: (i,j)) :: j where Snd '(_, b) = b type family NatDom (f :: Cat (i -> j)) :: Cat i where NatDom (Nat p _) = p type family NatCod (f :: Cat (i -> j)) :: Cat j where NatCod (Nat _ q) = q type Opd f = Op (Dom f) type Dom2 p = NatDom (Cod p) type Cod2 p = NatCod (Cod p) class (Ob p (Fst a), Ob q (Snd a)) => ProductOb (p :: Cat i) (q :: Cat j) (a :: (i,j)) instance (Ob p (Fst a), Ob q (Snd a)) => ProductOb (p :: Cat i) (q :: Cat j) (a :: (i,j)) instance (Category p, Category q) => Functor (Product p q) where type Dom (Product p q) = Op (Product (Opd p) (Opd q)) type Cod (Product p q) = Nat (Product (Dom2 p) (Dom2 q)) (->) instance (Category p, Category q, ProductOb p q a) => Functor (Product p q a) where type Dom (Product p q a) = Product (Dom2 p) (Dom2 q) type Cod (Product p q a) = (->) fmap = (.) instance (Category p, Category q) => Category (Product p q) where type Ob (Product p q) = ProductOb p q id = Product id id Product f f' . Product g g' = Product (f . g) (f' . g') target = undefined source = undefined }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 09:19:07 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 09:19:07 -0000 Subject: [GHC] #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) In-Reply-To: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> References: <051.e4e7a903cc2028990cc937a0b2bfe043@haskell.org> Message-ID: <066.1bb7c6c8991d2bbc9139ce0cc0a212b3@haskell.org> #12131: Can't solve constraints with UndecidableSuperClasses but can infer kind (+ undesired order of kinds) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: | UndecidableSuperClasses Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11480 #12025 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): `Product` doesn't make ghc spin, but oddly `j` appears before `i` even though `Cat i` appears before `Cat j`, etc. {{{ ghci> :t Product Product :: forall j i (p :: i -> i -> *) (q :: j -> j -> *) (a :: (i, j)) (b :: (i, j)). p (Fst a) (Fst b) -> q (Snd a) (Snd b) -> Product p q a b }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 10:22:20 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 10:22:20 -0000 Subject: [GHC] #12129: Optimize the implementation of minusInteger in the integer-gmp package In-Reply-To: <045.2163dd10a25b10afe0356071e88b814b@haskell.org> References: <045.2163dd10a25b10afe0356071e88b814b@haskell.org> Message-ID: <060.54c18ff2bba58480ba139845708355c8@haskell.org> #12129: Optimize the implementation of minusInteger in the integer-gmp package -------------------------------------+------------------------------------- Reporter: admock | Owner: admock Type: task | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: integer-gmp 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 hvr): * owner: => admock * keywords: => integer-gmp -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 10:52:04 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 10:52:04 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.1410b9302835a6344894370cd8577c20@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It seems like the issue here is that the uniques don't match. For instance, in the case of the error, {{{ GHC error in desugarer lookup in interactive:Ghci1: Can't find interface-file declaration for variable ghc- prim-0.5.0.0:GHC.Tuple.$tc'(,){v 78} Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error }}} I have only this in the PTE, {{{ Identifier ?ghc-prim-0.5.0.0:GHC.Tuple.$tc(,){v 45}? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 12:49:00 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 12:49:00 -0000 Subject: [GHC] #12132: Type representations missing for promoted boxed tuples In-Reply-To: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> References: <046.73dbaf7b6ca62d79018b512a7b0731f6@haskell.org> Message-ID: <061.f18debe76a416cf42aa94323319e7c98@haskell.org> #12132: Type representations missing for promoted boxed tuples -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 8.0.2 Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2279 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch * differential: => Phab:D2279 Comment: The issue ended up being that promoted tycons arising from the boxed tuple types weren't being included in `knownKeyNames`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 17:15:10 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 17:15:10 -0000 Subject: [GHC] #12129: Optimize the implementation of minusInteger in the integer-gmp package In-Reply-To: <045.2163dd10a25b10afe0356071e88b814b@haskell.org> References: <045.2163dd10a25b10afe0356071e88b814b@haskell.org> Message-ID: <060.08e3903dddc9fd0673d045384a4a311b@haskell.org> #12129: Optimize the implementation of minusInteger in the integer-gmp package -------------------------------------+------------------------------------- Reporter: admock | Owner: admock Type: task | Status: new Priority: normal | Milestone: Component: libraries | Version: 8.0.1 (other) | Resolution: | Keywords: integer-gmp Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2278 Wiki Page: | -------------------------------------+------------------------------------- Changes (by admock): * differential: => Phab:D2278 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 18:00:09 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 18:00:09 -0000 Subject: [GHC] #12115: CoreLint error in safe program In-Reply-To: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> References: <043.b37b5ed016135a00f96e08c4966051af@haskell.org> Message-ID: <058.5f3b106d4c3f7b01b110b8b25986b762@haskell.org> #12115: CoreLint error in safe program -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | codegen/should_compile/T12115 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I'm a bit lost with these patches. - The commentary says that `(# #)` becomes `Void#` during unarisation. But there is also a change in !TysWiredIn that removes the special case for nullary unboxed tuples. - `Note [The kind invariant]` is awfully out-of-date: {{{ Note [The kind invariant] ~~~~~~~~~~~~~~~~~~~~~~~~~ The kinds # UnliftedTypeKind OpenKind super-kind of *, # can never appear under an arrow or type constructor in a kind; they can only be at the top level of a kind. It follows that primitive TyCons, which have a naughty pseudo-kind State# :: * -> # must always be saturated, so that we can never get a type whose kind has a UnliftedTypeKind or ArgTypeKind underneath an arrow. Nor can we abstract over a type variable with any of these kinds. k :: = kk | # | ArgKind | (#) | OpenKind kk :: = * | kk -> kk | T kk1 ... kkn So a type variable can only be abstracted kk. }}} (I'm sure I'm implicated in letting this fall out-of-date. But I honestly don't know how to fix.) There is no `#` anymore, and there is no `OpenKind` anymore. One might think this means that a representation-polymorphic kind (that is, `TYPE r`) cannot appear below top-level, but indeed they do, as in the type of `error`. So I'm not sure what this is saying. Also, this Note is missing ''why'' these restrictions are in place. I recall several months ago moving to allow unsaturated unlifted things, but now we've backpedaled on this decision. I'm sure there's a good reason, but what is it? This Note is also missing ''where'' these restrictions are enforced. Is there a check in !CoreLint that we never abstract over a kind `* -> TYPE `? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 18:07:18 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 18:07:18 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.c4ec324b7eff5e49dc86ecf416e8856d@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Won't `ATcTyConUnpromoted` and `ATcTyCon` be the same, always? That is, if (and only if) we're currently checking a mutually recursive group containing the tycon `T`, `T` will be registered as `ATcTyCon`. Isn't that the exact scenario where you're proposing to use `ATcTyConUnpromoted`? So my take would be to check in `tcTyVar`, just as you suggest, but use the existing `ATcTyCon` instead of creating something new. Or what am I missing? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 18:17:51 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 18:17:51 -0000 Subject: [GHC] #12133: ConstraintKinds inference failure (regression from 7.10) Message-ID: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> #12133: ConstraintKinds inference failure (regression from 7.10) -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Posting for a friend who was believed to be spam: {{{#!hs {-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ImplicitParams #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} module T where #if __GLASGOW_HASKELL__ >= 800 import GHC.Classes (IP(..)) #else import GHC.IP (IP(..)) #endif import GHC.Exts (Constraint) -- | From "Data.Constraint": data Dict :: Constraint -> * where Dict :: a => Dict a newtype a :- b = Sub (a => Dict b) infixl 1 \\ -- required comment (\\) :: a => (b => r) -> (a :- b) -> r r \\ Sub Dict = r -- | GHC 7.10.2 type checks this function but GHC 8.0.1 does not unless -- you modify this example in one of the following ways: -- -- * uncomments the type signature for 'Sub' -- -- * flatten the nested pairs of constraints into a triple of constraints -- -- * replace 'IP sym ty' with 'c9', where 'c9' is a new constraint variable. -- -- The error message is listed below. foo :: forall c1 c2 c3 sym ty . (c1, c2) :- c3 -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3) foo sp = ( Sub -- :: ((c1, (IP sym ty, c2)) => Dict (IP sym ty, c3)) -- -> (c1, ((IP sym ty), c2)) :- (IP sym ty, c3) ) ( (Dict \\ sp) :: Dict (IP sym ty, c3) ) {- Compiler error message: GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling T ( t.hs, interpreted ) t.hs:44:13: error: ? Could not deduce: IP sym ty arising from a use of ?Dict? from the context: (c1, (IP sym ty, c2)) bound by a type expected by the context: (c1, (IP sym ty, c2)) => Dict (IP sym ty, c3) at t.hs:(40,10)-(44,49) or from: c3 bound by a type expected by the context: c3 => Dict (IP sym ty, c3) at t.hs:44:13-22 ? In the first argument of ?(\\)?, namely ?Dict? In the first argument of ?Sub?, namely ?((Dict \\ sp) :: Dict (IP sym ty, c3))? In the expression: (Sub) ((Dict \\ sp) :: Dict (IP sym ty, c3)) ? Relevant bindings include foo :: (c1, c2) :- c3 -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3) (bound at t.hs:40:1) Failed, modules loaded: none. -} }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 18:19:58 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 18:19:58 -0000 Subject: [GHC] #12134: PowerPC 64-bit: Foreign functions with more than 8 float parameters broken Message-ID: <047.b2f90e1cc5508bb649499a3ffa202a40@haskell.org> #12134: PowerPC 64-bit: Foreign functions with more than 8 float parameters broken -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (NCG) | Keywords: ccall | Operating System: Linux Architecture: powerpc64 | Type of failure: Incorrect result | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider the following: {{{#!c void many_floats(float f1, float f2, float f3, float f4, float f5, float f6, float f7, float f8, float f9, float f10, float f11, float f12, float f13, float f14) { printf("%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n%f\n", f1, f2, f3, f4, f5, f6, f7, f8, f9, f10, f11, f12, f13, f14); } }}} and {{{#!hs foreign import ccall "many_floats" many :: CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> CFloat -> IO () main = many 1.5 2.5 3.5 4.5 5.5 6.5 7.5 8.5 9.5 10.5 11.5 12.5 13.5 14.5 }}} gives {{{ 1.500000 2.500000 3.500000 4.500000 5.500000 6.500000 7.500000 8.500000 0.000000 0.000000 3.000000 14.500000 13.500000 0.000000 }}} on PowerPC 64-bit Linux. According to the ABI for PowerPC 64-bit ELF v1.9 and ELF v2.0 the first 13 floating or double parameters are passed in floating point registers. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 20:15:02 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 20:15:02 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.5597c4c868f583600a0c56aa5429ed6f@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by alexvieth): > Or what am I missing? Nothing, you're right about this. The patch is now very small. {{{ --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -881,7 +881,10 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon ; case thing of ATyVar _ tv -> return (mkTyVarTy tv, tyVarKind tv) - ATcTyCon tc_tc -> do { check_tc tc_tc + ATcTyCon tc_tc -> do { unless + (isTypeLevel (mode_level mode)) + (promotionErr name TyConPE) + ; check_tc tc_tc ; tc <- get_loopy_tc name tc_tc ; handle_tyfams tc tc_tc } -- mkNakedTyConApp: see Note [Type-checking inside the knot] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 22:20:29 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 22:20:29 -0000 Subject: [GHC] #11554: Self quantification in GADT data declarations In-Reply-To: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> References: <046.bec85a0842a04f6c9921baff0e29a2a1@haskell.org> Message-ID: <061.c2d6cec37475b79ca3b711775e970406@haskell.org> #11554: Self quantification in GADT data declarations -------------------------------------+------------------------------------- Reporter: Rafbill | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1-rc2 checker) | Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I like it! :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 22:43:34 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 22:43:34 -0000 Subject: [GHC] #10843: Allow do blocks without dollar signs as arguments In-Reply-To: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> References: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> Message-ID: <064.bc30ef26a3efd1fbf5d2bbd9bc6d98be@haskell.org> #10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Changes (by akio): * cc: akio (added) Comment: I would love this. Is there a way to move this forward? Write a wiki page? Or is this proposal abandoned? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun May 29 23:41:44 2016 From: ghc-devs at haskell.org (GHC) Date: Sun, 29 May 2016 23:41:44 -0000 Subject: [GHC] #10843: Allow do blocks without dollar signs as arguments In-Reply-To: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> References: <049.979a39a09d7a881598f53a6a6ce9bbe3@haskell.org> Message-ID: <064.8ee2fd57afd5a3651e6545e693af777a@haskell.org> #10843: Allow do blocks without dollar signs as arguments -------------------------------------+------------------------------------- Reporter: agibiansky | Owner: agibiansky Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11706 | Differential Rev(s): Phab:D1219 Wiki Page: | -------------------------------------+------------------------------------- Comment (by ezyang): I suspect, in practice, it will involve finding someone with commit bits to champion the change, and then making sure all the loose bits and bobs from the original PR are tied up. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 04:09:00 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 04:09:00 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.e8202463685fa6941bcc2f284fe00ec9@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2280 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2280 Comment: See also https://github.com/haskell/haddock/pull/520 for the necessary Haddock changes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 05:05:13 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 05:05:13 -0000 Subject: [GHC] #12099: ghc --show-options lists invalid flags In-Reply-To: <046.f661034fd1c4aa2ec7129aadde9e360e@haskell.org> References: <046.f661034fd1c4aa2ec7129aadde9e360e@haskell.org> Message-ID: <061.05fab81c28486b8360036d0ddee60889@haskell.org> #12099: ghc --show-options lists invalid flags -------------------------------------+------------------------------------- Reporter: DanielG | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2281 Wiki Page: | -------------------------------------+------------------------------------- Changes (by sgillespie): * differential: => Phab:D2281 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 05:29:20 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 05:29:20 -0000 Subject: [GHC] #11822: Pattern match checker exceeded (2000000) iterations In-Reply-To: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> References: <049.f2a29571b162949a036aa4b2a361c7f6@haskell.org> Message-ID: <064.4896a491b387d5311a59cc8362f1ffc4@haskell.org> #11822: Pattern match checker exceeded (2000000) iterations -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: gkaracha Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1-rc3 Resolution: | Keywords: | PatternMatchWarnings Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by NeilMitchell): Note that in getting to 2M iterations it took 35s (timings are from loading into ghci). That's a significant slowdown in overall compilation time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 06:05:31 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 06:05:31 -0000 Subject: [GHC] #12135: Failure to recompile when #include file is created earlier on include path Message-ID: <051.61c0d6672d978f0765786df80ed914a5@haskell.org> #12135: Failure to recompile when #include file is created earlier on include path -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Originally discovered when trying to improve Hadrian, for context see: https://github.com/snowleopard/hadrian/issues/247#issuecomment-222317602 If you create a file {{{Test.hs}}} {{{#!hs #include "a/Test.hs" main = print message }}} And a file {{{a/Test.h}}} {{{#!hs message = 1 }}} Then run and compile with {{{ghc --make -XCPP -Ib;a Main.hs}}} it compiles and runs properly, printing 1. Changing {{{a/Test.h}}} to {{{message = 2}}} then running {{{ghc}}} rebuilds and prints 2. Creating a fresh {{{b/Test.h}}} with {{{message = 3}}} does not cause {{{ghc}}} to recompile, and thus incorrectly still prints 2. Touching {{{Main.hs}}} causes recompilation, and then the correct header file is picked up, resulting in 3 being printed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 12:31:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 12:31:42 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.e544e39bf57149fd6433ce417a8c0c17@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2280 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): On Phab:D2280, kosmikus said: > In principle: I think this is great and definitely needed so that we can more reliably use all the different deriving-mechanisms, so thanks a lot for trying to move this forward. > > But: I think this should not be done via pragmas. (I know I've suggested using pragmas in the past myself, but I've changed my opinon.) I'm not sure whether there is a clear guideline for what should be a pragma and what not, but to me, I think stuff affecting optimizations or performance are perfectly fine, stuff that can make a difference between a program compiling at all or not (OVERLAPPING, OVERLAPPABLE) are critical, and stuff that changes the semantics/result of a program (this change) is too much. I'd much rather see this implemented via actual language syntax. It would also hopefully make it easier to extend it with more flexibility in subsequent versions. (Copying here because this is a design issue, not an implementation one.) I agree fully with this, including the bit that I, too, have suggested pragmas but now change my stance. I think we should have a guiding principle about pragmas. I propose this: * A pragma should either: 1. Behave precisely like options that could be passed in at the command line, OR 2. Have no effect on the semantics (static or dynamic) of the program Ideally, actually, we'd just have (2), but `LANGUAGE` doesn't qualify for (2). To be clear, by "semantics (static or dynamic)", I mean typability and runtime behavior. Browsing through the current set of accepted pragmas ([https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#pragmas in the manual], if that's complete) all pragmas meet this guideline except these: * The `OVERLAPPING`/`OVERLAPS`/`OVERLAPPABLE`/`INCOHERENT` pragmas, as these affect static semantics. * `RULES`, as these can affect dynamic semantics. Indeed, I'd be in favor of phasing out these pragmas in favor of other syntax. One could argue that `RULES` should be a pragma, because they shouldn't, if written correctly, affect runtime behavior. I would disagree with that argument, I think, but perhaps I'd be in the minority opinion. I know this is a larger discussion than on just this ticket, but I thought I'd mention this here to gauge response. If others like this idea at all, I'll post a fresh ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 14:18:40 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 14:18:40 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.b07fd2ff775dd1d4cf3e166e97a55e3b@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2280 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I don't really care what color we paint the bikeshed with, but I will caution that we're dealing with a perilous part of the parser here, and that cramming more syntax into `deriving` clauses might lead to more trouble than it's worth. The parser rule for `deriving` clauses is currently [http://git.haskell.org/ghc.git/blob/1e6701011425edb3553abc17c094a2a9faee4fd5:/compiler/parser/Parser.y#l1729 this]: {{{ deriv_types :: { [LHsSigType RdrName] } : typedoc { [mkLHsSigType $1] } | typedoc ',' deriv_types {% addAnnotation (gl $1) AnnComma (gl $2) >> return (mkLHsSigType $1 : $3) } }}} In other words, arbitrary types. This poses a problem for trying to introduce new syntax in front of a derived type, since: 1. Uppercase identifiers can be confused for type constructors 2. Lowercase identifiers can be confused for type variables To my knowledge, no one has proposed any alternatives to the suggested designs above, but if you do have a suggestion, please details how you would resolve this ambiguity. The pragma approach, while perhaps stretching the powers that most pragmas have, do not introduce any ambiguities into the parser. Also, I'm not sure why one pragmas wouldn't be amenable to "extend it with more flexibility in subsequent versions". In fact, that's precisely one of the reasons why I like pragmas, since it's cheap to add more of them in the future, and they're wildly configurable. In fact, later I hope to explore extending the GHC plugin mechanism to allow programmers to write their own deriving mechanisms, with something like: {{{#!hs data Foo = Foo Bar Baz deriving {-# CUSTOM myDeriv #-} C myDeriv :: SrcSpan -> TyCon -> TcM (LHsBinds RdrName, BagDerivStuff) myDeriv = ... }}} It would be dead simple to add this functionality via a pragma. With custom syntax, however, we'd have to reserve even more keywords... at least, I assume. I suppose I should ask: what exactly are folks proposing to use in place of pragmas? It's hard to have this discussion without something concrete to reference. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 17:03:48 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 17:03:48 -0000 Subject: [GHC] #11695: On GHCi prompt the arrow (movement) keys create strange character sequences In-Reply-To: <048.2c7ac4aadebf684928a9b23225097ed9@haskell.org> References: <048.2c7ac4aadebf684928a9b23225097ed9@haskell.org> Message-ID: <063.02e7557ce9c3f61266ed2adb3907cc26@haskell.org> #11695: On GHCi prompt the arrow (movement) keys create strange character sequences ---------------------------------+-------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: GHCi | Version: 8.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by heisenbug): Replying to [comment:9 judahj]: > Let's try this. Can you please download the file Read.hs from: > https://gist.github.com/judah/5c5ad518bb43d235efba4fa8f1e9953a > > And run (in the same terminal/environment that you have the ghci problem): > {{{ > ghc Read.hs > ./Read > }}} > > Then press some letter keys and some arrow keys, and let me know what the output is? > For example, on my terminal: > {{{ > $ ./Prompt > "a" > "s" > "d" > "\ESC[D" > "\ESC[B" > "\ESC[A" > }}} > The last three lines are from when I pressed arrow keys. Do you see them split into separate lines (e.g. "\ESC", "[" and "D")? If so, that's the problem we should try to solve. Does the same behavior of Read.hs occur on laptop<-vnc->hostA, or only on laptop<->hostA<->hostB? I see stuff like this: {{{ "\ESC[C" "\ESC[" "C" "\ESC[C" "\ESC[C" "\ESC[C" "\ESC[C" "\ESC[C\ESC[C" "\ESC[C" "\ESC[C" }}} Ha, this looks funny: {{{ "\ESC[B" "\ESC[B" "\ESC[B\ESC[B\ESC[B\ESC[B\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B\ESC[B\ESC[B" "\ESC[B" "\ESC[B\ESC[B" "\ESC[B\ESC[B" "\ESC[B" "\ESC[B" }}} Above sequences happen when via VNC. Let me test putty... ... completely dull. The strings look like this: {{{ "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" "\ESC[B" }}} Hope this helps!! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 17:41:42 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 17:41:42 -0000 Subject: [GHC] #11695: On GHCi prompt the arrow (movement) keys create strange character sequences In-Reply-To: <048.2c7ac4aadebf684928a9b23225097ed9@haskell.org> References: <048.2c7ac4aadebf684928a9b23225097ed9@haskell.org> Message-ID: <063.a8c26eb8a776327614d5b7cc38a1ac9b@haskell.org> #11695: On GHCi prompt the arrow (movement) keys create strange character sequences ---------------------------------+-------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: GHCi | Version: 8.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by heisenbug): Going via PC <-> VNC <-> hostA I sometimes see {{{ "\ESC[B" "\ESC[" "B" "\ESC[B" "\ESC" "[B" "\ESC[B" }}} The escape sequences seem to break up at strange places. Now the weird part. When going PC <-> hostA <-> hostB and opening an `xterm` there, and feeding `./Read` from there with keystrokes, I sometimes see duplicated escape sequences, but never the broken-up ones. Maybe this is just luck, but I really tried (even with considerable load on hostB). So maybe the X-Windows system is not the culprit at all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 18:33:30 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 18:33:30 -0000 Subject: [GHC] #8473: Generate table of cost-centre numbers with source locations In-Reply-To: <053.95380650abc814621da8b15bb4430f35@haskell.org> References: <053.95380650abc814621da8b15bb4430f35@haskell.org> Message-ID: <068.fc0da308bfb287329e9b3216289a803d@haskell.org> #8473: Generate table of cost-centre numbers with source locations -------------------------------------+------------------------------------- Reporter: lars_e_krueger | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #7105 | Differential Rev(s): Phab:D2282 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D2282 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 18:34:37 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 18:34:37 -0000 Subject: [GHC] #7105: Better names for derived SCCs of instances In-Reply-To: <042.2fbb06d1a4b326bebe4b64cda6396110@haskell.org> References: <042.2fbb06d1a4b326bebe4b64cda6396110@haskell.org> Message-ID: <057.db33972cb5b3fe870a95ffdb8aaab42a@haskell.org> #7105: Better names for derived SCCs of instances -------------------------------------+------------------------------------- Reporter: ksf | Owner: simonmar Type: feature request | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.4.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #11543 | Differential Rev(s): Phab:D2282 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * status: new => patch * differential: => Phab:D2282 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 18:35:00 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 18:35:00 -0000 Subject: [GHC] #11543: Profiling information ambiguous In-Reply-To: <047.f56e01bd6ad8bd0c84dfa18f1d7c5710@haskell.org> References: <047.f56e01bd6ad8bd0c84dfa18f1d7c5710@haskell.org> Message-ID: <062.08c6c4824aecd13d16c7c3923250e80c@haskell.org> #11543: Profiling information ambiguous -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Profiling | Version: 7.8.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #7105 | Differential Rev(s): Phab:D2282 Wiki Page: | -------------------------------------+------------------------------------- Changes (by osa1): * differential: => Phab:D2282 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 23:21:22 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 23:21:22 -0000 Subject: [GHC] #11094: Cost-center heap profiler should be able to emit samples to eventlog In-Reply-To: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> References: <046.5020b7d3a1ba23f2949a42c6789e9133@haskell.org> Message-ID: <061.be4fbff5d345dbc7a98484a0a5bedd7f@haskell.org> #11094: Cost-center heap profiler should be able to emit samples to eventlog -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: Profiling | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1722 Wiki Page: | -------------------------------------+------------------------------------- Changes (by maoe): * cc: maoe (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 23:46:49 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 23:46:49 -0000 Subject: [GHC] #10448: Implement rest of "Add bifunctor related classes to base"-Proposal In-Reply-To: <042.2a13dedaa488c75793ff62c67a501b4f@haskell.org> References: <042.2a13dedaa488c75793ff62c67a501b4f@haskell.org> Message-ID: <057.25ea02506437f2b2de52d63d499ebe95@haskell.org> #10448: Implement rest of "Add bifunctor related classes to base"-Proposal -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: task | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9682 | Differential Rev(s): Phab:D2284 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D2284 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon May 30 23:48:41 2016 From: ghc-devs at haskell.org (GHC) Date: Mon, 30 May 2016 23:48:41 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together In-Reply-To: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> References: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> Message-ID: <058.55c16d33f8b219c7edf557466c685aaa@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: RyanGlScott Type: bug | Status: patch Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D2280 Wiki Page: | -------------------------------------+------------------------------------- Comment (by oerjan): This may be off topic, but: Before the whole `OVERLAPPABLE` etc. stuff got included, I had somehow got the impression that pragmas were supposed to follow two simple principles, that improved portability between different compilers: * If a compiler does not understand a pragma other than a `LANGUAGE` pragma, it can safely ignore it, and if the program still compiles, its semantics must be the same. * If a compiler does not understand a `LANGUAGE` pragma, it should bail out with an error. The Haskell 2010 report seems to recommend this behavior, although it doesn't quite seem to require it. At some point things started to look inconsistent, so in a vain attempt to keep making sense of it I thought of an additional principle for added flexibility: * A `LANGUAGE` pragma might imply the existence of other pragmas, which must then also be understood. However, the `OVERLAPPABLE` etc. pragmas aren't as far as I know governed by any particular `LANGUAGE` pragma. Perhaps they still follow the first principle, I suspect there may be corner cases. Notably, I think the current Phab:D2280 implementation ''does'' obey the last principle. Any use of `DAC` or `GND` requires a corresponding language pragma, and `Builtin` never changes semantics. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 02:08:37 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 02:08:37 -0000 Subject: [GHC] #12136: SIGABRT on right-shift operation against long negative integer Message-ID: <046.ca96221614dc5a54b96ee86f683c2b18@haskell.org> #12136: SIGABRT on right-shift operation against long negative integer --------------------------------------+---------------------------------- Reporter: khibino | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.3 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: Runtime crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+---------------------------------- When the code like bellow is executed, the '''shiftR''' call causes SIGABRT. c128.hs {{{#!hs import Data.Bits x:: Integer x = 1 - (1 `shiftL` (128 + 64)) main :: IO () main = print $ x `shiftR` 128 }}} I make this report using examples in GHC 7.10.3, and I found the same problem in GHC 8.0.1 too. backtrace using GDB {{{ % ghc -O0 c128.hs [1 of 1] Compiling Main ( c128.hs, c128.o ) Linking c128 ... % gdb ./c128 GNU gdb (Debian 7.10-1+b1) 7.10 ... Reading symbols from ./c128...(no debugging symbols found)...done. (gdb) run Starting program: /home/hibi/src/haskell/crash/Haskell/c128 [Thread debugging using libthread_db enabled] Using host libthread_db library "/lib/x86_64-linux-gnu/libthread_db.so.1". Program received signal SIGABRT, Aborted. 0x00007ffff6ed4478 in __GI_raise (sig=sig at entry=6) at ../sysdeps/unix/sysv/linux/raise.c:55 55 ../sysdeps/unix/sysv/linux/raise.c: ??????????????? ???????. (gdb) bt #0 0x00007ffff6ed4478 in __GI_raise (sig=sig at entry=6) at ../sysdeps/unix/sysv/linux/raise.c:55 #1 0x00007ffff6ed58fa in __GI_abort () at abort.c:89 #2 0x00000000004716df in integer_gmp_mpn_rshift_2c () #3 0x000000000046e004 in salz_info () #4 0x0000000000000000 in ?? () (gdb) frame 2 #2 0x00000000004716df in integer_gmp_mpn_rshift_2c () (gdb) disas Dump of assembler code for function integer_gmp_mpn_rshift_2c: 0x0000000000471630 <+0>: push %r13 ... 0x00000000004716d8 <+168>: jne 0x4716c0 0x00000000004716da <+170>: callq 0x402c80 => 0x00000000004716df <+175>: nop 0x00000000004716e0 <+176>: lea 0x0(,%rdx,8),%rdx ... End of assembler dump. (gdb) }}} I found '''abort''' call in '''integer_gmp_mpn_rshift_2c'''. ghc-7.10.3/libraries/integer-gmp2/cbits/wrappers.c {{{#!c mp_limb_t integer_gmp_mpn_rshift_2c (mp_limb_t rp[], const mp_limb_t sp[], const mp_size_t sn, const mp_bitcnt_t count) { ... // round if non-zero bits were shifted out if (nz_shift_out) if (mpn_add_1(rp, rp, rn, 1)) abort(); /* should never happen */ return rp[rn-1]; } }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 12:36:30 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 12:36:30 -0000 Subject: =?utf-8?q?=5BGHC=5D_=2312137=3A_Warning_about_=E2=80=9CINLINE_bi?= =?utf-8?q?nder_is_=28non-rule=29_loop_breaker=E2=80=9D_with_=60-?= =?utf-8?q?dcore-lint=60?= Message-ID: <051.4a9a2dbe0c20bdb18f0b6695483f466f@haskell.org> #12137: Warning about ?INLINE binder is (non-rule) loop breaker? with `-dcore-lint` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With this code using `lens` {{{#!hs {-# Language TemplateHaskell #-} import Control.Lens data Config = Config { _companyName :: String } data AppState = AppState { _asConfig :: Config } makeClassy ''Config instance HasConfig AppState where config = undefined }}} gives {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP Ok, modules loaded: Main. *Main> }}} ---- `makeClass` actually dumps {{{ :64:54-72: Splicing declarations makeClassy ''Config ======> class HasConfig c_axo7 where config :: Lens' c_axo7 Config companyName :: Lens' c_axo7 String {-# INLINE companyName #-} companyName = (.) config companyName instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = iso (\ (Config x_axo8) -> x_axo8) Config }}} Using that to create a small example ---- {{{#!hs data Config = Config { name :: String } class HasConfig a where config :: a -> Config companyName :: a -> String {-# INLINE companyName #-} companyName a = name (config a) instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = name . config }}} which works perfectly fine without `-dcore-lint` but fails with {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q Ok, modules loaded: Main. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 12:37:26 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 12:37:26 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMjEzNzogV2FybmluZyBhYm91dCDigJxJTkxJ?= =?utf-8?q?NE_binder_is_=28non-rule=29_loop_breaker=E2=80=9D_with?= =?utf-8?q?_=60-dcore-lint=60?= In-Reply-To: <051.4a9a2dbe0c20bdb18f0b6695483f466f@haskell.org> References: <051.4a9a2dbe0c20bdb18f0b6695483f466f@haskell.org> Message-ID: <066.129a4e7c552f019fe139174130311ac0@haskell.org> #12137: Warning about ?INLINE binder is (non-rule) loop breaker? with `-dcore-lint` -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -1,1 +1,1 @@ - With this code using `lens` + Using `lens` @@ -74,1 +74,1 @@ - which works perfectly fine without `-dcore-lint` but fails with + which works perfectly fine without `-dcore-lint` but gives a warning with New description: Using `lens` {{{#!hs {-# Language TemplateHaskell #-} import Control.Lens data Config = Config { _companyName :: String } data AppState = AppState { _asConfig :: Config } makeClassy ''Config instance HasConfig AppState where config = undefined }}} gives {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:10:10: warning: [RHS of $ccompanyName_a7EP :: Lens' AppState String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a7EP Ok, modules loaded: Main. *Main> }}} ---- `makeClass` actually dumps {{{ :64:54-72: Splicing declarations makeClassy ''Config ======> class HasConfig c_axo7 where config :: Lens' c_axo7 Config companyName :: Lens' c_axo7 String {-# INLINE companyName #-} companyName = (.) config companyName instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = iso (\ (Config x_axo8) -> x_axo8) Config }}} Using that to create a small example ---- {{{#!hs data Config = Config { name :: String } class HasConfig a where config :: a -> Config companyName :: a -> String {-# INLINE companyName #-} companyName a = name (config a) instance HasConfig Config where {-# INLINE companyName #-} config = id companyName = name . config }}} which works perfectly fine without `-dcore-lint` but gives a warning with {{{ $ ghci -ignore-dot-ghci -dcore-lint /tmp/tvQq.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tvQq.hs, interpreted ) *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q *** Core Lint warnings : in result of Simplifier *** /tmp/tvQq.hs:11:3: warning: [RHS of $ccompanyName_a18Q :: Config -> String] INLINE binder is (non-rule) loop breaker: $ccompanyName_a18Q Ok, modules loaded: Main. }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 17:30:13 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 17:30:13 -0000 Subject: [GHC] #8095: TypeFamilies painfully slow In-Reply-To: <050.29bdc4d704aaf05e461a59330593e649@haskell.org> References: <050.29bdc4d704aaf05e461a59330593e649@haskell.org> Message-ID: <065.1602bf437b2f199318619a2a2f953644@haskell.org> #8095: TypeFamilies painfully slow -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 7.6.3 checker) | Resolution: | Keywords: TypeFamilies Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: 5321, #11598 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 17:30:29 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 17:30:29 -0000 Subject: [GHC] #11598: Cache coercion kinds and roles In-Reply-To: <047.56bbfff0d86db02c37b25ddc698d48a1@haskell.org> References: <047.56bbfff0d86db02c37b25ddc698d48a1@haskell.org> Message-ID: <062.de8a4acb8bfb6c705437af8ac8f7fc9c@haskell.org> #11598: Cache coercion kinds and roles -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: 8.2.1 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: #8095 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 17:44:35 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 17:44:35 -0000 Subject: [GHC] #12014: Make it possible to deprecate a method instantiation of a typeclass instance In-Reply-To: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> References: <046.a08943e3ed72d4b9657cf861b924653f@haskell.org> Message-ID: <061.564928deb8c7543f401c98af247d9d95@haskell.org> #12014: Make it possible to deprecate a method instantiation of a typeclass instance -------------------------------------+------------------------------------- Reporter: niteria | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by DanielDiaz): * cc: DanielDiaz (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 18:54:53 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 18:54:53 -0000 Subject: [GHC] #12138: Simplifier ticks exhausted at compiling svg-builder Message-ID: <048.fa1817cfd86227c5c1a3b631576bd10e@haskell.org> #12138: Simplifier ticks exhausted at compiling svg-builder -------------------------------------+------------------------------------- Reporter: JanUlrich | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.8.4-rc1 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: -------------------------------------+------------------------------------- I tried to install svg-builder by "cabal install svg-builder"and got the following error: Resolving dependencies... Configuring svg-builder-0.1.0.1... Building svg-builder-0.1.0.1... Preprocessing library svg-builder-0.1.0.1... [1 of 5] Compiling Graphics.Svg.Path ( src/Graphics/Svg/Path.hs, dist/build/Graphics/Svg/Path.o ) [2 of 5] Compiling Graphics.Svg.Core ( src/Graphics/Svg/Core.hs, dist/build/Graphics/Svg/Core.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.8.4 for x86_64-unknown-linux): Simplifier ticks exhausted When trying UnfoldingDone base:Foreign.Storable.$fStorableWord21{v r2cT} [gid] 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: 34200 I tried again with ghc -fsimpl-tick-factor=300 and it worked. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 21:41:11 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 21:41:11 -0000 Subject: [GHC] #11832: Allow reify to yield types in the current declaration group In-Reply-To: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> References: <056.c55a5c5fc06f6b4965766fc5bf61b445@haskell.org> Message-ID: <071.007eadffee483dcfc56bb9722778113b@haskell.org> #11832: Allow reify to yield types in the current declaration group -------------------------------------+------------------------------------- Reporter: | Owner: facundo.dominguez | facundo.dominguez Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.3 Resolution: | Keywords: reify Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | TemplateHaskell/Reify | -------------------------------------+------------------------------------- Changes (by facundo.dominguez): * owner: => facundo.dominguez -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue May 31 22:10:19 2016 From: ghc-devs at haskell.org (GHC) Date: Tue, 31 May 2016 22:10:19 -0000 Subject: [GHC] #12133: ConstraintKinds inference failure (regression from 7.10) In-Reply-To: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> References: <047.c733b50527f5eb857c28d94b329c6c5a@haskell.org> Message-ID: <062.88ebec16fb33ca5488130c0d7d83447b@haskell.org> #12133: ConstraintKinds inference failure (regression from 7.10) ---------------------------------+---------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+---------------------------------------- Changes (by j6carey): * os: Unknown/Multiple => Linux -- Ticket URL: GHC The Glasgow Haskell Compiler