From ghc-devs at haskell.org Wed Jul 1 02:02:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 02:02:08 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.7c538e4de2855f0a6608c01cf0bfd673@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by michaelt): And a bit more compressed, for what it may be worth: {{{#!hs {-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.Exts newtype Eval a = Eval {runEval :: State# RealWorld -> (# State# RealWorld, a #)} -- inline sequence :: [Eval a] -> Eval [a] well_sequenced :: [Eval a] -> Eval [a] well_sequenced = foldr op (Eval $ \s -> (# s, [] #)) where op e es = Eval $ \s -> case runEval e s of (# s', a #) -> case runEval es s' of (# s'', as #) -> (# s'', a : as #) -- seemingly demonic use of spark# ill_sequenced :: [Eval a] -> Eval [a] ill_sequenced as = Eval $ spark# (case well_sequenced as of Eval f -> case f realWorld# of (# _, a' #) -> a') main :: IO () main = print ((layer . layer . layer . layer . layer) show 'y') where layer :: (Char -> String) -> (Char -> String) layer f = (\(Eval x) -> case x realWorld# of (# _, as #) -> concat as) . well_sequenced . map ill_sequenced . map (map (\x -> Eval $ \s -> (# s, x #))) . chunk' . concatMap f . show }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 04:01:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 04:01:14 -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.f2770ba1d2ed94fdcd76880d46a382e6@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1016 -------------------------------------+------------------------------------- Comment (by osa1): Simon, how does this look: I have this program: {{{ module Main where type T5 = T4 type T4 = T3 type T3 = T2 type T2 = T1 type T1 = Int type T a = Int -> Bool -> a -> String f :: T (T3, T5, Int) -> Int f = undefined a :: Int a = f (undefined :: T (T5, T3, Bool)) main = print a }}} and this is the error message: {{{ ? t10547 ghc-stage1 Main.hs -fprint-expanded-synonyms [1 of 1] Compiling Main ( Main.hs, Main.o ) Main.hs:15:8: error: Couldn't match type ?Int? with ?Bool? Expected type: T (T3, T5, Int) Actual type: T (T5, T3, Bool) Type synonyms expanded: Expected type: T (T3, T3, Int) Actual type: T (T3, T3, Bool) In the first argument of ?f?, namely ?(undefined :: T (T5, T3, Bool))? In the expression: f (undefined :: T (T5, T3, Bool)) In an equation for ?a?: a = f (undefined :: T (T5, T3, Bool)) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 05:14:21 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 05:14:21 -0000 Subject: [GHC] #10592: Allow cycles in class declarations Message-ID: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: | Owner: MikeIzbicki | Status: new Type: feature | Milestone: request | Version: 7.10.1 Priority: normal | Operating System: Unknown/Multiple Component: Compiler | Type of failure: None/Unknown (Type checker) | Blocked By: Keywords: | Related Tickets: Architecture: | Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- In particular, I would like to have a class hierarchy that looks like: {{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} type family Scalar x class Field (Scalar x) => Vector x class Vector x => Field x }}} It is the case that every field is a vector, and the scalar associated with every vector is a field. But we can't currently enforce that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 05:35:24 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 05:35:24 -0000 Subject: [GHC] #3541: Allow local foreign imports In-Reply-To: <044.f182d5c0327086f8b5193630cf333bb0@haskell.org> References: <044.f182d5c0327086f8b5193630cf333bb0@haskell.org> Message-ID: <059.2d2901645f5752ae3cbd8d0cc2ceac6b@haskell.org> #3541: Allow local foreign imports -------------------------------------+------------------------------------- Reporter: mokus | Owner: Type: feature request | DevarshDesai Priority: normal | Status: new Component: Compiler (FFI) | Milestone: ? Resolution: | Version: 6.12.2 Operating System: Unknown/Multiple | Keywords: newcomer Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by DevarshDesai): * owner: => DevarshDesai * version: 6.10.4 => 6.12.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 05:41:18 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 05:41:18 -0000 Subject: [GHC] #3490: Relax superclass restrictions In-Reply-To: <046.d4ecd3a8759936af7853c82b7c4c099e@haskell.org> References: <046.d4ecd3a8759936af7853c82b7c4c099e@haskell.org> Message-ID: <061.450be0ec6133201394639f33ac6c0cf4@haskell.org> #3490: Relax superclass restrictions -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: feature request | DevarshDesai Priority: normal | Status: new Component: Compiler | Milestone: ? Resolution: | Version: 6.10.4 Operating System: Unknown/Multiple | Keywords: Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by DevarshDesai): * owner: => DevarshDesai * failure: => None/Unknown -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 07:04:58 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 07:04:58 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.2fd0b4437b821efc97783c61891117c7@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by Rydgel): I really think we might have 2 bugs here, 1 in GHC and 1 in Cabal. Can this Cabal bug be related to our problems? https://github.com/haskell/cabal/issues/2689 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 07:13:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 07:13:08 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.69491b05e0f41cd9182b75cd42715334@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) Comment: Somewhat surprisingly, this appears to be a valid workaround: {{{ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE UndecidableInstances #-} type family Scalar x type family FieldScalar x where FieldScalar x = Field (Scalar x) class FieldScalar x => Vector x class Vector x => Field x }}} I suspect the `"Cycle in class declaration (via superclasses)"` error is a little bit too conservative. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 07:51:43 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 07:51:43 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.69083be8e680083315219cde396f3a5e@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): Thanks! That workaround solves my immediate problem :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 08:27:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 08:27:32 -0000 Subject: [GHC] #10593: compilation failure on OpenBSD Message-ID: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> #10593: compilation failure on OpenBSD -------------------------------------+------------------------------------- Reporter: kgardas | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Runtime | Version: 7.11 System | Operating System: OpenBSD Keywords: | Type of failure: Building GHC Architecture: x86_64 | failed (amd64) | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- GHC HEAD as of June 30 2015 fails to compile on OpenBSD 5.7/5.8-beta with following error (I've cut off all warnings there): {{{ "inplace/bin/ghc-stage1" -optc-fno-stack-protector -optc-Wall -optc-Wall -optc-Wextra -optc-Wstrict-prototypes -optc-Wmissing-prototypes -optc- Wmissing-declarations -optc-Winline -optc-Waggregate -return -optc-Wpointer-arith -optc-Wmissing-noreturn -optc-Wnested-externs -optc-Wredundant-decls -optc-Iincludes -optc-Iincludes/dist -optc- Iincludes/dist-derivedconstants/header -optc-Iincludes /dist-ghcconstants/header -optc-Irts -optc-Irts/dist/build -optc- DCOMPILING_RTS -optc-fno-strict-aliasing -optc-fno-common -optc- Irts/dist/build/autogen -optc-O2 -optc-fomit-frame-pointer -optc-g -optc-DRtsWay=\"rts_v\" -static -H64m -O0 -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header -Iincludes/dist- ghcconstants/header -Irts -Irts/dist/build -DCOMPILING_RTS -this-pa ckage-key rts -dcmm-lint -i -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build -Irts/dist/build/autogen -O2 -c rts/Linker.c -o rts/dist/build/Linker.o In file included from rts/Linker.c:92:0: error: [...] rts/Linker.c: In function 'getSectionKind_ELF': rts/Linker.c:5308:0: error: error: 'SHT_INIT_ARRAY' undeclared (first use in this function) rts/Linker.c:5308:0: error: error: (Each undeclared identifier is reported only once rts/Linker.c:5308:0: error: error: for each function it appears in.) rts/ghc.mk:243: recipe for target 'rts/dist/build/Linker.o' failed gmake[1]: *** [rts/dist/build/Linker.o] Error 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 08:32:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 08:32:40 -0000 Subject: [GHC] #10593: compilation failure on OpenBSD In-Reply-To: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> References: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> Message-ID: <061.4589923826929ed3249cfe08a3be873e@haskell.org> #10593: compilation failure on OpenBSD -------------------------------------+------------------------------------- Reporter: kgardas | Owner: simonmar Type: bug | Status: patch Priority: normal | Milestone: Component: Runtime System | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kgardas): * status: new => patch Comment: Fixed in Phab:D1023 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 10:21:06 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 10:21:06 -0000 Subject: [GHC] #10565: GHC 7.10.2 RC: the impossible happened on hPDB-examples-1.2.0.2 In-Reply-To: <047.3ffddb89eb8d6f97040b05fb569a18d7@haskell.org> References: <047.3ffddb89eb8d6f97040b05fb569a18d7@haskell.org> Message-ID: <062.4248dc18f5ac61ad430c2d768d0759a9@haskell.org> #10565: GHC 7.10.2 RC: the impossible happened on hPDB-examples-1.2.0.2 ---------------------------------+----------------------------------------- Reporter: snoyberg | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by bgamari): * owner: => bgamari Comment: Thankfully this doesn't appear to be related to #10527 (which is quite a hard nut to crack). Instead this is due to the fact that `guessElement` is marked `INLINE`. To see why this is problematic, we have to look at how this function is desugared. The pattern match is using `OverloadedStrings`, which desugars this, {{{#!hs f :: ByteString -> String f "foo" = 1 f "bar" = 2 f _ = 3 }}} Roughly into this, {{{#!hs f :: ByteString -> String f x | x == (fromString "foo" :: ByteString) = 1 f x | x == (fromString "bar" :: ByteString) = 2 f _ = 3 }}} Note that we are using using `ByteString`'s `Eq` instance here to check the pattern match. These guards are then desugared to nested `case` analyses in the desugared Core. It is with this Core that we enter the Core-to-Core optimization pipeline. `ByteString`'s `Eq` instance looks like this, {{{#!hs instance Eq ByteString where (==) = eq eq :: ByteString -> ByteString -> Bool eq a@(PS fp off len) b@(PS fp' off' len') | len /= len' = False -- short cut on length | fp == fp' && off == off' = True -- short cut for the same string | otherwise = compareBytes a b == EQ {-# INLINE eq #-} compareBytes :: ByteString -> ByteString -> Ordering compareBytes = ... }}} Despite `(==)` not having an explicit `INLINE` pragma, GHC is still quite eager to inline in. Consequently our chain of equality comparisons in `f` quickly explodes into a large ball of `IO` To make matters a bit worse, the literal of each alternative is itself a fair amount of code. e.g. the `"OG1"` literal is floated out into a top- level binding looking like this, {{{#!hs lvl10_r5ix :: BS.ByteString [GblId, Str=DmdType] lvl10_r5ix = case newMutVar# @ Finalizers @ RealWorld NoFinalizers realWorld# of _ [Occ=Dead] { (# ipv_a3qk, ipv1_a3ql #) -> let { s_a263 :: Addr# [LclId, Str=DmdType] s_a263 = "OG1"# } in case {__pkg_ccall bytestring-0.10.6.0 strlen Addr# -> State# RealWorld -> (# State# RealWorld, Word# #)}_a3rx s_a263 ipv_a3qk of _ [Occ=Dead] { (# ds3_a3rC, ds4_a3rD #) -> Data.ByteString.Internal.PS s_a263 (PlainForeignPtr ipv1_a3ql) 0# (word2Int# ds4_a3rD) } } }}} == Resolution == Above we saw that the original code has a few issues, 1. `ByteString`'s sizeable `(==)` implementation is inlined once for each alternative, resulting in a large quantity of code for `f` 2. The pattern match desugars to a linear search where some more efficient strategy would be desired Let's first look at how we might fix (1), which causes the simplifier blow-up noted in this bug. After this we can move on to improving the asymptotic issue, (2). **Note**: To some extent, the pattern matching behavior exposed by `OverloadedStrings` is a bit dangerous as it emulates pattern matching, something that most Haskellers regard as "cheap" (up to the cost of forcing the scrutinee), with a call to an arbitrarily complex function. Issue (1) arises from the desugaring of the `OverloadedStrings` pattern match, which produces a new test for every alternative. GHC will then happily inline `(==)` in to each of these despite the fact that there is no benefit to doing so. Ideally we would want to make it obvious to GHC that the comparison should be shared. One way to accomplish this would be to encode the alternatives as an associated list and use `lookup`, {{{#!hs guessElement :: BS.ByteString -> String guessElement = \e -> fromMaybe "" $ lookup e els where els :: [(ByteString, String)] els = [ ("C" , "C"), ("C1'" , "C"), ("C2" , "C"), ... ] }}} Here we ensure that there is exactly one use of `(==)`, preventing the explosion of code. While we are looking at optimizations we might also consider that `ByteString` is generally best used with large strings. In the case of small comparisons like this it might be worthwhile to avoid using `ByteString`'s `Eq` altogether and instead compare `String`s, {{{#!hs guessElement :: BS.ByteString -> String guessElement = \e -> fromMaybe "" $ lookup (BS.unpack e) els where els :: [(String, String)] els = [ ... ] }}} However, both of these avoid solving the issue of linear search. For this we can turn to any number of finite map data structures. For instance, we know that `ByteString` has an `Ord` instance so we can employ `Data.Map` from `containers`, {{{#!hs guessElement :: BS.ByteString -> String guessElement = \e -> fromMaybe "" $ M.lookup e els where els :: M.Map BS.ByteString String els = M.fromList [ ... ] }}} Of course, it also has a `Hashable` instance so we can also try `Data.HashMap` from `unordered-containers`. I've prepared a small benchmark (https://github.com/bgamari/ghc-T10565) comparing these options. The results from a run on my Core i5 laptop can be found below. ||= **Implementation** =||||= **Time per iteration (?s)** =|| || Original pattern match || 21.2 || ? 1.9 || |||||| ''Association list'' || || `lookup` on `ByteString` || 42.1 || ? 2.0 || || `lookup` on `String` || 38.9 || ? 1.8 || |||||| ''Ordered map'' || || `lookup` on `ByteString` || 6.6 || ? 0.5 || || `lookup` on `String` || 8.5 || ? 0.4 || |||||| ''Unordered map'' || || `lookup` on `ByteString` || 4.1 || ? 0.1 || || `lookup` on `String` || 4.3 || ? 0.5 || == Improving GHC? == In an ideal world GHC would be able to look at the original code and independently determine something like we determined above. The key insight that we had here is that our `ByteString` type has structure beyond the `Eq` used by `OverloadedString`'s pattern matching behavior. Can we teach GHC to have this same insight? It would be possible for the compiler to construct a similar lookup data structure for pattern matches on `IsString` types also having an `Ord` instance. The trouble with this is that the operational behavior of the program is now dependent upon which instances are in scope. This seems like a very undesirable property. One could instead add a `compare' :: a -> a -> Ordering` to `IsString`, allowing GHC to generate efficient logarithmic lookups without a dependence on which instances are available. The above option, however, prevents us from using the best tool in our arsenault, the `HashMap`. Another more general possibility would be to add function to `IsString` to explicitly handle matching against groups of patterns. The compiler would collect the pattern matches which can be simultaneously resolved and pass them, along with the scrutinee, to a `match` function. This might look like this, {{{#!hs class IsString a where fromString :: String -> a toString :: a -> String match :: [(a, b)] -> a -> b }}} This, however, carries with it a number of issues. Perhaps most concerning is the fact that now a library author has the ability to break pattern matching semantics (consider, for instance, `match alts _ = last alts`). Moreover, all of these have unfortunate compatibility issues. Finally, these options all interact very poorly with more complex pattern matches. Take for instance, {{{#!hs f :: String -> Int -> Result f "a" _ = resultA f "b" _ = resultB f _ 3 = resultC f "c" _ = resultD f "d" 4 = resultE f "d" _ = resultF f _ _ = resultG }}} It would be rather difficult to define matching semantics which took advantage of the above `match` function yet treated cases like the above (or even simpler cases). Consequently, in many cases the user would still need to fall back to the current approach of manually implementing their desired match behavior. Ultimately, these are decisions that should arguably be left to the user anyways. Data structure choice will be highly specific to the structure of the alternatives and values being scrutinized. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 11:00:12 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 11:00:12 -0000 Subject: [GHC] #10587: Suspending and unsuspending ghci kills and spawns threads In-Reply-To: <046.86d123f20d63f11aba21b5ddb030dffb@haskell.org> References: <046.86d123f20d63f11aba21b5ddb030dffb@haskell.org> Message-ID: <061.0d8c3c46f00e7ccfa5d710744f92b147@haskell.org> #10587: Suspending and unsuspending ghci kills and spawns threads ---------------------------------+----------------------------------------- Reporter: niteria | Owner: niteria Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by niteria): * cc: AndreasVoellmy (added) Comment: {{{ ./inplace/bin/ghc-stage2 --interactive -j8 +RTS -Ds 7f0d94ff9700: returning; I want capability 0 7f0d94ff9700: resuming capability 0 7f0d94ff9700: cap 0: running thread 12 (ThreadRunGHC) 7f0d967fc700: returning; I want capability 0 7f0dd91ff700: returning; I want capability 0 7f0dd3fff700: returning; I want capability 0 7f0d957fa700: returning; I want capability 0 7f0d96ffd700: returning; I want capability 0 7f0d73fff700: returning; I want capability 0 7f0d95ffb700: returning; I want capability 0 7f0d94ff9700: cap 0: thread 12 stopped (yielding) 7f0d94ff9700: giving up capability 0 7f0d94ff9700: passing capability 0 to worker 0x7f0d967fc700 7f0d967fc700: resuming capability 0 7f0d967fc700: cap 0: running thread 16 (ThreadRunGHC) 7f0d967fc700: cap 0: thread 16 stopped (yielding) 7f0d967fc700: giving up capability 0 7f0d967fc700: passing capability 0 to worker 0x7f0dd91ff700 7f0dd91ff700: resuming capability 0 7f0dd91ff700: cap 0: running thread 2 (ThreadRunGHC) 7f0dd91ff700: cap 0: thread 2 stopped (yielding) 7f0dd91ff700: giving up capability 0 7f0dd91ff700: passing capability 0 to worker 0x7f0dd3fff700 7f0dd3fff700: resuming capability 0 7f0dd3fff700: cap 0: running thread 15 (ThreadRunGHC) 7f0dd3fff700: cap 0: thread 15 stopped (yielding) 7f0dd3fff700: giving up capability 0 7f0dd3fff700: passing capability 0 to worker 0x7f0d957fa700 7f0d957fa700: resuming capability 0 7f0d957fa700: cap 0: running thread 14 (ThreadRunGHC) 7f0d957fa700: cap 0: thread 14 stopped (yielding) 7f0d957fa700: giving up capability 0 7f0d957fa700: passing capability 0 to worker 0x7f0d96ffd700 7f0d96ffd700: resuming capability 0 7f0d96ffd700: cap 0: running thread 18 (ThreadRunGHC) 7f0d96ffd700: cap 0: thread 18 stopped (yielding) 7f0d96ffd700: giving up capability 0 7f0d96ffd700: 6 spare workers already, exiting 7f0d96ffd700: passing capability 0 to worker 0x7f0d73fff700 shutdownThread 0x33b047 7f0d73fff700: resuming capability 0 7f0d73fff700: cap 0: running thread 13 (ThreadRunGHC) 7f0d73fff700: cap 0: thread 13 stopped (yielding) 7f0d73fff700: giving up capability 0 7f0d73fff700: 6 spare workers already, exiting 7f0d73fff700: passing capability 0 to worker 0x7f0d95ffb700 shutdownThread 0x33b04c }}} After receiving SIGCONT, all the threads (including IO manager threads, that were waiting on epoll_wait) wake up and try to get capability 0. They eventually succeed and get put on the spare workers queue for this capability. The current limit on the the number of spare workers per capability is 6, so the remaining 2 threads get shut down. Why do we have so many threads? When compiling things in parallel we first increase the number of capabilities (to 8) and then we restore it (to 1). https://phabricator.haskell.org/diffusion/GHC/browse/master/compiler/main/GhcMake.hs;daa5097facb228307d52e5d3e789e5c81494a475$751 This increases the number of IO manager threads to 8. IO manager doesn't decrease the number of threads when the number of capabilities decreases, so we keep those threads forever. https://phabricator.haskell.org/diffusion/GHC/browse/master/libraries/base/GHC/Event/Thread.hs;daa5097facb228307d52e5d3e789e5c81494a475$325-326 I believe the fix is to decrease the number of IO manager threads when number of capabilities decreases. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 11:38:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 11:38:14 -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.2d80099aabcb9c1e2b62841cd246c615@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1016 -------------------------------------+------------------------------------- Comment (by simonpj): Looks good! Did you take the approach I sketched? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 12:33:47 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 12:33:47 -0000 Subject: [GHC] #10565: GHC 7.10.2 RC: the impossible happened on hPDB-examples-1.2.0.2 In-Reply-To: <047.3ffddb89eb8d6f97040b05fb569a18d7@haskell.org> References: <047.3ffddb89eb8d6f97040b05fb569a18d7@haskell.org> Message-ID: <062.f51856292b06e2ed1635285d97cdba5f@haskell.org> #10565: GHC 7.10.2 RC: the impossible happened on hPDB-examples-1.2.0.2 ---------------------------------+----------------------------------------- Reporter: snoyberg | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by bgamari): I should note that the original testcase (found here https://github.com/bgamari/ghc-T10565/blob/master/Rg.hs) compiles with 7.10.1 yet not with 7.10.2. It does, however, compile with 7.10.2 if one uses a more reasonable implementation of `guessElement`. It is do wonder what changed between 7.10.1 and 7.10.2, however. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 13:42:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 13:42: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.8867d19d08c88d6920516b31a417fad4@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1016 -------------------------------------+------------------------------------- Comment (by osa1): I did something a little more fancy and inefficient :) I updated my patch: https://phabricator.haskell.org/D1016 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 14:39:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 14:39:32 -0000 Subject: [GHC] #10575: "unsatisfied constraints" typo In-Reply-To: <045.95237d2ec1c60db7ff6ad28f67a1da5f@haskell.org> References: <045.95237d2ec1c60db7ff6ad28f67a1da5f@haskell.org> Message-ID: <060.81a8e702e1676ab5e457a5fe18328b11@haskell.org> #10575: "unsatisfied constraints" typo -------------------------------------+------------------------------------- Reporter: ekmett | Owner: ekmett Type: bug | Status: merge Priority: low | Milestone: 7.10.2 Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => merge * milestone: => 7.10.2 Comment: Fixed in 49d99ebf6e341e26caf1d3db794cb6fa06ee72f6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 14:44:57 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 14:44:57 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.0b25c7ed5756b620306e93fb0ce35c07@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Edsko and I were thinking about this a bit in light of the recent discussion on Reddit. He had what I thought was a rather nice idea: Putting aside the specific proposal made in this ticket, it seems like generally what we need is a more semantically-rich representation for our error messages. This need not be a giant AST encoding every possible error that might arise. Our current approach of encoding messages in `SDoc` works fairly well. What it lacks is the ability to denote meaningful references to various parts of the program (e.g. types, expressions, constraints). A moderately painless(?) way to fix this would be to index `Doc` (and `SDoc`) on a type which could then be embedded in the document. To put it concretely, {{{#!hs data Doc a = Embed a | Empty | NilAbove Doc . . . }}} The `Embed` constructor could then be used to embed various compiler-phase specific atoms into the document. For instance, the type-checker might emit errors in the form of `SDoc TcDoc` where, {{{#!hs data TcDoc = TcExprDoc CoreExpr | TypeDoc TcType | InstancesDoc ClsInstLookupResult . . . }}} Consumers of error messages could then use these annotations as they like. Most of the existing consumers would likely expose a function which would take a function to project the phase-specific data back to a plain `SDoc`. For instance, {{{#!hs showSDoc' :: DynFlags -> (a -> SDoc ()) -> SDoc a -> String }}} and we could avoid breaking existing users of `showSDoc` by defining it as, {{{#!hs showSDoc :: Outputable a => DynFlags -> SDoc a -> String showSDoc dflags = showSDoc' dflags ppr }}} Other uses (say, tooling using the GHC API) might choose to instead use a richer presentation of the data embedded in the document. These users will still be limited by the fact that the error representation is still ultimately a pretty-printer document, but at least now we can avoid parsing text. Moreover, we might be able to expose more context in this embedded data than we show in the current messages. One of the nice properties of this approach is that it allows a somewhat gradual transition. Adding the infrastructure to enable this sort of embedded doesn't requires only minor changes to existing code (e.g. adding the index to `SDoc`). Moreover, I have a sneaking suspicion that it would allow us to clean up the handling of `Name`s in `Outputable`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 14:47:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 14:47:40 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.8eb846f45c5a0835cf65e7800c2b0268@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 15:22:28 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 15:22:28 -0000 Subject: [GHC] #8222: CTYPE pragma on newtype is ignored In-Reply-To: <043.24c148c2b068a302763a274e94396a01@haskell.org> References: <043.24c148c2b068a302763a274e94396a01@haskell.org> Message-ID: <058.960cb08fe16c720112090346fc0af22f@haskell.org> #8222: CTYPE pragma on newtype is ignored -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: worksforme | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | patsyn/should_compile/T9857 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * testcase: => patsyn/should_compile/T9857 * resolution: => worksforme Comment: testsuite/tests/patsyn/should_compile/T9857.hs uses a CTYPE pragma on a newtype: `newtype {-# CTYPE "unsigned short" #-} Half = ...` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 15:32:39 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 15:32:39 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.81a37f0d994e6f68303d7d760de34ff3@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): It's [https://www.reddit.com/r/haskell/comments/3bnpa7/compiler_errors_for_humans/ come to my attention] that my comment:2 may have shut down the conversation here. That was the opposite of my intent! I'd love to figure out how to break down the problem of difficult-to-work-with error messages into its pieces so that we can debate them (and hopefully implement improvements) sensibly. I should also be clear on one particular point: the biggest barrier to getting this done is the love from someone(s) to see it all through. This would be a valuable service, indeed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 15:51:04 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 15:51:04 -0000 Subject: [GHC] #9348: "Symbol not found" when using a shared library In-Reply-To: <049.505411c990d6efe7c6bbe51db4210fb4@haskell.org> References: <049.505411c990d6efe7c6bbe51db4210fb4@haskell.org> Message-ID: <064.dd37425087639e2f1718f295f24fe51a@haskell.org> #9348: "Symbol not found" when using a shared library -------------------------------------+----------------------------------- Reporter: alex.davis | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+----------------------------------- Changes (by thomie): * cc: simonmar (removed) * os: MacOS X => Unknown/Multiple * component: Runtime System => Documentation Comment: Replying to [comment:3 alex.davis]: > This represents a mismatch between the behavior of the compiler and its documentation. People looking to make shared libraries will read [https://www.haskell.org/ghc/docs/latest/html/users_guide/using-shared- libs.html#idp12506320 section 4.13.3 of the GHC user's guide]. They will see "To build Haskell modules that export a C API into a shared library use the -dynamic, -fPIC and -shared flag". No mention of linking the runtime system. The next sentence does say: "As before, the -dynamic flag specifies that this library links against the shared library versions of the rts and base package." And after that: "In principle you can use -shared without -dynamic in the link step. That means to statically link the rts all the base libraries into your new shared library. This would make a very big, but standalone shared library. On most platforms however that would require all the static libraries to have been built with -fPIC so that the code is suitable to include into a shared library and we do not do that at the moment." Improvements to the documentation are always welcome. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 16:28:42 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 16:28:42 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.39bfc40973b10c6178086597e06e7ce8@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by diatchki): It would be nice if we could refactor GHC so that error messages are kept in some sort of structured format with all information that might be relevant. Then, when printed we could have flags to specify how to render the errors (e.g., "machine form", which would be good for external tools, such as IDEs; or "human form", which could have the nice formatting in the example). I just saw a post about error messages in Elm, which looked pretty, and might give us ideas about formatting: http://elm-lang.org/blog/compiler- errors-for-humans -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 16:36:31 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 16:36:31 -0000 Subject: [GHC] #1388: Newbie help features In-Reply-To: <044.efaff92cf2e79b2f529fa901fdcbafbb@haskell.org> References: <044.efaff92cf2e79b2f529fa901fdcbafbb@haskell.org> Message-ID: <059.2f2549df802bb83e208b14f2eb052fc0@haskell.org> #1388: Newbie help features -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: feature request | Status: new Priority: low | Milestone: ? Component: GHCi | Version: 6.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #4929 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: bgamari (added) * related: => #4929 Comment: Support for top-level declarations was added in #4929. With 1ff7f09b3abedb2a6daf384b55ad3d0134f0d174, `f = 1` now prints: {{{ + parse error on input ?=? + Perhaps you need a 'let' in a 'do' block? + e.g. 'let x = 5' instead of 'x = 5' }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 16:49:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 16:49:03 -0000 Subject: [GHC] #4092: Floating point manipulation : ulp and coerce IEEE-754 Double# into Word64# In-Reply-To: <045.5cc829a852152f43b89d9843483d1a41@haskell.org> References: <045.5cc829a852152f43b89d9843483d1a41@haskell.org> Message-ID: <060.4820002e22deedd52ece6d419dca430a@haskell.org> #4092: Floating point manipulation : ulp and coerce IEEE-754 Double# into Word64# -------------------------------------+------------------------------------- Reporter: malosh | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by duncan): In the meantime, in the absence of primops, this is the best I can manage. I suggest we add this or similar to GHC.Float: {{{ {-# INLINE castWord2Float #-} castWord2Float :: Word32 -> Float castWord2Float (W32# w#) = F# (castWord2Float# w#) {-# NOINLINE castWord2Float# #-} castWord2Float# :: Word# -> Float# castWord2Float# w# = case newByteArray# 4# realWorld# of (# s', mba# #) -> case writeWord32Array# mba# 0# w# s' of s'' -> case readFloatArray# mba# 0# s'' of (# _, f# #) -> f# {-# INLINE castWord2Double #-} castWord2Double :: Word64 -> Double castWord2Double (W64# w#) = D# (castWord2Double# w#) {-# NOINLINE castWord2Double# #-} castWord2Double# :: Word# -> Double# castWord2Double# w# = case newByteArray# 8# realWorld# of (# s', mba# #) -> case writeWord64Array# mba# 0# w# s' of s'' -> case readDoubleArray# mba# 0# s'' of (# _, f# #) -> f# }}} This is similar to the "cast STUArray" method, but avoids the extra call and closure allocation due to the `runSTRep`. For the "cast STUArray" method, see: http://hackage.haskell.org/package/reinterpret-cast-0.1.0/docs/src/Data- ReinterpretCast-Internal-ImplArray.html The `NOINLINE` means that the use of `realWorld#` should be ok, despite `newByteArray# 8# realWorld#` being a constant. It'll need a very similar impl for 32bit systems that need the Word64# type. Compare the CMM of the above: {{{ castWord2Double#_entry() // [R2] { info_tbl: [(c2Qn, label: castWord2Double#_info rep:HeapRep static { Fun {arity: 1 fun_type: ArgSpec 4} })] stack_info: arg_space: 8 updfr_space: Just 8 } {offset c2Qn: Hp = Hp + 24; if (Hp > HpLim) goto c2Qr; else goto c2Qq; c2Qr: HpAlloc = 24; R2 = R2; R1 = castWord2Double#_closure; call (stg_gc_fun)(R2, R1) args: 8, res: 0, upd: 8; c2Qq: I64[Hp - 16] = stg_ARR_WORDS_info; I64[Hp - 8] = 8; _s2Q9::P64 = Hp - 16; I64[_s2Q9::P64 + 16] = R2; D1 = F64[_s2Q9::P64 + 16]; call (P64[Sp])(D1) args: 8, res: 0, upd: 8; } } }}} with the version that uses runST / runSTRep {{{ sat_s2QX_entry() // [R1] { info_tbl: [(c2Rd, label: sat_s2QX_info rep:HeapRep 1 nonptrs { Fun {arity: 1 fun_type: ArgSpec 3} })] stack_info: arg_space: 8 updfr_space: Just 8 } {offset c2Rd: Hp = Hp + 40; if (Hp > HpLim) goto c2Rj; else goto c2Ri; c2Rj: HpAlloc = 40; R1 = R1; call (stg_gc_fun)(R1) args: 8, res: 0, upd: 8; c2Ri: _s2QN::I64 = I64[R1 + 7]; I64[Hp - 32] = stg_ARR_WORDS_info; I64[Hp - 24] = 8; _s2QR::P64 = Hp - 32; I64[_s2QR::P64 + 16] = _s2QN::I64; _s2QV::F64 = F64[_s2QR::P64 + 16]; I64[Hp - 8] = D#_con_info; F64[Hp] = _s2QV::F64; R1 = Hp - 7; call (P64[Sp])(R1) args: 8, res: 0, upd: 8; } }, castWord2Double#_entry() // [R2] { info_tbl: [(c2Rk, label: castWord2Double#_info rep:HeapRep static { Fun {arity: 1 fun_type: ArgSpec 4} })] stack_info: arg_space: 8 updfr_space: Just 8 } {offset c2Rk: Hp = Hp + 16; if (Hp > HpLim) goto c2Ro; else goto c2Rn; c2Ro: HpAlloc = 16; R2 = R2; R1 = castWord2Double#_closure; call (stg_gc_fun)(R2, R1) args: 8, res: 0, upd: 8; c2Rn: I64[Hp - 8] = sat_s2QX_info; I64[Hp] = R2; R2 = Hp - 7; call runSTRep_info(R2) args: 8, res: 0, upd: 8; } } }}} The runSTRep version involves allocating a `sat_s2QX` closure and calling `runSTRep` to call that closure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 16:56:09 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 16:56:09 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.f08211fc59590e503e9c2ddd3c43ab43@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:6 diatchki]: > It would be nice if we could refactor GHC so that error messages are kept in some sort of structured format with all information that might be relevant. Then, when printed we could have flags to specify how to render the errors (e.g., "machine form", which would be good for external tools, such as IDEs; or "human form", which could have the nice formatting in the example). > Indeed this would be nice, however placing all of the information necessary for an error comes at a cost. I think Simon PJ articulates this fairly well in this [[comment https://www.reddit.com/r/haskell/comments/3bnpa7/compiler_errors_for_humans/csoksqg]] on the Reddit post mentioned by goldfire (reproduced here for archival sake), >Building error messages from strings (or in GHC's case `SDoc`s) is pretty lame because you can write them but not analyse them. The "obvious" alternative is to use a huge algebraic data type with one constructor for each error message that GHC can produce. Then you generate the constructor in one place, and render it into a string somewhere else, perhaps in more than one way. I am not optimistic about this, because it puts a big central road-block in the way of generating error messages, and splits the work into two different places (the renderer and the generator). That's an advantage in some ways, but there are so darn MANY different error messages that it feels far too centralised and brittle to me. > >Idris does something in the middle. As I understand David Cristiansen, they have an abstract type a bit like `SDoc`, but it is much richer than GHC's `SDoc`. They can certainly do colour (and `SDoc`s should too). And you can attach auxilary info to the `SDoc` so that when rendered in a web browser you get popup hints. This would all be very feasible in GHC, if someone did the work. > >Another big issue is having enough information to hand when you are generating the message in the first place. Attaching provenance information to type constraints is a huge help (as the Elm article suggests) which GHC does, but not well enough. For example Lennart Augustsson gave a talk at the Haskell Implementors workshop last year with some simple suggestions that work really well in his Mu compiler. Jurriaan Hage and his colleages at Utrecht have a lot of experience of this kind of thing with Helium. GHC is better placed to do this now than it has ever been before, because the type inference engine is increasingly based on solving constraints. Almost all type errors are generated in a single module, `TcErrors`, if you are interested to look there. > >I'm keen to make sure that running GHC in batch mode sending output to a text file or dumb terminal gives something useful. I don't want to require a snazzy IDE or emacs mode. But I'd love to be able to exploit one if it was available. The proposal I lay out in comment:3 was an attempt to find a way to implement the alternative that Simon describes above while minimizing the impact of the change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:05:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:05:40 -0000 Subject: [GHC] #9638: Speed up Data.Char.isDigit In-Reply-To: <045.8305c40432408fead5554261d41a3400@haskell.org> References: <045.8305c40432408fead5554261d41a3400@haskell.org> Message-ID: <060.e3c75116695683f2ea85561ce0653afe@haskell.org> #9638: Speed up Data.Char.isDigit -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: ekmett Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Core Libraries | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: core-libraries-committee@? (added) Comment: dfeuer, is 31571270625a690410b794b7cfe48d866c084e74/ghc sufficient to close this ticket or is there more to be done here? {{{ Author: David Feuer <> Date: Tue Oct 21 15:01:14 2014 -0500 Improve isDigit, isSpace, etc. Summary: Make things less branchy; use unsigned comparisons for range checking. Eliminate non-spaces more quickly in common cases in isSpace. Reviewers: ekmett, carter, austin Reviewed By: austin Subscribers: thomie, carter, ezyang, simonmar Differential Revision: https://phabricator.haskell.org/D340 GHC Trac Issues: #1473 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:12:51 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:12:51 -0000 Subject: [GHC] #8695: Arithmetic overflow from (minBound :: Int) `quot` (-1) In-Reply-To: <046.b48445f821d50909a0ec2f285f6886c0@haskell.org> References: <046.b48445f821d50909a0ec2f285f6886c0@haskell.org> Message-ID: <061.f283b3bef298c792c0f1052a205d61fa@haskell.org> #8695: Arithmetic overflow from (minBound :: Int) `quot` (-1) -------------------------------------+------------------------------------- Reporter: rleslie | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Documentation | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: #1042 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * failure: Incorrect result at runtime => Documentation bug * component: Core Libraries => Documentation * resolution: wontfix => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:31:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:31:08 -0000 Subject: [GHC] #8578: Improvements to SpinLock implementation In-Reply-To: <044.7d4d696b896537d8c685483f715ea999@haskell.org> References: <044.7d4d696b896537d8c685483f715ea999@haskell.org> Message-ID: <059.c28192bf75e25171ecb83c68668f2f30@haskell.org> #8578: Improvements to SpinLock implementation -------------------------------------+------------------------------------- Reporter: parcs | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:40:27 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:40:27 -0000 Subject: [GHC] #5071: GHCi crashes on large alloca/allocaBytes requests In-Reply-To: <044.2a54a775d63eaecd5de3fad1b818b5ff@haskell.org> References: <044.2a54a775d63eaecd5de3fad1b818b5ff@haskell.org> Message-ID: <059.b6137f134f1594eb81c007b08ae9bd13@haskell.org> #5071: GHCi crashes on large alloca/allocaBytes requests -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: bug | Status: new Priority: normal | Milestone: ? Component: Compiler | Version: 7.0.3 Resolution: | Keywords: report- Operating System: Unknown/Multiple | impact Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => report-impact Comment: Quoting [comment:4 comment:4]: > I think we made a mistake in the standard here. In fact, by changing `alloca` to raise an exception I think we'll be ''fixing'' a lot of broken code! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:53:22 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:53:22 -0000 Subject: [GHC] #8363: Order matters for unused import warnings when reexporting identifiers In-Reply-To: <047.398c655035bcdb3804c2c1b5f20b099c@haskell.org> References: <047.398c655035bcdb3804c2c1b5f20b099c@haskell.org> Message-ID: <062.966c40b48e4fcc790d5954fd8bf478d6@haskell.org> #8363: Order matters for unused import warnings when reexporting identifiers -------------------------------------+------------------------------------- Reporter: bergmark | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:56:52 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:56:52 -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 Message-ID: <046.69b85de5f279bc6fd8a3f5ec62466a80@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: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: MacOS X Architecture: x86_64 (amd64) | Type of failure: Other Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -----------------------------------------+---------------------------- Using the ghc-7.10.1-x86_64-apple-darwin.tar.bz2 binary release to install ghc 7.10.1 with... ./configure --prefix=/sw make DESTDIR=/sw install fails to install a populated /sw/lib/ghc-7.10.1/ghcpr_8TmvWUcS1U1IKHT0levwg3/GHC subdirectory causing builds of ghc packages with gcc-prim dependencies to fail. The only non- documentation files installed are... -rwxr-xr-x root/admin 647620 2015-07-01 13:20 ./sw/lib/ghc-7.10.1/ghcpr_8TmvWUcS1U1IKHT0levwg3/libHSghc- prim-0.4.0.0-8TmvWUcS1U1IKHT0levwg3-ghc7.10.1.dylib -rw-r--r-- root/admin 1326504 2015-07-01 13:20 ./sw/lib/ghc-7.10.1/ghcpr_8TmvWUcS1U1IKHT0levwg3/libHSghc- prim-0.4.0.0-8TmvWUcS1U1IKHT0levwg3.a -rw-r--r-- root/admin 814 2015-07-01 13:20 ./sw/lib/ghc-7.10.1/package.conf.d/ghc- prim-0.4.0.0-7c945cc0c41d3b7b70f3edd125671166.conf This compares to the same installation of the ghc-7.8.3-x86_64-apple- darwin.tar.bz2 binary release which does install the required files as... drwxr-xr-x root/admin 0 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/ drwxr-xr-x root/admin 0 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/ -rw-r--r-- root/admin 373897 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Classes.dyn_hi -rw-r--r-- root/admin 373885 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Classes.hi -rw-r--r-- root/admin 373889 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Classes.p_hi -rw-r--r-- root/admin 2661 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/CString.dyn_hi -rw-r--r-- root/admin 2649 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/CString.hi -rw-r--r-- root/admin 2653 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/CString.p_hi -rw-r--r-- root/admin 1940 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Debug.dyn_hi -rw-r--r-- root/admin 1928 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Debug.hi -rw-r--r-- root/admin 1932 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Debug.p_hi -rw-r--r-- root/admin 942 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/IntWord64.dyn_hi -rw-r--r-- root/admin 930 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/IntWord64.hi -rw-r--r-- root/admin 934 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/IntWord64.p_hi -rw-r--r-- root/admin 388 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Magic.dyn_hi -rw-r--r-- root/admin 376 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Magic.hi -rw-r--r-- root/admin 380 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Magic.p_hi -rw-r--r-- root/admin 50032 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/PrimopWrappers.dyn_hi -rw-r--r-- root/admin 50020 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/PrimopWrappers.hi -rw-r--r-- root/admin 50024 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/PrimopWrappers.p_hi -rw-r--r-- root/admin 1100 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Tuple.dyn_hi -rw-r--r-- root/admin 1088 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Tuple.hi -rw-r--r-- root/admin 1092 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Tuple.p_hi -rw-r--r-- root/admin 939 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Types.dyn_hi -rw-r--r-- root/admin 927 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Types.hi -rw-r--r-- root/admin 931 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/GHC/Types.p_hi -rwxr-xr-x root/admin 631192 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/libHSghc-prim-0.3.1.0-ghc7.8.3.dylib -rw-r--r-- root/admin 792352 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/libHSghc-prim-0.3.1.0.a -rw-r--r-- root/admin 1134504 2015-07-01 13:08 ./sw/lib/ghc-7.8.3/ghc- prim-0.3.1.0/libHSghc-prim-0.3.1.0_p.a -rw-r--r-- root/admin 871 2015-07-01 13:09 ./sw/lib/ghc-7.8.3/package.conf.d/ghc- prim-0.3.1.0-954cb57749cf319beafdc89b3415422c.conf -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 17:59:39 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 17:59:39 -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.7c4b2dd069e64477dd36e5560633ae4b@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: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -----------------------------+----------------------------------------- Changes (by thomie): * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 18:22:02 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 18:22:02 -0000 Subject: [GHC] #9505: Bounded instance for Word (and possibly others) uses explicitly unboxed literals In-Reply-To: <046.095a614b9437d6cfe76c234b07042878@haskell.org> References: <046.095a614b9437d6cfe76c234b07042878@haskell.org> Message-ID: <061.b5bb8280d63fbc469c0450c359fb3a53@haskell.org> #9505: Bounded instance for Word (and possibly others) uses explicitly unboxed literals -------------------------------------+------------------------------------- Reporter: schyler | Owner: ekmett Type: task | Status: new Priority: lowest | Milestone: ? Component: Core Libraries | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): In `libraries/base/GHC/Base.hs`: {{{#!haskell maxInt, minInt :: Int {- Seems clumsy. Should perhaps put minInt and MaxInt directly into MachDeps.h -} #if WORD_SIZE_IN_BITS == 31 minInt = I# (-0x40000000#) maxInt = I# 0x3FFFFFFF# #elif WORD_SIZE_IN_BITS == 32 minInt = I# (-0x80000000#) maxInt = I# 0x7FFFFFFF# #else minInt = I# (-0x8000000000000000#) maxInt = I# 0x7FFFFFFFFFFFFFFF# #endif }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 18:22:18 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 18:22:18 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.eff9fe40fb427b486770820eb91c7bcb@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by michaelt): Sorry, I'm spamming the trac a bit. Notice that in the ultra-simplified module, now attached properly, the wrapping with `Lift` that `parallel` uses for `rparWith` is no where to be found. If I wrap stuff in my `ill_sequenced` with `Lift`, I can't get the effect. If though, that use of `Lift` in the definition of `rparWith` is required by whatever is going on with `spark#` and some of these other opaque-to-me primitives, then there is a question whether it is used enough: the original program is doing an end-run around this. It is presumably obviously undesirable, but if in rbarton's par.hs I complicate the definition of `rpar` , which is {{{#!hs rpar :: a -> Eval a rpar x = Eval $ \s -> spark# x s }}} and use instead something like {{{#!hs rpar :: a -> Eval a rpar x = Eval $ \s -> case y of Eval f -> case f s of (# s1 , l #) -> case l of Lift w -> (# s1 , w #) where y = Eval $ \s -> spark# (Lift x) s }}} then it seems all is well again. That probably destroys all the desired effects; but if it doesn't, then the problem may just be that the library is letting the user get too close to `spark#` which is practically naked in `rpar`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 18:28:46 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 18:28:46 -0000 Subject: [GHC] #8363: Order matters for unused import warnings when reexporting identifiers In-Reply-To: <047.398c655035bcdb3804c2c1b5f20b099c@haskell.org> References: <047.398c655035bcdb3804c2c1b5f20b099c@haskell.org> Message-ID: <062.0c60f408993d18699776f77713407e71@haskell.org> #8363: Order matters for unused import warnings when reexporting identifiers -------------------------------------+------------------------------------- Reporter: bergmark | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Be aware though that it has become somewhat popular to exploit this bug(?) to avoid writing CPP to manage the changes in Prelude's exports in 7.10. {{{ module Main where import Control.Applicative -- needed in 7.8, and not a warning in 7.10 -- because it comes before the Prelude import, -- though it actually is redundant in 7.10 import Prelude -- has the effect of canceling the implicit -- import of Prelude ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 18:33:12 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 18:33:12 -0000 Subject: [GHC] #8363: Order matters for unused import warnings when reexporting identifiers In-Reply-To: <047.398c655035bcdb3804c2c1b5f20b099c@haskell.org> References: <047.398c655035bcdb3804c2c1b5f20b099c@haskell.org> Message-ID: <062.5438c60b662d9363c680084d6b76328b@haskell.org> #8363: Order matters for unused import warnings when reexporting identifiers -------------------------------------+------------------------------------- Reporter: bergmark | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: newcomer => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 18:56:44 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 18:56:44 -0000 Subject: [GHC] #5954: Performance regression 7.0 -> 7.2 (still in 7.4) In-Reply-To: <047.8be864281aa54fbc2cb186b2afb9a1a6@haskell.org> References: <047.8be864281aa54fbc2cb186b2afb9a1a6@haskell.org> Message-ID: <062.b1cd167d49c18e9a2e933ac64ac1480e@haskell.org> #5954: Performance regression 7.0 -> 7.2 (still in 7.4) -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:11 carter]: > is this bug still going on in head? No reply to this so changing status to infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 18:57:10 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 18:57:10 -0000 Subject: [GHC] #5954: Performance regression 7.0 -> 7.2 (still in 7.4) In-Reply-To: <047.8be864281aa54fbc2cb186b2afb9a1a6@haskell.org> References: <047.8be864281aa54fbc2cb186b2afb9a1a6@haskell.org> Message-ID: <062.337fc96c559b58a2445bb1caf975c6b0@haskell.org> #5954: Performance regression 7.0 -> 7.2 (still in 7.4) -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonpj Type: bug | Status: infoneeded Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by George): * status: new => infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 19:23:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 19:23:25 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.6e8bf51a4c68561fa6836307e2c41ca4@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 19:55:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 19:55:14 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.8eff06a527ad28f455aad758ccf467af@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I took a look at the generated STG for par2.hs before and after the cardinality analysis commit. Before, there are no `\s` thunks at all. After, there are two. One is in {{{ Main.main_go [Occ=LoopBreaker] :: [[GHC.Types.Char]] -> [GHC.Types.Char] [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType , Unf=OtherCon []] = \r srt:SRT:[] [ds_s1nu] case ds_s1nu of _ { [] -> [] []; : y_s1ny [Occ=Once] ys_s1nz [Occ=Once] -> let { sat_s1pj [Occ=Once, Dmd=] :: [GHC.Types.Char] [LclId, Str=DmdType] = \s srt:SRT:[] [] Main.main_go ys_s1nz; } in GHC.Base.++ y_s1ny sat_s1pj; }; }}} This comes from the Core {{{ Main.main_go [Occ=LoopBreaker] :: [[GHC.Types.Char]] -> [GHC.Types.Char] [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType ] Main.main_go = \ (ds_XrA :: [[GHC.Types.Char]]) -> case ds_XrA of _ { [] -> GHC.Types.[] @ GHC.Types.Char; : y_arg ys_arh -> GHC.Base.++ @ GHC.Types.Char y_arg (Main.main_go ys_arh) } }}} which presumably comes from the use of `concat` in `layer`. This happens even when I build the program with `-fkill-absence -fkill-one-shot`. Could that be because base was built with cardinality analysis enabled? I don't entirely see how, but I can try rebuilding the libraries with `-fkill- absence -fkill-one-shot`. Anyways I guess the main question, which I'm not sure how to answer, is whether the fact that this thunk is marked as single-entry is correct. The other single-entry thunk is, I think, very similar and arises from `concatMap`: {{{ {- note $wlayer_r1m6 :: (GHC.Types.Char -> GHC.Base.String) -> GHC.Prim.Char# -> GHC.Base.String [GblId, Caf=NoCafRefs, Str=DmdType, Unf=OtherCon []] w3_r1ma :: GHC.Types.Char -> GHC.Base.String [GblId, Arity=1, Str=DmdType, Unf=OtherCon []] -} Main.main_go2 [Occ=LoopBreaker] :: [GHC.Types.Char] -> [GHC.Types.Char] [GblId, Arity=1, Str=DmdType , Unf=OtherCon []] = \r srt:SRT:[(r8, Main.main_go2), (r1m6, $wlayer_r1m6), (r1ma, w3_r1ma)] [ds_s1oh] case ds_s1oh of _ { [] -> [] []; : y_s1ol [Occ=Once!] ys_s1oq [Occ=Once] -> case y_s1ol of _ { GHC.Types.C# ww1_s1oo [Occ=Once] -> let { sat_s1pv [Occ=Once, Dmd=] :: [GHC.Types.Char] [LclId, Str=DmdType] = \s srt:SRT:[(r8, Main.main_go2)] [] Main.main_go2 ys_s1oq; } in case $wlayer_r1m6 w3_r1ma ww1_s1oo of sat_s1pu { __DEFAULT -> GHC.Base.++ sat_s1pu sat_s1pv; }; }; }; }}} I'm going to see what happens when I inline the definitions of `concat` and `concatMap` into this module. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 20:46:16 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 20:46:16 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.fd2f2b11b427ae9fb6573702a2a0b1fc@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Inlining `concat` and `concatMap` made no difference, the program still loops and a `\s` thunk is still generated inside "`main_mygo`". This happens for any combination of the `-fkill-absence` and `-fkill-one-shot` flags, and in every version I tested (the 7.7 commit adding cardinality analysis, 7.8.4, 7.10.1 and HEAD). I then tried removing the `SingleEntry` case as Simon suggested in comment:9 and that did generate a `\u` thunk instead and the program no longer <>s. So, one conclusion is that `-fkill-absence`/`-fkill-one-shot` don't fully disable cardinality analysis like they are expected to. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 22:49:27 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 22:49:27 -0000 Subject: [GHC] #10398: Support consecutive named Haddock comments In-Reply-To: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> References: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> Message-ID: <062.aa76742b81dd751179010bc83d32690c@haskell.org> #10398: Support consecutive named Haddock comments -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | haddock/should_compile_flag_haddock/T10398 Related Tickets: | Blocking: | Differential Revisions: Phab:D1025 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch * testcase: => haddock/should_compile_flag_haddock/T10398 * differential: => Phab:D1025 * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 22:54:05 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 22:54:05 -0000 Subject: [GHC] #10593: compilation failure on OpenBSD In-Reply-To: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> References: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> Message-ID: <061.0e52fb7a0005661da4e9e4ff083f4ba3@haskell.org> #10593: compilation failure on OpenBSD -------------------------------------+------------------------------------- Reporter: kgardas | Owner: simonmar Type: bug | Status: patch Priority: normal | Milestone: 7.10.3 Component: Runtime System | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:1023 -------------------------------------+------------------------------------- Changes (by thoughtpolice): * differential: => Phab:1023 * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 23:04:12 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 23:04:12 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. Message-ID: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- It seems that the Class op * rules will override a user defined rule for class functions. This seems to be a long outstanding issue: http://stackoverflow.com/questions/9811294/rewrite-rules-not-firing-for- rules-matching-multiple-instance-methods I also just ran into someone else on the haskell IRC channel who had an even simpler example then the one on that page: {{{#!hs {-# NOINLINE d #-} {-# RULES "d exp" d exp = exp #-} d :: (Double -> Double) -> (Double -> Double) d f = f . (+20.0) g :: Double -> Double g = (+5.0) main = do print $ d exp 1.0 -- FAIL should print 2.718281828459045 >> printed exp 21.0 instead print $ d g 3.0 -- PASS should print 28.0 -- Compiled with: -- ghc -fenable-rewrite-rules -O rules.hs }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 23:21:16 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 23:21:16 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.cb3a196e41d6fa378a7f2ff66f45e5ea@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gjsimms): Well, I don't really know how to use trac to modify files... Anyway the ruleTest.hs file is a working version (rule gets hit) of example in the description. ruleTest2.hs is a failing case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 1 23:39:21 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 01 Jul 2015 23:39:21 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.3a8de57059221aaed3e7053859d9538a@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by NicX): Seconding gjsimms comment re. rulesTest.hs. That version uses exp' (defined on lines 6-7) instead of exp so the comment on line 13 should say: -- PASS should print 2.718281828459045 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 04:36:04 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 04:36:04 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work Message-ID: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.10.1 Haskell | Operating System: Unknown/Multiple Keywords: getQ putQ | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Functions `getQ` and `putQ` in the module `Language.Haskell.TH.Syntax` do not work. Following code is an example of this problem. The variable `x` should be `(Just B)`, but `x` is `Nothing`. {{{#!hs {-# LANGUAGE TemplateHaskell #-} module X where import Language.Haskell.TH import Language.Haskell.TH.Syntax do putQ (100 :: Int) x <- getQ :: Q (Maybe Int) -- It should print "Just 100" but "Nothing" runIO $ print x return [] }}} As a result, I get following output on compile. {{{#!hs $ ghc -fforce-recomp X.hs [1 of 1] Compiling X ( X.hs, X.o ) Nothing }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 04:54:01 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 04:54:01 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.80adaacfa83ca089d37e653c7d30976b@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Bug is quite simple (wrong type is used for lookup), fix on the way... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 05:25:07 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 05:25:07 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.ed348cbbdb95a783742c2ce3ef87946d@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kiripon): I fixed this bug and checked work correctly. {{{ diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index a7363d8..2bcb78c 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -836,7 +836,7 @@ instance TH.Quasi (IOEnv (Env TcGblEnv TcLclEnv)) where qGetQ = do th_state_var <- fmap tcg_th_state getGblEnv th_state <- readTcRef th_state_var - let x = Map.lookup (typeOf x) th_state >>= fromDynamic + let x = Map.lookup (typeOf $ fromJust x) th_state >>= fromDynamic return x qPutQ x = do diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs }}} {{{ kiripon% ghc -fforce-recomp Y.hs [1 of 1] Compiling Y ( Y.hs, Y.o ) Nothing Nothing kiripon% $HOME/opt/local/ghc-head/bin/ghc -fforce-recomp Y.hs [1 of 1] Compiling Y ( Y.hs, Y.o ) Just 100 Just 100 kiripon% cat Y.hs {-# LANGUAGE TemplateHaskell #-} module Y where import Language.Haskell.TH import Language.Haskell.TH.Syntax -- splice for testing getQ and putQ do putQ (100 :: Int) :: Q () x <- getQ :: Q (Maybe Int) runIO $ print x -- prints Nothing return [] do x <- getQ :: Q (Maybe Int) runIO $ print x -- prints Nothing return [] kiripon% }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 05:55:17 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 05:55:17 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.9dd59403f50b8103f071e8fe29a36121@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by ezyang): * differential: => Phab:D1026 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 07:52:28 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 07:52:28 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.caccaf1fdf20ba09c739bdca0c4a7378@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by trommler): Replying to [comment:5 rwbarton]: > I'm a little worried about whether the obvious fix for this (adding `-lfoo` to the gcc command line for building the temporary shared objects for each library `-lfoo` specified on the ghci command line) might cause #8935 to occur again in some configurations. If we add every library that we've loaded there then what was the point of loading the libraries with RTLD_LOCAL? We need RTLD_LOCAL when we want to override symbols in a shared library previously loaded with symbols from a shared library loaded later. Given that we do not want to override symbols from C libraries, we can add them to the link command. My understanding of what we want to be able to override is very hazy. Do we have a wiki page that describes the semantics of loading packages and libraries into ghci? > Possibly we only need to use RTLD_LOCAL when building the ghci linker statically? Then we could revert the other changes like #10322 and #10110 and #10058. What does it mean "building the ghci linker statically"? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 08:16:08 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 08:16:08 -0000 Subject: [GHC] #10394: LLVM mangler doesn't mangle AVX instructions In-Reply-To: <047.b85b8723ab1fa78e7e23f08be8ccae23@haskell.org> References: <047.b85b8723ab1fa78e7e23f08be8ccae23@haskell.org> Message-ID: <062.b3e3b942718e09425eb283a58f85bdac@haskell.org> #10394: LLVM mangler doesn't mangle AVX instructions -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler (LLVM) | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch Comment: Paging bgamari. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 09:43:00 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 09:43:00 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.87ea6527e8a33a6c1a7846c02b77d6c2@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Michael, Reid, that is super-helpful. The cardinality analysis is plain wrong, so now we know just what is happening. I'm working on a fix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 10:01:32 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 10:01:32 -0000 Subject: [GHC] #4092: Floating point manipulation : ulp and coerce IEEE-754 Double# into Word64# In-Reply-To: <045.5cc829a852152f43b89d9843483d1a41@haskell.org> References: <045.5cc829a852152f43b89d9843483d1a41@haskell.org> Message-ID: <060.a71b0495efebef6373d90f133ca72cec@haskell.org> #4092: Floating point manipulation : ulp and coerce IEEE-754 Double# into Word64# -------------------------------------+------------------------------------- Reporter: malosh | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonmar): Ooh, that's a nice use for the new inline array allocation support in the codegen. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 10:07:01 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 10:07:01 -0000 Subject: [GHC] #10089: feature: warn about unused data definitions (with typeclass instances) In-Reply-To: <045.113d906ba3b76ec22ad2f715d9c6da96@haskell.org> References: <045.113d906ba3b76ec22ad2f715d9c6da96@haskell.org> Message-ID: <060.0eb1058db377c900783f2af8ee539754@haskell.org> #10089: feature: warn about unused data definitions (with typeclass instances) -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 10:07:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 10:07:38 -0000 Subject: [GHC] #9839: RTS options parser silently accepts invalid flags In-Reply-To: <049.1ac180907787acdf75c140998b5b4263@haskell.org> References: <049.1ac180907787acdf75c140998b5b4263@haskell.org> Message-ID: <064.05139dedbec9c9b28fab000182195ce5@haskell.org> #9839: RTS options parser silently accepts invalid flags -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Runtime System | Version: 7.8.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #4243 | Differential Revisions: Phab:D748 -------------------------------------+------------------------------------- Changes (by simonmar): * priority: high => highest Comment: Must fix before 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 13:21:36 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 13:21:36 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support Message-ID: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: OpenBSD Architecture: x86_64 | Type of failure: Building GHC (amd64) | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- OpenBSD provides since 5.3 version IIRC support for position independent executables (PIE) by default. This means GNU C bundled with OpenBSD by default compiles position independent code. GHC does not count with this and generates normal code and while linking linker complains about wrong relocations in linked object code. Example: {{{ /usr/bin/ld: utils/hsc2hs/dist-install/build/Main.o: relocation R_X86_64_32S against `stg_upd_frame_info' can not be used when making a shared object; recompile with -fPIC }}} This of course means that build of GHC itself fails. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 13:21:53 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 13:21:53 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support In-Reply-To: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> References: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> Message-ID: <061.d47b47823149c8bfa688ef61fa392dc7@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: kgardas Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kgardas): * owner: => kgardas -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 13:30:35 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 13:30:35 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support In-Reply-To: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> References: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> Message-ID: <061.c392c2ef23151634c95b2101c6b00b78@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: kgardas Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kgardas): * status: new => patch Comment: Fix provided in Phab:D1027 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 14:57:30 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 14:57:30 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support In-Reply-To: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> References: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> Message-ID: <061.222b2e71713a9827202d9a71d7ae32c2@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: kgardas Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): This is presumably fine, but the discussion at #9007 is relevant too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 15:49:04 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 15:49:04 -0000 Subject: [GHC] #9007: fails to build with hardening flags enabled (relocation R_X86_64_32 against `stg_CHARLIKE_closure'...) In-Reply-To: <046.e2d123aa0cc7380f3c5c662bb8d8022e@haskell.org> References: <046.e2d123aa0cc7380f3c5c662bb8d8022e@haskell.org> Message-ID: <061.9760f809df64ecaa14a07f126746d3ee@haskell.org> #9007: fails to build with hardening flags enabled (relocation R_X86_64_32 against `stg_CHARLIKE_closure'...) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: infoneeded Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kgardas): Replying to [comment:19 slyfox]: > Hardened gentoo patches gcc to default to -fPIC -fPIE -pie. Defaults there: > {{{ > # gcc -dM -E - < /dev/null | grep -E -i 'pic|pie' > #define __pie__ 2 > #define __PIE__ 2 > #define __pic__ 2 > #define __PIC__ 2 > }}} > > What bothers me is -optl-pie seems not to work even for -split-objs case on vanilla gcc/ghc: > {{{ > $ echo 'main = print "hello"' > a.hs > $ ghc --make -optl-pie -fPIC -optc-fPIC -dynamic a.hs -fforce-recomp > [1 of 1] Compiling Main ( a.hs, a.o ) > Linking a ... > $ ghc --make -optl-pie -fPIC -optc-fPIC -dynamic a.hs -fforce-recomp -split-objs > [1 of 1] Compiling Main ( a.hs, a.o ) > /usr/lib/gcc/x86_64-pc-linux-gnu/5.1.0/../../../../x86_64-pc-linux- gnu/bin/ld: -r and -shared may not be used together > collect2: error: ld returned 1 exit status > }}} > An evil corner case as we use ld for partial linking. Can be an argument for native > fPIE/pie support in ghc. I'm curious but isn't -split-objs purely static library thing? IMHO it's not usable for -shared nor -dynamic nor -fPIC etc. Please correct me if I'm wrong here... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 17:35:03 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 17:35:03 -0000 Subject: [GHC] #10018: Cannot define custom fixity for infix data constructors in GHCi In-Reply-To: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> References: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> Message-ID: <065.418e7511127da35648a9de341a289707@haskell.org> #10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | ghci/scripts/T10018 Related Tickets: #9830, #2947, | Blocking: #4929 | Differential Revisions: Phab:D1028 -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => ghci/scripts/T10018 * differential: => Phab:D1028 * related: #9830 => #9830, #2947, #4929 * milestone: => 7.12.1 Comment: I'm not sure why it partially worked when you added `deriving Show` in comment:2, but I have a patch up for review in Phab:D1028 that enables custom fixity declarations for infix data constructors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 18:04:26 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 18:04:26 -0000 Subject: [GHC] #10018: Cannot define custom fixity for infix data constructors in GHCi In-Reply-To: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> References: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> Message-ID: <065.b084b15d61ec4c4e0c53581ccd76f7d1@haskell.org> #10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | ghci/scripts/T10018 Related Tickets: #9830, #2947, | Blocking: #4929 | Differential Revisions: Phab:D1028 -------------------------------------+------------------------------------- Comment (by RyanGlScott): Replying to [comment:5 thomie]: > I'm not sure why it partially worked when you added `deriving Show` in comment:2, but I have a patch up for review in Phab:D1028 that enables custom fixity declarations for infix data constructors. I'm guessing that the fixity info that derived `Read`/`Show` instances see must be distinct from the fixity info that's used when parenthesizing expressions (I'm not a GHC developer, this is just my speculation). I added #9830 since it addresses a similar issue, so maybe there's a clue in simonpj's fix for it. In any case, it looks like your patch will fix this discrepancy, so all is good. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 18:34:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 18:34:38 -0000 Subject: [GHC] #10023: Relax Monad constraint in traceM and traceShowM to Applicative In-Reply-To: <050.7023a64f597b119154f3ec65be43878d@haskell.org> References: <050.7023a64f597b119154f3ec65be43878d@haskell.org> Message-ID: <065.c8c90194854ceb29653f056e62118b38@haskell.org> #10023: Relax Monad constraint in traceM and traceShowM to Applicative -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.10.1-rc1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer Comment: For Newcomers: easy ticket. Also add an entry in `libraries/base/changelog.md`, and add `hvr` as a reviewer. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 19:58:36 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 19:58:36 -0000 Subject: [GHC] #10023: Relax Monad constraint in traceM and traceShowM to Applicative In-Reply-To: <050.7023a64f597b119154f3ec65be43878d@haskell.org> References: <050.7023a64f597b119154f3ec65be43878d@haskell.org> Message-ID: <065.085c0df0ee5243f8f8326b96b37e18ee@haskell.org> #10023: Relax Monad constraint in traceM and traceShowM to Applicative -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: new Component: libraries/base | Milestone: 7.12.1 Resolution: | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: newcomer Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: => RyanGlScott -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 20:58:16 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 20:58:16 -0000 Subject: [GHC] #10023: Relax Monad constraint in traceM and traceShowM to Applicative In-Reply-To: <050.7023a64f597b119154f3ec65be43878d@haskell.org> References: <050.7023a64f597b119154f3ec65be43878d@haskell.org> Message-ID: <065.9bade30eac2882a06958b712049c07e8@haskell.org> #10023: Relax Monad constraint in traceM and traceShowM to Applicative -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: new Component: libraries/base | Milestone: 7.12.1 Resolution: | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: newcomer Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1029 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D1029 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 20:58:53 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 20:58:53 -0000 Subject: [GHC] #8206: Add support for Portable Native Client In-Reply-To: <044.0e9301156a0eb3e01f0cb8995b726d63@haskell.org> References: <044.0e9301156a0eb3e01f0cb8995b726d63@haskell.org> Message-ID: <059.437326f18cfec1034fc4d143ab8fc5f4@haskell.org> #8206: Add support for Portable Native Client -------------------------------------+------------------------------------- Reporter: guest | Owner: Alex Type: feature request | Sayers Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | Version: Operating System: Unknown/Multiple | Keywords: NaCl PNaCl Type of failure: None/Unknown | Portable Native Client pexe Blocked By: | Architecture: Related Tickets: | Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jakzale): * cc: jakzale (added) Comment: I'm working on this issue as a part of GSOC'15. Apart from minor issues with the build system, there are some additional clashes between ghc's dependencies and native client's (nacl) newlib I found so far: - the rts depends on posix signals, which are not supported in nacl newlib (although there seems to be a workaround), - the unix package depends on posix semaphores, which are currently not supported in nacl newlib, - additionally, dlfcn.h (and all functionality regarding dynamic linking) is not available in nacl newlib. Would it be possible to build ghc without the unix package? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 21:28:25 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 21:28:25 -0000 Subject: [GHC] #9970: Export more types in GHC.RTS.Flags In-Reply-To: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> References: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> Message-ID: <065.3a785d8b3912b56e2ae4fbe4c8e946ff@haskell.org> #9970: Export more types in GHC.RTS.Flags -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: new Component: libraries/base | Milestone: 7.12.1 Resolution: | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1030 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: => RyanGlScott * differential: => Phab:D1030 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 2 22:54:31 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 02 Jul 2015 22:54:31 -0000 Subject: [GHC] #10394: LLVM mangler doesn't mangle AVX instructions In-Reply-To: <047.b85b8723ab1fa78e7e23f08be8ccae23@haskell.org> References: <047.b85b8723ab1fa78e7e23f08be8ccae23@haskell.org> Message-ID: <062.d5f7eb2222cb9d82ea3a2d818bed7618@haskell.org> #10394: LLVM mangler doesn't mangle AVX instructions -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler (LLVM) | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Ahh, sorry, this somehow slipped through the cracks. I'll have a look first thing tomorrow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 00:32:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 00:32:32 -0000 Subject: [GHC] #10598: DeriveAnyClass and GND don't work well together Message-ID: <043.eb0a3cc9875acc25d45d33a9b9c86b64@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I think we definitely have a bug here, but I'm not sure what it really is. Here's the program: {{{ newtype MyMaybe a = MyMaybe (Maybe a) deriving (Functor, Show) main = print $ MyMaybe $ Just (10 :: Int) }}} I'm using GHC 7.10.1. {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XDeriveAnyClass -XGeneralizedNewtypeDeriving [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:2:13: Can't make a derived instance of ?Functor MyMaybe? (even with cunning newtype deriving): You need DeriveFunctor to derive an instance for this class Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension In the newtype declaration for ?MyMaybe? }}} Just to try, changing argument order: {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XGeneralizedNewtypeDeriving -XDeriveAnyClass [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:2:13: Can't make a derived instance of ?Functor MyMaybe? (even with cunning newtype deriving): You need DeriveFunctor to derive an instance for this class Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension In the newtype declaration for ?MyMaybe? }}} It works fine if I remove `DeriveAnyClass`: {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XGeneralizedNewtypeDeriving [1 of 1] Compiling Main ( Test.hs, Test.o ) Linking Test ... }}} GHC HEAD is failing in exactly the same way. User manual is saying this in 7.5.6: > In case you try to derive some class on a newtype, and -XGeneralizedNewtypeDeriving is also on, -XDeriveAnyClass takes precedence. But then why is it telling me to enable `GeneralizedNewtypeDeriving` in the error message? Even if I already enabled it? Also, maybe it could try `GND` when `DeriveAnyClass` fails? Because the doc is saying `DeriveAnyClass` has precedence but doesn't specify what happens if it fails. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 00:33:25 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 00:33:25 -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.f38046a86a0ffb1472c44546c7b52982@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by osa1: Old description: > I think we definitely have a bug here, but I'm not sure what it really > is. > > Here's the program: > > {{{ > newtype MyMaybe a = MyMaybe (Maybe a) > deriving (Functor, Show) > > main = print $ MyMaybe $ Just (10 :: Int) > }}} > > I'm using GHC 7.10.1. > > {{{ > ? deriveany_bug ghc --make -fforce-recomp Test.hs -XDeriveAnyClass > -XGeneralizedNewtypeDeriving > [1 of 1] Compiling Main ( Test.hs, Test.o ) > > Test.hs:2:13: > Can't make a derived instance of ?Functor MyMaybe? > (even with cunning newtype deriving): > You need DeriveFunctor to derive an instance for this class > Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension > In the newtype declaration for ?MyMaybe? > }}} > > Just to try, changing argument order: > > {{{ > ? deriveany_bug ghc --make -fforce-recomp Test.hs > -XGeneralizedNewtypeDeriving -XDeriveAnyClass > [1 of 1] Compiling Main ( Test.hs, Test.o ) > > Test.hs:2:13: > Can't make a derived instance of ?Functor MyMaybe? > (even with cunning newtype deriving): > You need DeriveFunctor to derive an instance for this class > Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension > In the newtype declaration for ?MyMaybe? > }}} > > It works fine if I remove `DeriveAnyClass`: > > {{{ > ? deriveany_bug ghc --make -fforce-recomp Test.hs > -XGeneralizedNewtypeDeriving > [1 of 1] Compiling Main ( Test.hs, Test.o ) > Linking Test ... > }}} > > GHC HEAD is failing in exactly the same way. > > User manual is saying this in 7.5.6: > > > In case you try to derive some class on a newtype, and > -XGeneralizedNewtypeDeriving is also on, -XDeriveAnyClass takes > precedence. > > But then why is it telling me to enable `GeneralizedNewtypeDeriving` in > the error message? Even if I already enabled it? > > Also, maybe it could try `GND` when `DeriveAnyClass` fails? Because the > doc is saying `DeriveAnyClass` has precedence but doesn't specify what > happens if it fails. New description: I think we definitely have a bug here, but I'm not sure what it really is. Here's the program: {{{ newtype MyMaybe a = MyMaybe (Maybe a) deriving (Functor, Show) main = print $ MyMaybe $ Just (10 :: Int) }}} I'm using GHC 7.10.1. {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XDeriveAnyClass -XGeneralizedNewtypeDeriving [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:2:13: Can't make a derived instance of ?Functor MyMaybe? (even with cunning newtype deriving): You need DeriveFunctor to derive an instance for this class Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension In the newtype declaration for ?MyMaybe? }}} Just to try, changing argument order: {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XGeneralizedNewtypeDeriving -XDeriveAnyClass [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:2:13: Can't make a derived instance of ?Functor MyMaybe? (even with cunning newtype deriving): You need DeriveFunctor to derive an instance for this class Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension In the newtype declaration for ?MyMaybe? }}} It works fine if I remove `DeriveAnyClass`: {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XGeneralizedNewtypeDeriving [1 of 1] Compiling Main ( Test.hs, Test.o ) Linking Test ... }}} GHC HEAD is failing in exactly the same way. User manual is saying this in 7.5.6: > In case you try to derive some class on a newtype, and -XGeneralizedNewtypeDeriving is also on, -XDeriveAnyClass takes precedence. But then why is it telling me to enable `GeneralizedNewtypeDeriving` in the error message? Even if I already enabled it? Also, maybe it could try `GND` when `DeriveAnyClass` fails? Because the doc is saying `DeriveAnyClass` has precedence but doesn't specify what happens if it fails. EDIT: I'd like to work on this myself if experts here help me figuring the right behavior here. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 00:39:59 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 00:39:59 -0000 Subject: [GHC] #3541: Allow local foreign imports In-Reply-To: <044.f182d5c0327086f8b5193630cf333bb0@haskell.org> References: <044.f182d5c0327086f8b5193630cf333bb0@haskell.org> Message-ID: <059.b461326a8265f7658b820c3b1dc68f63@haskell.org> #3541: Allow local foreign imports -------------------------------------+------------------------------------- Reporter: mokus | Owner: Type: feature request | DevarshDesai Priority: normal | Status: new Component: Compiler (FFI) | Milestone: ? Resolution: | Version: 6.12.2 Operating System: Unknown/Multiple | Keywords: newcomer Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: omeragacan@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 02:12:38 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 02:12: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.97551cfec227d1a02fe363c996925a3f@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): The documentation says "With `-XDeriveAnyClass` you can derive any other class", where "other" seems to allude to the classes which can be derived by GHC extensions as described in sections 7.5.3 and 7.5.4 (we have to ignore section 7.5.5 here since the interaction with GND is described explicitly), as well as, presumably, the classes which can be derived in Haskell 2010. And, in fact, if you try to compile your test case with `-XDeriveAnyClass` only, GHC tells you {{{ Test.hs:2:13: Can't make a derived instance of ?Functor MyMaybe?: You need DeriveFunctor to derive an instance for this class Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension In the newtype declaration for ?MyMaybe? }}} which is consistent with this interpretation (it's the same error you get without `-XDeriveAnyClass`). So, I would expect that in all cases of `deriving (Functor)`, the presence of `-XDeriveAnyClass` should have no effect. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 02:27:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 02:27:18 -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.bdacf39ee2d9c62cd6601181776cfe20@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): It sounds to me, from the original summary, that GHC is behaving as documented, with the exception of a poor choice of error message. Fixing the error message is one way forward. But -- if you're keen on this sort of thing -- what would be even better is to come up with a way for users to direct GHC in this matter. GHC now has 3 distinct ways of `deriving` classes: the built-in way (extended beyond Haskell 2010 by various extensions), the GND way, and the !DeriveAnyClass way. In your example, they are '''all''' applicable (at least with `-XDeriveFunctor` on). And, I believe they will each produce different instances! What I've wanted here is to have some way to control GHC's choice of `deriving` mechanism, per instance. Something like {{{ newtype MyMaybe a = Mk (Maybe a) deriving( {-# GND #-} Functor , {-# BuiltIn #-} Show , {-# GND #-} Read , {-# Any #-} FromJSON ) }}} Now, the user chooses what facility provides the instances. Note that I've done something currently impossible: I've used GND for the `Read` class. Normally, we don't want this behavior, and (to my knowledge) there's no way to convince GHC to use GND to derive a `Read` or `Show` instance. But maybe some user out there does want it. This, of course, needs to be extended to standalone-deriving, and all the details (particularly, what are the default choices for the `deriving` mechanism) need to be worked out. If you (or anyone else) wants to have a go at this, I'd happily lend a hand. Or, if you're not ready to tackle feature design, we'd gladly welcome a patch just to fix the (clearly broken) error message originally reported. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 03:10:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 03:10:36 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.d9d8ffdae114dc98f6a4acf2ecfb9989@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:3 bgamari]: > Edsko and I were thinking about this a bit in light of the recent discussion on Reddit. He had what I thought was a rather nice idea: ... I think the idea of embedding richer info into `SDoc` is a good one. In particular, I like the idea that this enables a gradual transition. For example, we could have some large ADT defined in !TcErrors that represents all of the errors that the module produces (but not other modules). Then some of the downside of the big-ADT approach that Simon is worried about is reduced. And then we could do another module... and so on. However, I think indexing `SDoc` is going to lead to trouble. We won't be able to have lists of errors that originated in disparate parts of the compiler. And we won't be able to embed multiple types of information in the same error message. Instead, what if we just use dynamic typing here? (gasp!) By this, I mean something like {{{ data Doc = forall a. Typeable a => Embed a | Empty | ... }}} When pulling out embedded bits, we just use dynamic checks to get the types. Although this seems somewhat un-Haskellish, I think it's forced by the very-dynamic nature of an error message. During parsing, a consumer can discover what type of embedded information should be at a certain spot, and then do the dynamic check. This seems like just the sort of thing that dynamic typing excels at. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 03:12:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 03:12:56 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` Message-ID: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 7.10.1 Haskell | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Using `type` as a name is, of course, forbidden. OTOH, `type_1` is allowed as a name. However, using GHC 7.10.1 and `ghc --make T.hs` on files: {{{#!hs -- T.hs {-# LANGUAGE TemplateHaskell #-} module T where import Q test -- Q.hs module Q where import Language.Haskell.TH test :: Q [Dec] test = do t <- newName "type" return [FunD t [Clause [] (NormalB $ LitE $ CharL 't') []]] }}} Leads to the following error: {{{ $ ghc --make -ddump-splices T.hs [2 of 2] Compiling T ( T.hs, T.o ) T.hs:6:1: Illegal variable name: ?type? When splicing a TH declaration: ident_0 type_1 = type_1 }}} The above example works fine for GHC 7.8.4, so it's a regression. Reference: https://github.com/yesodweb/persistent/issues/412 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 03:15:31 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 03:15:31 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.05c1c0a74da220d8baa5e9d8c0f89efc@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by GregWeber): I just tested on 7.10.2 (the docker image which uses the hvr ppa). ``` ? th-bug docker run --rm -v `pwd`:/proj -w /proj haskell:7.10.2 ghc T.hs [1 of 2] Compiling Q ( Q.hs, Q.o ) [2 of 2] Compiling T ( T.hs, T.o ) T.hs:5:1: Illegal variable name: ?type? When splicing a TH declaration: ident_0 type_1 = type_1 ``` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 03:18:46 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 03:18:46 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.49585b69d1e42effb1d73a25b1e52a90@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by GregWeber): * priority: normal => high * version: 7.10.1 => 7.10.2-rc2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 03:41:08 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 03:41:08 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.dfbb4de77d6642872aa99635c76d35eb@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire * milestone: => 7.12.1 Comment: Interesting. Part of the confusion here is that names generated by `newName` are different from other names you can use in Haskell. So when you say `newName "type"`, the variable's name really is `type`, but because it comes from `newName`, GHC prints it specially, as it's '''different''' from any other variable named `type`. So what you're trying to do -- create a variable named `type` -- is objectionable. It's just that the pretty-printer makes it look more sensible. On the other hand, there is no reason at all for TH to be picky about `newName` names. GHC got pickier about TH names between 7.8 and 7.10 because 7.8 allowed non-`newName` names that aren't allowed in Haskell, making variables that can't be referred to outside of TH. However, with `newName`, the whole point is that you can't refer to them outside of TH. So I think an improvement would be just to let `newName` be very liberal in what it accepts. As I'm inclined to say that GHC is doing the Right Thing here (that is, rejecting a variable named `type`), it seems most sensible to wait until 7.12 to fix. But if this is ruining your day, speak up. I don't feel very strongly on this point, at all. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 05:40:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 05:40:56 -0000 Subject: [GHC] #10447: DeriveFoldable rejects instances with constraints in last argument of data type In-Reply-To: <050.655803d4d5fe3ef1b8f5abc5e3585493@haskell.org> References: <050.655803d4d5fe3ef1b8f5abc5e3585493@haskell.org> Message-ID: <065.34bd06dcfb2eb31725d1534f335a4873@haskell.org> #10447: DeriveFoldable rejects instances with constraints in last argument of data type -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8678 | Differential Revisions: Phab:D1031 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D1031 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 07:23:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 07:23:36 -0000 Subject: [GHC] #10600: -fwarn-incomplete-patterns doesn't work with -fno-code Message-ID: <043.972d3170891da80a4e96bca7b675a836@haskell.org> #10600: -fwarn-incomplete-patterns doesn't work with -fno-code -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: | -------------------------------------+------------------------------------- `-fwarn-incomplete-patterns` doensn't seem to generate any warnings when `-fno-code` is specified. To reproduce, save this module as `foo.hs`. {{{#!hs module Foo where foo True = 4 }}} and compile with `-fwarn-incomplete-patterns`, with and without `-fno- code`. {{{ % ghc -fwarn-incomplete-patterns -fforce-recomp foo.hs [1 of 1] Compiling Foo ( foo.hs, foo.o ) foo.hs:2:1: Warning: Pattern match(es) are non-exhaustive In an equation for ?foo?: Patterns not matched: False % ghc -fwarn-incomplete-patterns -fforce-recomp -fno-code foo.hs [1 of 1] Compiling Foo ( foo.hs, nothing ) % }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 07:44:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 07:44:44 -0000 Subject: [GHC] #9007: fails to build with hardening flags enabled (relocation R_X86_64_32 against `stg_CHARLIKE_closure'...) In-Reply-To: <046.e2d123aa0cc7380f3c5c662bb8d8022e@haskell.org> References: <046.e2d123aa0cc7380f3c5c662bb8d8022e@haskell.org> Message-ID: <061.6b3f656f3e8727ed6d41212752e228d1@haskell.org> #9007: fails to build with hardening flags enabled (relocation R_X86_64_32 against `stg_CHARLIKE_closure'...) -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: bug | Status: infoneeded Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): Replying to [comment:21 kgardas]: > Replying to [comment:19 slyfox]: > > Hardened gentoo patches gcc to default to -fPIC -fPIE -pie. Defaults there: > > ... > > An evil corner case as we use ld for partial linking. Can be an argument for native > > fPIE/pie support in ghc. > > I'm curious but isn't -split-objs purely static library thing? IMHO it's not usable for -shared nor -dynamic nor -fPIC etc. Please correct me if I'm wrong here... A couple of points here: - -fPIC is valid for static libraries (it's used for hardening even statically linked binaries), recent example of accidental fPIC no a static haskell library: https://ghc.haskell.org/trac/ghc/ticket/10402#comment:14 . It's not necessary but not outright harmful. - -split-objs used to split .o files into smaller .o files to allow linker remove unused code. That unused code can come from: - external static haskell library (typical case) when linking static binary, no need to run -spit-objs - internal static or dynamic haskell library (or binary) I would say it makes sense to run -split-objs every time object files are produced. I view it as trick similar to 'gcc -function-sections -fdata- sections -Wl,--gc-sections'. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 07:51:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 07:51:56 -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.c7e172dbe8bdaba276dbcddd9d38052f@haskell.org> #10600: -fwarn-incomplete-patterns doesn't work with -fno-code -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.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: Blocked By: | Blocking: Related Tickets: #8101 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * related: => #8101 * milestone: => 7.12.1 Comment: This has been addressed before in #8101. The fix there doesn't seem to work, and is missing a test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 08:09:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 08:09:58 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.cb556c18871f736e4f26ccec07cd2043@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ekmett): As a brief addendum: You _could_ reference a non-`newName`'d variable named `type` that was produced from within `template-haskell` from within the language before: `Foo.type` parsed just fine as a qualified name. (This has apparently happened in some code folks have out there using `lens`.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 08:18:53 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 08:18:53 -0000 Subject: [GHC] #8881: No way to unsubscribe a bug In-Reply-To: <046.3e20bef03cc312ed086d6bf0a5bf092e@haskell.org> References: <046.3e20bef03cc312ed086d6bf0a5bf092e@haskell.org> Message-ID: <061.efc7a9d279f9dd2f5498227927c59ab1@haskell.org> #8881: No way to unsubscribe a bug -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Trac & Git | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: 9138 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ulysses4ever): * owner: hvr => * status: closed => new * resolution: invalid => Comment: > Nothing we can do about it. That is not excatly true, because there is a workaround suggested in [http://trac.edgewall.org/ticket/9971 your link]: change Trac setting `always_notify_updater` into `always_cc_updater`. It adds a commenter to a Cc list and then he can remove himself from the list through modifying a ticket. All Cc'ed users receive emails, so a commenter is automatically have subscription but can dissolve it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 08:37:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 08:37:55 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.64a250afcd013243a9cf96c0dad031c3@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): It seems to me that we should be closing up the cases where `type` can be used as a name, not opening more of these holes. It would be quite confusing to the user if they end up with a situation where a they see an export named `type`, find that it can be imported without trouble if qualified, and then try to define another similarly named definition without of TH, only to find that they get a syntax error. I'm not entirely sure what we want to do about the parsing issue, but it seems that TH's current behavior is what we would want here, no? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 08:59:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 08:59:56 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.fd644061722b5b8667ebcc2c9a9c9270@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): goldfire, indeed the an ADT-per-compiler-phase is exactly what I was thinking (and I have the beginnings of a branch looking at `TcErrors` in particular. In my case though, I was thinking of at least starting by merely annotating a few semantically-important elements of the message (e.g. `Name`s, `Type`s, `TyVar`s, etc.). This would enable, for instance, allow links to the definition span of a symbol, printing an expanded representation of a type, etc. That being said, there is no reason why one couldn't go further with this same approach and encode the entire error as a value. This certainly offers further advantages, although also implies a bit more work (which is why I'm starting with the atoms listed above). As far as the indexing issue goes, I was thinking we would give `Doc` a `Monad` instance. This would allow a number of quite convenient patterns. For instance, have `msgs :: Doc TcErrDoc` containing some errors you'd like to print: If you have `pprTcErrDoc :: TcErrDoc -> Doc Void`, you could trivially flatten the document with `msgs >>= pprTcErrDoc`. Further if you want to combine a `Doc TcErrDoc` with a `Doc ParserErrDoc`, you'd simply lift them both into an ADT `data GhcErrDoc = TcErrDoc TcErrDoc | ParserErrDoc ParserErrDoc` with `Applicative`. Alternatively, if you'd rather keep the universe of error types open, you could opt to lift them into a universally quantified `newtype`, roughly like you suggest. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 09:14:07 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 09:14:07 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.86dd01fbaba100cfe09cc488556db72b@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): I should note that adding an index and `Monad` instance to `Doc` isn't entirely trivial. I believe it is possible (and have a patch with much of the work) but I haven't yet proven to myself that it will preserve the invariants that the Hughes pretty-printer expects. There are a few implementations of annotated pretty-printers of various flavors on Hackage, but they either provide only `Functor` (e.g. [[http://hackage.haskell.org/package/pretty-1.1.3.2/docs/Text-PrettyPrint- Annotated.html|pretty]], [[http://hackage.haskell.org/package/annotated- wl-pprint-0.6.0/docs/Text-PrettyPrint-Annotated-Leijen.html|annotated-wl- pprint]]), or are of the Wadler-Leijan variety (e.g. [[http://hackage.haskell.org/package/wl-pprint-extras-3.5.0.5/docs/Text- PrettyPrint-Free-Internal.html|wl-pprint-extras]]). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 09:27:09 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 09:27:09 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.7dd9c7fa7691c42d2995f08859cd51fb@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by sopvop): As a workaround for vinyl removing INLINE pragma from rcast helps. Produced core is similar to 7.10.1 with INLINE pragma. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 10:41:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 10:41:05 -0000 Subject: [GHC] #9977: Nicer imports In-Reply-To: <045.95372b208ceb242d2c3dcf27f2958596@haskell.org> References: <045.95372b208ceb242d2c3dcf27f2958596@haskell.org> Message-ID: <060.1dab92a75c5e626b9fad3cbeede723b0@haskell.org> #9977: Nicer imports -------------------------------------+------------------------------------- Reporter: tolysz | Owner: Type: feature request | Status: closed Priority: lowest | Milestone: ? Component: Compiler | Version: 7.11 (Parser) | Keywords: imports Resolution: wontfix | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => wontfix Comment: Try to get support for this on one of the mailing lists first. See also: WorkingConventions/AddingFeatures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 10:42:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 10:42:10 -0000 Subject: [GHC] #285: hp-ux 11.11 binaries In-Reply-To: <044.973042cd7618270d83934312097da719@haskell.org> References: <044.973042cd7618270d83934312097da719@haskell.org> Message-ID: <059.f12e0c51904f8ac91c6af656d2079659@haskell.org> #285: hp-ux 11.11 binaries ------------------------------------+--------------------------------- Reporter: amyhr | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ? Component: None | Version: None Resolution: wontfix | Keywords: Operating System: HPUX | Architecture: hppa Type of failure: None/Unknown | Test Case: N/A Blocked By: | Blocking: Related Tickets: | Differential Revisions: ------------------------------------+--------------------------------- Changes (by thomie): * status: new => closed * failure: => None/Unknown * resolution: None => wontfix Comment: No activity in 8 years. Closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:04:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:04:05 -0000 Subject: [GHC] #5239: Em-dash for "--" with UnicodeSyntax. In-Reply-To: <045.d30aa0f82b842c2a0e88ff4c0f31f0c3@haskell.org> References: <045.d30aa0f82b842c2a0e88ff4c0f31f0c3@haskell.org> Message-ID: <060.2d5c2bf7b2e4030492f9d0bb5e18d03d@haskell.org> #5239: Em-dash for "--" with UnicodeSyntax. -------------------------------------+------------------------------------- Reporter: Eelis- | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ? Component: Compiler | Version: 7.0.3 (Parser) | Keywords: unicode Resolution: invalid | syntax extension Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => invalid * milestone: 7.12.1 => ? Comment: Please try to get support for this feature on one of the mailing lists first. See also: WorkingConventions/AddingFeatures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:05:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:05:06 -0000 Subject: [GHC] #9119: Additional symbols for XUnicodeSyntax In-Reply-To: <050.28440c83618567b1dad67ee6e8f31e47@haskell.org> References: <050.28440c83618567b1dad67ee6e8f31e47@haskell.org> Message-ID: <065.11f589cda60d2d5c3c62cc75a1bebe1f@haskell.org> #9119: Additional symbols for XUnicodeSyntax -------------------------------------+------------------------------------- Reporter: spacekitteh | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ? Component: Compiler | Version: 7.8.2 (Parser) | Keywords: unicode Resolution: invalid | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => invalid * milestone: => ? Comment: See also: WorkingConventions/AddingFeatures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:05:59 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:05:59 -0000 Subject: [GHC] #9748: Disambiguate IO actions in GHCi with :set +t In-Reply-To: <051.eb64c51829f1760c379502433f79e297@haskell.org> References: <051.eb64c51829f1760c379502433f79e297@haskell.org> Message-ID: <066.e59af216529f8306916d955d4500bb88@haskell.org> #9748: Disambiguate IO actions in GHCi with :set +t -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by zudov): * owner: zudov => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:21:50 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:21:50 -0000 Subject: [GHC] #5542: also parse class/instance declarations as "HEAD <= CONTEXT where" In-Reply-To: <046.9fbd477508d5f525ff2af0d477b5cc3e@haskell.org> References: <046.9fbd477508d5f525ff2af0d477b5cc3e@haskell.org> Message-ID: <061.88378fa1f111cc5a9d1a3831dc3af8b0@haskell.org> #5542: also parse class/instance declarations as "HEAD <= CONTEXT where" -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: feature request | Status: new Priority: normal | Milestone: ? Component: Compiler | Version: 7.2.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * milestone: 7.12.1 => ? Comment: Please try to get support for this feature on one of the mailing lists first. See also: WorkingConventions/AddingFeatures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:22:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:22:06 -0000 Subject: [GHC] #5542: also parse class/instance declarations as "HEAD <= CONTEXT where" In-Reply-To: <046.9fbd477508d5f525ff2af0d477b5cc3e@haskell.org> References: <046.9fbd477508d5f525ff2af0d477b5cc3e@haskell.org> Message-ID: <061.40a5d3b36e257d30a51115947a80594a@haskell.org> #5542: also parse class/instance declarations as "HEAD <= CONTEXT where" -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ? Component: Compiler | Version: 7.2.1 (Parser) | Keywords: Resolution: invalid | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => invalid -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:22:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:22:10 -0000 Subject: [GHC] #10394: LLVM mangler doesn't mangle AVX instructions In-Reply-To: <047.b85b8723ab1fa78e7e23f08be8ccae23@haskell.org> References: <047.b85b8723ab1fa78e7e23f08be8ccae23@haskell.org> Message-ID: <062.31210844e0a207a9e24452cf4268068f@haskell.org> #10394: LLVM mangler doesn't mangle AVX instructions -------------------------------------+------------------------------------- Reporter: dobenour | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler (LLVM) | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1034 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D1034 Comment: I've opened Phab:D1034 with this. dobenour, you should feel free to commandeer this Diff so it has the proper attribution. I'll review the patch itself on Phab. Indeed it would be nice if we could eliminate this mangling altogether. I'll add it to my queue although that shouldn't discourage others from looking at this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:22:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:22:17 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.aea4b0354b3e02ae945b0d1008d3215c@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by GregWeber): > So when you say newName "type", the variable's name really is type, but because it comes from newName, GHC prints it specially, as it's different from any other variable named type. So what you're trying to do -- create a variable named type -- is objectionable This isn't the goal here. If it was, `mkName` would be used. > It seems to me that we should be closing up the cases where type can be used as a name, not opening more of these holes. It would be quite confusing to the user if they end up with a situation where a they see an export named type, find that it can be imported without trouble if qualified, and then try to define another similarly named definition without of TH, only to find that they get a syntax error. Again, "type" is not being used for a name but instead to seed a new name From a TH user perspective it seems that in 7.10 `newName` has become a leaky abstraction where I am forced to understand how GHC is internalizing these names in a way that is different than what is printed out. As a library author, I can certainly work around this. But it isn't something I would think to test and I only found out about it when a user reported that their program stopped working on 7.10. So at this point there is no way for us to quantify the breakage it would cause. I would expect it to be fairly rare that a name gets into a TH function that is reserved as an identifier: for persistent this happens because it later adds a record field prefix to the name before generating a record field. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:35:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:35:05 -0000 Subject: [GHC] #10530: Update transformers library In-Reply-To: <052.0c31d10f46f9c718da9cede6af3f558b@haskell.org> References: <052.0c31d10f46f9c718da9cede6af3f558b@haskell.org> Message-ID: <067.26957a9d1a892c7f1efd11899c1352a3@haskell.org> #10530: Update transformers library -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: libraries | Version: 7.10.2-rc2 (other) | Keywords: Resolution: | transformers Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by asr): * version: 7.10.2-rc1 => 7.10.2-rc2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:42:25 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:42:25 -0000 Subject: [GHC] #10289: compiling huge HashSet hogs memory In-Reply-To: <044.7a75381e3cbd52797d1fc50b07f81ee0@haskell.org> References: <044.7a75381e3cbd52797d1fc50b07f81ee0@haskell.org> Message-ID: <059.cf0d70c05d4832e86d7c1ec1ab0b88fd@haskell.org> #10289: compiling huge HashSet hogs memory -------------------------------------+------------------------------------- Reporter: zudov | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by zudov): I've just tried to run the build, and it still runs OOM. I guess travis just doesn't have enough memory. https://travis-ci.org/zudov/html5-entity/jobs/69424559#L519 Replying to [comment:4 thoughtpolice]: > After looking back at my tests, the situation should be significantly better with GHC 7.10.2 based on my quick examination; the resident memory usage for me at least looks to be closer to 2GB on my machine. However, the total build time seems to be worse (1m52s to compile `EntrySet` at `-O2` vs your Travis machines ~30 seconds, but only a maximum residency of 2GB). > > So there's still more to be done here, but enabling -O2 shouldn't cripple you anymore at least. > > Would you mind giving this a go with the latest `ghc-7.10` branch (or the 7.10.2 RC, which will be out soon?) You can use Herbert's PPA in combination with travis to get automated testing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:42:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:42:42 -0000 Subject: [GHC] #8809: Prettier error messages? In-Reply-To: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> References: <047.4dbdad421fcd945584d210433034ccb5@haskell.org> Message-ID: <062.3b433652297be86a29c782335d1e19e2@haskell.org> #8809: Prettier error messages? -------------------------------------+------------------------------------- Reporter: joelteon | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Check out * [http://www.itu.dk/people/drc/drafts/error-reflection-submission.pdf Reflect on your mistakes] (TFP 14), by [https://www.itu.dk/people/drc/ David Christansen], in Idris. * [http://www.davidchristiansen.dk/2014/09/06/pretty-printing-idris/ A pretty printer that says what it means], also David Christiansen Any other useful links? I'm all in favour of this kind of thinking but it needs careful thinking through. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:50:07 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:50:07 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.acf60b09963fc7ecd7ae087f7df33ecf@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Good news on this front; I think I've identified what is going on. Patch coming. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:55:30 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:55:30 -0000 Subject: [GHC] #10162: Add unicode syntax for banana brackets In-Reply-To: <045.f7ad53896487f5f5496f96174e92dff7@haskell.org> References: <045.f7ad53896487f5f5496f96174e92dff7@haskell.org> Message-ID: <060.d708841a9a3a915894ac2d15542a8fbf@haskell.org> #10162: Add unicode syntax for banana brackets -------------------------------------+------------------------------------- Reporter: zardoz | Owner: Type: feature request | Status: closed Priority: low | Milestone: ? Component: Compiler | Version: 7.8.4 (Parser) | Keywords: unicode, Resolution: invalid | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => unicode, UnicodeSyntax * resolution: => invalid * status: new => closed * component: Compiler => Compiler (Parser) * milestone: => ? Comment: I'm closing some of these `unicode` related feature requests, as a discussion needs to happen first on one of the mailing lists. Please reopen this ticket once there is sufficient support. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 11:56:07 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 11:56:07 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2310006=3A_Add_baseline_ellipsis_as_u?= =?utf-8?q?nicode_alternative_to_=C2=AB=2E=2E=C2=BB?= In-Reply-To: <045.85f8084d7488f7960b150b416bd80d83@haskell.org> References: <045.85f8084d7488f7960b150b416bd80d83@haskell.org> Message-ID: <060.c6245980419f6bc9a157cbbde376f5f1@haskell.org> #10006: Add baseline ellipsis as unicode alternative to ?..? -------------------------------------+------------------------------------- Reporter: zardoz | Owner: Type: feature request | Status: closed Priority: normal | Milestone: ? Component: Compiler | Version: 7.8.4 (Parser) | Keywords: unicode, Resolution: invalid | UnicodeSyntax Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #3894 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => unicode, UnicodeSyntax * status: new => closed * resolution: => invalid * milestone: => ? Comment: I'm closing some of these `unicode` related feature requests, as a discussion needs to happen first on one of the mailing lists. Please reopen this ticket once there is sufficient support. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 12:08:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 12:08:58 -0000 Subject: [GHC] #10498: "if ... then \case -> else ..." causes a "missing else clause" error In-Reply-To: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> References: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> Message-ID: <065.4807f5ffd5ee882211d360b14cc5245a@haskell.org> #10498: "if ... then \case -> else ..." causes a "missing else clause" error -------------------------------------+------------------------------------- Reporter: dramforever | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: MikeIzbicki (added) * milestone: => 7.10.3 Comment: @MikeIzbicki: as the author of Phab:D201, could you have a look? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 12:18:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 12:18:35 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.163e3a1698f4de98310996d14ae18554@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Drat. On further reflection I the cardinality analysis is correct. So it looks as though there is a bug in the runtime system. '''Simon M''': might you find time to investigate? With only two single- entry thunks it can't be that hard! I have literally no hypothesis for why a single-entry thunk could cause ``. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 13:30:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 13:30:35 -0000 Subject: [GHC] #1388: Newbie help features In-Reply-To: <044.efaff92cf2e79b2f529fa901fdcbafbb@haskell.org> References: <044.efaff92cf2e79b2f529fa901fdcbafbb@haskell.org> Message-ID: <059.4995d4e5c1fdf6829daaf882b2fe259a@haskell.org> #1388: Newbie help features -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: feature request | Status: closed Priority: low | Milestone: ? Component: GHCi | Version: 6.6.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #4929, #7253, | Blocking: #9177 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * related: #4929 => #4929, #7253, #9177 Comment: > "why doesn't `f = 1` work?" (that is function definitions) This is the only part remaining for this ticket, and already tracked as #7253. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 13:37:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 13:37:10 -0000 Subject: [GHC] #10416: GHC 7.10.1 User Guide profiling section 5.4 missing images In-Reply-To: <044.0e4dde9e3a0324f18f8091c422680492@haskell.org> References: <044.0e4dde9e3a0324f18f8091c422680492@haskell.org> Message-ID: <059.76822b08c38175f29e5a8f067f1a3a2c@haskell.org> #10416: GHC 7.10.1 User Guide profiling section 5.4 missing images -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Documentation | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D958, | Phab:D970 -------------------------------------+------------------------------------- Comment (by alanz): This appears still to be broken in rc2 http://downloads.haskell.org/~ghc/7.10.2-rc2/docs/html/users_guide/prof- heap.html The image link now refers to http://downloads.haskell.org/~ghc/7.10.2-rc2/docs/html/users_guide/prof_scc.eps -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 13:39:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 13:39:17 -0000 Subject: [GHC] #10416: GHC 7.10.1 User Guide profiling section 5.4 missing images In-Reply-To: <044.0e4dde9e3a0324f18f8091c422680492@haskell.org> References: <044.0e4dde9e3a0324f18f8091c422680492@haskell.org> Message-ID: <059.bbf48636879fc2a45866883514dfbf05@haskell.org> #10416: GHC 7.10.1 User Guide profiling section 5.4 missing images -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Documentation | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D958, | Phab:D970 -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: fixed => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 13:39:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 13:39:32 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.bd7b4a556523d40f6cf995247a6d5faf@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:5 bgamari]: > It would be quite confusing to the user if they end up with a situation where a they see an export named `type`, Ah. Good point. I hadn't thought about exports. If `newName`s were used only as locals, we would be fine with a very liberal treatment for `newName`. But once we think about exporting, we do run into an issue. Come to think of it, we really shouldn't allow exporting of names created with `newName`. As Greg has pointed out, there's no reason a user should assume that a `newName "foo"` creates a variable named `foo`. If we allow exporting, then `newName`s are leaky, indeed. If we disallow exports, would that alleviate your concerns, Ben? At that point, we should really allow any (non-empty?) string as the argument for `newName`. I think Greg is spot on in suggesting that the argument to `newName` is merely a seed, not the name in question. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 13:49:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 13:49:55 -0000 Subject: [GHC] #10162: Add unicode syntax for banana brackets In-Reply-To: <045.f7ad53896487f5f5496f96174e92dff7@haskell.org> References: <045.f7ad53896487f5f5496f96174e92dff7@haskell.org> Message-ID: <060.68aa2136b9c66499b862062ebb0258ca@haskell.org> #10162: Add unicode syntax for banana brackets -------------------------------------+------------------------------------- Reporter: zardoz | Owner: Type: feature request | Status: new Priority: low | Milestone: ? Component: Compiler | Version: 7.8.4 (Parser) | Keywords: unicode, Resolution: | UnicodeSyntax, newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: unicode, UnicodeSyntax => unicode, UnicodeSyntax, newcomer * status: closed => new * resolution: invalid => Comment: Though getting a groundswell of support for feature requests is indeed a good idea, this one here seems pretty obviously a good idea, to me. It's a great way for a newcomer to contribute! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 14:25:14 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 14:25:14 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.8f019f03ffc645a100ba9ab7cdcc419e@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I think I've finally come up with at least part of a plausible explanation. Tell me if this seems right... Suppose I have a heap object whose initial value is {{{ x = \u [] concat [[1],[]] -- using "\u []" as syntax for "updatable thunk", -- otherwise normal Core syntax (not STG) }}} and suppose first some thread evaluates `x` to WHNF. Using the definition of `concat` as `main_go` from above, this will allocate a single-entry thunk `y = \s [] concat []`, and then calling `(++)` will lead to {{{ x = 1 : z y = \s [] concat [] z = \u [] (++) [] y }}} At this point the heap has the following property (*) The heap contains a single-entry thunk (`y`) and a regular thunk (`z`) such that entering the regular thunk will cause the single-entry thunk to be entered as well. (The key point is that the single-entry thunk has already been allocated on the heap, in contrast to a situation in which entering a regular thunk would cause a ''new'' single-entry thunk to be allocated, possibly entered, and then become garbage, all before evaluation of that regular thunk is complete.) Now, consider the following execution path of two threads A and B. * Both threads enter `z` simultaneously (before either manages to overwrite it with a black hole, if eager blackholing was enabled when we compiled `(++)`; otherwise before either manages to update it to an indirection). * Thread A does the case analysis inside `(++)` and enters `y`, and overwrites it with a black hole before thread B does anything else. * Now thread B does the case analysis inside `(++)` and enters `y`, but `y` has been overwritten with a black hole so thread B blocks. But `y` is never going to be updated, so thread B will block forever. This is bad! * Finally thread A finishes evaluating `y` (to `[]`) and then updates `z` accordingly. But thread B is still blocking on the black hole and even if it could get unblocked by some mechanism (say in the GC) there's no longer enough information on the heap to recover the correct value of `y` and allow thread B to continue. This doesn't exactly explain why the programs in this ticket <>, but a thread becoming permanently blocked is equally bad behavior I think. Some extra evidence that something like this is going on is that if I inline the definition of `(++)` into par2.hs as well, so that it is compiled with eager blackholing enabled, the program <>s much less frequently, just a few percent of the time as opposed to over half the time. That would match up with a smaller window of simultaneity in the first step of the execution trace above. If this analysis is correct, then assuming we want to continue to allow threads to enter thunks in an unsynchronized way (to avoid prohibitive locking costs), it seems we have to ensure that the condition (*) never holds, at least when eager blackholing is enabled. Generating single-entry thunks is still okay as long as they never survive as live heap objects after the thunk that allocated them has been reduced to WHNF. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 14:37:54 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 14:37:54 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.f83c556bc3122e10950eb21430f4dda9@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I also came across this comment in `rts/ThreadPaused.c` (I think it is concerning a different scenario): {{{ // NB. Blackholing is *compulsory*, we must either do lazy // blackholing, or eager blackholing consistently. See Note // [upd-black-hole] in sm/Scav.c. }}} Does this mean that every module in the entire program, including all the libraries the program links against like base, needs to be compiled with the same presence or absence of `-feager-blackholing`? The User's Guide doesn't mention anything about this and if that is the case, the flag seems essentially unusable except for those who are building their own GHC from source. I'm hoping the comment is just worded unclearly. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:03:13 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:03:13 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.7f4b1cae416537390618039f4bebbecc@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): We need Simon Marlow's advice here. What you say does seem plausible: * With lazy blackholing, a single-entry thunk will never be black-holed. Lazy black-holing only black-holes thunks with an update frame on the stack, and single-entry thunks do not push an update frame. So that could explain why `-feager-blackholing` is required. * Rather to my surprise, a single-entry thunk is black-holed. I can't see any good reason why this happens. Look at `StgCmmClosure.blackHoleOnEntry`. * Re comment:22 we need Simon to say. It would be pretty bad if every module had to be compiled consistently. However I note that the comment in `Scav.c` is in code that messes with update frames, and so single-entry thunks probably don't matter. Even if all this is right, we still don't know why we get `<>`. I'm assuming that this means we have entered a black hole, ''that is under evaluation by this thread''; but suddenly I'm not sure. (For a black hole being evaluated by another thread, we'd block.) I suggest you try making `blackHoleOnEntry` return False for single-entry thunks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:20:28 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:20:28 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.050f0bc3dee987854989ae13103a5629@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ekmett): I likewise agree with Greg. I'd expect to be able to call `newName` with more or less anything. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:27:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:27:35 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.95719270aba99772b4fc602003c8bd90@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonmar): Thanks for all the awesome debugging work here, I think we finally have all the pieces! @rwbarton's analysis seems plausible to me too. A single-entry thunk can still be entered multiple times in a parallel setting, and if eager blackholing is on then it is possible that a thread can get blocked indefinitely. Threads blocked indefinitely are detected by the GC as deadlocked, and receive an exception, which results in the `` message. The fix should be simple: just don't do eager blackholing for single-entry thunks. Regarding this comment: {{{ // NB. Blackholing is *compulsory*, we must either do lazy // blackholing, or eager blackholing consistently. See Note // [upd-black-hole] in sm/Scav.c. }}} It means every update frame must refer to a black hole by the time the GC runs, it's an invariant the GC relies on. It shouldn't be a problem here because it only applies to update frames. I can reword the comment so it's clearer. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:42:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:42:36 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.f0cbfd2ef93315f68abbff852aa5d3c4@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): See also #10318 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:51:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:51:27 -0000 Subject: [GHC] #10498: "if ... then \case -> else ..." causes a "missing else clause" error In-Reply-To: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> References: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> Message-ID: <065.80a5ebae1f8dafdce68cf1e8d4456b8c@haskell.org> #10498: "if ... then \case -> else ..." causes a "missing else clause" error -------------------------------------+------------------------------------- Reporter: dramforever | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): I'm sorry, but I doubt I'll have time to look into this anytime soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:53:16 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:53:16 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.46325b58d44dfdc39e3a047538cd2b21@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): The actual cause of the <> here seems to be that two threads are each blocking on a black hole that is being evaluated, or more likely has been evaluated but not updated, by the other thread. I attached a complete `-Ds` log above, but the relevant lines are {{{ ... 0.011574 7ff6be7fc700: cap 1: thread 6 stopped (blocked on black hole owned by thread 5) ... 0.011808 7ff6c6700740: cap 0: thread 5 stopped (blocked on black hole owned by thread 6) ... }}} I didn't work out exactly how this can arise, but it probably involves two single-entry thunks and two ordinary thunks whose evaluations force both of the single-entry thunks, but in different orders. Changing `blackHoleOnEntry` for single-entry thunks as suggested did fix `par2.hs`. I'm going to test the other examples in this ticket now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 15:54:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 15:54:58 -0000 Subject: [GHC] #8171: Extending ExtendedDefaultRules In-Reply-To: <045.d77bd9544286ea508e1fa1aea2399f0c@haskell.org> References: <045.d77bd9544286ea508e1fa1aea2399f0c@haskell.org> Message-ID: <060.01746ddd1a5c00f405f4d84f13a8a344@haskell.org> #8171: Extending ExtendedDefaultRules -------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kanetw): * owner: kanetw => Comment: Currently don't have the time for this, but I might revisit this later. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 16:01:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 16:01:42 -0000 Subject: [GHC] #10571: GHC 7.10.1 segfaults when shiftL-ing Integers by negative amounts In-Reply-To: <046.5fe10823e2d0a9badb1b3a63cbe8bcdb@haskell.org> References: <046.5fe10823e2d0a9badb1b3a63cbe8bcdb@haskell.org> Message-ID: <061.1ebb07bfab3ef84fb058e013fd78ea4b@haskell.org> #10571: GHC 7.10.1 segfaults when shiftL-ing Integers by negative amounts -------------------------------------+------------------------------------- Reporter: anders_ | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Runtime crash | (amd64) Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kanetw): Is there anything that prevents us from adding a guard that checks whether the shift amount is negative and giving an `error` when it is? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 16:15:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 16:15:44 -0000 Subject: [GHC] #10571: GHC 7.10.1 segfaults when shiftL-ing Integers by negative amounts In-Reply-To: <046.5fe10823e2d0a9badb1b3a63cbe8bcdb@haskell.org> References: <046.5fe10823e2d0a9badb1b3a63cbe8bcdb@haskell.org> Message-ID: <061.aaaeab4a8494f3d9af29c4f8d9609360@haskell.org> #10571: GHC 7.10.1 segfaults when shiftL-ing Integers by negative amounts -------------------------------------+------------------------------------- Reporter: anders_ | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Runtime crash | (amd64) Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Might not be possible inside integer-gmp for dependency reasons (`error` is defined in base which depends on integer-gmp) but certainly possible in the instance in Data.Bits. Having `shiftLInteger` itself crash on negative shifts is fine IMHO as it's not intended for end-user use. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 17:29:34 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 17:29:34 -0000 Subject: [GHC] #9863: Provide PowerPC 64 bit native code generator In-Reply-To: <047.abf3d61d6edeed38824d04625109fece@haskell.org> References: <047.abf3d61d6edeed38824d04625109fece@haskell.org> Message-ID: <062.dae6e7fbdcb72d28eca26bcca34ae496@haskell.org> #9863: Provide PowerPC 64 bit native code generator ------------------------------------+------------------------------------ Reporter: trommler | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: powerpc64 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D629 ------------------------------------+------------------------------------ Comment (by Ben Gamari ): In [changeset:"d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984" Implement PowerPC 64-bit native code backend for Linux Extend the PowerPC 32-bit native code generator for "64-bit PowerPC ELF Application Binary Interface Supplement 1.9" by Ian Lance Taylor and "Power Architecture 64-Bit ELF V2 ABI Specification -- OpenPOWER ABI for Linux Supplement" by IBM. The latter ABI is mainly used on POWER7/7+ and POWER8 Linux systems running in little-endian mode. The code generator supports both static and dynamic linking. PowerPC 64-bit code for ELF ABI 1.9 and 2 is mostly position independent anyway, and thus so is all the code emitted by the code generator. In other words, -fPIC does not make a difference. rts/stg/SMP.h support is implemented. Following the spirit of the introductory comment in PPC/CodeGen.hs, the rest of the code is a straightforward extension of the 32-bit implementation. Limitations: * Code is generated only in the medium code model, which is also gcc's default * Local symbols are not accessed directly, which seems to also be the case for 32-bit * LLVM does not work, but this does not work on 32-bit either * Must use the system runtime linker in GHCi, because the GHC linker for "static" object files (rts/Linker.c) for PPC 64-bit is not implemented. The system runtime (dynamic) linker works. * The handling of the system stack (register 1) is not ELF- compliant so stack traces break. Instead of allocating a new stack frame, spill code should use the "official" spill area in the current stack frame and deallocation code should restore the back chain * DWARF support is missing Fixes #9863 Test Plan: validate (on powerpc, too) Reviewers: simonmar, trofi, erikd, austin Reviewed By: trofi Subscribers: bgamari, arnons1, kgardas, thomie Differential Revision: https://phabricator.haskell.org/D629 GHC Trac Issues: #9863 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 17:54:01 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 17:54:01 -0000 Subject: [GHC] #10576: REPL returns list of all imported names when operator completion requested In-Reply-To: <047.d28f43369ab4f4eebeb74c70f6d59630@haskell.org> References: <047.d28f43369ab4f4eebeb74c70f6d59630@haskell.org> Message-ID: <062.14585dfba42c5407d9243893a9408e41@haskell.org> #10576: REPL returns list of all imported names when operator completion requested -------------------------------------+------------------------------------- Reporter: Geraldus | Owner: Geraldus Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | completions complete command Type of failure: Incorrect result | operator at runtime | Architecture: Blocked By: | Unknown/Multiple Related Tickets: #9996 | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Geraldus): * owner: thomie => Geraldus -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 18:08:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 18:08:36 -0000 Subject: [GHC] #4092: Floating point manipulation : ulp and coerce IEEE-754 Double# into Word64# In-Reply-To: <045.5cc829a852152f43b89d9843483d1a41@haskell.org> References: <045.5cc829a852152f43b89d9843483d1a41@haskell.org> Message-ID: <060.ae2bed4e476270d218a616882c6a8ae2@haskell.org> #4092: Floating point manipulation : ulp and coerce IEEE-754 Double# into Word64# -------------------------------------+------------------------------------- Reporter: malosh | Owner: bgamari Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * owner: => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 18:39:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 18:39:18 -0000 Subject: [GHC] #10402: powerpc: unhandled ELF relocation(RelA) type 252 In-Reply-To: <047.64cabbbba17f1f097b7e64d90dcccda9@haskell.org> References: <047.64cabbbba17f1f097b7e64d90dcccda9@haskell.org> Message-ID: <062.82cca37e93a5a12fb084a815b9cb9235@haskell.org> #10402: powerpc: unhandled ELF relocation(RelA) type 252 -----------------------------------+------------------------------------ Reporter: cjwatson | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Runtime System | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D996 -----------------------------------+------------------------------------ Comment (by nomeata): I uploaded 7.10.2-rc2 to Debian now, but it seems that something else broke here: {{{ rts/Linker.c: In function 'do_Elf_Rela_relocations': rts/Linker.c:5963:10: error: duplicate case value case R_PPC_PLTREL24: ^ rts/Linker.c:5959:10: error: previously used here case R_PPC_PLTREL24: ^ rts/Linker.c:5996:10: error: duplicate case value case R_PPC_REL16_LO: ^ rts/Linker.c:5984:10: error: previously used here case R_PPC_REL16_LO: ^ rts/Linker.c:6000:10: error: duplicate case value case R_PPC_REL16_HI: ^ rts/Linker.c:5988:10: error: previously used here case R_PPC_REL16_HI: ^ rts/Linker.c:6004:10: error: duplicate case value case R_PPC_REL16_HA: ^ rts/Linker.c:5992:10: error: previously used here case R_PPC_REL16_HA: ^ }}} https://buildd.debian.org/status/fetch.php?pkg=ghc&arch=powerpc&ver=7.10.1.20150630-1&stamp=1435929642 Any ideas? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 18:48:29 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 18:48:29 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.00dc892c56c9a5a3f5994968de754571@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by cheecheeo): * cc: cheecheeo@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 19:30:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 19:30:10 -0000 Subject: [GHC] #9675: Unreasonable memory usage on large data structures In-Reply-To: <047.9ab90e8da30a204a6defabed11bcf527@haskell.org> References: <047.9ab90e8da30a204a6defabed11bcf527@haskell.org> Message-ID: <062.f5c524698dd1bfe1c31974b6d972f55b@haskell.org> #9675: Unreasonable memory usage on large data structures -------------------------------------+------------------------------------- Reporter: Polarina | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b5e1944e2b069a7df3444e57bae0b4ee15bde73c/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b5e1944e2b069a7df3444e57bae0b4ee15bde73c" Use `+RTS -G1` for more stable residency measurements (#9675) Reviewers: ezyang, austin, thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1006 GHC Trac Issues: #10557 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 19:30:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 19:30:10 -0000 Subject: [GHC] #10557: Use `+RTS -G1` for more stable residency measurements In-Reply-To: <045.b69f224ec7b010fc435a2530f08e6526@haskell.org> References: <045.b69f224ec7b010fc435a2530f08e6526@haskell.org> Message-ID: <060.7d4515831018c8eb18352b4e714bd8a8@haskell.org> #10557: Use `+RTS -G1` for more stable residency measurements -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Test Suite | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b5e1944e2b069a7df3444e57bae0b4ee15bde73c/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b5e1944e2b069a7df3444e57bae0b4ee15bde73c" Use `+RTS -G1` for more stable residency measurements (#9675) Reviewers: ezyang, austin, thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1006 GHC Trac Issues: #10557 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:41:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:41:27 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.d9fbefa79ed2eea1b9b85bd3bd25e64d@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by George): Replying to [comment:3 trommler]: > Can you try with HEAD and/or the tip of the 7.10 branch, please. I just built 7.10.2 rc2 which just came out today: ghc -V The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150630 cabal install -j3 GLUT The problem is still here: ghci -package GLUT GHCi, version 7.10.1.20150630: http://www.haskell.org/ghc/ :? for help : can't load .so/.DLL for: /Users/gcolpitts/Library/Haskell/ghc-7.10.1.20150630-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -2JXXB99wAF71Fd1Kg3RhIm-ghc7.10.1.20150630.dylib (dlopen(/Users/gcolpitts/Library/Haskell/ghc-7.10.1.20150630-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -2JXXB99wAF71Fd1Kg3RhIm-ghc7.10.1.20150630.dylib, 5): Symbol not found: _glutBitmap8By13 Referenced from: /Users/gcolpitts/Library/Haskell/ghc-7.10.1.20150630-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -2JXXB99wAF71Fd1Kg3RhIm-ghc7.10.1.20150630.dylib Expected in: flat namespace in /Users/gcolpitts/Library/Haskell/ghc-7.10.1.20150630-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -2JXXB99wAF71Fd1Kg3RhIm-ghc7.10.1.20150630.dylib) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:42:23 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:42:23 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.853e4168e10db064e82a1d4363edee4a@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Changes (by George): * status: infoneeded => new -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:44:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:44:15 -0000 Subject: [GHC] #10439: Opt_ImplicitImportQualified doesn't work for constructor field name In-Reply-To: <046.7eeda0ab82b2b7fc80cf5d3190f2c3b2@haskell.org> References: <046.7eeda0ab82b2b7fc80cf5d3190f2c3b2@haskell.org> Message-ID: <061.7ec2545624928e1ec99f74ed406216bd@haskell.org> #10439: Opt_ImplicitImportQualified doesn't work for constructor field name -------------------------------------+------------------------------------- Reporter: watashi | Owner: watashi Type: bug | Status: patch Priority: highest | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Phab:D900 Related Tickets: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"1d6ead7d71ae9ad104f9bed9579462ce4a218594/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="1d6ead7d71ae9ad104f9bed9579462ce4a218594" Enable using qualified field of constructor in GHCi The -fimplicit-import-qualified made it possible to uses qualifed names in GHCi without explicitly import the modules. But it didn't work for field of constructor, this patch fixed this issue. Test Plan: cd testsuite/tests/rename/ && make cd testsuite/tests/ghci/ && make Reviewers: austin, simonpj Reviewed By: austin, simonpj Subscribers: bgamari, thomie Differential Revision: https://phabricator.haskell.org/D900 GHC Trac Issues: #10439 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:44:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:44:15 -0000 Subject: [GHC] #10519: Can't put wildcard behind forall In-Reply-To: <046.25f8a351d42fe346e193d0c867e5e854@haskell.org> References: <046.25f8a351d42fe346e193d0c867e5e854@haskell.org> Message-ID: <061.aaa0ca69b2731b238e4abecf81a23f6d@haskell.org> #10519: Can't put wildcard behind forall -------------------------------------+------------------------------------- Reporter: yongqli | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D994 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f8563838603f9a60f5012c3837142c5df89b8de2/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="f8563838603f9a60f5012c3837142c5df89b8de2" Fix Trac #10519 Look through nested foralls when checking the validity of a partial type signature. The combination of D836 and D613 prompts this change. Test Plan: The test T10519 must pass Reviewers: simonpj, alanz, austin Reviewed By: simonpj, alanz, austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D994 GHC Trac Issues: #10519 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:44:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:44:15 -0000 Subject: [GHC] #10023: Relax Monad constraint in traceM and traceShowM to Applicative In-Reply-To: <050.7023a64f597b119154f3ec65be43878d@haskell.org> References: <050.7023a64f597b119154f3ec65be43878d@haskell.org> Message-ID: <065.3ab242b5f78291bda183112cf849e27f@haskell.org> #10023: Relax Monad constraint in traceM and traceShowM to Applicative -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: new Component: libraries/base | Milestone: 7.12.1 Resolution: | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: newcomer Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1029 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"39d83f239d33b1d214bdb7f7b3ce94d76d3e1467/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="39d83f239d33b1d214bdb7f7b3ce94d76d3e1467" Generalize traceM, traceShowM (fixes #10023) This generalizes the type signatures of `traceM` and `traceShowM` to use `Applicative` rather than `Monad`. Reviewers: austin, ekmett, hvr, bgamari Reviewed By: ekmett, hvr, bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1029 GHC Trac Issues: #10023 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:44:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:44:15 -0000 Subject: [GHC] #10560: -f and -O options interact in non-obvious, order dependent ways In-Reply-To: <046.4b383b5f0fce35e0e7803ffe12bdc717@haskell.org> References: <046.4b383b5f0fce35e0e7803ffe12bdc717@haskell.org> Message-ID: <061.3312c9181851f5a4ff9ad2167e6086fe@haskell.org> #10560: -f and -O options interact in non-obvious, order dependent ways -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6400c7687223c5b2141176aa92f7ff987f61aba6/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="6400c7687223c5b2141176aa92f7ff987f61aba6" users_guide: Describe order-dependence of -f and -O flags The behavior of the -f and -O options can be quite surprising. Document this fact. At some point this behavior should likely be changed. Test Plan: documentation only Reviewers: austin, trofi Reviewed By: austin, trofi Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1008 GHC Trac Issues: #10560 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:44:16 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:44:16 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.44fa552a1f13b745299b901cc3341abc@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | thoughtpolice Priority: normal | Status: patch Component: Compiler | Milestone: 7.10.3 (Parser) | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #5108 | Differential Revisions: Phab:D969 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"6b01d3ce6c681428e7a9865af85685c2a76ba657/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="6b01d3ce6c681428e7a9865af85685c2a76ba657" parser: Allow Lm (MODIFIER LETTER) category in identifiers Easy fix in the parser to stop regressions, due to Unicode 7.0 changing the classification of some prior code points. Signed-off-by: Austin Seipp Test Plan: `tests/parser/should_compile/T10196.hs` Reviewers: hvr, austin, bgamari Reviewed By: austin, bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D969 GHC Trac Issues: #10196 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 20:44:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 20:44:15 -0000 Subject: [GHC] #9665: Add "since" information to LANGUAGE extensions in GHC user guide In-Reply-To: <051.0c91deb9283c869eec678c3caa22587e@haskell.org> References: <051.0c91deb9283c869eec678c3caa22587e@haskell.org> Message-ID: <066.0b86d3249ced487f8e375250c2cea4ab@haskell.org> #9665: Add "since" information to LANGUAGE extensions in GHC user guide -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: rasen Type: task | Status: new Priority: normal | Milestone: Component: Documentation | Version: 7.9 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1019 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"8b55788cae54c9b79b9fc973e9e77f0de1ccc49b/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="8b55788cae54c9b79b9fc973e9e77f0de1ccc49b" Add "since" column for LANGUAGE extensions in user guide Reviewers: austin Reviewed By: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1019 GHC Trac Issues: #9665 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 21:45:34 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 21:45:34 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.dc0f70c2328037b0eac8f986fd0b9642@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #3699 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by WrenThornton): Yeah, even if they aren't supported (yet), we shouldn't panic! :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 22:40:01 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 22:40:01 -0000 Subject: [GHC] #8620: make -j3 build of head on Mac 10.9 with xcode 5 fails In-Reply-To: <045.6b8d5402d68421f521d87e4314812585@haskell.org> References: <045.6b8d5402d68421f521d87e4314812585@haskell.org> Message-ID: <060.98fc44e06b7705298d01e03f4c771130@haskell.org> #8620: make -j3 build of head on Mac 10.9 with xcode 5 fails -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: Resolution: duplicate | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: #9709 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): This resolution is fine with me as I am no longer seeing this problem, but the wiki does say: "If you encounter this without touching any files after typing 'make', then it's probably a bug in the build system.". I believe this was the case for me but I'm not sure. If it does happen in the future I'll be sure to better describe the circumstances. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 22:43:50 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 22:43:50 -0000 Subject: [GHC] #7651: Buiding GHC with parallel IO manager freezes on Mac (not on FreeBSD) In-Reply-To: <052.b5316a423cedc87fa6cecb2672f617b3@haskell.org> References: <052.b5316a423cedc87fa6cecb2672f617b3@haskell.org> Message-ID: <067.7607369fbfc1f7cea1cda02c116c850c@haskell.org> #7651: Buiding GHC with parallel IO manager freezes on Mac (not on FreeBSD) -------------------------------------+------------------------------------- Reporter: kazu-yamamoto | Owner: Type: bug | Status: infoneeded Priority: high | Milestone: 7.12.1 Component: Build System | Version: 7.7 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:12 kazu-yamamoto]: > Which does "fail" mean, freeze (non stopping) or stop with an error? I believe, at the time, I meant with an error as described in #8620. As I've just elaborated there, I believe the case for me was that I encountered this without touching any files after typing 'make', which, according to the wiki, is probably a bug in the build system. In any case I haven't seen this in a long time. I just build 7.10.2 rc with make -j5 and had no problems. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 22:43:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 22:43:55 -0000 Subject: [GHC] #8620: make -j3 build of head on Mac 10.9 with xcode 5 fails In-Reply-To: <045.6b8d5402d68421f521d87e4314812585@haskell.org> References: <045.6b8d5402d68421f521d87e4314812585@haskell.org> Message-ID: <060.72be98aa27900cd8a0e5b78dd1d0db0d@haskell.org> #8620: make -j3 build of head on Mac 10.9 with xcode 5 fails -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: Resolution: duplicate | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: #9709 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): There *is* a bug in the build system. That's why #9709 is still open. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 3 22:45:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 03 Jul 2015 22:45:05 -0000 Subject: [GHC] #7651: Buiding GHC with parallel IO manager freezes on Mac (not on FreeBSD) In-Reply-To: <052.b5316a423cedc87fa6cecb2672f617b3@haskell.org> References: <052.b5316a423cedc87fa6cecb2672f617b3@haskell.org> Message-ID: <067.0bcad731c9ac5b191f998ab09645316c@haskell.org> #7651: Buiding GHC with parallel IO manager freezes on Mac (not on FreeBSD) -------------------------------------+------------------------------------- Reporter: kazu-yamamoto | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Build System | Version: 7.7 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by George): * status: infoneeded => new * architecture: Unknown/Multiple => x86_64 (amd64) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 03:41:09 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 03:41:09 -0000 Subject: [GHC] #10402: powerpc: unhandled ELF relocation(RelA) type 252 In-Reply-To: <047.64cabbbba17f1f097b7e64d90dcccda9@haskell.org> References: <047.64cabbbba17f1f097b7e64d90dcccda9@haskell.org> Message-ID: <062.27f217d9e2ba106591921d01b14c31a2@haskell.org> #10402: powerpc: unhandled ELF relocation(RelA) type 252 -----------------------------------+------------------------------------ Reporter: cjwatson | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Runtime System | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D996 -----------------------------------+------------------------------------ Comment (by slyfox): Replying to [comment:21 nomeata]: > I uploaded 7.10.2-rc2 to Debian now, but it seems that something else broke here: > {{{ > rts/Linker.c: In function 'do_Elf_Rela_relocations': > > rts/Linker.c:5963:10: > error: duplicate case value > case R_PPC_PLTREL24: > ^ > > rts/Linker.c:5959:10: > error: previously used here > case R_PPC_PLTREL24: > ^ > > rts/Linker.c:5996:10: > error: duplicate case value > case R_PPC_REL16_LO: > ^ > > rts/Linker.c:5984:10: > error: previously used here > case R_PPC_REL16_LO: > ^ > > rts/Linker.c:6000:10: > error: duplicate case value > case R_PPC_REL16_HI: > ^ > > rts/Linker.c:5988:10: > error: previously used here > case R_PPC_REL16_HI: > ^ > > rts/Linker.c:6004:10: > error: duplicate case value > case R_PPC_REL16_HA: > ^ > > rts/Linker.c:5992:10: > error: previously used here > case R_PPC_REL16_HA: > ^ > }}} > https://buildd.debian.org/status/fetch.php?pkg=ghc&arch=powerpc&ver=7.10.1.20150630-1&stamp=1435929642 > > Any ideas? I think you can safely drop debian-specific patch: > dpkg-source: info: applying PPC-relocations.patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 08:25:07 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 08:25:07 -0000 Subject: [GHC] #10402: powerpc: unhandled ELF relocation(RelA) type 252 In-Reply-To: <047.64cabbbba17f1f097b7e64d90dcccda9@haskell.org> References: <047.64cabbbba17f1f097b7e64d90dcccda9@haskell.org> Message-ID: <062.ac1872de6d07c6f3d0443fb987b85850@haskell.org> #10402: powerpc: unhandled ELF relocation(RelA) type 252 -----------------------------------+------------------------------------ Reporter: cjwatson | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Runtime System | Version: 7.8.4 Resolution: fixed | Keywords: Operating System: Linux | Architecture: powerpc Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D996 -----------------------------------+------------------------------------ Comment (by nomeata): > > Any ideas? > > I think you can safely drop debian-specific patch: > > > dpkg-source: info: applying PPC-relocations.patch Oups. Quite right. I thought I did. sorry for the noise. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 08:36:27 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 08:36:27 -0000 Subject: [GHC] #10601: GHC should be distributed with debug symbols Message-ID: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> #10601: GHC should be distributed with debug symbols -------------------------------------+------------------------------------- Reporter: bitonic | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Now that we have the capability of producing code with DWARF symbols, we should distribute GHC with them, or at least give the option. The DWARF symbols in these case would be both for the C RTS and for the base Haskell libraries shipped with GHC. Building GHC with said symbols amounts to adding {{{ GhcRtsHcOpts += -g GhcLibHcOpts += -g }}} to `mk/build.mk`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 08:41:50 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 08:41:50 -0000 Subject: [GHC] #8881: No way to unsubscribe a bug In-Reply-To: <046.3e20bef03cc312ed086d6bf0a5bf092e@haskell.org> References: <046.3e20bef03cc312ed086d6bf0a5bf092e@haskell.org> Message-ID: <061.904c8502cd3a1bdb7acc39e60e1ae753@haskell.org> #8881: No way to unsubscribe a bug -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Trac & Git | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: 9138 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): That sounds like a very nice solution. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 10:51:32 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 10:51:32 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.a1fd5f8173b794063cf967c19fdf0150@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b1d1c652908ecd7bfcf13cf2e5dd06ac7926992c/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b1d1c652908ecd7bfcf13cf2e5dd06ac7926992c" Support MO_{Add,Sub}IntC and MO_Add2 in the LLVM backend This includes: - Adding new LlvmType called LMStructP that represents an unpacked struct (this is necessary since LLVM's instructions the llvm.sadd.with.overflow.* return an unpacked struct). - Modifications to LlvmCodeGen.CodeGen to generate the LLVM instructions for the primops. - Modifications to StgCmmPrim to actually use those three instructions if we use the LLVM backend (so far they were only used for NCG). Test Plan: validate Reviewers: austin, rwbarton, bgamari Reviewed By: bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D991 GHC Trac Issues: #9430 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 11:25:20 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 11:25:20 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 Message-ID: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: Linux Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I've seen a few related tickets, but they are market as closed. % ghc -O2 binlist.hs [1 of 1] Compiling Main ( binlist.hs, binlist.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.1.20150630 for x86_64-unknown-linux): Template variable unbound in rewrite rule sg_s5zh [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] [: @ a_a3fo sc_s5zf sc_s5zg] [: @ a_a3fo sc_s5zb sc_s5zc] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug % cat binlist.hs import Control.Monad import Data.Binary import Data.List newtype A a = A [a] instance Binary a => Binary (A a) where put (A xs) = case splitAt 254 xs of (_, []) -> mapM_ put xs (a, b) -> put (A b) get = do xs <- replicateM 254 get A ys <- get return $ A $ xs ++ ys main :: IO () main = undefined -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 13:35:30 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 13:35:30 -0000 Subject: [GHC] #10408: The behavior of -ignore-dot-ghci and -ghci-script are weird In-Reply-To: <046.9a385a1c8826dd0a905fd10c48159e27@haskell.org> References: <046.9a385a1c8826dd0a905fd10c48159e27@haskell.org> Message-ID: <061.f6b3af6bfde1353ea1b022b78389120f@haskell.org> #10408: The behavior of -ignore-dot-ghci and -ghci-script are weird -------------------------------------+------------------------------------- Reporter: watashi | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Incorrect result | Test Case: at runtime | Blocking: Blocked By: | Differential Revisions: Phab:D887 Related Tickets: | -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"124f3999d78d8ef6b093e4f1bb1dcef87e4283da/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="124f3999d78d8ef6b093e4f1bb1dcef87e4283da" Testsuite: add -ignore-dot-ghci to some tests Since T10408A and T10408B would become the same now, delete T10408A and rename T10408B to T10408. The test without -ignore-dot-ghci (T10408A) didn't add anything (#10408). }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 13:35:30 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 13:35:30 -0000 Subject: [GHC] #9723: Give Tab warning only once per file In-Reply-To: <046.f226613e47ca73faa0ff03e64040a117@haskell.org> References: <046.f226613e47ca73faa0ff03e64040a117@haskell.org> Message-ID: <061.9413d69d38ba5f3662d2585e2403885f@haskell.org> #9723: Give Tab warning only once per file -------------------------------------+------------------------------------- Reporter: nomeata | Owner: dalaing Type: feature request | Status: closed Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 7.9 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | parser/should_compile/T9723{a,b} | Blocking: | Differential Revisions: Phab:D760 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"ced27def2d33119ed9fcc22f92856f132fd72217/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="ced27def2d33119ed9fcc22f92856f132fd72217" Remove dead code / overlapping pattern (#9723) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 15:23:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 15:23:36 -0000 Subject: [GHC] #7389: can't link postgresql-libpq on windows In-Reply-To: <047.308461056cfcd94cf59d943fa58b1d9d@haskell.org> References: <047.308461056cfcd94cf59d943fa58b1d9d@haskell.org> Message-ID: <062.1a79260686fa9790f6e9c53bed0056bb@haskell.org> #7389: can't link postgresql-libpq on windows -------------------------------------+------------------------------------- Reporter: eflister | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.4.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Runtime crash | (amd64) Blocked By: 3658 | Test Case: Related Tickets: #9907 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => closed * resolution: => fixed * related: => #9907 * blockedby: 3658, 5987 => 3658 Comment: Already fixed in 7.10.1 by #9907 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 15:33:38 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 15:33:38 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly Message-ID: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Template | Operating System: Unknown/Multiple Haskell | Type of failure: Other Keywords: | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Sometimes, Template Haskell splices lack necessary parentheses. Minimal example: {{{ $ ghci -XTemplateHaskell -ddump-splices GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help ?> :t $([| case Just 'a' of Just a -> Just ((\x -> x) a) |]) :1:3-53: Splicing expression [| case Just 'a' of { Just a_avZ -> Just ((\ x_aw0 -> x_aw0) a_avZ) } |] ======> case Just 'a' of { Just a_a3wI -> Just (\ x_a3wJ -> x_a3wJ a_a3wI) } $([| case Just 'a' of Just a -> Just ((\x -> x) a) |]) :: Maybe Char }}} The suspect part is {{{case Just 'a' of { Just a_a3wI -> Just (\ x_a3wJ -> x_a3wJ a_a3wI) } }}}, which should be {{{case Just 'a' of { Just a_a3wI -> Just ((\ x_a3wJ -> x_a3wJ) a_a3wI) } }}}. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 16:19:25 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 16:19:25 -0000 Subject: [GHC] #5941: Add compilation stage plugins In-Reply-To: <044.b57cf00ec831ffd77a7e1faf72cc142b@haskell.org> References: <044.b57cf00ec831ffd77a7e1faf72cc142b@haskell.org> Message-ID: <059.a973fcfd46d939b7c1781a44bc0e3b54@haskell.org> #5941: Add compilation stage plugins -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: feature request | Status: infoneeded Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by adamgundry): * cc: adamgundry (added) Comment: I've felt for a while that there should be better integration between [wiki:Plugins/TypeChecker plugins] and [wiki:Ghc/Hooks hooks], so that a plugin could hook into more stages of the compilation pipeline, and that hooks could register typechecker plugins. But I don't have a clear design yet, nor any spare cycles to work on this at the moment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 20:58:38 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 20:58:38 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.697868af0e60d308e8e3f719580d5547@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by michaelt): rwbarton, I think I have tested all of these examples on my machine, for it's worth. I rebuilt HEAD with what I took to be the patch described above: {{{ - LFThunk _ _no_fvs _updatable _ _ -> True + LFThunk _ _no_fvs _updatable _ _ -> _updatable }}} for https://github.com/ghc/ghc/blob/master/compiler/codeGen/StgCmmClosure.hs#L769 . Everything works fine, or seems to work fine. The complex program yongqli linked, with all the fancy imports, was a little erratic; I increased the size of the csv a lot, to make it more reliably bad somewhere along the way. I then just used the scheme of running ` ./bugcsv +RTS -N_ | grep loop ` 500 times each with -N5 and -N3 . (-N2 does't seem to make bring out the pathology with this program.) With ghc-7.10.1 I got `bugcsv: <>` about 200 times either way, but with the patched head, blessed silence. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 22:42:10 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 22:42:10 -0000 Subject: [GHC] #10601: GHC should be distributed with debug symbols In-Reply-To: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> References: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> Message-ID: <061.7b1be7f332a9da8740443502ffc269d6@haskell.org> #10601: GHC should be distributed with debug symbols -------------------------------------+------------------------------------- Reporter: bitonic | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Build System -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 23:40:11 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 23:40:11 -0000 Subject: [GHC] #8353: Easy way to defer type errors In-Reply-To: <047.34842edf8c636f9b11361128b151d960@haskell.org> References: <047.34842edf8c636f9b11361128b151d960@haskell.org> Message-ID: <062.afbf50bf236485e946b28db20c607621@haskell.org> #8353: Easy way to defer type errors -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D960 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"5d48e67fac952f7188fc9ebcfbf6e3ccb9b75705/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5d48e67fac952f7188fc9ebcfbf6e3ccb9b75705" Easy way to defer type errors (implements #8353) Added load! and reload! commands, effectively setting "-fdefer-type-errors" before loading a file and unsetting it after loading if it has not been set before. Differential Revision: https://phabricator.haskell.org/D960 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 4 23:44:50 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 04 Jul 2015 23:44:50 -0000 Subject: [GHC] #8353: Easy way to defer type errors In-Reply-To: <047.34842edf8c636f9b11361128b151d960@haskell.org> References: <047.34842edf8c636f9b11361128b151d960@haskell.org> Message-ID: <062.2459cea1be4ef3a4dccfdc36fc26a311@haskell.org> #8353: Easy way to defer type errors -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.6.3 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | ghci/scripts/T8353 | Blocking: | Differential Revisions: Phab:D960 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * testcase: => ghci/scripts/T8353 * resolution: => fixed * milestone: => 7.12.1 Comment: Thanks Benjamin. Hope to see you tackle another ticket soon. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 00:57:29 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 00:57:29 -0000 Subject: [GHC] #9839: RTS options parser silently accepts invalid flags In-Reply-To: <049.1ac180907787acdf75c140998b5b4263@haskell.org> References: <049.1ac180907787acdf75c140998b5b4263@haskell.org> Message-ID: <064.7d68749153c6042c14f3ffd8a55bff4f@haskell.org> #9839: RTS options parser silently accepts invalid flags -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: nkartashov Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Runtime System | Version: 7.8.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #4243 | Differential Revisions: Phab:D748 -------------------------------------+------------------------------------- Changes (by nkartashov): * owner: => nkartashov -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 04:51:25 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 04:51:25 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic Message-ID: <050.900476330e5007bcb132f742a5f2d072@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: | Owner: ekmett DerekElkins | Status: new Type: feature | Milestone: request | Version: 7.10.1 Priority: low | Operating System: Unknown/Multiple Component: Core | Type of failure: None/Unknown Libraries | Blocked By: Keywords: | Related Tickets: Architecture: | Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- It looks to me that the Generic1 class (and the Rep1 associated type) can immediately be generalized to forall k. k -> *. If k was instantiated to anything other than *, you wouldn't be able to make an instance for Par1, but then I don't think it would ever come up so that would be exactly the right behavior. This allows, in particular, DataKinds to be used as a parameter to instances of Generic1. I don't know if this would affect deriving, but I wouldn't really expect it to. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 05:46:52 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 05:46:52 -0000 Subject: [GHC] #10605: mispelling Indentity in Data.Traversable Message-ID: <043.e49768f98f094b33809ed4575039eca1@haskell.org> #10605: mispelling Indentity in Data.Traversable -------------------------------------+------------------------------------- Reporter: uznx | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.10.1 libraries/base | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The documentation for Data.Traversable has Identity misspelled as Indentity: instance Applicative Indentity where -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 08:37:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 08:37:36 -0000 Subject: [GHC] #9839: RTS options parser silently accepts invalid flags In-Reply-To: <049.1ac180907787acdf75c140998b5b4263@haskell.org> References: <049.1ac180907787acdf75c140998b5b4263@haskell.org> Message-ID: <064.a33b090d914253a72f38c5e4e2c0a842@haskell.org> #9839: RTS options parser silently accepts invalid flags -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: nkartashov Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Runtime System | Version: 7.8.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #4243 | Differential Revisions: Phab:D1039 -------------------------------------+------------------------------------- Changes (by nkartashov): * differential: Phab:D748 => Phab:D1039 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 10:37:34 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 10:37:34 -0000 Subject: [GHC] #10605: mispelling Indentity in Data.Traversable In-Reply-To: <043.e49768f98f094b33809ed4575039eca1@haskell.org> References: <043.e49768f98f094b33809ed4575039eca1@haskell.org> Message-ID: <058.7b6f8b7fc36ea8c9581737e08d8103cb@haskell.org> #10605: mispelling Indentity in Data.Traversable -------------------------------------+------------------------------------- Reporter: uznx | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"3fabb71a559b493efdfb5bb91907f6a0f696a114/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="3fabb71a559b493efdfb5bb91907f6a0f696a114" Fix typo [skip ci] (#10605) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 10:38:00 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 10:38:00 -0000 Subject: [GHC] #10605: mispelling Indentity in Data.Traversable In-Reply-To: <043.e49768f98f094b33809ed4575039eca1@haskell.org> References: <043.e49768f98f094b33809ed4575039eca1@haskell.org> Message-ID: <058.dc494795721334ef2da4ac78ea02900f@haskell.org> #10605: mispelling Indentity in Data.Traversable -------------------------------------+------------------------------------- Reporter: uznx | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 7.12.1 Comment: Thanks. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 11:36:12 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 11:36:12 -0000 Subject: [GHC] #8206: Add support for Portable Native Client In-Reply-To: <044.0e9301156a0eb3e01f0cb8995b726d63@haskell.org> References: <044.0e9301156a0eb3e01f0cb8995b726d63@haskell.org> Message-ID: <059.0f4e83858253860b4d1014ca5fe7104b@haskell.org> #8206: Add support for Portable Native Client -------------------------------------+------------------------------------- Reporter: guest | Owner: Alex Type: feature request | Sayers Priority: normal | Status: new Component: Compiler | Milestone: Resolution: | Version: Operating System: Unknown/Multiple | Keywords: NaCl PNaCl Type of failure: None/Unknown | Portable Native Client pexe Blocked By: | Architecture: Related Tickets: | Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by asayers): I just want to make sure you're aware of some recent developments in this area. Until recently there have been two competing solutions to the same problem: nacl and asm.js, developed by Google and Mozilla respectively. Recently a new approach ([https://github.com/WebAssembly/design/blob/master/README.md web assembly]) was [http://brendaneich.com/2015/06/from-asm-js-to-webassembly/ proposed], and it seems to have buy-in from both parties. You should be prepared for the possibility that Google will deprecate nacl in favour of web assembly. There was a [https://github.com/ghcjs/ghcjs/issues/359 suggestion] that the GHCJS project should target web assembly. Luite investigated and had some concerns, but concluded that more research was needed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 11:55:49 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 11:55:49 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly In-Reply-To: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> References: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> Message-ID: <065.4f9b854c40fbbeee4a23a87b67bc40a6@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => newcomer Comment: This is indeed a bug, but straightforward to fix. The code is all in `libraries/template-haskell/Language/Haskell/TH/Ppr.hs`. Anyone want to submit a patch? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 11:58:41 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 11:58:41 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.4ca5143b424450025f9d18521d6acba1@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by goldfire: Old description: > I've seen a few related tickets, but they are market as closed. > > % ghc -O2 binlist.hs > > [1 of 1] Compiling Main ( binlist.hs, binlist.o ) > ghc: panic! (the 'impossible' happened) > (GHC version 7.10.1.20150630 for x86_64-unknown-linux): > Template variable unbound in rewrite rule > sg_s5zh > [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] > [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] > [: @ a_a3fo sc_s5zf sc_s5zg] > [: @ a_a3fo sc_s5zb sc_s5zc] > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > > % cat binlist.hs > import Control.Monad > import Data.Binary > import Data.List > > newtype A a = A [a] > > instance Binary a => Binary (A a) where > put (A xs) = case splitAt 254 xs of > (_, []) -> mapM_ put xs > (a, b) -> put (A b) > > get = do xs <- replicateM 254 get > A ys <- get > return $ A $ xs ++ ys > > main :: IO () > main = undefined New description: I've seen a few related tickets, but they are market as closed. {{{ % ghc -O2 binlist.hs [1 of 1] Compiling Main ( binlist.hs, binlist.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.1.20150630 for x86_64-unknown-linux): Template variable unbound in rewrite rule sg_s5zh [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] [: @ a_a3fo sc_s5zf sc_s5zg] [: @ a_a3fo sc_s5zb sc_s5zc] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug % cat binlist.hs import Control.Monad import Data.Binary import Data.List newtype A a = A [a] instance Binary a => Binary (A a) where put (A xs) = case splitAt 254 xs of (_, []) -> mapM_ put xs (a, b) -> put (A b) get = do xs <- replicateM 254 get A ys <- get return $ A $ xs ++ ys main :: IO () main = undefined }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 12:04:26 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 12:04:26 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.a5c07005c36875add749fbfb7aaf9c5c@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * priority: normal => highest * os: Linux => Unknown/Multiple Comment: This is a regression since 7.10.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 18:22:18 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 18:22:18 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.905fb0f540cd9e9c515bd15487949828@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: | Phab:D10414 -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => patch * differential: => Phab:D10414 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 18:24:26 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 18:24:26 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.8c8770d2ac44521201f2d4efdcd1a5bd@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by rwbarton): Replying to [comment:29 Rydgel]: > Can this Cabal bug be related to our problems? https://github.com/haskell/cabal/issues/2689 Might be, depending on the root cause (is `frameworks: OpenAL` somehow getting lost, or does Cabal simply not pass the appropriate option to the C preprocessor). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 18:57:57 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 18:57:57 -0000 Subject: [GHC] #10601: GHC should be distributed with debug symbols In-Reply-To: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> References: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> Message-ID: <061.bb352cdeaf95b605f1cda6f03868d2c3@haskell.org> #10601: GHC should be distributed with debug symbols -------------------------------------+------------------------------------- Reporter: bitonic | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Tarrasch): This will incerease the binary size by about 50% I think. Here's an old comparison [1]. Just note that "debug_ghc" in that diagram doesn't exist in GHC HEAD, so just ignore that one. [1]: https://github.com/scpmw/ghc/commit/bbf6f35d8c341c8aadca1a48657084c007837b21#commitcomment-5527280 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 20:08:53 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 20:08:53 -0000 Subject: [GHC] #10606: avoid redundant stores to the stack when examining already-tagged data Message-ID: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> #10606: avoid redundant stores to the stack when examining already-tagged data -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.11 Component: Compiler | Operating System: Unknown/Multiple (CodeGen) | Type of failure: None/Unknown Keywords: | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- GHC compiles a function that performs case analysis on a value of an ADT like {{{ bool :: a -> a -> Bool -> a bool f t b = case b of False -> f True -> t }}} to Cmm of the form {{{ {offset cwV: if ((Sp + -24) < SpLim) goto cwW; else goto cwX; cwW: R4 = R4; R3 = R3; R2 = R2; R1 = Bool.bool_closure; call (stg_gc_fun)(R4, R3, R2, R1) args: 8, res: 0, upd: 8; cwX: I64[Sp - 24] = cwL; -- (*) R1 = R4; P64[Sp - 16] = R2; -- (?1) P64[Sp - 8] = R3; -- (?2) Sp = Sp - 24; -- (?) if (R1 & 7 != 0) goto cwL; else goto cwM; cwM: call (I64[R1])(R1) returns to cwL, args: 8, res: 8, upd: 8; cwL: if (R1 & 7 >= 2) goto cwT; else goto cwU; cwT: R1 = P64[Sp + 16]; Sp = Sp + 24; call stg_ap_0_fast(R1) args: 8, res: 0, upd: 8; cwU: R1 = P64[Sp + 8]; Sp = Sp + 24; call stg_ap_0_fast(R1) args: 8, res: 0, upd: 8; } }}} Statement (*) stores a return address for the evaluation of `b` to return to, and statements (?1), (?2) save local variables that are live in case alternatives, since they cannot be held in registers across the evaluation of `b`. But in the event that `b` is already evaluated and represented by a tagged pointer, all these stores are unnecessary: the return address written by (*) is simply dead, and the values saved in (?1), (?2) are still available in whatever locations they were copied to the stack from. In many cases the data we examine is mostly tagged, and while the active part of the stack is likely to be in L1 cache, the cost of these stores and reads is probably still positive (barring secondary effects from changes to pipelining, branch prediction, and so on). In this case we could certainly move the return address store (*) into block `cwM`, and possibly move the local variable stores (?1), (?2) into `cwM` as well, though it's then not clear to me how to recover the values in the alternatives (does Cmm have something like phi nodes?) I don't propose to move the statement (?), as arithmetic on registers is essentially free anyways. I tried implementing the part of this pertaining to the return address (*) and ran into two complications. * For some reason, when I moved the return address store (*) into the "data is not tagged" branch in the Stg->Cmm translation, this also resulted in both the local variable stores (?1), (?2) and the update to Sp (?) being sunk into both branches of the "is the data tagged" conditional at some point in the Cmm optimization pipeline. This was useless since they couldn't be pushed further past the branch on the returned tag value, so the result was enlarged code size that outweighed the savings of avoiding a single store. I didn't investigate exactly why this sinking was dependent on the location of the store (*), but this should be fixable. * There may be heap checks in the alternatives. In that case, the code generator currently cleverly reuses the stack frame and info table set up for the evaluation of `b` in the heap failure branches. If we move some of the stores (*), (?1), (?2) into the evaluation branch `cwM`, then we either have to duplicate them in heap failure branches, or set up a new stack frame and info table, or do some other clever thing. Or in the worst case, only do this optimization when performing the heap check before the case (which may then become slightly more attractive). I'm attaching the current version of my patch mainly for my own future reference; it seems to produce correct, but larger and marginally slower code, I believe for the reasons described above. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 21:50:14 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 21:50:14 -0000 Subject: [GHC] #10606: avoid redundant stores to the stack when examining already-tagged data In-Reply-To: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> References: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> Message-ID: <062.2c225c7fbaed29dac0c7e68493b04a46@haskell.org> #10606: avoid redundant stores to the stack when examining already-tagged data -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Changes (by rwbarton): * failure: None/Unknown => Runtime performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 23:15:34 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 23:15:34 -0000 Subject: [GHC] #9839: RTS options parser silently accepts invalid flags In-Reply-To: <049.1ac180907787acdf75c140998b5b4263@haskell.org> References: <049.1ac180907787acdf75c140998b5b4263@haskell.org> Message-ID: <064.340cedab9acf470a8fe31b411a5504e7@haskell.org> #9839: RTS options parser silently accepts invalid flags -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: nkartashov Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Runtime System | Version: 7.8.3 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #4243 | Differential Revisions: Phab:D1039 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"75de6131efc780dbdba30fa3fc48c16231ab66a9/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="75de6131efc780dbdba30fa3fc48c16231ab66a9" rts: fix incorrect checking start for -x arguments (#9839) After previous fix, flag combinations such as -xt and -xc resulted in an error due to the fact that the checking started from index 2, which was always 'x' in that case. Now they are correctly processed. Differential Revision: https://phabricator.haskell.org/D1039 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 5 23:16:51 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 05 Jul 2015 23:16:51 -0000 Subject: [GHC] #9839: RTS options parser silently accepts invalid flags In-Reply-To: <049.1ac180907787acdf75c140998b5b4263@haskell.org> References: <049.1ac180907787acdf75c140998b5b4263@haskell.org> Message-ID: <064.0ebb91a40a9732e73121b8cd2e9af496@haskell.org> #9839: RTS options parser silently accepts invalid flags -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: nkartashov Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Runtime System | Version: 7.8.3 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #4243 | Differential Revisions: Phab:D748, | Phab:D1039 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * differential: Phab:D1039 => Phab:D748, Phab:D1039 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 08:37:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 08:37:52 -0000 Subject: [GHC] #10439: Opt_ImplicitImportQualified doesn't work for constructor field name In-Reply-To: <046.7eeda0ab82b2b7fc80cf5d3190f2c3b2@haskell.org> References: <046.7eeda0ab82b2b7fc80cf5d3190f2c3b2@haskell.org> Message-ID: <061.06f43e6ae17846f9cb180c61c6e2f055@haskell.org> #10439: Opt_ImplicitImportQualified doesn't work for constructor field name -------------------------------------+------------------------------------- Reporter: watashi | Owner: watashi Type: bug | Status: patch Priority: highest | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | ghci/scripts/T10439 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D900 -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => ghci/scripts/T10439 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 08:40:02 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 08:40:02 -0000 Subject: [GHC] #10519: Can't put wildcard behind forall In-Reply-To: <046.25f8a351d42fe346e193d0c867e5e854@haskell.org> References: <046.25f8a351d42fe346e193d0c867e5e854@haskell.org> Message-ID: <061.86d76016231d1cf7cc1f83f4599f2d9c@haskell.org> #10519: Can't put wildcard behind forall -------------------------------------+------------------------------------- Reporter: yongqli | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1-rc3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: partial- Related Tickets: | sigs/should_compile/T10519 | Blocking: | Differential Revisions: Phab:D994 -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => partial-sigs/should_compile/T10519 Comment: So this is fixed? If so let's close it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 08:48:15 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 08:48:15 -0000 Subject: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? In-Reply-To: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> References: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> Message-ID: <060.e4e3b0cd58f4141d6000b4ff56ea85de@haskell.org> #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? -------------------------------------+------------------------------------- Reporter: iustin | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1012 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"4681f55970cabc6e33591d7e698621580818f9a2/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="4681f55970cabc6e33591d7e698621580818f9a2" Specialise: Avoid unnecessary recomputation of free variable information When examining compile times for code with large ADTs (particularly those with many record constructors), I found that the specialiser contributed disproportionately to the compiler runtime. Some profiling suggested that the a great deal of time was being spent in `pair_fvs` being called from `consDictBind`. @simonpj pointed out that `flattenDictBinds` as called by `specBind` was unnecessarily discarding cached free variable information, which then needed to be recomputed by `pair_fvs`. Here I refactor the specializer to retain the free variable cache whenever possible. **Open Qustions** * I used `fst` in a couple of places to extract the bindings from a `DictBind`. Perhaps this is a sign that `DictBind` has outgrown its type synonym status? Test Plan: validate Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: thomie, bgamari, simonpj Differential Revision: https://phabricator.haskell.org/D1012 GHC Trac Issues: #7450 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 09:00:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 09:00:48 -0000 Subject: [GHC] #10519: Can't put wildcard behind forall In-Reply-To: <046.25f8a351d42fe346e193d0c867e5e854@haskell.org> References: <046.25f8a351d42fe346e193d0c867e5e854@haskell.org> Message-ID: <061.7ce2972d1d9753a0cd707a34c80dd411@haskell.org> #10519: Can't put wildcard behind forall -------------------------------------+------------------------------------- Reporter: yongqli | Owner: thomasw Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1-rc3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: partial- Related Tickets: | sigs/should_compile/T10519 | Blocking: | Differential Revisions: Phab:D994 -------------------------------------+------------------------------------- Changes (by thomasw): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 09:07:58 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 09:07:58 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.d4ade6f54c2e345805d18431e3788cca@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: ekmett Type: feature request | Status: new Priority: low | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Old description: > It looks to me that the Generic1 class (and the Rep1 associated type) can > immediately be generalized to forall k. k -> *. If k was instantiated to > anything other than *, you wouldn't be able to make an instance for Par1, > but then I don't think it would ever come up so that would be exactly the > right behavior. This allows, in particular, DataKinds to be used as a > parameter to instances of Generic1. > > I don't know if this would affect deriving, but I wouldn't really expect > it to. New description: It looks to me that the `Generic1` class (and the `Rep1` associated type) can immediately be generalized to `forall k. k -> *`. If `k` was instantiated to anything other than `*`, you wouldn't be able to make an instance for `Par1`, but then I don't think it would ever come up so that would be exactly the right behavior. This allows, in particular, `DataKinds` to be used as a parameter to instances of `Generic1`. I don't know if this would affect deriving, but I wouldn't really expect it to. -- Comment (by simonpj): Happily, Andres Loh has agreed to take a lead in `Generics` and `DeriveAnyClass`, but only later this summer. Thanks Andres! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 09:10:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 09:10:52 -0000 Subject: [GHC] #10601: GHC should be distributed with debug symbols In-Reply-To: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> References: <046.ddcd45dcc3f972fc17c42b77b9184272@haskell.org> Message-ID: <061.65e37b0e312c40bf3f741b0ac34e7366@haskell.org> #10601: GHC should be distributed with debug symbols -------------------------------------+------------------------------------- Reporter: bitonic | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Build System | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by scpmw): Also note that `.debug_info` got significantly smaller, because it doesn't contain block information like before. This reduces the amount of overhead to about 18% total, according to my experiments back then: https://mail.haskell.org/pipermail/ghc-devs/2015-January/007872.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 10:01:19 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 10:01:19 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.b07a0bbadbf8ded3f04ac6c0cb880511@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * owner: => bgamari Comment: Oh dear. I'll have a look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 10:08:15 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 10:08:15 -0000 Subject: [GHC] #10575: "unsatisfied constraints" typo In-Reply-To: <045.95237d2ec1c60db7ff6ad28f67a1da5f@haskell.org> References: <045.95237d2ec1c60db7ff6ad28f67a1da5f@haskell.org> Message-ID: <060.552a7dfd58c901a5767444e76ea4df26@haskell.org> #10575: "unsatisfied constraints" typo -------------------------------------+------------------------------------- Reporter: ekmett | Owner: ekmett Type: bug | Status: closed Priority: low | Milestone: 7.10.2 Component: Core Libraries | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 10:08:46 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 10:08:46 -0000 Subject: [GHC] #10575: "unsatisfied constraints" typo In-Reply-To: <045.95237d2ec1c60db7ff6ad28f67a1da5f@haskell.org> References: <045.95237d2ec1c60db7ff6ad28f67a1da5f@haskell.org> Message-ID: <060.434f565b1bb4ca9e2c18322ed9f64fd7@haskell.org> #10575: "unsatisfied constraints" typo -------------------------------------+------------------------------------- Reporter: ekmett | Owner: ekmett Type: bug | Status: closed Priority: low | Milestone: 7.10.2 Component: Core Libraries | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Merged to 7.10 with, {{{ commit df6665e0cfdd23567bd32d222154ab25dbc39079 Author: Gabor Greif Date: Tue Feb 17 16:00:24 2015 +0100 Fix typo in error message }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 10:19:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 10:19:55 -0000 Subject: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? In-Reply-To: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> References: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> Message-ID: <060.37545917aacf23ddb7b5b9ebb7acaa6e@haskell.org> #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? -------------------------------------+------------------------------------- Reporter: iustin | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1012 -------------------------------------+------------------------------------- Comment (by bgamari): I finally had a chance to look further into this. It seems that after the fix `CmmPipeline.doRTs` may still be non-linear. With 2048 constructors, {{{ COST CENTRE MODULE %time %alloc lintAnnots CoreLint 12.5 20.4 doSRTs CmmPipeline 11.6 16.9 FloatOutwards SimplCore 6.3 2.0 simplLetUnfolding Simplify 4.5 2.7 pprNativeCode AsmCodeGen 4.3 5.0 completeBind Simplify 4.1 2.0 StgCmm HscMain 3.3 2.7 ... }}} With 4096 constructors, {{{ COST CENTRE MODULE %time %alloc doSRTs CmmPipeline 23.0 33.0 lintAnnots CoreLint 16.9 26.5 FloatOutwards SimplCore 7.8 1.6 completeBind Simplify 4.0 1.2 simplLetUnfolding Simplify 3.9 1.6 pprNativeCode AsmCodeGen 3.3 3.3 ... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 10:42:19 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 10:42:19 -0000 Subject: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? In-Reply-To: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> References: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> Message-ID: <060.76670434b161e663fdb14f844b970d06@haskell.org> #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? -------------------------------------+------------------------------------- Reporter: iustin | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1012 -------------------------------------+------------------------------------- Comment (by bgamari): In particular most of this appears to be coming from `CmmBuildInfoTables.procpointSRT.bitmap`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 10:51:40 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 10:51:40 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.655852a6295268579bbc7d1234062256@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:7 goldfire]: > If we disallow exports, would that alleviate your concerns, Ben? At that point, we should really allow any (non-empty?) string as the argument for `newName`. I think Greg is spot on in suggesting that the argument to `newName` is merely a seed, not the name in question. This sounds fine to me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 11:59:20 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 11:59:20 -0000 Subject: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? In-Reply-To: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> References: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> Message-ID: <060.856b5a30355387e64d3359547b6e6b10@haskell.org> #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? -------------------------------------+------------------------------------- Reporter: iustin | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1012 -------------------------------------+------------------------------------- Comment (by bgamari): Indeed the implementation of `intsToBitmap` had non-linear behavior due to the accumulation of nested `map` thunks. I've opened Phab:D1041 to resolve this. With this fix the profile for the 4096 constructor testcase looks like this, {{{ total time = 245.76 secs (245764 ticks @ 1000 us, 1 processor) total alloc = 255,033,667,528 bytes (excludes profiling overheads) COST CENTRE MODULE %time %alloc lintAnnots CoreLint 19.8 34.1 FloatOutwards SimplCore 9.7 2.1 flatten.lookup CmmBuildInfoTables 4.8 5.2 simplLetUnfolding Simplify 4.1 2.2 completeBind Simplify 3.9 1.6 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 12:30:27 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 12:30:27 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.a2e680d9f09ebe92d0b413ead6b018ad@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomasw): * owner: => thomasw -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 12:51:07 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 12:51:07 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.1899ad2a3a39f8838d0cbd44bf25b334@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Precisely what version of GHC are you using? I can reproduce this neither with 7.10.1 nor the current state of the 7.10.2 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 12:51:32 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 12:51:32 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.38f4bdb2f0449242be746067907d74c8@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => infoneeded -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 12:52:25 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 12:52:25 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.98a9526df539efee07e30963a1d78590@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): I can reproduce this, but only with the `perf` build, not the `stage2` build. Strange. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 13:01:44 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 13:01:44 -0000 Subject: [GHC] #10607: Auto derive from top to bottom Message-ID: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.11 Component: Compiler | Operating System: Unknown/Multiple Keywords: deriving, | Type of failure: None/Unknown typeclass, auto | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- It is very good to see that Template Haskell types are now `Generic` and `DeriveAnyClass` have been implemented. I suppose that this auto-deriving thing can go even further. The problem is like the following: When we manipulate a complex composite JSON object, we need to define a dozen of data types for each of the dozen we may need to derive `Eq`, `Show`, `Generic` etc. Another situaition can be manipulating the AST of a language, there may be dozens of data type definitions, also, for each of them, we need to derive `Show`, `Eq`, `Generic`. Take the old Template Haskell types without `Generic` as an example, I want to make them instances of `Generic` type class, I wrote: {{{#!hs deriving instance Generic FixityDirection deriving instance Generic Inline deriving instance Generic RuleBndr deriving instance Generic Match deriving instance Generic Name deriving instance Generic RuleMatch deriving instance Generic Pred deriving instance Generic Phases deriving instance Generic Con deriving instance Generic Module deriving instance Generic AnnTarget deriving instance Generic Type deriving instance Generic TyVarBndr deriving instance Generic TyLit deriving instance Generic Exp deriving instance Generic Lit deriving instance Generic Pat deriving instance Generic Dec deriving instance Generic Clause deriving instance Generic FunDep deriving instance Generic Foreign deriving instance Generic Fixity deriving instance Generic Pragma deriving instance Generic FamFlavour ... }}} How can we use `Generic`? Say we want to serialize Template Haskell data type with `Binary` type class, Of course, by writing `Binary` empty instances or just derive it with `DeriveAnyClass` extension. However, the problem is that we still need to write deriving Binary dozens of times, as many as the trivial `Generic` deriving declaration above. What if GHC can attemp to derive the instance from the top of the tree down to the leaf in the data type declarations? For example: {{{#!hs data Person = Person Names Address | Student Names Address deriving Generic data Names = Names String deriving Generic data Address = Address Gate deriving Generic type Gate = (String,Int) deriving topdown Eq Person }}} It will generate `Eq` instances of `Person`, `Names` and `Address`, since it is in the Person data declaration tree. I tried to implement a prototype see https://github.com/HaskellZhangSong /derive-topdown It is rather an experiment tryout than a formal implementation. If you think this feature is attractive, I would like to discuss it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 13:03:43 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 13:03:43 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.a09fc83ae96974694e98cde0dde58551@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | typeclass, auto Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by songzh: Old description: > It is very good to see that Template Haskell types are now `Generic` and > `DeriveAnyClass` have been implemented. I suppose that this auto-deriving > thing can go even further. The problem is like the following: > > When we manipulate a complex composite JSON object, we need to define a > dozen of data types for each of the dozen we may need to derive `Eq`, > `Show`, `Generic` etc. > > Another situaition can be manipulating the AST of a language, there may > be dozens of data type definitions, also, for each of them, we need to > derive `Show`, `Eq`, `Generic`. > > Take the old Template Haskell types without `Generic` as an example, I > want to make them instances of `Generic` type class, I wrote: > > {{{#!hs > deriving instance Generic FixityDirection > deriving instance Generic Inline > deriving instance Generic RuleBndr > deriving instance Generic Match > deriving instance Generic Name > deriving instance Generic RuleMatch > deriving instance Generic Pred > deriving instance Generic Phases > deriving instance Generic Con > deriving instance Generic Module > deriving instance Generic AnnTarget > deriving instance Generic Type > deriving instance Generic TyVarBndr > deriving instance Generic TyLit > deriving instance Generic Exp > deriving instance Generic Lit > deriving instance Generic Pat > deriving instance Generic Dec > deriving instance Generic Clause > deriving instance Generic FunDep > deriving instance Generic Foreign > deriving instance Generic Fixity > deriving instance Generic Pragma > deriving instance Generic FamFlavour > ... > }}} > > How can we use `Generic`? Say we want to serialize Template Haskell data > type with `Binary` type class, Of course, by writing `Binary` empty > instances or just derive it with `DeriveAnyClass` extension. However, the > problem is that we still need to write deriving Binary dozens of times, > as many as the trivial `Generic` deriving declaration above. > > What if GHC can attemp to derive the instance from the top of the tree > down to the leaf in the data type declarations? For example: > > {{{#!hs > data Person = Person Names Address > | Student Names Address deriving Generic > data Names = Names String deriving Generic > data Address = Address Gate deriving Generic > type Gate = (String,Int) > > deriving topdown Eq Person > }}} > It will generate `Eq` instances of `Person`, `Names` and `Address`, since > it is in the Person data declaration tree. > > I tried to implement a prototype see https://github.com/HaskellZhangSong > /derive-topdown > > It is rather an experiment tryout than a formal implementation. If you > think this feature is attractive, I would like to discuss it. New description: It is very good to see that Template Haskell types are now `Generic` and `DeriveAnyClass` have been implemented. I suppose that this auto-deriving thing can go even further. The problem is like the following: When we manipulate a complex composite JSON object, we need to define a dozen of data types for each of the dozen we may need to derive `Eq`, `Show`, `Generic` etc. Another situaition can be manipulating the AST of a language, there may be dozens of data type definitions, also, for each of them, we need to derive `Show`, `Eq`, `Generic`. Take the old Template Haskell types without `Generic` as an example, I want to make them instances of `Generic` type class, I wrote: {{{#!hs deriving instance Generic FixityDirection deriving instance Generic Inline deriving instance Generic RuleBndr deriving instance Generic Match deriving instance Generic Name deriving instance Generic RuleMatch deriving instance Generic Pred deriving instance Generic Phases deriving instance Generic Con deriving instance Generic Module deriving instance Generic AnnTarget deriving instance Generic Type deriving instance Generic TyVarBndr deriving instance Generic TyLit deriving instance Generic Exp deriving instance Generic Lit deriving instance Generic Pat deriving instance Generic Dec deriving instance Generic Clause deriving instance Generic FunDep deriving instance Generic Foreign deriving instance Generic Fixity deriving instance Generic Pragma deriving instance Generic FamFlavour ... }}} How can we use `Generic`? Say we want to serialize Template Haskell data type with `Binary` type class, Of course, by writing `Binary` empty instances or just derive it with `DeriveAnyClass` extension. However, the problem is that we still need to write deriving Binary dozens of times, as many as the trivial `Generic` deriving declaration above. What if GHC can attemp to derive the instance from the top of the tree down to the leaf in the data type declarations? For example: {{{#!hs data Person = Person Names Address | Student Names Address deriving Generic data Names = Names String deriving Generic data Address = Address Gate deriving Generic type Gate = (String,Int) deriving topdown Eq Person }}} It will generate `Eq` instances of `Person`, `Names` and `Address` since `Name` and `Address` are in the Person data declaration tree. I tried to implement a prototype see https://github.com/HaskellZhangSong /derive-topdown It is rather an experiment tryout than a formal implementation. If you think this feature is attractive, I would like to discuss it. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 13:05:35 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 13:05:35 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.99c9ae7f9d32f0a149d4ed965e2a5ba7@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by pacak): rc2 downloaded from ghc website as {{{ghc-7.10.1.20150630-src.tar.xz}}} {{{ % cat mk/build.mk GhcRTSWays += debug GhcRTSWays += debug_p GhcRTSWays += thr_debug GhcRTSWays += thr_debug_p BUILD_DOCBOOK_HTML = YES DYNAMIC_GHC_PROGRAMS = NO }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 13:06:16 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 13:06:16 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.b60f98bcbc9bfe3d7d95bb9dcbadb831@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | typeclass, auto Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by songzh: Old description: > It is very good to see that Template Haskell types are now `Generic` and > `DeriveAnyClass` have been implemented. I suppose that this auto-deriving > thing can go even further. The problem is like the following: > > When we manipulate a complex composite JSON object, we need to define a > dozen of data types for each of the dozen we may need to derive `Eq`, > `Show`, `Generic` etc. > > Another situaition can be manipulating the AST of a language, there may > be dozens of data type definitions, also, for each of them, we need to > derive `Show`, `Eq`, `Generic`. > > Take the old Template Haskell types without `Generic` as an example, I > want to make them instances of `Generic` type class, I wrote: > > {{{#!hs > deriving instance Generic FixityDirection > deriving instance Generic Inline > deriving instance Generic RuleBndr > deriving instance Generic Match > deriving instance Generic Name > deriving instance Generic RuleMatch > deriving instance Generic Pred > deriving instance Generic Phases > deriving instance Generic Con > deriving instance Generic Module > deriving instance Generic AnnTarget > deriving instance Generic Type > deriving instance Generic TyVarBndr > deriving instance Generic TyLit > deriving instance Generic Exp > deriving instance Generic Lit > deriving instance Generic Pat > deriving instance Generic Dec > deriving instance Generic Clause > deriving instance Generic FunDep > deriving instance Generic Foreign > deriving instance Generic Fixity > deriving instance Generic Pragma > deriving instance Generic FamFlavour > ... > }}} > > How can we use `Generic`? Say we want to serialize Template Haskell data > type with `Binary` type class, Of course, by writing `Binary` empty > instances or just derive it with `DeriveAnyClass` extension. However, the > problem is that we still need to write deriving Binary dozens of times, > as many as the trivial `Generic` deriving declaration above. > > What if GHC can attemp to derive the instance from the top of the tree > down to the leaf in the data type declarations? For example: > > {{{#!hs > data Person = Person Names Address > | Student Names Address deriving Generic > data Names = Names String deriving Generic > data Address = Address Gate deriving Generic > type Gate = (String,Int) > > deriving topdown Eq Person > }}} > It will generate `Eq` instances of `Person`, `Names` and `Address` since > `Name` and `Address` are in the Person data declaration tree. > > I tried to implement a prototype see https://github.com/HaskellZhangSong > /derive-topdown > > It is rather an experiment tryout than a formal implementation. If you > think this feature is attractive, I would like to discuss it. New description: It is very good to see that Template Haskell types are now `Generic` and `DeriveAnyClass` have been implemented. I suppose that this auto-deriving thing can go even further. The problem is like the following: When we manipulate a complex composite JSON object, we need to define a dozen of data types for each of the dozen we may need to derive `Eq`, `Show`, `Generic` etc. Another situaition can be manipulating the AST of a language, there may be dozens of data type definitions, also, for each of them, we need to derive `Show`, `Eq`, `Generic`. Take the old Template Haskell types without `Generic` as an example, I want to make them instances of `Generic` type class, I wrote: {{{#!hs deriving instance Generic FixityDirection deriving instance Generic Inline deriving instance Generic RuleBndr deriving instance Generic Match deriving instance Generic Name deriving instance Generic RuleMatch deriving instance Generic Pred deriving instance Generic Phases deriving instance Generic Con deriving instance Generic Module deriving instance Generic AnnTarget deriving instance Generic Type deriving instance Generic TyVarBndr deriving instance Generic TyLit deriving instance Generic Exp deriving instance Generic Lit deriving instance Generic Pat deriving instance Generic Dec deriving instance Generic Clause deriving instance Generic FunDep deriving instance Generic Foreign deriving instance Generic Fixity deriving instance Generic Pragma deriving instance Generic FamFlavour ... }}} How can we use `Generic`? Say we want to serialize Template Haskell data type with `Binary` type class, Of course, by writing `Binary` empty instances or just derive it with `DeriveAnyClass` extension. However, the problem is that we still need to write deriving Binary dozens of times, as many as the trivial `Generic` deriving declaration above. What if GHC can attemp to derive the instance from the top of the tree down to the leaf in the data type declarations? For example: {{{#!hs data Person = Person Names Address | Student Names Address data Names = Names String data Address = Address Gate type Gate = (String,Int) deriving topdown Generic Person deriving topdown Eq Person }}} It will generate `Eq` instances of `Person`, `Names` and `Address` since `Name` and `Address` are in the Person data declaration tree. I tried to implement a prototype see https://github.com/HaskellZhangSong /derive-topdown It is rather an experiment tryout than a formal implementation. If you think this feature is attractive, I would like to discuss it. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 13:10:01 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 13:10:01 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.07f2be25dd838a3753f05df250971d2b@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by pacak): ghc 7.10.1 can compile the same code without any problems. This build of rc2 was compiled by ghc 7.10.1 plus a few patches on top related to event manager issues. Before submitting the bug I've confirmed that somebody from #ghc can reproduce it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 14:16:58 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 14:16:58 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.ddbd4951e51af6e704606c046342ff23@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): I observed the failure with 7.10.2-rc1 (7.10.1.20150612). I forget if I built it myself or downloaded from somewhere. I don't have more recent builds to hand. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 14:26:13 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 14:26:13 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.c68d357e6f16a507847f5039901cce90@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1040 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: Phab:D10414 => Phab:D1040 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 14:38:00 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 14:38:00 -0000 Subject: [GHC] #10608: Compile error regression from GHC 7.10 to 7.11 Message-ID: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> #10608: Compile error regression from GHC 7.10 to 7.11 -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Consider the following program, {{{#!hs {-# LANGUAGE OverloadedStrings #-} -- {-# LANGUAGE FlexibleContexts #-} chunksOf :: Int -> String -> [String] chunksOf n = go where -- go :: String -> [String] go "" = [] go s@(_:_) = a : go b where (a,b) = splitAt n s }}} when compiled with GHC 7.8.4: {{{ GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( chunksof.hs, interpreted ) chunksof.hs:8:5: Warning: Pattern match(es) are overlapped In an equation for ?go?: go s@(_ : _) = ... Ok, modules loaded: Main. ?:2> }}} when compiled with GHC 7.10: {{{ GHCi, version 7.10.1.20150630: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( chunksof.hs, interpreted ) chunksof.hs:8:5: Non type-variable argument in the constraint: Data.String.IsString [t] (Use FlexibleContexts to permit this) When checking that ?go? has the inferred type go :: forall t. (Eq t, Data.String.IsString [t]) => [t] -> [[t]] In an equation for ?chunksOf?: chunksOf n = go where go "" = [] go s@(_ : _) = a : go b where (a, b) = splitAt n s Failed, modules loaded: none. }}} NB: `FlexibleContexts` is rightly suggested! However, when compiled with GHC HEAD: {{{ GHCi, version 7.11.20150630: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( chunksof.hs, interpreted ) chunksof.hs:8:8: error: Could not deduce (IsString [t]) arising from the literal ?""? from the context: Eq t bound by the inferred type of go :: Eq t => [t] -> [[t]] at chunksof.hs:(8,5)-(11,27) In the pattern: "" In an equation for ?go?: go "" = [] In an equation for ?chunksOf?: chunksOf n = go where go "" = [] go s@(_ : _) = a : go b where (a, b) = splitAt n s Failed, modules loaded: none. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 14:45:33 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 14:45:33 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.069b3e456206c23925f4d3c90d9b1b6a@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomasw): The changes to TH itself are straightforward. However Adam is right, the (named) wild cards must be known before renaming starts, and TH type splices are run ''during'' renaming. Besides a small bug I'm looking into, I see no problem with supporting anonymous wild cards in TH type splices. Named wild cards will require much more work and a refactoring of how splices and wild cards interact during renaming. Does it make sense to only allow anonymous wild cards in TH type splices but not named wild cards? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 14:46:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 14:46:52 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.8a77b900ae6f50b4bef6fb44fcae7517@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Changes (by simonpj): * owner: scpmw => * status: closed => new * resolution: fixed => Comment: Lots of cost is still attributed to `lintAnnots`, so the original problem doesn't seem to be fixed. So I'll re-open. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 14:52:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 14:52:53 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.a005643aeffd015bd4f2f286d3cea432@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomasw): I forgot to add that extra-constraints wild cards (`_ => ...`) have the same problem as named wild cards: they must be known before renaming. If people are ok with only having anonymous type wild cards in TH type splices, then I'll post a diff on Phabricator. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 15:04:42 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 15:04:42 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.bed8d191c5e1302ccc80493be6779a6d@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by adamgundry): Thanks for looking at this! I can't speak for everyone, but for my use case I need only anonymous type wild cards, not named or extra-constraints wild cards. Please do post a diff. We can perhaps put off the extra work until anyone comes up with a reason for wanting the other cases... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 15:05:51 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 15:05:51 -0000 Subject: [GHC] #10094: Template Haskell cannot represent type wildcards In-Reply-To: <049.6629ff791e291b2d66323173df5c56f5@haskell.org> References: <049.6629ff791e291b2d66323173df5c56f5@haskell.org> Message-ID: <064.47ea8248dd77828f49e806de0a3d8092@haskell.org> #10094: Template Haskell cannot represent type wildcards -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1-rc1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #9879, #10548 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by adamgundry): * status: new => closed * resolution: => duplicate Comment: Duplicate of #10548. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 15:41:33 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 15:41:33 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.db49d20e25c0836f8f8c3f6a7f5044b6@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.1 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Comment (by scpmw): Yes - I investigated this again a month ago, and found that SM's fix didn't correct the whole problem. In fact, if I remember correctly what we end up with is something like {{{ case scctick specConstrProgram of ... }}} In this situation the tick will fail to actually capture any cost in `specConstrProgram`, which will instead end up in the cost-centre next in the hierarchy, which happens to be `lintAnnots` (`Core2Core` before). As explained in D616 and #5654, this is a fairly fundamental problem: GHC simply doesn't implement the cost-centre semantics for function values correctly. Correcting this isn't exactly easy - I have been experimenting in the past weeks, and the best solution I can come up with (still?) involves a new closure type that wraps function values when they escape cost-centre scopes. Two possible solutions here: We could attempt another stopgap measure. For example, the above code should probably in-line as it is only used once. Building the full solution will still need a bit more tinkering, but I might be able to make a proposal soon-ish (... just need to get it to stop crashing. Seems getting register saving right can be surprisingly tricky). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 16:12:01 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 16:12:01 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.c506672910c431cca541704447b3eab8@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Simon has identified that the issue is the simplifier expending a great deal of effort simplifying an argument which is ultimately ignored by the callee. I have merged 07a1f32e8bacecd450112607df3fdf39e553c91e into the `ghc-7.10` branch which should resolve this for 7.10.2. Simonpj is working on a more thorough fix for `master`. I'll leave this open until the latter fix has been merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 16:13:58 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 16:13:58 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.0fa626959877165e71b912eec432b7d0@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: bgamari Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Simon, your explanation raises a question: what would happen if the argument weren't thrown away? It seems that the simplifier would blow up in this case, no? Perhaps this is another issue that should be tracked? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 22:43:56 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 22:43: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.d7b76b2ce404a4eb92d836518b7b0063@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jb55): * cc: bill@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 22:51:29 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 22:51:29 -0000 Subject: [GHC] #10579: full module names of names not in scope have gone missing in ghci In-Reply-To: <047.b63d248973b529e66515b0b0ffe3a663@haskell.org> References: <047.b63d248973b529e66515b0b0ffe3a663@haskell.org> Message-ID: <062.cb7afecd9f82a9fcd1ac99af1e447455@haskell.org> #10579: full module names of names not in scope have gone missing in ghci -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * owner: => simonpj Comment: This was done purposely, but it does seem like the case here was an unintended consequence. The relevant code is (noting that ParserCombinators is from base): {{{ qual_name mod occ | [] <- unqual_gres , modulePackageKey mod `elem` [primPackageKey, basePackageKey, thPackageKey] , not (isDerivedOccName occ) = NameUnqual -- For names from ubiquitous packages that come with GHC, if -- there are no entities called unqualified 'occ', then -- print unqualified. Doing so does not cause ambiguity, -- and it reduces the amount of qualification in error -- messages. We can't do this for all packages, because we -- might get errors like "Can't unify T with T". But the -- ubiquitous packages don't contain any such gratuitous -- name clashes. -- -- A motivating example is 'Constraint'. It's often not in -- scope, but printing GHC.Prim.Constraint seems overkill. }}} from {{{ commit 547c597112954353cef7157cb0a389bc4f6303eb Author: Simon Peyton Jones Tue Apr 7 05:48:30 2015 Committer: Simon Peyton Jones Tue Apr 7 07:10:22 2015 Reduce module qualifiers in pretty-printing }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 6 23:08:05 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 06 Jul 2015 23:08:05 -0000 Subject: [GHC] #10599: Template Haskell doesn't allow `newName "type"` In-Reply-To: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> References: <048.829d4ff7778a587a956aa230325a65a0@haskell.org> Message-ID: <063.276ec304a5250fb7b7ece338f854e9b9@haskell.org> #10599: Template Haskell doesn't allow `newName "type"` -------------------------------------+------------------------------------- Reporter: meteficha | Owner: goldfire Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jb55): * cc: jb55 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 00:41:45 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 00:41:45 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.44101b034fe745fbb28b3463c7a249ed@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Based on conversation with simonpj et al, we have a different plan to accomplish this: 1. We introduce a new concept, the *version hash*, a hash of package name, package version, and the version hashes of all textual dependencies (i.e. packages which were include.) A version hash is a coarse approximation of installed package IDs, which are suitable for inclusion in package keys (you don't want to put an IPID in a package key, since it means the key will change any time the source changes.) Version hashes are calculated by Cabal and passed to GHC, and they are recorded in the installed package database. 2. GHC now accepts a new flag `-version-hash` which Cabal can invoke in order to pass in a version hash. So now we get something like `-version- hash 8TmvWUcS1U1IKHT0levwg3 -hide-all-packages -package-id ...` when we call GHC. GHC takes `-version-hash` and then computes a package key based on it. 3. Cabal computes the version hash by looking at the recorded version hashes in the installed package database of all the external dependencies of the library portion of the package. It then calls GHC's `--package-key` major mode to get the package key that the package will end up having. Cabal tracking bug: https://github.com/haskell/cabal/pull/2685 One minor complication: sometimes, GHC needs to know what the package name of the package currently being built is to give a good error message. Since the version hash is just a hash, this isn't enough information. There are two ways we can get the information we need: 1. Just pass it to GHC. `-package-name` is not a bad flag name for this. 2. Put it into an (inplace) package database and have GHC query that database for the information. This requires some Cabal changes, see https://github.com/haskell/cabal/issues/2710 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 04:17:57 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 04:17:57 -0000 Subject: [GHC] #10609: Make up instances Message-ID: <047.ffaf9fde9cde45ea3283521ce42e1f8c@haskell.org> #10609: Make up instances -------------------------------------+------------------------------------- Reporter: fumieval | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.10.1 Component: | Operating System: Unknown/Multiple libraries/base | Type of failure: None/Unknown Keywords: | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The following instances are missing as of now. * Foldable ZipList * Traversable ZipList * Functor Complex * Foldable Complex * Traversable Complex * Applicative Complex * Monad Complex * Monoid a => Monoid (Identity a) Original discussion: https://mail.haskell.org/pipermail/libraries/2015-June/025886.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 04:20:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 04:20:51 -0000 Subject: [GHC] #10609: Make up instances In-Reply-To: <047.ffaf9fde9cde45ea3283521ce42e1f8c@haskell.org> References: <047.ffaf9fde9cde45ea3283521ce42e1f8c@haskell.org> Message-ID: <062.678ed88089fc773e37f30e9b600c8b82@haskell.org> #10609: Make up instances -------------------------------------+------------------------------------- Reporter: fumieval | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1046 -------------------------------------+------------------------------------- Changes (by fumieval): * differential: => Phab:D1046 Old description: > The following instances are missing as of now. > > * Foldable ZipList > * Traversable ZipList > * Functor Complex > * Foldable Complex > * Traversable Complex > * Applicative Complex > * Monad Complex > * Monoid a => Monoid (Identity a) > > Original discussion: > https://mail.haskell.org/pipermail/libraries/2015-June/025886.html New description: The following instances are missing as of now. * Foldable ZipList * Traversable ZipList * Functor Complex * Foldable Complex * Traversable Complex * Applicative Complex * Monad Complex * Monoid a => Monoid (Identity a) * Storable () Original discussion: https://mail.haskell.org/pipermail/libraries/2015-June/025886.html -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 04:21:36 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 04:21:36 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.e0b851ecc00f7fabc14ba1818afcd1a8@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by gjsimms): * version: 7.10.1 => 7.11 Comment: Tested this occurs in HEAD on my machine. I think I have determined why this occurs, I don't see an easy fix offhand. If this is an know issue or if it is not a priority feel free to change the priority/close. Evaluation of rewrite rules seems to work up the syntax tree (lower leafs will be rewritten before the final expressions). So given a BuiltinRule for exp (exp -> exp???) and the Rule (f . exp -> exp) for some fixed f. Processing 1) f . exp 2) (.) f exp Rewrite branches, f has no rule. 3) (.) f exp??? Done, no more rewrites possible. Some code which I believe demonstrates this correctly. (compile with rewrite rules active) {{{ class A a where ida :: a -> a idb :: a -> a class B a where idB :: a -> a instance A Bool where ida _ = False idb _ = True instance B Bool where idB False = True idB True = False {-# NOINLINE ida' #-} ida' :: A a => a -> a ida' = ida {-# NOINLINE idb' #-} idb' :: A a => a -> a idb' = idb {-# RULES "SuccessB" forall f. idB (idB f) = idB f "Failure1" forall f. ida (ida f) = idb f "Failure2" forall f. ida' (ida f) = idb f "Success1" forall f. ida (ida' f) = idb f "Success2" forall f. ida' (ida' f) = idb' f #-} main = do print (ida (ida True)) -- FAIL should print True >> prints False print (ida' (ida True)) -- FAIL should print True >> prints False print (ida' (ida' True)) -- PASS should print True print (ida (ida' True)) -- PASS should print TRUE print (idB (idB False)) -- PASS should print True (INLINING may make this run specific it seems consistent on my machine though) }}} I would appreciate someone more knowledgeable than me checking this out... I have tried forcing BuiltinRules activation on the last step only -- infinite loop in the rewriter during tests (fixes the issue for simple cases). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 04:21:58 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 04:21:58 -0000 Subject: [GHC] #10573: Generalize forever to Applicative In-Reply-To: <047.69a95e7ce51e2fd0eb11bda65dfbf5a4@haskell.org> References: <047.69a95e7ce51e2fd0eb11bda65dfbf5a4@haskell.org> Message-ID: <062.82cd2986617bc8992cf5531245f345ee@haskell.org> #10573: Generalize forever to Applicative -------------------------------------+------------------------------------- Reporter: fumieval | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: AMP Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1045 -------------------------------------+------------------------------------- Changes (by fumieval): * differential: => Phab:D1045 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 05:41:10 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 05:41:10 -0000 Subject: [GHC] #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture Message-ID: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture -------------------------------------+------------------------------------- Reporter: | Owner: amitkumar_ghatwal | Status: new Type: bug | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I am a newbie to GHC platform. I am trying to port GHC to my power architecture , and whilst following the below: 1. wget http://www.haskell.org/ghc/dist/7.6.3/ghc-7.6.3-src.tar.bz2 2. tar xjvf ghc-7.6.3-src.tar.bz2 3. cd ghc-7.6.3 4. ./configure --enable-hc-boot --enable-hc-boot-unregisterised 5. make 6. sudo make install I am getting below errors while performing above step 4 : configure: WARNING: unrecognized options: --enable-hc-boot-unregisterised checking for gfind... no checking for find... /usr/bin/find checking for sort... /usr/bin/sort checking for ghc... no checking build system type... ./config.guess: unable to guess system type This script, last modified 2012-02-10, has failed to recognize the operating system you are using. It is advised that you download the most up to date version of the config scripts from http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.guess;hb=HEAD and http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.sub;hb=HEAD If the version you run (./config.guess) is already up to date, please send the following data and any information you think might be pertinent to in order to provide the needed information to handle your system. config.guess timestamp = 2012-02-10 uname -m = ppc64le uname -r = 3.16.0-23-generic uname -s = Linux uname -v = #31-Ubuntu SMP Tue Oct 21 17:55:08 UTC 2014 /usr/bin/uname -p = /bin/uname -X = hostinfo = /bin/universe = /usr/bin/arch -k = /bin/arch = /usr/bin/oslevel = /usr/convex/getsysinfo = UNAME_MACHINE = ppc64le UNAME_RELEASE = 3.16.0-23-generic UNAME_SYSTEM = Linux UNAME_VERSION = #31-Ubuntu SMP Tue Oct 21 17:55:08 UTC 2014 configure: error: cannot guess build type; you must specify one My system arch is as below : $ lscpu Architecture: ppc64le Byte Order: Little Endian CPU(s): 2 On-line CPU(s) list: 0,1 Thread(s) per core: 1 Core(s) per socket: 2 Socket(s): 1 NUMA node(s): 1 Model: IBM pSeries (emulated by qemu) Hypervisor vendor: KVM Virtualization type: full L1d cache: 64K L1i cache: 32K NUMA node0 CPU(s): 0,1 Any pointers in above will be greatly appreciated. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 07:10:07 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 07:10:07 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.8a49b68a3468bb28680ca23529dca0ee@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * owner: bgamari => simonpj -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 07:11:46 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 07:11:46 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.fc1c97ef065afc9643ab10903768d46b@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Unfortunately the fix on 7.10 regresses the test-case for #5113. I'm looking into why. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 07:29:52 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 07:29:52 -0000 Subject: [GHC] #10579: full module names of names not in scope have gone missing in ghci In-Reply-To: <047.b63d248973b529e66515b0b0ffe3a663@haskell.org> References: <047.b63d248973b529e66515b0b0ffe3a663@haskell.org> Message-ID: <062.9aec7c3e932477f60b81ccbab43a0e30@haskell.org> #10579: full module names of names not in scope have gone missing in ghci -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Correct. I'm not sure what the "right" solution is here. Printing qualifiers on everything in `base` is painful. But not printing them is also painful. Any suggestions? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 07:38:32 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 07:38:32 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.3e73f9913b755db64334b95dc5429da2@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): There are many wiki pages about the package system, but the [wiki:Commentary/Packages/Concepts] is bang up to date, and describes version hashes with much more precision; so in reading Edward's comments above, read that page too. > sometimes, GHC needs to know what the package name of the package currently being built is to give a good error message Examples? Even a list of all the examples. There are probably not many. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 07:51:57 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 07:51:57 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.f45059207c9e529de9765f8bafd898bb@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): GHC has a crude-but-effective way to control the order of application of rules, called "phases". See the reference to phase control in [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/rewrite- rules.html 7.23.1 in the manual]. Phases count down; currently 2, 1, 0. Currently, though, a class-method has a built-in rule (selection from dictionary) which is always active. There is no way for the user to override this, to make it active in (say) phase 1 and later. If you could, that would solve your problem. The only straightforward solution I can see is to make the built-in rule for class methods inactive in phase 2, so that user-written rules take precedence. The trouble with this is that it will delay the moment at which the per-instance functions (which may have rules of their own) become visible. Rather than attempt a change with global consequences, I suggest that you simply make a new intermediate function, just as you have done with `ida'`. Instead of NOINLINE you can say `INLINE [1]` which will inline it in phase 1. Now write your rules for `ida'`. This has the effect of delaying the built-in class-method rule for `ida` without affecting any other functions. I'll add a paragraph to the user manual about this. And I'll close this as wont-fix, because there is a good workaround and no obviously better design. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:01:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:01:24 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.9db3d3ee01d2c0b431b0966f509bacf8@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): > Examples? Even a list of all the examples. There are probably not many. The main situation is when GHC decides that, when printing a type, we have to disambiguate package identity since providing a module is not enough. This happens fairly rarely unless you have multiple versions of a package in scope, since Haskell library authors are fairly good at not having module name collisions; and in any case, one of the packages is going to be in the installed package database in any case. But this capability is more important for Backpack, when we instantiate a package multiple times: then we want to say `p(A -> q():A).M.T` is not equal to `p(A -> r():A).M.T`, rather than say that `1XrbHBg7VzL5pL46pujtdS` is not equal to `ISxd2jw4dc5G3vUrxkRNkV`. So I built in the package name to the definition of a package key. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:06:49 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:06:49 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.56313b796945946f5b1da6c588ab9897@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1040 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"aaa0cd20fdaf8e923e3a083befc2612154cba629/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="aaa0cd20fdaf8e923e3a083befc2612154cba629" Don't eagerly blackhole single-entry thunks (#10414) In a parallel program they can actually be entered more than once, leading to deadlock. Reviewers: austin, simonmar Subscribers: michaelt, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1040 GHC Trac Issues: #10414 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:06:49 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:06:49 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.fa9f60d85c08914b33ea3e33de0f6521@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1040 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d27e7fdb1f16ebb28fee007fc0b1dfbd761789d7/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d27e7fdb1f16ebb28fee007fc0b1dfbd761789d7" Add more discussion of black-holing logic for #10414 Signed-off-by: Ben Gamari }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:11:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:11:51 -0000 Subject: [GHC] #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) In-Reply-To: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> References: <044.8b5ce9f8e233bb071d820a2c5b8037cb@haskell.org> Message-ID: <059.8f567752dbe6ea63f7484f37249e51ca@haskell.org> #10414: Buggy behavior with threaded runtime (-N1 working, -N2 getting into <>) -------------------------------------+------------------------------------- Reporter: exio4 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 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 Revisions: Phab:D1040 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Merged. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:36:21 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:36:21 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.da5e35627bea2918221ee0089c8803fc@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): It appears that the following failures are triggered by the fix on `ghc-7.10`, * `simplCore/should_compile T4945 [bad stdout] (normal)` {{{ =====> T4945(normal) 1533 of 4449 [0, 1, 0] cd ./simplCore/should_compile && $MAKE -s --no-print-directory T4945 T4945.run.stdout 2> T4945.run.stderr Actual stdout output differs from expected: --- ./simplCore/should_compile/T4945.stdout 2015-07-06 17:16:38.859135774 -0400 +++ ./simplCore/should_compile/T4945.run.stdout 2015-07-07 03:57:30.592499506 -0400 @@ -1,7 +0,0 @@ - -> STUArray RealWorld Int Int - (ipv3 [OS=OneShot] :: STUArray RealWorld Int Int) -> - case ipv3 of _ [Occ=Dead] { STUArray ds5 ds6 dt ds7 -> - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray - (Data.Array.Base.STUArray *** unexpected failure for T4945(normal) }}} * `perf/should_run T5113 [stat not good enough] (normal)` {{{ =====> T5113(normal) 2426 of 4449 [0, 2, 0] cd ./perf/should_run && "/home/ben/trees/ghc/ghc-7.10/inplace/bin/ghc- stage2" -o T5113 T5113.hs -fforce-recomp -dcore-lint -dcmm-lint -dno- debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-ghci-history -O > T5113.comp.stderr 2>&1 cd ./perf/should_run && ./T5113 +RTS -V0 -tT5113.stats --machine-readable -RTS T5113.run.stdout 2> T5113.run.stderr bytes allocated value is too high: Expected T5113(normal) bytes allocated: 8000000 +/-5% Lower bound T5113(normal) bytes allocated: 7600000 Upper bound T5113(normal) bytes allocated: 8400000 Actual T5113(normal) bytes allocated: 806747568 Deviation T5113(normal) bytes allocated: 9984.3 % *** unexpected stat test failure for T5113(normal) }}} * `perf/compiler T9961 [stat too good] (normal)` {{{ =====> T9961(normal) 2474 of 4449 [0, 2, 0] cd ./perf/compiler && "/home/ben/trees/ghc/ghc-7.10/inplace/bin/ghc- stage2" -c T9961.hs -fforce-recomp -dno-debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-ghci-history -O +RTS -V0 -tT9961.comp.stats --machine-readable -RTS > T9961.comp.stderr 2>&1 bytes allocated value is too low: (If this is because you have improved GHC, please update the test so that GHC doesn't regress again) Expected T9961(normal) bytes allocated: 663978160 +/-5% Lower bound T9961(normal) bytes allocated: 630779252 Upper bound T9961(normal) bytes allocated: 697177068 Actual T9961(normal) bytes allocated: 616521968 Deviation T9961(normal) bytes allocated: -7.1 % *** unexpected stat test failure for T9961(normal) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:42:07 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:42:07 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.fee2a164f48861b7af6b7116c0c4bee1@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): In this case it seems that what we want to do is rewrite the left hand side of the new rule itself. Not sure if this is a good idea in general though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:49:15 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:49:15 -0000 Subject: [GHC] #4945: Another SpecConstr infelicity In-Reply-To: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> References: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> Message-ID: <068.dc98808f4a6645d7e562ccc43bc471c6@haskell.org> #4945: Another SpecConstr infelicity -------------------------------------+------------------------------------- Reporter: batterseapower | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | simplCore/should_compile/T4945 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => new * resolution: fixed => Comment: It seems that the patch that caused #10527 is likely responsible for this test suddenly starting to work again. Unfortunately, when we fixed #10527 the test broke again. I'm going to again mark it as `expect_broken` and reopen this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 08:52:37 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 08:52:37 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.42c9e338e958ea47f57a2a5d49faa624@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by rwbarton): * priority: normal => high -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 09:02:20 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 09:02:20 -0000 Subject: [GHC] #4945: Another SpecConstr infelicity In-Reply-To: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> References: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> Message-ID: <068.9fdec3872d0b9d50bc1cddc0e19b0e7b@haskell.org> #4945: Another SpecConstr infelicity -------------------------------------+------------------------------------- Reporter: batterseapower | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | simplCore/should_compile/T4945 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Actually, it turns out that thomie's fix to the testcase, 506522c95f5d43db4d469135878c56fe20eb81f6, never made it to the ghc-7.10 branch. This resolves this issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 09:03:01 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 09:03:01 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.a1504f509f438b7cc67aa6dfdf97e509@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): #4945 has been accounted for (the test-case was wrong; see the ticket for details). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 09:17:33 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 09:17:33 -0000 Subject: [GHC] #10590: RTS failing with removeThreadFromDeQueue: not found message In-Reply-To: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> References: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> Message-ID: <060.e598d54daad8be1bc605c79c98b152a6@haskell.org> #10590: RTS failing with removeThreadFromDeQueue: not found message -------------------------------------+------------------------------------- Reporter: qnikst | Owner: slyfox Type: bug | Status: patch Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1024 -------------------------------------+------------------------------------- Changes (by slyfox): * status: new => patch * failure: None/Unknown => Runtime crash -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 09:41:28 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 09:41:28 -0000 Subject: [GHC] #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) In-Reply-To: <056.858e88f48ff10f001159bd74508dd654@haskell.org> References: <056.858e88f48ff10f001159bd74508dd654@haskell.org> Message-ID: <071.a11f3d7d3cc840b9d63017840c7f9237@haskell.org> #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) -------------------------------------+------------------------------------- Reporter: | Owner: daniel.is.fischer | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.0.3 Component: Compiler | Keywords: Resolution: fixed | performance, MonoLocalBinds Operating System: Linux | Architecture: x86 Type of failure: Runtime | Test Case: performance bug | perf/should_run/T5113 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Unfortunately it seems that simonpj's fix for #10527, 07a1f32e8bacecd450112607df3fdf39e553c91e, again breaks this testcase. The `dump-simpl` output for the testcase both before and after the patch can be found [[https://gist.github.com/bgamari/25785a88152fc174cd4f|here]]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 09:44:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 09:44:51 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.5b986391e65b9a47c85dcbe7a194e539@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Changes (by thomasw): * differential: => Phab:D1048 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 09:55:18 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 09:55:18 -0000 Subject: [GHC] #10609: Make up instances In-Reply-To: <047.ffaf9fde9cde45ea3283521ce42e1f8c@haskell.org> References: <047.ffaf9fde9cde45ea3283521ce42e1f8c@haskell.org> Message-ID: <062.0bcc0606d40e2be8b202294803a33ff4@haskell.org> #10609: Make up instances -------------------------------------+------------------------------------- Reporter: fumieval | Owner: Type: feature request | Status: patch Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1049 -------------------------------------+------------------------------------- Changes (by fumieval): * status: new => patch * differential: Phab:D1046 => Phab:D1049 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 10:40:43 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 10:40:43 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.6d5faba7dff718511cd361bb9e66e736@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"37de4ad76b75d403e6a8dae9539af08c859d46a4/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="37de4ad76b75d403e6a8dae9539af08c859d46a4" Build system: don't set GhcLibWays explicitly in build.mk.sample (#10536) We used to have the following in mk/build.mk.sample: GhcLibWays = $(if $(filter $(DYNAMIC_GHC_PROGRAMS),YES),v dyn,v) This commit removes that statement for the following reasons: 1) It depends on the variable DYNAMIC_GHC_PROGRAMS, which is set later in the file for some BuildFlavours. Although this works because `make` does multiple passes when reading Makefiles, it is confusing to users [1]. Instead, test for DYNAMIC_GHC_PROGRAMS in mk/config.mk.in. 2) Although it looks like that line is about compiling the `dyn` way, its purpose is really to not build the `prof` way. This commit introduces the variable BUILD_PROF_LIBS, to make this more explicit. This simplifies mk/build.mk.sample and mk/validate-settings.mk. Note that setting GhcLibWays explicitly still works, and DYNAMIC_GHC_PROGRAMS=NO in build.mk does not build the `dyn` way. [1] https://mail.haskell.org/pipermail/ghc-devs/2014-December/007725.html Differential Revision: https://phabricator.haskell.org/D1021 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 10:50:44 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 10:50:44 -0000 Subject: [GHC] #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) In-Reply-To: <056.858e88f48ff10f001159bd74508dd654@haskell.org> References: <056.858e88f48ff10f001159bd74508dd654@haskell.org> Message-ID: <071.fa0009ec479c4a12ba0e8408953925d4@haskell.org> #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) -------------------------------------+------------------------------------- Reporter: | Owner: daniel.is.fischer | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.0.3 Component: Compiler | Keywords: Resolution: fixed | performance, MonoLocalBinds Operating System: Linux | Architecture: x86 Type of failure: Runtime | Test Case: performance bug | perf/should_run/T5113 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): The above bindings are introduced during FloatOut in both the good and bad cases, as expected. The cases diverge in the very next pass (`SimplMode {Phase = 2 [main], inline, rules, eta-expand, case-of-case}`) where they are inlined in the good case but not in the bad. This of course isn't terribly surprising but I thought I'd write it down anyways. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 11:24:44 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 11:24:44 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.7257d4789e5588ffe03d4af121abf7d9@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1021 -------------------------------------+------------------------------------- Changes (by thomie): * differential: => Phab:D1021 Comment: bgamari mentioned in Phab:D1021: > The exact semantics of `DYNAMIC_GHC_PROGRAMS` actually perplexed me quite a bit at first, in large part due to this overloading of roles. Perhaps it would make sense to just tear off the band-aid: We could retain `DYNAMIC_GHC_PROGRAMS` and its associated logic for the time being, emitting a warning if we find it set. Alongside it we could introduce a new `DYNAMIC_GHC_EXECUTABLES` (or some other name) flag strictly intended to control whether we link ghc and friends dynamically. Finally, we could introduce another flag for specifying whether dynamic libraries should be built. Eventually `DYNAMIC_GHC_PROGRAMS` could be dropped. thoughtpolice: > I'm somewhat against putting in all this work because it does sound confusing, but also because I think the state of shared library support is in the air (personally I'm coming around to the "Nuke it from orbit" position.) So this improvement is at least a cleanup with no substantial semantics change for right now. Leaving this ticket open till we make up our mind about this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 11:39:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 11:39:14 -0000 Subject: [GHC] #10205: On Windows ghc-pkg always reports cache out of date In-Reply-To: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> References: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> Message-ID: <061.b50b129faaf18235a106ef6804c452a1@haskell.org> #10205: On Windows ghc-pkg always reports cache out of date -------------------------------------+------------------------------------- Reporter: hgolden | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: ghc-pkg | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D990 -------------------------------------+------------------------------------- Changes (by svenpanne): * owner: thomie => * status: closed => new * resolution: fixed => Comment: This is still broken in the 7.10rc2 on Windows. {{{ $ which ghc-pkg /c/Program Files/Haskell Platform/7.10.2/bin/ghc-pkg }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 11:47:26 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 11:47:26 -0000 Subject: [GHC] #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) In-Reply-To: <056.858e88f48ff10f001159bd74508dd654@haskell.org> References: <056.858e88f48ff10f001159bd74508dd654@haskell.org> Message-ID: <071.87ef96b5be19d88a364fae9ea110a6f9@haskell.org> #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) -------------------------------------+------------------------------------- Reporter: | Owner: daniel.is.fischer | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.0.3 Component: Compiler | Keywords: Resolution: fixed | performance, MonoLocalBinds Operating System: Linux | Architecture: x86 Type of failure: Runtime | Test Case: performance bug | perf/should_run/T5113 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): It seems that this all comes down to a specialisation rule not firing. Namely this one: `Rule fired: SPEC note @ (ST s) ` which happens twice in the good case and never in the bad case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 11:50:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 11:50:14 -0000 Subject: [GHC] #10611: Runtime crash while running psc Message-ID: <044.6711fcf2994b3fa4d0ff74f3c08bc1a4@haskell.org> #10611: Runtime crash while running psc -------------------------------------+------------------------------------- Reporter: qxjit | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Runtime crash (amd64) | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Got a runtime crash while running the purescript compiler: psc: internal error: evacuate(static): strange closure type 6647784 (GHC version 7.8.3 for x86_64_unknown_linux) As yet I have not be able to reproduce it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 11:53:05 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 11:53:05 -0000 Subject: [GHC] #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) In-Reply-To: <056.858e88f48ff10f001159bd74508dd654@haskell.org> References: <056.858e88f48ff10f001159bd74508dd654@haskell.org> Message-ID: <071.4e05a40e99c88f83867a8e387e772de8@haskell.org> #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) -------------------------------------+------------------------------------- Reporter: | Owner: daniel.is.fischer | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.0.3 Component: Compiler | Keywords: Resolution: fixed | performance, MonoLocalBinds Operating System: Linux | Architecture: x86 Type of failure: Runtime | Test Case: performance bug | perf/should_run/T5113 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): This is odd as the good and bad cases have identical output from `-ddump- rules` and I can clearly see the rule in the Core output in both cases. For some reason it just never fires in the bad case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 12:06:00 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 12:06:00 -0000 Subject: [GHC] #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) In-Reply-To: <056.858e88f48ff10f001159bd74508dd654@haskell.org> References: <056.858e88f48ff10f001159bd74508dd654@haskell.org> Message-ID: <071.7e6a323decdef69e243444fd027c8cab@haskell.org> #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) -------------------------------------+------------------------------------- Reporter: | Owner: daniel.is.fischer | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.0.3 Component: Compiler | Keywords: Resolution: fixed | performance, MonoLocalBinds Operating System: Linux | Architecture: x86 Type of failure: Runtime | Test Case: performance bug | perf/should_run/T5113 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): It seems to me like the fix for #10527 is a bit questionable. I may be missing something but I don't see how arguments could possibly get to the rebuilder (which is responsible for trying rewrite rules) as we now simply perform a bunch of substitutions on them with `substExprS` instead of passing them to`simplExpr`. Surely I'm missing something as one would think this would result in massive a performance regression if it really were the case. Simon, perhaps you can explain how you intended this to work? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 12:08:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 12:08:24 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.1dd9ffa70e099a95d38ad6192efed507@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Simon, I've left a comment on #5113:comment:11 describing a concern I have with your patch against `ghc-7.10`. When you get a chance, could you briefly explain how argument expressions are supposed to now make it to the rebuilder? Currently it appears that we merely perform substitutions on them, which means rules won't fire on them. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 12:11:53 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 12:11:53 -0000 Subject: [GHC] #10205: On Windows ghc-pkg always reports cache out of date In-Reply-To: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> References: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> Message-ID: <061.23937761a2a2cc1f52ee20e3fc2be064@haskell.org> #10205: On Windows ghc-pkg always reports cache out of date -------------------------------------+------------------------------------- Reporter: hgolden | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: ghc-pkg | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D990 -------------------------------------+------------------------------------- Comment (by thomie): {{{ Timestamp 2015-07-06 19:15:52 UTC for c:/Program Files/Haskell Platform/7.10.2\lib\package.conf.d\package.cache Timestamp 2015-07-07 07:51:56.8491787 UTC for c:/Program Files/Haskell Platform/7.10.2\lib\package.conf.d (NEWER than cache) WARNING: cache is out of date: c:/Program Files/Haskell Platform/7.10.2\lib\package.conf.d\package.cache ghc will see an old view of this package db. Use 'ghc-pkg recache' to fix. }}} Try running 'ghc-pkg recache' as the message says. Does it fix the problem? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 12:13:09 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 12:13:09 -0000 Subject: [GHC] #10205: On Windows ghc-pkg always reports cache out of date In-Reply-To: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> References: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> Message-ID: <061.c16931c3e7972cb2ed2eb00d6b03223f@haskell.org> #10205: On Windows ghc-pkg always reports cache out of date -------------------------------------+------------------------------------- Reporter: hgolden | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: ghc-pkg | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D990 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 12:22:05 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 12:22:05 -0000 Subject: [GHC] #10205: On Windows ghc-pkg always reports cache out of date In-Reply-To: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> References: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> Message-ID: <061.0a4fea36339b178ad6dd3f5fccdc033d@haskell.org> #10205: On Windows ghc-pkg always reports cache out of date -------------------------------------+------------------------------------- Reporter: hgolden | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: ghc-pkg | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D990 -------------------------------------+------------------------------------- Comment (by svenpanne): OK, running 'ghc-pkg recache' fixes the problem, but: a) You have to do it as an Administrator, which might not be an option for all users. b) The Windows installer for 7.10rc2 shouldn't install the package DB like this, forcing users to recache as an Administrator directly after installation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 12:44:09 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 12:44:09 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.472244ff6442c1dcb585c050d56c4abe@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:5 rwbarton]: > In this case it seems that what we want to do is rewrite the left hand side of the new rule itself. Not sure if this is a good idea in general though. That sounds delicate and I have no idea what will really happen. The solution I proposed is simple and robust. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 13:59:58 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 13:59:58 -0000 Subject: [GHC] #10612: Progain 350 new Muscle Product! Message-ID: <051.eb9f1f9691c1192fec57c173fecef2a5@haskell.org> #10612: Progain 350 new Muscle Product! -------------------------------------+------------------------------------- Reporter: | Owner: ddeserddeser | Status: new Type: bug | Milestone: Priority: lowest | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Progain 350 supplement Progain 350 supplement is a wholly naturally supplement for people who are looking to gain strong and lean muscles within no time. the supplement is manufactured by highly professional doctors in some of the country?s best equipped scientific laboratories to provide nothing but the best results and male performance. Designed to boost the amount of testosterone in the body, the [http://www.progain-350.reviews/ Progain 350] dietary supplement is an ultimate answer for young and older men who would love to improve their bodies without regrets. The supplement is also an excellent option for people who lift a lot of weights and work out hard already, but who have not seem meaningful results. The Benefits of Progain 350 Both young and older men who are interested in impressing women with their ripped abs and performance in the bedroom will certainly find the supplement beneficial. People who desire well-defined muscles that make their muscles more visible will see the results, as well. The supplement is also recommendable for for for people who spend a significant amount of time in the gym but haven?t seen any meaningful results. By shortening healing time and endurance, the supplement allows the user to exercise more, build muscles while shedding pounds faster. Healing time is reduced, so muscle pains can also be avoided, even after going through a thorough two-hour endurance training. The Ingredients of Progain 350 The Progain 350 dietary supplement is developed to give a 100% natural solution for men who intend to break up with steroids, and have well- defined, lean muscles. [http://www.progain-350.reviews/progain-350-ingredients/ Progain 350] has the Nitric Oxide compound, which is the key supplement for building strong, lean muscles. Known Side Effects as we speak, there aren?t any serious side effects of Progain 350. Because Progain 350 is wholly natural, it does not come with side effects that are caused by synthetic drugs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 16:00:52 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 16:00:52 -0000 Subject: [GHC] #10587: Suspending and unsuspending ghci kills and spawns threads In-Reply-To: <046.86d123f20d63f11aba21b5ddb030dffb@haskell.org> References: <046.86d123f20d63f11aba21b5ddb030dffb@haskell.org> Message-ID: <061.8f3c89de6c5055efbd4516fb1388deae@haskell.org> #10587: Suspending and unsuspending ghci kills and spawns threads ---------------------------------+----------------------------------------- Reporter: niteria | Owner: Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by niteria): * owner: niteria => Comment: I've tried to change it, so that the number of IO manager threads gets decreased when number of capabilities decreases, but I couldn't come up with a solution that satisfied me. The main problem is that the thread is not the only resource associated with the IO manager, there are also callback that should be executed in the future. If we stopped the thread before its loop is empty, we would break the promise of executing that callback. This problem is also described here: https://phabricator.haskell.org/rGHC12f3fef5ec52c1ec0958b674adcd981f48048428 I've considered: * Checking if the loop is empty - I couldn't tell if all the implementations support that, so I abandoned that idea * Migrating the file descriptors and callbacks to another instance of IO manager - the problem is that it isn't obvious which one to migrate to and if we'd want to spread them across available ones. @simonmar suggested just being less aggressive about killing spare workers. I'm starting to like that idea. I'm out of ideas and it's not really that urgent for me, so I'll suspend working on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 16:48:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 16:48:25 -0000 Subject: [GHC] #10536: Clear up how to turn off dynamic linking in build.mk In-Reply-To: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> References: <045.541a8a1a6994293a5767d3af2bef8566@haskell.org> Message-ID: <060.ef712962198c1d8001da39ac97d3f769@haskell.org> #10536: Clear up how to turn off dynamic linking in build.mk -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1021 -------------------------------------+------------------------------------- Comment (by int-e): Could we still mention `GhcLibWays` in `build.mk.sample`? For example, under `Other settings...`: {{{ # Set library ways directly instead of computing it from BUILD_PROF_LIBS and # DYNAMIC_GHC_PROGRAMS (may result in build failures) #GhcLibWays = v dyn p }}} On the topic of `DYNAMIC_GHC_PROGRAMS`, I believe the logic for enabling the `dyn` way is as follows: Since the flag implies that ghci is linked dynamically, using the dynamic rts, that means ghci requires the `dyn` libraries in order to work. Also regarding the semantics, `DYNAMIC_BY_DEFAULT` is another option which affects the usability of the resulting ghc: on Linux (presumably the story on Windows is different) Cabal doesn't interact with the resulting ghc properly if the vanilla way is enabled in Cabal's configuration, resulting in obscure build failures. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 16:50:21 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 16:50:21 -0000 Subject: [GHC] #10205: On Windows ghc-pkg always reports cache out of date In-Reply-To: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> References: <046.5c996b873263a26e2fbcfb59ab0dc22d@haskell.org> Message-ID: <061.331c81ade5f45d2c79c1cc547c1043df@haskell.org> #10205: On Windows ghc-pkg always reports cache out of date -------------------------------------+------------------------------------- Reporter: hgolden | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: ghc-pkg | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D990 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: Ok, then it is not a reappearance of this bug. Sorry for leading you this way. I have opened the following ticket in the Haskell platform issue tracker for you: https://github.com/haskell/haskell-platform/issues/189. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:24 -0000 Subject: [GHC] #10283: Make it possible to suppress warnings produced by -fdefer-type-errors In-Reply-To: <049.e826a9f4dc5636b8c6eb248fd99f1fda@haskell.org> References: <049.e826a9f4dc5636b8c6eb248fd99f1fda@haskell.org> Message-ID: <064.756354ede72474a47f9a797b94a43071@haskell.org> #10283: Make it possible to suppress warnings produced by -fdefer-type-errors -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: kanetw Type: feature request | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: newcomer Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D864 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f753cf11eb9e310b54b08d9a1ea1d11540d8eb69/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="f753cf11eb9e310b54b08d9a1ea1d11540d8eb69" Allow deferred type error warnings to be suppressed Adds a flag -fwarn-deferred-type-errors similar to -fwarn-typed-holes. Changes the boolean flag of -fdefer-type-errors to a 3-state flag similar to the one used by -fdefer-typed-holes/-fwarn-typed-holes. Test Plan: Since only the absence of deferred type error warnings when -fno-warn-deferred-type-errors is passed has to be tested, I duplicated a test case checking -fdefer-type-errors and adjusted it accordingly. Reviewers: nomeata, simonpj, austin, thomie, bgamari, hvr Reviewed By: nomeata, simonpj, austin, thomie, bgamari, hvr Subscribers: bgamari, simonpj, nomeata, thomie Projects: #ghc Differential Revision: https://phabricator.haskell.org/D864 GHC Trac Issues: #10283 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:24 -0000 Subject: [GHC] #10284: Create a dedicated `TypeError` exception type In-Reply-To: <047.839fde5ec581c7ee24adc8fc2d4d35b0@haskell.org> References: <047.839fde5ec581c7ee24adc8fc2d4d35b0@haskell.org> Message-ID: <062.96e8357ad04cc81621d941bbc2ab666c@haskell.org> #10284: Create a dedicated `TypeError` exception type -------------------------------------+------------------------------------- Reporter: kosmikus | Owner: kanetw Type: feature request | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: phab:D866 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9a3e1657db4c0292fc06d6183a802af631c3666a/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="9a3e1657db4c0292fc06d6183a802af631c3666a" Deferred type errors now throw TypeError (#10284) Depends on D864. Previous behaviour was ErrorCall, which might mask issues in tests using -fdefer-type-errors Signed-off-by: David Kraeutmann Test Plan: Test whether the error thrown is indeed TypeError and not ErrorCall. Reviewers: hvr, nomeata, austin Reviewed By: nomeata, austin Subscribers: nomeata, simonpj, thomie Differential Revision: https://phabricator.haskell.org/D866 GHC Trac Issues: #10284 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #3: DiffArray should be instance of Show In-Reply-To: <047.3d7bfcea6c6c5eaaf4a369a972367c38@haskell.org> References: <047.3d7bfcea6c6c5eaaf4a369a972367c38@haskell.org> Message-ID: <062.5b0bf4091904985beabe909bc6cc3a55@haskell.org> #3: DiffArray should be instance of Show --------------------------+-------------------- Reporter: magunter | Owner: nobody Type: bug | Status: closed Priority: normal | Milestone: Component: hslibs/lang | Version: 5.0 Resolution: Fixed | Keywords: --------------------------+-------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #4: -fext-core -fno-core behaves funny In-Reply-To: <045.ae3f8b0e845fade77535d5ec02817b6a@haskell.org> References: <045.ae3f8b0e845fade77535d5ec02817b6a@haskell.org> Message-ID: <060.49d06c5b42a4d1bef2b200624ab8569c@haskell.org> #4: -fext-core -fno-core behaves funny ---------------------+-------------------- Reporter: josefs | Owner: nobody Type: bug | Status: closed Priority: normal | Milestone: Component: Driver | Version: None Resolution: Fixed | Keywords: ---------------------+-------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #6: Debugging info confuses runtime linker In-Reply-To: <047.f0ad9cac1869b4c4c3b4613e6dbb6f53@haskell.org> References: <047.f0ad9cac1869b4c4c3b4613e6dbb6f53@haskell.org> Message-ID: <062.fee3421befffa47322a76024b559dc8d@haskell.org> #6: Debugging info confuses runtime linker -----------------------------+--------------------- Reporter: simonmar | Owner: sewardj Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 5.02 Resolution: Fixed | Keywords: -----------------------------+--------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #5: fails if library has main() In-Reply-To: <045.5aafe47c7b47732eda828244576abf66@haskell.org> References: <045.5aafe47c7b47732eda828244576abf66@haskell.org> Message-ID: <060.b8461880494ffce146756c4bdbbbbcb2@haskell.org> #5: fails if library has main() -----------------------+---------------------- Reporter: cwitty | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: Driver | Version: 5.02 Resolution: Wont Fix | Keywords: -----------------------+---------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #8: Regex failure In-Reply-To: <045.f8ed3d6828e64883829f70bbb0708aa0@haskell.org> References: <045.f8ed3d6828e64883829f70bbb0708aa0@haskell.org> Message-ID: <060.a07475277edcfd47763c8913d188874f@haskell.org> #8: Regex failure --------------------------+---------------------- Reporter: xoltar | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: hslibs/text | Version: 5.02 Resolution: Fixed | Keywords: --------------------------+---------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #7: dodgy case of unboxed tuple type In-Reply-To: <046.d0162c2c79173b600f159e4160473f60@haskell.org> References: <046.d0162c2c79173b600f159e4160473f60@haskell.org> Message-ID: <061.f18785a74316b6fe00d8054575195fa1@haskell.org> #7: dodgy case of unboxed tuple type -----------------------+-------------------- Reporter: mtehver | Owner: nobody Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 5.02 Resolution: Fixed | Keywords: -----------------------+-------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #10590: RTS failing with removeThreadFromDeQueue: not found message In-Reply-To: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> References: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> Message-ID: <060.92c9ae203b367493f4b072f9afbf9907@haskell.org> #10590: RTS failing with removeThreadFromDeQueue: not found message -------------------------------------+------------------------------------- Reporter: qnikst | Owner: slyfox Type: bug | Status: patch Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1024 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:17:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:17:25 -0000 Subject: [GHC] #4934: threadWaitRead works incorrectly on nonthreaded RTS In-Reply-To: <045.715babeb9b3b7ae09fbdae7fcb37f116@haskell.org> References: <045.715babeb9b3b7ae09fbdae7fcb37f116@haskell.org> Message-ID: <060.684315cc68cc60727325ff9e3595bcee@haskell.org> #4934: threadWaitRead works incorrectly on nonthreaded RTS ------------------------------------------------+-------------------------- Reporter: slyfox | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: Runtime System | Version: 7.0.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect result at runtime | (amd64) Blocked By: | Test Case: Related Tickets: | Blocking: ------------------------------------------------+-------------------------- Comment (by Ben Gamari ): In [changeset:"5857e0afb5823987e84e6d3dd8d0b269b7546166/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="5857e0afb5823987e84e6d3dd8d0b269b7546166" fix EBADF unqueueing in select backend (Trac #10590) Alexander found a interesting case: 1. We have a queue of two waiters in a blocked_queue 2. first file descriptor changes state to RUNNABLE, second changes to INVALID 3. awaitEvent function dequeued RUNNABLE thread to a run queue and attempted to dequeue INVALID descriptor to a run queue. Unqueueing INVALID fails thusly: #3 0x000000000045cf1c in barf (s=0x4c1cb0 "removeThreadFromDeQueue: not found") at rts/RtsMessages.c:42 #4 0x000000000046848b in removeThreadFromDeQueue (...) at rts/Threads.c:249 #5 0x000000000049a120 in removeFromQueues (...) at rts/RaiseAsync.c:719 #6 0x0000000000499502 in throwToSingleThreaded__ (...) at rts/RaiseAsync.c:67 #7 0x0000000000499555 in throwToSingleThreaded (..) at rts/RaiseAsync.c:75 #8 0x000000000047c27d in awaitEvent (wait=rtsFalse) at rts/posix/Select.c:415 The problem here is a throwToSingleThreaded function that tries to unqueue a TSO from blocked_queue, but awaitEvent function leaves blocked_queue in a inconsistent state while traverses over blocked_queue: case RTS_FD_IS_READY: IF_DEBUG(scheduler, debugBelch("Waking up blocked thread %lu\n", (unsigned long)tso->id)); tso->why_blocked = NotBlocked; tso->_link = END_TSO_QUEUE; // Here we break the queue head pushOnRunQueue(&MainCapability,tso); break; Signed-off-by: Sergei Trofimovich Test Plan: tested on a sample from T10590 Reviewers: austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: qnikst, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1024 GHC Trac Issues: #10590, #4934 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:47:08 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:47:08 -0000 Subject: [GHC] #10590: RTS failing with removeThreadFromDeQueue: not found message In-Reply-To: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> References: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> Message-ID: <060.abbd070d54ac9f20e45385922764713f@haskell.org> #10590: RTS failing with removeThreadFromDeQueue: not found message -------------------------------------+------------------------------------- Reporter: qnikst | Owner: slyfox Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1024 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:47:45 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:47:45 -0000 Subject: [GHC] #10573: Generalize forever to Applicative In-Reply-To: <047.69a95e7ce51e2fd0eb11bda65dfbf5a4@haskell.org> References: <047.69a95e7ce51e2fd0eb11bda65dfbf5a4@haskell.org> Message-ID: <062.70ec5601c6f72f00d43a5e5d8b7da795@haskell.org> #10573: Generalize forever to Applicative -------------------------------------+------------------------------------- Reporter: fumieval | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: fixed | Keywords: AMP Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1045 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:48:40 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:48:40 -0000 Subject: [GHC] #10283: Make it possible to suppress warnings produced by -fdefer-type-errors In-Reply-To: <049.e826a9f4dc5636b8c6eb248fd99f1fda@haskell.org> References: <049.e826a9f4dc5636b8c6eb248fd99f1fda@haskell.org> Message-ID: <064.1b0691d6e87065017a2364507072a369@haskell.org> #10283: Make it possible to suppress warnings produced by -fdefer-type-errors -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: kanetw Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: newcomer Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D864 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:49:11 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:49:11 -0000 Subject: [GHC] #10590: RTS failing with removeThreadFromDeQueue: not found message In-Reply-To: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> References: <045.1d70a7521e31b555660aa59499823ca1@haskell.org> Message-ID: <060.d1e397797f00a53be82f92f24753218e@haskell.org> #10590: RTS failing with removeThreadFromDeQueue: not found message -------------------------------------+------------------------------------- Reporter: qnikst | Owner: slyfox Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1024 -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => merge * milestone: 7.10.2 => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:52:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:52:24 -0000 Subject: [GHC] #8131: T7571 with WAY=llvm fails, but not WAY=optllvm In-Reply-To: <052.22eb4f882263987206e929bacae5db28@haskell.org> References: <052.22eb4f882263987206e929bacae5db28@haskell.org> Message-ID: <067.f56212002d1838f7afc65e4c26bfa21c@haskell.org> #8131: T7571 with WAY=llvm fails, but not WAY=optllvm -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: rwbarton Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | llvm/should_compile/T8131 | Blocking: | Differential Revisions: Phab:D624 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:53:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:53:24 -0000 Subject: [GHC] #9863: Provide PowerPC 64 bit native code generator In-Reply-To: <047.abf3d61d6edeed38824d04625109fece@haskell.org> References: <047.abf3d61d6edeed38824d04625109fece@haskell.org> Message-ID: <062.5372e2a346f97b94520d503265ac5285@haskell.org> #9863: Provide PowerPC 64 bit native code generator ------------------------------------+------------------------------------ Reporter: trommler | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 Resolution: fixed | Keywords: Operating System: Linux | Architecture: powerpc64 Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D629 ------------------------------------+------------------------------------ Changes (by bgamari): * status: patch => closed * resolution: => fixed Comment: Well done trommler! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:53:37 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:53:37 -0000 Subject: [GHC] #10557: Use `+RTS -G1` for more stable residency measurements In-Reply-To: <045.b69f224ec7b010fc435a2530f08e6526@haskell.org> References: <045.b69f224ec7b010fc435a2530f08e6526@haskell.org> Message-ID: <060.d46586d51021fc68f72088b406099b29@haskell.org> #10557: Use `+RTS -G1` for more stable residency measurements -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: merge Priority: normal | Milestone: 7.12.1 Component: Test Suite | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:53:48 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:53:48 -0000 Subject: [GHC] #10439: Opt_ImplicitImportQualified doesn't work for constructor field name In-Reply-To: <046.7eeda0ab82b2b7fc80cf5d3190f2c3b2@haskell.org> References: <046.7eeda0ab82b2b7fc80cf5d3190f2c3b2@haskell.org> Message-ID: <061.e8028d7c1d2ca55c3d2f7639a116599e@haskell.org> #10439: Opt_ImplicitImportQualified doesn't work for constructor field name -------------------------------------+------------------------------------- Reporter: watashi | Owner: watashi Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | ghci/scripts/T10439 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D900 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:53:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:53:59 -0000 Subject: [GHC] #10023: Relax Monad constraint in traceM and traceShowM to Applicative In-Reply-To: <050.7023a64f597b119154f3ec65be43878d@haskell.org> References: <050.7023a64f597b119154f3ec65be43878d@haskell.org> Message-ID: <065.f4cd82fd39690f486071f3fe5e99362e@haskell.org> #10023: Relax Monad constraint in traceM and traceShowM to Applicative -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: closed Component: libraries/base | Milestone: 7.12.1 Resolution: fixed | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: newcomer Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1029 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:54:16 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:54:16 -0000 Subject: [GHC] #10557: Use `+RTS -G1` for more stable residency measurements In-Reply-To: <045.b69f224ec7b010fc435a2530f08e6526@haskell.org> References: <045.b69f224ec7b010fc435a2530f08e6526@haskell.org> Message-ID: <060.75509f300db867bf21e797e93124063a@haskell.org> #10557: Use `+RTS -G1` for more stable residency measurements -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Test Suite | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:54:40 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:54:40 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.4286d177bc96f57e998dded3c59de076@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | thoughtpolice Priority: normal | Status: closed Component: Compiler | Milestone: 7.10.3 (Parser) | Version: 7.10.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: #5108 | Differential Revisions: Phab:D969 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:55:07 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:55:07 -0000 Subject: [GHC] #9665: Add "since" information to LANGUAGE extensions in GHC user guide In-Reply-To: <051.0c91deb9283c869eec678c3caa22587e@haskell.org> References: <051.0c91deb9283c869eec678c3caa22587e@haskell.org> Message-ID: <066.63158bfaa61d4d1acae9ca880057f2b3@haskell.org> #9665: Add "since" information to LANGUAGE extensions in GHC user guide -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: rasen Type: task | Status: closed Priority: normal | Milestone: Component: Documentation | Version: 7.9 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1019 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 17:56:27 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 17:56:27 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.4e7fd326bcc8021d899b3a58c2bbb1f2@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): It looks like we're still looking for someone to contribute support for `MO_U_Mul2` and `MO_U_QuotRem2`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 18:20:35 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 18:20:35 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.99d9c14944b7b0ed570b5a70d17b9f94@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by michalt): Sorry I wasn't clear in the previous message - I'm actually planning to implement support for the two remaining operations as well (hopefully I'll have some time over the weekend). I just wanted to split the work into two parts since I'm not very familiar with the codebase. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 18:46:23 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 18:46:23 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.51c898a936e8e7dfddeefd889eee5c26@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Ahh, great! Looking forward to reviewing the next patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 18:49:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 18:49:24 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support In-Reply-To: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> References: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> Message-ID: <061.9dbcde73c03801e106ae7cc33f495d0f@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: kgardas Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Karel Gardas ): In [changeset:"d03bcfaa255279c7f0c0d931b3202d45faa9b8e0/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d03bcfaa255279c7f0c0d931b3202d45faa9b8e0" always use -fPIC on OpenBSD/AMD64 platform Summary: This patch switches -fPIC on for every invocation of GHC on OpenBSD/AMD64 platform. The reason is OpenBSD's support for PIE (PIC for executables) hence -fPIC is also needed for GHC compiled code. Fixes #10597 Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1027 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 18:55:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 18:55:14 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support In-Reply-To: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> References: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> Message-ID: <061.33ca06494ccb571448174dcbcb61a85a@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: kgardas Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kgardas): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:20:35 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:20:35 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.2a963f53027cba95e9bcf4b8c9efaf47@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"00c8d4d551472940303437be1496bf23b882273b/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="00c8d4d551472940303437be1496bf23b882273b" Fix #10596 by looking up 'Int' not 'Maybe Int' in the map. Test Plan: validate Reviewers: goldfire, austin, simonpj, bgamari Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1026 GHC Trac Issues: #10596 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:20:35 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:20:35 -0000 Subject: [GHC] #9970: Export more types in GHC.RTS.Flags In-Reply-To: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> References: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> Message-ID: <065.5684b2282db1546dfc07e65fdfcbd4e6@haskell.org> #9970: Export more types in GHC.RTS.Flags -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: new Component: libraries/base | Milestone: 7.12.1 Resolution: | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1030 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"1967a52df5bea5539e46393fa0da0a1ebd6d9db8/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="1967a52df5bea5539e46393fa0da0a1ebd6d9db8" Export more types from GHC.RTS.Flags (#9970) Export the data types `GiveGCStats`, `DoCostCentres`, `DoHeapProfiles`, and `DoTrace`, as well as the type synonyms `Time` and `RtsNat`. The above data types appear as fields in the `-Stats` data types in `GHC.RTS.Flags`, but since they only have `Show` instances, it is practically impossible to due anything useful with the above types unless they are exported. Reviewers: hvr, ekmett, austin, ezyang, bgamari Reviewed By: bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1030 GHC Trac Issues: #9970 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:22:10 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:22:10 -0000 Subject: [GHC] #9970: Export more types in GHC.RTS.Flags In-Reply-To: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> References: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> Message-ID: <065.22b3fa681e505da1bc498feb7b915845@haskell.org> #9970: Export more types in GHC.RTS.Flags -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: merge Component: libraries/base | Milestone: 7.10.3 Resolution: | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1030 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: 7.12.1 => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:22:30 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:22:30 -0000 Subject: [GHC] #9970: Export more types in GHC.RTS.Flags In-Reply-To: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> References: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> Message-ID: <065.1f9045edf20cc2b06cbef0cd0c7857c6@haskell.org> #9970: Export more types in GHC.RTS.Flags -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | RyanGlScott Priority: normal | Status: closed Component: libraries/base | Milestone: 7.10.3 Resolution: fixed | Version: 7.10.1-rc1 Operating System: Unknown/Multiple | Keywords: Type of failure: Other | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: Phab:D1030 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:22:38 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:22:38 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.29e98cc56ed570a300fd9cc84d71d806@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:22:53 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:22:53 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.141dfc27eef6eb7c495225373c9d6173@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 19:25:34 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 19:25:34 -0000 Subject: [GHC] #7258: Compiling DynFlags is jolly slow In-Reply-To: <046.5b0ca13f8e67074efa6f0020a75c7792@haskell.org> References: <046.5b0ca13f8e67074efa6f0020a75c7792@haskell.org> Message-ID: <061.ff7492c503a85a99fc03a2ffc7b45c84@haskell.org> #7258: Compiling DynFlags is jolly slow -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): I strongly suspect that some of the fixes that I've made while working on #7450 will help this although I have yet to test this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 20:25:30 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 20:25:30 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.90bcc16038bfc4702d3739da0649c36a@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gjsimms): I am happy with the workaround/documentation at this point: Just to note, this can be done almost entirely in the Rule system by substituting into temporary functions. So class-methods can be used normally with rewrite rules. {{{ {-# INLINE [1] f' #-} f' = f {-# RULES f = f' #-} {-# RULES (exp1 (f' ...) ...) = exp2) #-} }}} Long term I think it would be most clear if BuiltinRules had no effect on user supplied rewrite rules. This does affect some current libraries e.g. all the RULES in Control.Arrow do nothing, I do not know if/how it affects other libraries. Feel free to close. I do think it is worthwhile making note of in case the simplifier gets overhauled at any point in the future. ida' idb' above can be inlined in the above (all phases) and the rule will still fire for me, I figure this may be somewhat random. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 20:51:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 20:51:14 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.e7c6a5b22e8ea88e9795618d5430cc75@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | thoughtpolice Priority: normal | Status: closed Component: Compiler | Milestone: 7.10.3 (Parser) | Version: 7.10.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: #5108 | Differential Revisions: Phab:D969 -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:10 Ben Gamari ]: > parser: Allow Lm (MODIFIER LETTER) category in identifiers > > Easy fix in the parser to stop regressions, due to Unicode 7.0 changing > the classification of some prior code points. nitpick: the way the commit message is worded (as well the comments in this ticket) suggests that e.g. `x?x` is now a valid identifier... which it isn't... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 20:52:10 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 20:52:10 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.52c843a14525710d5193af40ac3db609@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Phab:D969 Related Tickets: #5108 | -------------------------------------+------------------------------------- Changes (by hvr): * owner: thoughtpolice => * status: closed => new * resolution: fixed => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 20:52:53 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 20:52:53 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.891c205eb50f3a1dd9b98dc15c017f7c@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Phab:D969 Related Tickets: #5108 | -------------------------------------+------------------------------------- Comment (by hvr): I'm reopening this temporarily, because GHC 7.8.4 does in fact accept e.g. {{{ ?:6> let x?x = () x?x :: () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 21:07:03 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 21:07:03 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.28647e4137c4b2d5fc953c5710289900@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Phab:D969 Related Tickets: #5108 | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => merge * milestone: 7.10.3 => 7.10.2 Comment: Please merge. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 21:15:44 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 21:15:44 -0000 Subject: [GHC] #8582: Record syntax for pattern synonyms In-Reply-To: <045.711f298e5aa28ce184df85985d614bd2@haskell.org> References: <045.711f298e5aa28ce184df85985d614bd2@haskell.org> Message-ID: <060.b55646ed499ee079fb0f2e5183810adf@haskell.org> #8582: Record syntax for pattern synonyms -------------------------------------+------------------------------------- Reporter: cactus | Owner: cactus Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | PatternSynonyms Type of failure: None/Unknown | Architecture: Blocked By: 5144 | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by mpickering): I was also thinking this would be nice and would be interested to implement it before 7.12. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 21:38:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 21:38:59 -0000 Subject: [GHC] #10223: Cleanup `mk/build.mk.sample` In-Reply-To: <045.7ed59dbe44609faf808ed2eef55dcc31@haskell.org> References: <045.7ed59dbe44609faf808ed2eef55dcc31@haskell.org> Message-ID: <060.529c6f486cf9690a15eb7fe743b21bbc@haskell.org> #10223: Cleanup `mk/build.mk.sample` -------------------------------------+------------------------------------- Reporter: thomie | Owner: thomie Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by thomie: Old description: New description: The goal is to make build.mk.sample easier to understand for GHC developers. There are currently 13 BuildFlavours available to us. It should be clear what the differences between them are, and if those differences are put there on purpose or it they are bugs. There is a certain amount of cargo culting going on in build.mk.sample, with settings just left alone for years because nobody dares touching them (-H64m -fasm) (or nobody cares). Quiz question: what is the difference between the quick and the devel2 build is. We should try to keep the changes backward-compatible, because there are blog posts etc out there that refer to the existing BuildFlavours. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 23:14:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 23:14:14 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly In-Reply-To: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> References: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> Message-ID: <065.5cd929f8310ab4d800ad0f437cafc49a@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: dnusbaum Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by dnusbaum): * owner: => dnusbaum Comment: I am new to GHC development, and this looks like a good first bug for me, so I'll work on a patch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 7 23:57:30 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 07 Jul 2015 23:57:30 -0000 Subject: [GHC] #10168: generalize filterM, mapAndUnzipM, zipWithM, zipWithM_, replicateM, replicateM_ In-Reply-To: <048.86721c518b657437564df331356981ea@haskell.org> References: <048.86721c518b657437564df331356981ea@haskell.org> Message-ID: <063.f661a20818f889b1635a0e985dcb3be2@haskell.org> #10168: generalize filterM, mapAndUnzipM, zipWithM, zipWithM_, replicateM, replicateM_ -------------------------------------+------------------------------------- Reporter: strake888 | Owner: ekmett Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by fumieval): +1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 00:05:51 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 00:05:51 -0000 Subject: [GHC] #10168: generalize filterM, mapAndUnzipM, zipWithM, zipWithM_, replicateM, replicateM_ In-Reply-To: <048.86721c518b657437564df331356981ea@haskell.org> References: <048.86721c518b657437564df331356981ea@haskell.org> Message-ID: <063.0a7ea4257c5bf6dbc63e9caae2c88b14@haskell.org> #10168: generalize filterM, mapAndUnzipM, zipWithM, zipWithM_, replicateM, replicateM_ -------------------------------------+------------------------------------- Reporter: strake888 | Owner: ekmett Type: bug | Status: patch Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 01:47:27 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 01:47:27 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.08b706a4db03858f96d0c53a41c05e17@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Another reason it's important to support `-package-name` separately from `-version-hash` is that they can vary separately. Consider a Backpack file that looks like: {{{ package p where ... package q where ... }}} both of which come from the same Hackage distribution unit `p` (i.e. you can `cabal install p`). Since GHC is responsible for building both p and q at the same time (and Cabal knows nothing about these subpackages), the version hash of these packages has to be the same. However, we still have to distinguish package p and package q, so here we vary the package name. So it has semantic meaning too! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 05:57:31 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 05:57:31 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.f9661046680ecc4c971b728c47814a55@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:6 simonpj]: > Replying to [comment:5 rwbarton]: > > In this case it seems that what we want to do is rewrite the left hand side of the new rule itself. Not sure if this is a good idea in general though. > > That sounds delicate and I have no idea what will really happen. The solution I proposed is simple and robust. Agreed, but when the method in question belongs to a type class defined in another package (as in the original report), this solution is non-modular. A second library that defines `d'` cannot define a rule for `d' exp` that coexists with a rule for `d exp` unless the two libraries agree on a "`exp'`". It would be nicer if the rules could somehow refer directly to the- instance-of-exp-for-Double. Of course, this is in feature request territory. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 06:54:16 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 06:54:16 -0000 Subject: [GHC] #10613: Mechanism for checking that we only enter single-entry thunks once Message-ID: <046.787816a81f7da40c6d0ca0afdcdd9dbb@haskell.org> #10613: Mechanism for checking that we only enter single-entry thunks once -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: Other Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- During this week's GHC call it came up that it would be nice to have a linting mechanism for verifying that we only enter single-entry thunks once, as currently this invariant appears to be completely unchecked. Currently we do not record whether a thunk is intended to be single-entry when we emit its code. Moreover, I don't believe there is any room for this left in the info table to record this fact. There are two ways I can think of accomodating this, * stealing a bit from the thunk type field * add a flags field to `StgDebugInfo` such that the lint requires the `debug` way As far as implementing the check itself, I think it should be rather straightforward. When we enter a thunk we simply want to check whether it is single-entry. If it is then we replace it with a special type of `BLACKHOLE`-like thunk which crashes the program (or merely emits a warning) on entry. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 09:33:02 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 09:33:02 -0000 Subject: [GHC] #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture In-Reply-To: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> References: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> Message-ID: <071.965fdc211184d16f6f4e895dab14481c@haskell.org> #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture -------------------------------------+------------------------------------- Reporter: | Owner: amitkumar_ghatwal | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Keywords: Resolution: invalid | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by trommler): * status: new => closed * resolution: => invalid Comment: This is fixed in HEAD. The port to powerpc64le was done in ticket #9863. The patch applies with minimal changes to release 7.10.1 [https://build.opensuse.org/source/devel:languages:haskell:lts/ghc/0001 -implement-native-code-generator-for- ppc64.patch?rev=b4a84907abb1251170ffd8d48b45ec60] and also to 7.8.4 (with a few more changes)[https://build.opensuse.org/source/devel:languages:haskell/ghc/0001 -implement-native-code-generator-for- ppc64.patch?rev=2a88150541f7efa445602b8730d72bae]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 09:50:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 09:50:32 -0000 Subject: [GHC] #10614: Show constraints in ``Found hole...'' Message-ID: <047.e629c8600a92660c55de2127511a14cd@haskell.org> #10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Currently it is not clear when types are known equal. Consider writing castWith: {{{#!hs {-# LANGUAGE GADTs , TypeOperators #-} import Data.Type.Equality hiding (castWith) castWith :: a :~: b -> a -> b castWith Refl x = _ }}} which results in {{{ TypeEq.hs:5:19: error: Found hole: _ :: b Where: ?b? is a rigid type variable bound by the type signature for: castWith :: a :~: b -> a -> b at TypeEq.hs:4:13 Relevant bindings include x :: a (bound at TypeEq.hs:5:15) castWith :: a :~: b -> a -> b (bound at TypeEq.hs:5:1) In the expression: _ In an equation for ?castWith?: castWith Refl x = _ }}} Filling the hole with x is correct, but it is not clear from the message that GHC knows this. It would be useful to have a section "Constraints include" e.g. {{{ TypeEq.hs:5:19: error: Found hole: _ :: b Where: ?b? is a rigid type variable bound by the type signature for: castWith :: a :~: b -> a -> b at TypeEq.hs:4:13 Relevant bindings include x :: a (bound at TypeEq.hs:5:15) castWith :: a :~: b -> a -> b (bound at TypeEq.hs:5:1) Constraints include <------ NEW LINE a ~ b (from Refl :: a :~: a at TypeEq.hs:5:10) <------ NEW LINE In the expression: _ In an equation for ?castWith?: castWith Refl x = _ }}} And show class constraints (Show a etc.) similarly -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 09:52:53 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 09:52:53 -0000 Subject: [GHC] #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture In-Reply-To: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> References: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> Message-ID: <071.e4ea71216c1ebe8ff07d1bc8e9a59202@haskell.org> #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture --------------------------------------+--------------------------------- Reporter: amitkumar_ghatwal | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Other Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: --------------------------------------+--------------------------------- Changes (by amitkumar_ghatwal): * os: Unknown/Multiple => Linux * architecture: Unknown/Multiple => Other Comment: Hi , WIll this patch work for " power - ppc64le - architecture " ? Regards, Amit -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 09:55:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 09:55:03 -0000 Subject: [GHC] #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture In-Reply-To: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> References: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> Message-ID: <071.27f393018593c290a0fb660fb596277d@haskell.org> #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture --------------------------------------+--------------------------------- Reporter: amitkumar_ghatwal | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Other Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: --------------------------------------+--------------------------------- Comment (by trommler): Replying to [comment:2 amitkumar_ghatwal]: > Hi , > > WIll this patch work for " power - ppc64le - architecture " ? Yes, it does. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 10:39:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 10:39:13 -0000 Subject: [GHC] #10615: Panic; no skolem info (partial type signatures) Message-ID: <047.cefe16dab67fa27c50fe96bd91e89a00@haskell.org> #10615: Panic; no skolem info (partial type signatures) -------------------------------------+------------------------------------- Reporter: holzensp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- This rather minimal program {{{#!hs f :: _ => _f f = const }}} results in this: {{{ GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Panic.hs, interpreted ) Panic.hs:1:6: Found hole ?_? with inferred constraints: () To use the inferred type, enable PartialTypeSignatures In the type signature for ?f?: _ => _f Panic.hs:2:5: Couldn't match expected type ?_f? with actual type ?a0 -> b0 -> a0? ?_f? is untouchable inside the constraints () bound by the inferred type of f :: _f at Panic.hs:2:1-9ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-apple-darwin): No skolem info: _f_alF[sk] }}} The newest open bugs (that reporter could find at the time of reporting) with "no skolem info" in their description are #10404 and #10432. The newest bug (which is closed) is #10503. It seems likely, though, that the above comes from the PartialTypeSignatures implementation (considering the simplicity of the repro). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 10:43:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 10:43:01 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.7a393bcb0db982495c6ee511a1829faf@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: scpmw Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) * owner: => scpmw * milestone: 7.10.1 => 7.10.3 Comment: Thanks for the update! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 10:43:26 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 10:43:26 -0000 Subject: [GHC] #10615: Panic; no skolem info (partial type signatures) In-Reply-To: <047.cefe16dab67fa27c50fe96bd91e89a00@haskell.org> References: <047.cefe16dab67fa27c50fe96bd91e89a00@haskell.org> Message-ID: <062.9119082077fb57c6b2981cd39e72fd10@haskell.org> #10615: Panic; no skolem info (partial type signatures) -------------------------------------+------------------------------------- Reporter: holzensp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by holzensp): BTW, actually turning on ```PartialTypeSignatures``` gives the expected output: {{{ GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Test ( Test.hs, interpreted ) Test.hs:47:6: Warning: Found hole ?_f? with type: a -> b -> a Where: ?a? is a rigid type variable bound by the inferred type of f :: a -> b -> a at Test.hs:48:1 ?b? is a rigid type variable bound by the inferred type of f :: a -> b -> a at Test.hs:48:1 In the type signature for ?f?: _f Ok, modules loaded: Test. *Test> :r [1 of 1] Compiling Test ( Test.hs, interpreted ) Test.hs:47:6: Warning: Found hole ?_? with inferred constraints: () In the type signature for ?f?: _ => _f Test.hs:47:11: Warning: Found hole ?_f? with type: a -> b -> a Where: ?a? is a rigid type variable bound by the inferred type of f :: a -> b -> a at Test.hs:48:1 ?b? is a rigid type variable bound by the inferred type of f :: a -> b -> a at Test.hs:48:1 In the type signature for ?f?: _ => _f Ok, modules loaded: Test. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 10:47:58 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 10:47:58 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.3ba078ed3e9a191716bc318344ba11eb@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by pacak): Step by step manual to reproduce {{{ % tar xf ../ghc-7.10.1.20150630-src.tar.xz % cp mk/build.mk.sample build.mk % vim mk/build.mk -- uncomment BuildFlavour = perf % autoreconf % perl boot % ./configure && make -j4 [stuff] % ./inplace/bin/ghc-stage2 binlist.hs -O2 [1 of 1] Compiling Main ( binlist.hs, binlist.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1.20150630 for x86_64-unknown-linux): Template variable unbound in rewrite rule sg_s5zd [sc_s5zb, sc_s5zc, sg_s5zd, sg_s5ze] [sc_s5zb, sc_s5zc, sg_s5zd, sg_s5ze] [: @ a_a3fj sc_s5zb sc_s5zc] [: @ a_a3fj sc_s5z7 sc_s5z8] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 10:49:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 10:49:13 -0000 Subject: [GHC] #8168: ghc "Simplifier ticks exhausted" "When trying UnfoldingDone" In-Reply-To: <045.ae6d7c8dc2cac763fcfd91e8b07b080d@haskell.org> References: <045.ae6d7c8dc2cac763fcfd91e8b07b080d@haskell.org> Message-ID: <060.b0f770d39f0d624ef020626ebab6a523@haskell.org> #8168: ghc "Simplifier ticks exhausted" "When trying UnfoldingDone" -------------------------------------+------------------------------------- Reporter: sp55aa | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Simplifier, UnfoldingDone, simpl- Type of failure: GHC rejects | tick-factor valid program | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * priority: high => normal Comment: I'm going to bump down the priority of this following the reasoning given in the User's Guide. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 11:08:00 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 11:08:00 -0000 Subject: [GHC] #10215: Optimizer has bugs regarding handling of -0.0 In-Reply-To: <045.bec2708cfecaad6939bf692a32bcb7aa@haskell.org> References: <045.bec2708cfecaad6939bf692a32bcb7aa@haskell.org> Message-ID: <060.2a304ce05785ca5b6b0e148623b9e5e5@haskell.org> #10215: Optimizer has bugs regarding handling of -0.0 -------------------------------------+------------------------------------- Reporter: lerkok | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.8.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9238 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate Comment: Indeed this gets turned into a `case` expression matching on a float so I believe thi is the same as #9238. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 13:24:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 13:24:08 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.8a1b5c31dbd2cbcc687d6e2874feaecf@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | typeclass, auto Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): To me, this looks like the perfect application of Template Haskell. Yes, this ''could'' be built into GHC, but this seems like one step too far. If you're keen on this being built-in, perhaps seek out support on mailing lists and such to see whether others agree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 13:34:09 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 13:34:09 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.3125682a87a0ffa639384331a1405c87@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Indeed I have reproduced this. Previously I missed that `-O2` was necessary; I believe I was just using `-O` previously. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:14:45 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:14:45 -0000 Subject: [GHC] #9238: Negative zero broken In-Reply-To: <047.56415c116f5d14a35293c7c7b01ed1ce@haskell.org> References: <047.56415c116f5d14a35293c7c7b01ed1ce@haskell.org> Message-ID: <062.906ce5ffaf65192f8b115767350c1d30@haskell.org> #9238: Negative zero broken -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #7858, #9451 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Replying to [comment:6 simonpj]: > I can tell you exactly where it's created: line 2107 of `Simplify.lhs` (in today's HEAD), in function `simplAlt`. > > However I'm suspicious of adding a special case for float/double here. Rather, I think we should prohibit using Core-language `case` expressions to scrutinise float/double, so that `case` (in Core) behaves in a simple, predictable way. > > Rather I think we should probably generate > {{{ > case eqDouble# ds1 0.0## of > True -> ... > False -> ... > }}} > (or, rather, today's unboxed-boolean version). Now the magic is confined to how `eqDouble#` is implemented, which is the proper place for it. simonpj, how do you think your suggestion should interact with the `litEq` rule? As far as I can tell this `PrelRule` is responsible for most of the floating-point pattern matches that we are seeing. As you essentially suggesting we disable `litEq` for floating-point types? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:18:30 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:18:30 -0000 Subject: [GHC] #8347: Add a Strict LANGUAGE pragma In-Reply-To: <044.d01bb368b2606104539d1aa05530b018@haskell.org> References: <044.d01bb368b2606104539d1aa05530b018@haskell.org> Message-ID: <059.0214243abcf0a73d06834205998733eb@haskell.org> #8347: Add a Strict LANGUAGE pragma -------------------------------------+------------------------------------- Reporter: tibbe | Owner: tibbe Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1033 -------------------------------------+------------------------------------- Changes (by thomie): * differential: => Phab:D1033 * milestone: => 7.12.1 Comment: From https://ghc.haskell.org/trac/ghc/wiki/StrictPragma: > Haskell doesn't allow for ~ patterns in data constructor definitions today: we'll add support for such definitions and have it give the current lazy behavior. From Phab:D1033, I understand that using `~` in data constructor definitions without `-XStrictData` will be the error: "Lazy annotation (~) without StrictData" Maybe it would be useful to be able to compile a module both with and without `-XStrictData`, to compare performance differences. In that case this new `~` syntax should be under a different language pragma. Has this been given consideration? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:23:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:23:25 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.7e9c32f281ea6a7bc9b3a6794211f486@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, that being said, this is an extremely sensitive bug. I still haven't been able to reproduce it with the current state of the `ghc-7.10` branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:23:54 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:23:54 -0000 Subject: [GHC] #10616: Panic in ghci debugger with PolyKinds and PhantomTypes Message-ID: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> #10616: Panic in ghci debugger with PolyKinds and PhantomTypes -----------------------------------------+------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: GHCi crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -----------------------------------------+------------------------------- The code {{{#!hs {-# LANGUAGE PolyKinds #-} data D a = A | B f d at A = const True d f B = False }}} when loaded in ghci, runs fine without breakpoints, but panics when breaking on {{{f A}}}, thus: {{{ *Main> f A True *Main> :break 5 Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 *Main> f A ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp }}} It is fine in 7.4.1 and 7.8.1. It panics in 7.10.1 and HEAD at d71b65f53a1daa2631d2c818c7ea6add77813532 Without one (or both) of PolyKinds or the phantom type it runs fine. {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} {{{ gcc -v: Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} With {{{ghci-7.10.1 -v}}} {{{ ghci-7.10.1 -v ./DebuggerCrash.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Glasgow Haskell Compiler, Version 7.10.1, stage 2 booted by GHC version 7.8.2 Using binary package database: /5playpen/t-bepric/ghc-7.10.1-build/inplace/lib/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: Loading package ghc-prim-0.4.0.0 ... linking ... done. *** gcc: /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE -L/5playpen/t-bepric/ghc-7.10.1-build/libraries/integer-gmp2/dist- install/build --print-file-name libgmp.so Loading package integer-gmp-1.0.0.0 ... linking ... done. Loading package base-4.8.0.0 ... linking ... done. wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [] Upsweep completely successful. *** Deleting temp files: Deleting: *** Chasing dependencies: Chasing modules from: *DebuggerCrash.hs Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-08 14:18:11 UTC ms_mod = Main, ms_textual_imps = [import (implicit) Prelude] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file DebuggerCrash.hs Created temporary directory: /tmp/ghc22370_0 *** Checking old interface for Main: [1 of 1] Compiling Main ( DebuggerCrash.hs, interpreted ) *** Parser: *** Renamer/typechecker: *** Desugar: Result size of Desugar (before optimization) = {terms: 16, types: 26, coercions: 0} Result size of Desugar (after optimization) = {terms: 12, types: 18, coercions: 0} *** Simplifier: Result size of Simplifier iteration=1 = {terms: 12, types: 20, coercions: 0} Result size of Simplifier = {terms: 12, types: 20, coercions: 0} *** Tidy Core: Result size of Tidy Core = {terms: 12, types: 20, coercions: 0} *** CorePrep: Result size of CorePrep = {terms: 16, types: 30, coercions: 0} *** ByteCodeGen: Upsweep completely successful. *** Deleting temp files: Deleting: /tmp/ghc22370_0/ghc22370_2.c /tmp/ghc22370_0/ghc22370_1.o Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_2.c Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_1.o Ok, modules loaded: Main. *Main> f A *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: True *Main> :break 5 Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 *Main> f A *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:39:59 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:39:59 -0000 Subject: [GHC] #8347: Add a Strict LANGUAGE pragma In-Reply-To: <044.d01bb368b2606104539d1aa05530b018@haskell.org> References: <044.d01bb368b2606104539d1aa05530b018@haskell.org> Message-ID: <059.9c75115a939f706e16639f4a0945fc21@haskell.org> #8347: Add a Strict LANGUAGE pragma -------------------------------------+------------------------------------- Reporter: tibbe | Owner: tibbe Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1033 -------------------------------------+------------------------------------- Comment (by tibbe): I would pile on even more stuff on ?Phab:D1033, but we could add a `-XExplicitLazyFields` language pragma that's implied by `-XStrictFields` in a separate commit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:55:02 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:55:02 -0000 Subject: [GHC] #10617: Panic in GHCi debugger with GADTs, PolyKinds and Phantom types Message-ID: <047.e5cfdcd1d6a6564527514ba8c400a822@haskell.org> #10617: Panic in GHCi debugger with GADTs, PolyKinds and Phantom types -----------------------------------------+------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: GHCi crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -----------------------------------------+------------------------------- Potentially related: #10616 (I noticed this one first, and in simplifying the code it changed to that error - note TcUnify.hs vs TcType.hs) The code {{{#!hs {-# LANGUAGE GADTs , PolyKinds #-} data AppTreeT (a::k) where Con :: AppTreeT a App :: AppTreeT a -> AppTreeT b -> AppTreeT (a b) tmt :: AppTreeT (Maybe Bool) tmt = App (Con :: AppTreeT Maybe) Con f :: AppTreeT a -> Bool f (App (c at Con) _) = const True c f _ = False }}} when loaded in ghci runs fine without breakpoints, but panics when breaking on {{{f (App )c at Con) _) = ...}}}: {{{ *Main> f tmt True *Main> :break 11 Breakpoint 0 activated at DebuggerCrash2.hs:11:21-32 *Main> f tmt ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150708 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcType.hs line 739 k_anx }}} It fails to load in 7.4.1: {{{DebuggerCrash2.hs:3:19: parse error on input `k'}}} It fails to load in 7.8.2: {{{ DebuggerCrash2.hs:5:50: Kind occurs check The first argument of ?a? should have kind ?k0?, but ?b? has kind ?k0 -> k1? In the type ?AppTreeT (a b)? In the definition of data constructor ?App? In the data declaration for ?AppTreeT? }}} It has the panic in both 7.10.1 and HEAD at d71b65f53a1daa2631d2c818c7ea6add77813532 {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} {{{ gcc -v: Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} With {{{ghci-7.10.1 -v}}} {{{ GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Glasgow Haskell Compiler, Version 7.10.1, stage 2 booted by GHC version 7.8.2 Using binary package database: /5playpen/t-bepric/ghc-7.10.1-build/inplace/lib/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: Loading package ghc-prim-0.4.0.0 ... linking ... done. *** gcc: /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE -L/5playpen/t-bepric/ghc-7.10.1-build/libraries/integer-gmp2/dist- install/build --print-file-name libgmp.so Loading package integer-gmp-1.0.0.0 ... linking ... done. Loading package base-4.8.0.0 ... linking ... done. wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [] Upsweep completely successful. *** Deleting temp files: Deleting: *** Chasing dependencies: Chasing modules from: *DebuggerCrash2.hs Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-08 13:56:59 UTC ms_mod = Main, ms_textual_imps = [import (implicit) Prelude] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file DebuggerCrash2.hs Created temporary directory: /tmp/ghc22446_0 *** Checking old interface for Main: [1 of 1] Compiling Main ( DebuggerCrash2.hs, interpreted ) *** Parser: *** Renamer/typechecker: *** Desugar: Result size of Desugar (before optimization) = {terms: 32, types: 72, coercions: 1} Result size of Desugar (after optimization) = {terms: 26, types: 55, coercions: 0} *** Simplifier: Result size of Simplifier iteration=1 = {terms: 24, types: 79, coercions: 2} Result size of Simplifier = {terms: 21, types: 76, coercions: 2} *** Tidy Core: Result size of Tidy Core = {terms: 31, types: 109, coercions: 4} *** CorePrep: Result size of CorePrep = {terms: 45, types: 157, coercions: 5} *** ByteCodeGen: Upsweep completely successful. *** Deleting temp files: Deleting: /tmp/ghc22446_0/ghc22446_2.c /tmp/ghc22446_0/ghc22446_1.o Warning: deleting non-existent /tmp/ghc22446_0/ghc22446_2.c Warning: deleting non-existent /tmp/ghc22446_0/ghc22446_1.o Ok, modules loaded: Main. *Main> f tmt *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: True *Main> :break 11 Breakpoint 0 activated at DebuggerCrash2.hs:11:21-32 *Main> f tmt *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcType.hs line 730 k_an3 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:56:20 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:56:20 -0000 Subject: [GHC] #10616: Panic in ghci debugger with PolyKinds and PhantomTypes In-Reply-To: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> References: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> Message-ID: <062.0bd1c726970f656f54073551eee7ad06@haskell.org> #10616: Panic in ghci debugger with PolyKinds and PhantomTypes -------------------------------+----------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Description changed by bjmprice: Old description: > The code > {{{#!hs > {-# LANGUAGE PolyKinds #-} > > data D a = A | B > > f d at A = const True d > f B = False > }}} > when loaded in ghci, runs fine without breakpoints, but panics when > breaking on {{{f A}}}, thus: > {{{ > *Main> f A > True > *Main> :break 5 > Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 > *Main> f A > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.10.1 for x86_64-unknown-linux): > ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp > }}} > > It is fine in 7.4.1 and 7.8.1. > It panics in 7.10.1 and HEAD at d71b65f53a1daa2631d2c818c7ea6add77813532 > > Without one (or both) of PolyKinds or the phantom type it runs fine. > > {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP > Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} > {{{ > gcc -v: > Using built-in specs. > COLLECT_GCC=gcc > COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper > Target: x86_64-linux-gnu > Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro > 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs > --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- > suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib > --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix > --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable- > nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug > --enable-libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin > --enable-objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic > --enable-checking=release --build=x86_64-linux-gnu --host=x86_64-linux- > gnu --target=x86_64-linux-gnu > Thread model: posix > gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) > }}} > > With {{{ghci-7.10.1 -v}}} > {{{ > ghci-7.10.1 -v ./DebuggerCrash.hs > GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help > Glasgow Haskell Compiler, Version 7.10.1, stage 2 booted by GHC version > 7.8.2 > Using binary package database: > /5playpen/t-bepric/ghc-7.10.1-build/inplace/lib/package.conf.d/package.cache > wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace > wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace > wired-in package base mapped to base-4.8.0.0-inplace > wired-in package rts mapped to builtin_rts > wired-in package template-haskell mapped to template- > haskell-2.10.0.0-inplace > wired-in package ghc mapped to ghc-7.10.1-inplace > wired-in package dph-seq not found. > wired-in package dph-par not found. > Hsc static flags: > Loading package ghc-prim-0.4.0.0 ... linking ... done. > *** gcc: > /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE > -L/5playpen/t-bepric/ghc-7.10.1-build/libraries/integer-gmp2/dist- > install/build --print-file-name libgmp.so > Loading package integer-gmp-1.0.0.0 ... linking ... done. > Loading package base-4.8.0.0 ... linking ... done. > wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace > wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace > wired-in package base mapped to base-4.8.0.0-inplace > wired-in package rts mapped to builtin_rts > wired-in package template-haskell mapped to template- > haskell-2.10.0.0-inplace > wired-in package ghc mapped to ghc-7.10.1-inplace > wired-in package dph-seq not found. > wired-in package dph-par not found. > *** Chasing dependencies: > Chasing modules from: > Stable obj: [] > Stable BCO: [] > unload: retaining objs [] > unload: retaining bcos [] > Ready for upsweep [] > Upsweep completely successful. > *** Deleting temp files: > Deleting: > *** Chasing dependencies: > Chasing modules from: *DebuggerCrash.hs > Stable obj: [] > Stable BCO: [] > unload: retaining objs [] > unload: retaining bcos [] > Ready for upsweep > [NONREC > ModSummary { > ms_hs_date = 2015-07-08 14:18:11 UTC > ms_mod = Main, > ms_textual_imps = [import (implicit) Prelude] > ms_srcimps = [] > }] > *** Deleting temp files: > Deleting: > compile: input file DebuggerCrash.hs > Created temporary directory: /tmp/ghc22370_0 > *** Checking old interface for Main: > [1 of 1] Compiling Main ( DebuggerCrash.hs, interpreted ) > *** Parser: > *** Renamer/typechecker: > *** Desugar: > Result size of Desugar (before optimization) > = {terms: 16, types: 26, coercions: 0} > Result size of Desugar (after optimization) > = {terms: 12, types: 18, coercions: 0} > *** Simplifier: > Result size of Simplifier iteration=1 > = {terms: 12, types: 20, coercions: 0} > Result size of Simplifier = {terms: 12, types: 20, coercions: 0} > *** Tidy Core: > Result size of Tidy Core = {terms: 12, types: 20, coercions: 0} > *** CorePrep: > Result size of CorePrep = {terms: 16, types: 30, coercions: 0} > *** ByteCodeGen: > Upsweep completely successful. > *** Deleting temp files: > Deleting: /tmp/ghc22370_0/ghc22370_2.c /tmp/ghc22370_0/ghc22370_1.o > Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_2.c > Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_1.o > Ok, modules loaded: Main. > *Main> f A > *** Parser: > *** Desugar: > *** Simplify: > *** CorePrep: > *** ByteCodeGen: > True > *Main> :break 5 > Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 > *Main> f A > *** Parser: > *** Desugar: > *** Simplify: > *** CorePrep: > *** ByteCodeGen: > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.10.1 for x86_64-unknown-linux): > ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp > }}} New description: Potentially related: #10616 (I noticed that one first, and in simplifying the code it changed to this error - note TcUnify.hs vs TcType.hs) The code {{{#!hs {-# LANGUAGE PolyKinds #-} data D a = A | B f d at A = const True d f B = False }}} when loaded in ghci, runs fine without breakpoints, but panics when breaking on {{{f A}}}, thus: {{{ *Main> f A True *Main> :break 5 Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 *Main> f A ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp }}} It is fine in 7.4.1 and 7.8.1. It panics in 7.10.1 and HEAD at d71b65f53a1daa2631d2c818c7ea6add77813532 Without one (or both) of PolyKinds or the phantom type it runs fine. {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} {{{ gcc -v: Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} With {{{ghci-7.10.1 -v}}} {{{ ghci-7.10.1 -v ./DebuggerCrash.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Glasgow Haskell Compiler, Version 7.10.1, stage 2 booted by GHC version 7.8.2 Using binary package database: /5playpen/t-bepric/ghc-7.10.1-build/inplace/lib/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: Loading package ghc-prim-0.4.0.0 ... linking ... done. *** gcc: /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE -L/5playpen/t-bepric/ghc-7.10.1-build/libraries/integer-gmp2/dist- install/build --print-file-name libgmp.so Loading package integer-gmp-1.0.0.0 ... linking ... done. Loading package base-4.8.0.0 ... linking ... done. wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [] Upsweep completely successful. *** Deleting temp files: Deleting: *** Chasing dependencies: Chasing modules from: *DebuggerCrash.hs Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-08 14:18:11 UTC ms_mod = Main, ms_textual_imps = [import (implicit) Prelude] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file DebuggerCrash.hs Created temporary directory: /tmp/ghc22370_0 *** Checking old interface for Main: [1 of 1] Compiling Main ( DebuggerCrash.hs, interpreted ) *** Parser: *** Renamer/typechecker: *** Desugar: Result size of Desugar (before optimization) = {terms: 16, types: 26, coercions: 0} Result size of Desugar (after optimization) = {terms: 12, types: 18, coercions: 0} *** Simplifier: Result size of Simplifier iteration=1 = {terms: 12, types: 20, coercions: 0} Result size of Simplifier = {terms: 12, types: 20, coercions: 0} *** Tidy Core: Result size of Tidy Core = {terms: 12, types: 20, coercions: 0} *** CorePrep: Result size of CorePrep = {terms: 16, types: 30, coercions: 0} *** ByteCodeGen: Upsweep completely successful. *** Deleting temp files: Deleting: /tmp/ghc22370_0/ghc22370_2.c /tmp/ghc22370_0/ghc22370_1.o Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_2.c Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_1.o Ok, modules loaded: Main. *Main> f A *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: True *Main> :break 5 Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 *Main> f A *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 14:59:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 14:59:01 -0000 Subject: [GHC] #10616: Panic in ghci debugger with PolyKinds and PhantomTypes In-Reply-To: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> References: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> Message-ID: <062.8b2bd0232ed2085dab4954c81727f5ad@haskell.org> #10616: Panic in ghci debugger with PolyKinds and PhantomTypes -------------------------------+----------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Description changed by bjmprice: Old description: > Potentially related: #10616 (I noticed that one first, and in simplifying > the code it changed to this error - note TcUnify.hs vs TcType.hs) > > The code > {{{#!hs > {-# LANGUAGE PolyKinds #-} > > data D a = A | B > > f d at A = const True d > f B = False > }}} > when loaded in ghci, runs fine without breakpoints, but panics when > breaking on {{{f A}}}, thus: > {{{ > *Main> f A > True > *Main> :break 5 > Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 > *Main> f A > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.10.1 for x86_64-unknown-linux): > ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp > }}} > > It is fine in 7.4.1 and 7.8.1. > It panics in 7.10.1 and HEAD at d71b65f53a1daa2631d2c818c7ea6add77813532 > > Without one (or both) of PolyKinds or the phantom type it runs fine. > > {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP > Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} > {{{ > gcc -v: > Using built-in specs. > COLLECT_GCC=gcc > COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper > Target: x86_64-linux-gnu > Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro > 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs > --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- > suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib > --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix > --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable- > nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug > --enable-libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin > --enable-objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic > --enable-checking=release --build=x86_64-linux-gnu --host=x86_64-linux- > gnu --target=x86_64-linux-gnu > Thread model: posix > gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) > }}} > > With {{{ghci-7.10.1 -v}}} > {{{ > ghci-7.10.1 -v ./DebuggerCrash.hs > GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help > Glasgow Haskell Compiler, Version 7.10.1, stage 2 booted by GHC version > 7.8.2 > Using binary package database: > /5playpen/t-bepric/ghc-7.10.1-build/inplace/lib/package.conf.d/package.cache > wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace > wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace > wired-in package base mapped to base-4.8.0.0-inplace > wired-in package rts mapped to builtin_rts > wired-in package template-haskell mapped to template- > haskell-2.10.0.0-inplace > wired-in package ghc mapped to ghc-7.10.1-inplace > wired-in package dph-seq not found. > wired-in package dph-par not found. > Hsc static flags: > Loading package ghc-prim-0.4.0.0 ... linking ... done. > *** gcc: > /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE > -L/5playpen/t-bepric/ghc-7.10.1-build/libraries/integer-gmp2/dist- > install/build --print-file-name libgmp.so > Loading package integer-gmp-1.0.0.0 ... linking ... done. > Loading package base-4.8.0.0 ... linking ... done. > wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace > wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace > wired-in package base mapped to base-4.8.0.0-inplace > wired-in package rts mapped to builtin_rts > wired-in package template-haskell mapped to template- > haskell-2.10.0.0-inplace > wired-in package ghc mapped to ghc-7.10.1-inplace > wired-in package dph-seq not found. > wired-in package dph-par not found. > *** Chasing dependencies: > Chasing modules from: > Stable obj: [] > Stable BCO: [] > unload: retaining objs [] > unload: retaining bcos [] > Ready for upsweep [] > Upsweep completely successful. > *** Deleting temp files: > Deleting: > *** Chasing dependencies: > Chasing modules from: *DebuggerCrash.hs > Stable obj: [] > Stable BCO: [] > unload: retaining objs [] > unload: retaining bcos [] > Ready for upsweep > [NONREC > ModSummary { > ms_hs_date = 2015-07-08 14:18:11 UTC > ms_mod = Main, > ms_textual_imps = [import (implicit) Prelude] > ms_srcimps = [] > }] > *** Deleting temp files: > Deleting: > compile: input file DebuggerCrash.hs > Created temporary directory: /tmp/ghc22370_0 > *** Checking old interface for Main: > [1 of 1] Compiling Main ( DebuggerCrash.hs, interpreted ) > *** Parser: > *** Renamer/typechecker: > *** Desugar: > Result size of Desugar (before optimization) > = {terms: 16, types: 26, coercions: 0} > Result size of Desugar (after optimization) > = {terms: 12, types: 18, coercions: 0} > *** Simplifier: > Result size of Simplifier iteration=1 > = {terms: 12, types: 20, coercions: 0} > Result size of Simplifier = {terms: 12, types: 20, coercions: 0} > *** Tidy Core: > Result size of Tidy Core = {terms: 12, types: 20, coercions: 0} > *** CorePrep: > Result size of CorePrep = {terms: 16, types: 30, coercions: 0} > *** ByteCodeGen: > Upsweep completely successful. > *** Deleting temp files: > Deleting: /tmp/ghc22370_0/ghc22370_2.c /tmp/ghc22370_0/ghc22370_1.o > Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_2.c > Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_1.o > Ok, modules loaded: Main. > *Main> f A > *** Parser: > *** Desugar: > *** Simplify: > *** CorePrep: > *** ByteCodeGen: > True > *Main> :break 5 > Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 > *Main> f A > *** Parser: > *** Desugar: > *** Simplify: > *** CorePrep: > *** ByteCodeGen: > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.10.1 for x86_64-unknown-linux): > ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp > }}} New description: Potentially related: #10617 (I noticed that one first, and in simplifying the code it changed to this error - note TcUnify.hs vs TcType.hs) The code {{{#!hs {-# LANGUAGE PolyKinds #-} data D a = A | B f d at A = const True d f B = False }}} when loaded in ghci, runs fine without breakpoints, but panics when breaking on {{{f A}}}, thus: {{{ *Main> f A True *Main> :break 5 Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 *Main> f A ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp }}} It is fine in 7.4.1 and 7.8.1. It panics in 7.10.1 and HEAD at d71b65f53a1daa2631d2c818c7ea6add77813532 Without one (or both) of PolyKinds or the phantom type it runs fine. {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} {{{ gcc -v: Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} With {{{ghci-7.10.1 -v}}} {{{ ghci-7.10.1 -v ./DebuggerCrash.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Glasgow Haskell Compiler, Version 7.10.1, stage 2 booted by GHC version 7.8.2 Using binary package database: /5playpen/t-bepric/ghc-7.10.1-build/inplace/lib/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: Loading package ghc-prim-0.4.0.0 ... linking ... done. *** gcc: /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE -L/5playpen/t-bepric/ghc-7.10.1-build/libraries/integer-gmp2/dist- install/build --print-file-name libgmp.so Loading package integer-gmp-1.0.0.0 ... linking ... done. Loading package base-4.8.0.0 ... linking ... done. wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [] Upsweep completely successful. *** Deleting temp files: Deleting: *** Chasing dependencies: Chasing modules from: *DebuggerCrash.hs Stable obj: [] Stable BCO: [] unload: retaining objs [] unload: retaining bcos [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-08 14:18:11 UTC ms_mod = Main, ms_textual_imps = [import (implicit) Prelude] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file DebuggerCrash.hs Created temporary directory: /tmp/ghc22370_0 *** Checking old interface for Main: [1 of 1] Compiling Main ( DebuggerCrash.hs, interpreted ) *** Parser: *** Renamer/typechecker: *** Desugar: Result size of Desugar (before optimization) = {terms: 16, types: 26, coercions: 0} Result size of Desugar (after optimization) = {terms: 12, types: 18, coercions: 0} *** Simplifier: Result size of Simplifier iteration=1 = {terms: 12, types: 20, coercions: 0} Result size of Simplifier = {terms: 12, types: 20, coercions: 0} *** Tidy Core: Result size of Tidy Core = {terms: 12, types: 20, coercions: 0} *** CorePrep: Result size of CorePrep = {terms: 16, types: 30, coercions: 0} *** ByteCodeGen: Upsweep completely successful. *** Deleting temp files: Deleting: /tmp/ghc22370_0/ghc22370_2.c /tmp/ghc22370_0/ghc22370_1.o Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_2.c Warning: deleting non-existent /tmp/ghc22370_0/ghc22370_1.o Ok, modules loaded: Main. *Main> f A *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: True *Main> :break 5 Breakpoint 0 activated at DebuggerCrash.hs:5:9-20 *Main> f A *** Parser: *** Desugar: *** Simplify: *** CorePrep: *** ByteCodeGen: ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): ASSERT failed! file compiler/typecheck/TcUnify.hs line 1138 k_amp }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:19:30 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:19:30 -0000 Subject: [GHC] #10618: HEAD@d71b65f53a panics: ``get_op (--$)'' Message-ID: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> #10618: HEAD at d71b65f53a panics: ``get_op (--$)'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- (Note that 7.10.1 works as expected) This one line generates a panic: {{{#!hs panic = GarbageConstructorName $ a --$ b }}} (in an otherwise blank file, when passed to {{{ghc }}} or {{{ghci}}}. Just the right hand side panics {{{ghci}}} interactively.) Error message: {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150708 for x86_64-unknown-linux): get_op (--$) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} {{{uname -a: Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux}}} {{{ gcc -v: Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} With {{{ghc -v}}} (Was built with {{{BuildFlavour = devel2}}}, default {{{build.mk}}} otherwise): {{{ Glasgow Haskell Compiler, Version 7.11.20150708, stage 2 booted by GHC version 7.8.2 Using binary package database: /5playpen/t-bepric/ghc- build/inplace/lib/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.2.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.11.20150708-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.2.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.11.20150708-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: *GetOpCrash.hs Stable obj: [] Stable BCO: [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-08 15:09:13 UTC ms_mod = Main, ms_textual_imps = [import (implicit) Prelude] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file GetOpCrash.hs Created temporary directory: /tmp/ghc22576_0 *** Checking old interface for Main: [1 of 1] Compiling Main ( GetOpCrash.hs, GetOpCrash.o ) *** Parser: *** Renamer/typechecker: *** Deleting temp files: Deleting: /tmp/ghc22576_0/ghc_1.s Warning: deleting non-existent /tmp/ghc22576_0/ghc_1.s *** Deleting temp dirs: Deleting: /tmp/ghc22576_0 ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150708 for x86_64-unknown-linux): get_op (--$) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:22:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:22:25 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.0acf645345c4c6f52edfac06964747b8@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by bgamari): Has there been any progress on this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:22:36 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:22:36 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.b31e81be40df66787e6ba622d86c1394@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:24:07 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:24:07 -0000 Subject: [GHC] #10619: Order matters when type-checking Message-ID: <047.c2e45977ca8a75932617b490ff36950d@haskell.org> #10619: Order matters when type-checking -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- When I say {{{ {-# LANGUAGE RankNTypes #-} module Bug where foo True = (\x -> x) :: (forall a. a -> a) -> forall b. b -> b foo False = \y -> y }}} the module compiles. But when I say {{{ {-# LANGUAGE RankNTypes #-} module Bug where foo False = \y -> y foo True = (\x -> x) :: (forall a. a -> a) -> forall b. b -> b }}} it doesn't, failing with {{{ Bug.hs:6:13: Couldn't match type ?b0 -> b0? with ?forall a. a -> a? Expected type: (forall a. a -> a) -> forall a. a -> a Actual type: (forall a. a -> a) -> b0 -> b0 In the expression: (\ x -> x) :: (forall a. a -> a) -> forall b. b -> b In an equation for ?foo?: foo True = (\ x -> x) :: (forall a. a -> a) -> forall b. b -> b }}} I believe this behavior stems from the special case in `tcMonoBinds`, for non-recursive functions without a type signature. I believe the bug would be fixed if that function also checks to make sure that there is precisely one clause to the function. Do you agree? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:31:17 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:31:17 -0000 Subject: [GHC] #10585: Implement proper bidirectional type inference In-Reply-To: <047.d9317282c6b0be672717b58e6191b767@haskell.org> References: <047.d9317282c6b0be672717b58e6191b767@haskell.org> Message-ID: <062.4c0190250e2054e4af634369ac688f51@haskell.org> #10585: Implement proper bidirectional type inference -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: wontfix | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => wontfix Comment: Bah. Well, I tried doing this, and it just made everything worse. The problem is that, in the nice simple systems in published papers, there are only a few forms that can make good use of an expected type (abstractions being the poster child here). However, in GHC, it's just much, much more complicated, where the vast majority of expression forms can make good use of an expected return type. So the structural changes I was hoping would reduce the possibility of errors only improve a few cases, while making the whole structure more intricate. Not worth it. I will add a Note though explaining why there aren't two typechecker functions, though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:40:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:40:40 -0000 Subject: [GHC] #10619: Order matters when type-checking In-Reply-To: <047.c2e45977ca8a75932617b490ff36950d@haskell.org> References: <047.c2e45977ca8a75932617b490ff36950d@haskell.org> Message-ID: <062.05027099a519aac6dccbe4a8d49013c8@haskell.org> #10619: Order matters when type-checking -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): It gets worse. The same problem happens between these two: This succeeds: {{{ {-# LANGUAGE RankNTypes #-} module Bug where foo _ = if True then ((\x -> x) :: (forall a. a -> a) -> forall b. b -> b) else \y -> y }}} This fails: {{{ foo _ = if True then \y -> y else ((\x -> x) :: (forall a. a -> a) -> forall b. b -> b) }}} But the cause is different. This second case is caused by the fact that `ReturnTv`s can unify with polytypes, and the `ReturnTv` for the whole expression is just pushed into the `if`'s branches. But even if the `ReturnTv` were replaced by a `TauTv` before pushing into the `if`'s branches, it would ''still'' be broken because a `TauTv` with an !OpenKind can also unify with polytypes. I think the solution for this case is to create a new flavor of `TauTv` that truly insists on being a tau-type. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 15:55:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 15:55:34 -0000 Subject: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules In-Reply-To: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> References: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> Message-ID: <066.5109ea414665a9db9cb666ec80ae677e@haskell.org> #10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): dreixel, do you intend on putting together a patch to fix this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 16:04:11 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 16:04:11 -0000 Subject: [GHC] #7521: Accelerate examples does not compile with default value of -fsimpl-tick-factor In-Reply-To: <046.a165b81ceec1b63f8c0bcb4e673ec08e@haskell.org> References: <046.a165b81ceec1b63f8c0bcb4e673ec08e@haskell.org> Message-ID: <061.5f2bd36ee5ab8c92965c0b8b5a151e03@haskell.org> #7521: Accelerate examples does not compile with default value of -fsimpl-tick- factor -------------------------------------+------------------------------------- Reporter: eamsden | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Also #10491 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 16:41:00 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 16:41:00 -0000 Subject: [GHC] #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) In-Reply-To: <056.858e88f48ff10f001159bd74508dd654@haskell.org> References: <056.858e88f48ff10f001159bd74508dd654@haskell.org> Message-ID: <071.4de5be48a9bc1b78f9f347e70b676d20@haskell.org> #5113: Huge performance regression of 7.0.2, 7.0.3 and HEAD over 7.0.1 and 6.12 (MonoLocalBinds) -------------------------------------+------------------------------------- Reporter: | Owner: daniel.is.fischer | Status: closed Type: bug | Milestone: Priority: normal | Version: 7.0.3 Component: Compiler | Keywords: Resolution: fixed | performance, MonoLocalBinds Operating System: Linux | Architecture: x86 Type of failure: Runtime | Test Case: performance bug | perf/should_run/T5113 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): The new `substExprS` was dropping rules and specialisations, which is terribly wrong. So I backed out and fixed #10527 another way; see the commit comments. I'm getting a small number of apparently-unrelated validate failures, but I figure it's better to push this so that Ben can try it out. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 16:46:27 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 16:46:27 -0000 Subject: [GHC] #10618: HEAD@d71b65f53a panics: ``get_op (--$)'' In-Reply-To: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> References: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> Message-ID: <062.116e3f53ed9baa119fa0aa734089d5f0@haskell.org> #10618: HEAD at d71b65f53a panics: ``get_op (--$)'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Changes (by thomie): * cc: simonpj (added) * os: Linux => Unknown/Multiple * component: Compiler => Compiler (Type checker) * architecture: x86_64 (amd64) => Unknown/Multiple * milestone: => 7.12.1 Comment: Smaller example that fails: `ghc-stage2 -e 'Just $ Nothing <> Nothing'` I bisected it down to the following commit: fb7b6922573af76a954d939c85e6af7c39a19896 (#10569). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 17:32:44 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 17:32:44 -0000 Subject: [GHC] #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter Message-ID: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott RyanGlScott | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Template | Operating System: Unknown/Multiple Haskell | Type of failure: GHC rejects Keywords: | valid program Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Currently, Template Haskell can't quasiquote {{{Char#}}} or {{{Addr#}}} values: {{{ $ ghci -XTemplateHaskell -XMagicHash GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help ?> import Language.Haskell.TH ?> $([| 'a'# |]) :3:6: Exotic literal not (yet) handled by Template Haskell 'a'# ?> $([| "a"# |]) :4:6: Exotic literal not (yet) handled by Template Haskell "a"## }}} To fix this, we'd need to change the API of {{{template-haskell}}} a bit, since {{{Lit}}} has a {{{StringPrimL}}} but not a {{{CharPrimL}}} constructor. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 17:49:23 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 17:49:23 -0000 Subject: [GHC] #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter In-Reply-To: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> References: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> Message-ID: <065.86b0df0108b3ee8e1fbfe83e59559a8a@haskell.org> #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | RyanGlScott Priority: normal | Status: new Component: Template Haskell | Milestone: Resolution: | Version: 7.10.1 Operating System: Unknown/Multiple | Keywords: Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #4168, #5218, | Blocking: #5877, | Differential Revisions: Phab:D1054 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D1054 * related: => #4168, #5218, #5877, -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 18:27:41 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 18:27:41 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.10ac77d9ded1e28f7bc9630ae37093f7@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: ekmett Type: feature request | Status: new Priority: low | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by dreixel): Do you have any particular use for this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 19:33:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 19:33:25 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.b2f6f9929e20a6159f19ddfbf64a0650@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: ekmett Type: feature request | Status: new Priority: low | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by DerekElkins): Replying to [comment:2 dreixel]: > Do you have any particular use for this? I was making a data type parameterized by a data kind because it was built over another data type parameterized by a data kind. This blocked being able to use GHC Generics with the type. In this case, since I controlled the other data type, I just switched it to using empty data types of kind * rather than a data kind, so I'm not blocked by this. If that other data type had been from a library or if data kinds were critical, this wouldn't have been an option. The Tree type here https://github.com/derekelkins/ads/blob/master/Data/Authenticated/GenericExample.hs was where I ran into the problem when the Auth type was parameterized by a data kind. You can see here, https://github.com/derekelkins/ads/blob/master/Data/Authenticated/Generic.hs, that the Par1 constructor doesn't make sense in my context. In fact, with DataKinds I would not need that comment, because it would simply be illegal to make a type that used Par1. It would be a self-evident kind error rather than a less obvious missing instance error. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 19:42:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 19:42:25 -0000 Subject: [GHC] #9238: Negative zero broken In-Reply-To: <047.56415c116f5d14a35293c7c7b01ed1ce@haskell.org> References: <047.56415c116f5d14a35293c7c7b01ed1ce@haskell.org> Message-ID: <062.520e46785ff88999b712414b2db81c5a@haskell.org> #9238: Negative zero broken -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #7858, #9451 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:13 bgamari]: > simonpj, how do you think your suggestion should interact with the `litEq` rule? As far as I can tell this `PrelRule` is responsible for most of the floating-point pattern matches that we are seeing. As you essentially suggesting we disable `litEq` for floating-point types? Well, IF we agree that Core case expressions should not scrutinise floating point values, THEN * We should document that invariant, with explanation of why * We should make Core Lint check for it * And yes `litEq` (which generates such case expressions) should not do so for floating point values Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 19:56:38 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 19:56:38 -0000 Subject: [GHC] #10604: Make Generic1 kind polymorphic In-Reply-To: <050.900476330e5007bcb132f742a5f2d072@haskell.org> References: <050.900476330e5007bcb132f742a5f2d072@haskell.org> Message-ID: <065.cd143f407b6098d4927fd05646d04741@haskell.org> #10604: Make Generic1 kind polymorphic -------------------------------------+------------------------------------- Reporter: DerekElkins | Owner: ekmett Type: feature request | Status: new Priority: low | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ekmett): I have a number of data types for things like McBride-style indexed monads for which I currently can't use Generic support because of this issue. This consequently requires me to laboriously hand-implement support for things like serialization. It seems relatively painless to implement. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 20:52:59 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 20:52:59 -0000 Subject: [GHC] #10618: HEAD@d71b65f53a panics: ``get_op (--$)'' In-Reply-To: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> References: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> Message-ID: <062.1197a6d8c995458afe512ac677740eb4@haskell.org> #10618: HEAD at d71b65f53a panics: ``get_op (--$)'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj Comment: Spot on. Sorry for the oversight; patch coming. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 20:54:29 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 20:54:29 -0000 Subject: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules In-Reply-To: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> References: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> Message-ID: <066.bf8e4e6858cc0a42a77b3b8690fcbb7d@haskell.org> #10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Andres Loh has offered to take over `Generic` and `DeriveAnyClass`, but only at the end of the summer. I'm not sure what his Trac alias is. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 21:00:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 21:00:40 -0000 Subject: [GHC] #10616: Panic in ghci debugger with PolyKinds and PhantomTypes In-Reply-To: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> References: <047.2301fd74ded448fa87313da3f771dc74@haskell.org> Message-ID: <062.54a7910bc3f33f9a8b41bac91f0ab013@haskell.org> #10616: Panic in ghci debugger with PolyKinds and PhantomTypes -------------------------------+----------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by simonpj): Thanks for reporting this. GHC's debugger needs some love. It was implemented by a student, and vaguely maintained by me since. It's pretty crufty, and I'm swamped. Would anyone like to take it on? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 21:16:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 21:16:13 -0000 Subject: [GHC] #10614: Show constraints in ``Found hole...'' In-Reply-To: <047.e629c8600a92660c55de2127511a14cd@haskell.org> References: <047.e629c8600a92660c55de2127511a14cd@haskell.org> Message-ID: <062.b7291c074bd8401140e04903d76c5f37@haskell.org> #10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes, that would not be hard. Are you sure you want the class constraints too? Why? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 21:22:26 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 21:22:26 -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.6063e12c0d333bc71e8cf4314fc1b17f@haskell.org> #2439: Missed optimisation with dictionaries and loops -------------------------------------+------------------------------------- Reporter: rl | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: 7.12.1 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 Revisions: -------------------------------------+------------------------------------- Changes (by ekmett): * cc: ekmett (added) Comment: @simonpj: Right now the reflection library (and a few other less savory libraries of mine) rely on the internals of a dictionary with one member and that member being the same thing so I can `unsafeCoerce` to build one. An example outside of the `reflection` library where we need to be able to build a dictionary out of whole cloth: {{{ data SNat (n :: Nat) where Snat :: KnownNat n => SNat n }}} Even if in a context we know `(KnownNat n, KnownNat m)`, we still can't derive `KnownNat (n + m)` with the current Nat solver. Yet having an operator {{{ (+) :: SNat n -> SNat m -> SNat (n + m) }}} for adding such `SNat`'s at the value level makes sense and things like that are important for many (if not most) applications of having a type level natural number type. I wind up having to backfill these things in by constructing dictionaries by hand. In theory, if I had to, I could start to rely on, say, it being the same as a one member data type instead if we decided to make that transition, so long as I have something available to me that has the right form that I could `unsafeCoerce` into a dictionary. Regarding performance impact: it'd introduce an extra pointer-dereference everywhere for dictionaries like `KnownNat` or `Reifies`, which currently just carry an `Integer` or a value in newtype form, but now would have an extra reference involved. It is not terribly significant, assuming light usage, but it is not free. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 21:39:59 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 21:39:59 -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.0f0bc2e4bc62fa8b9b4fe34ad77b574d@haskell.org> #2439: Missed optimisation with dictionaries and loops -------------------------------------+------------------------------------- Reporter: rl | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: 7.12.1 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 Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): You don't give an actual example, and my brain is too small to reconstruct the code you have in mind. Still, I do agree that wrapping a single value in a data type carries an indirection cost. We could make GHC strict in non-single-method dictionaries; indeed that's the way it's supposed to work right now. But someone needs to actually try it out, benchmark etc. In short, I'm in no hurry to make this change. Meanwhile, it's a crime that you have to fake this stuff up. The more concrete your examples of what you can't do type-securely, the more likely someone is to fix them. At the moment I am clueless. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 22:31:26 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 22:31:26 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.9ee01eb91035284b874bede4da0c451c@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Comment (by spinda): Ideally I'd like to see all type features accessible from TH, but this fits my use case right now. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 22:36:53 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 22:36:53 -0000 Subject: [GHC] #10621: Handle annotations in hsig/boot files Message-ID: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> #10621: Handle annotations in hsig/boot files -------------------------------------+------------------------------------- Reporter: spinda | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.10.1 Component: GHC API | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Currently annotations are [https://github.com/ghc/ghc/blob/228ddb95ee137e7cef02dcfe2521233892dd61e0/compiler/typecheck/TcRnDriver.hs#L642 thrown away] when typechecking hsig or hs-boot files. Can we process them as in normal hs source files? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 22:42:39 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 22:42:39 -0000 Subject: [GHC] #10618: HEAD@d71b65f53a panics: ``get_op (--$)'' In-Reply-To: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> References: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> Message-ID: <062.39a396b597983f9d4eeaddd2da7ceac8@haskell.org> #10618: HEAD at d71b65f53a panics: ``get_op (--$)'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"4f9d6008c04b71fc9449b3dc10861f757539ed0f/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="4f9d6008c04b71fc9449b3dc10861f757539ed0f" Fix Trac #10618 (out of scope operator) Out of scope variables now generate HsUnboundVar, and the fixity re-jigging wasn't taking this into account. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 22:53:51 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 22:53:51 -0000 Subject: [GHC] #10608: Compile error regression from GHC 7.10 to 7.11 In-Reply-To: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> References: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> Message-ID: <057.690cdcab9e1f1f8beced60a12ac1026c@haskell.org> #10608: Compile error regression from GHC 7.10 to 7.11 -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Harump. This was deliberate: {{{ commit b83160d07e626bee685f329a9a73e90a4a6074ae Author: Simon Peyton Jones Date: Thu Apr 30 09:18:49 2015 +0100 Tidy up treatment of FlexibleContexts Previously (Trac #10351) we could get Non type-variable argument in the constraint: C [t] (Use FlexibleContexts to permit this) When checking that `f' has the inferred type f :: forall t. C [t] => t -> () which is a bit stupid: we have *inferred* a type that we immediately *reject*. This patch arranges that that the generalisation mechanism (TcSimplify.decideQuantification) doesn't pick a predicate that will be rejected by the subsequent validity check. }}} Moreover #10351 comment 3 makes essentially the same point as you do here. I'll just reverse the change, which is easy to do. Two people have complained about the new behaviour and I don't think anyone complained about the old! Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 23:01:07 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 23:01:07 -0000 Subject: [GHC] #10618: HEAD@d71b65f53a panics: ``get_op (--$)'' In-Reply-To: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> References: <047.6330dd1b6d1c334ef92659dc7b5be3a2@haskell.org> Message-ID: <062.c2c4ff4e718bc72e9dabe806cf1045a0@haskell.org> #10618: HEAD at d71b65f53a panics: ``get_op (--$)'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | rename/should_fail/T10618 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => rename/should_fail/T10618 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 23:12:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 23:12:32 -0000 Subject: [GHC] #10606: avoid redundant stores to the stack when examining already-tagged data In-Reply-To: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> References: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> Message-ID: <062.cc36a8a0fe6d72585ddab9dd4b65d46d@haskell.org> #10606: avoid redundant stores to the stack when examining already-tagged data -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by simonpj): Moreover, the code for each alternative has to work regardless of whether we arrive at it by doing an eval-and-return, or just jump to it for the fully-tagged case. So the code for the alternative needs to know where t,f are going to be. You say that you can use them "wherever they are", and that may be true if they are in local variables (= registers). But then the return-from-eval code will need to re-load them from the stack into the agreed registers, before going to the shared code for the alternative. And that could be bad if the first thing the alternative does is to save them on the stack for another eval! Morover, an unboxed-tuple-return might use up a bunch of registers. This looks tricky to me. Happy to Skype about it if you are keen to pursue. But I think there is lower-hanging fruit: see "Cmm and code generation" on [wiki:Status/SLPJ-Tickets]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 23:25:47 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 23:25:47 -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.d9d145bec6089d200521a60ac1a5645c@haskell.org> #2439: Missed optimisation with dictionaries and loops -------------------------------------+------------------------------------- Reporter: rl | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: 7.12.1 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 Revisions: -------------------------------------+------------------------------------- Comment (by ekmett): Here's a worked version of the `SNat` thing I was talking about: {{{ {-# LANGUAGE RankNTypes, TypeOperators, GADTs, DataKinds #-} module SNat where import GHC.TypeLits import Unsafe.Coerce data SNat n where SNat :: KnownNat n => SNat n snatVal :: SNat n -> Integer snatVal n at SNat = natVal n instance Show (SNat n) where showsPrec d n = showsPrec d (snatVal n) newtype Magic n = Magic (KnownNat n => SNat n) add :: SNat n -> SNat m -> SNat (n + m) add n m = unsafeCoerce (Magic SNat) (snatVal n + snatVal m) mul :: SNat n -> SNat m -> SNat (n * m) mul n m = unsafeCoerce (Magic SNat) (snatVal n * snatVal m) }}} With that at the ghci prompt we can now look at `SNat`'s {{{ ghci> SNat :: SNat 32 32 }}} and I can work around the limitations of the nat solver, by helping it out as needed at the value level: {{{ ghci> add (SNat :: SNat 1) (SNat :: SNat 2) 3 }}} Then if I need the fabricated `KnownNat` instance for the sum I can just open up my `SNat` constructor and bring it into scope, like the Show instance just did. Here I had to make up my own `SNat` type as the one that is provided by GHC is actually not exported. `add` and `mul` are evil and unsafe, but here they do precisely the right thing. Their results are correct, even if the methodology is suspect. We get them by coercing `Magic n` into a function and passing it the value that is the representation of KnownNat. The core that gets generated is just that of explicit dictionary passing, same as with reflection. With `reflection` I relied on the quantifier when reifying to ensure things were generative. Here I rely on the fact that I'm working with singleton values, but the mechanism used to cheat the system is the same. The current `reflection` code looks similar, just using a different `Magic` type and some quantifier and `Proxy` noise to permit use in more situation. {{{ class Reifies s a | s -> a where reflect :: proxy s -> a newtype Magic a r = Magic (forall (s :: *). Reifies s a => Proxy s -> r) -- | Reify a value at the type level, to be recovered with 'reflect'. reify :: forall a r. a -> (forall (s :: *). Reifies s a => Proxy s -> r) -> r reify a k = unsafeCoerce (Magic k :: Magic a r) (const a) Proxy }}} In a world that was modified to make all dictionaries live inside a data type so they could be forced without consequence then I'd be changing `reify` to something more like: {{{ data Dictionary a = Dictionary a reify :: forall a r. a -> (forall (s :: *). Reifies s a => Proxy s -> r) -> r reify a k = unsafeCoerce (Magic k :: Magic a r) (Dictionary (const a)) Proxy }}} assuming that the dictionary representation and the representation of a data type with exactly one field (like `Dictionary`) were the same. I could patch around it if needed, but the proposal here seems odd to me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 23:55:55 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 23:55:55 -0000 Subject: [GHC] #10614: Show constraints in ``Found hole...'' In-Reply-To: <047.e629c8600a92660c55de2127511a14cd@haskell.org> References: <047.e629c8600a92660c55de2127511a14cd@haskell.org> Message-ID: <062.ed1b51a9cbf4db9130a4d6d22cb98e62@haskell.org> #10614: Show constraints in ``Found hole...'' -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): +1. And with the class constraints listed, too. When you're having trouble knowing what type you want, more information is better (to me). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 8 23:57:45 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 08 Jul 2015 23:57:45 -0000 Subject: [GHC] #9669: Long compile time/high memory usage for modules with many deriving clauses In-Reply-To: <047.d2e05ff2cf33283bc3e60e65402ecabf@haskell.org> References: <047.d2e05ff2cf33283bc3e60e65402ecabf@haskell.org> Message-ID: <062.3cb11e1741fac68489f23a28a8d1afa6@haskell.org> #9669: Long compile time/high memory usage for modules with many deriving clauses -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #75 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * related: => #75 Comment: I suspect this will be positively affected by my recent work on #7450 (which focussed on compile time of datatypes with large numbers of constructors). This work has thusfar produced two fixes (Phab:D1012 and Phab:D1041). Let's characterize their effect on this and a couple of other related testcases with 7.11. This test will start with 7a3d85e705665fbf2c28f83bb3997e8979f2b88c, the parent commit of the merge of D1012 (4681f55970cabc6e33591d7e698621580818f9a2), as the base commit. I will also test D1041 (which I have yet to land) applied directly on top of this. I will look at the "maximum residency", "MUT time", "Total time", and "allocated in the heap" statistics from `+RTS -s`. ||= testcase =||= commit =||= max residency =||= MUT time =||= total time =||= allocated =|| ||= T9669 =|| base commit || 410 MB || 46.0 s || 79.4 s || 81.0 GB || || || + D1012 || 438 MB || 46.0 s || 79.7 s || 80.9 GB || || || + D1041 || 438 MB || 46.2 s || 79.9 s || 80.8 GB || ||= T7450 =|| base commit || 404 MB || 35.5 s || 48.4 s || 61.0 GB || || || + D1012 || 460 MB || 23.0 s || 35.0 s || 38.3 GB || || || + D1041 || 438 MB || 22.3 s || 35.0 s || 37.0 GB || ||= T7450-2k =|| base commit || 919 MB || 112.1 s || 140.0 s || 191.5 GB || || || + D1012 || 961 MB || 57.7 s || 84.1 s || 102.0 GB || || || + D1041 || 986 MB || 54.6 s || 82.1 s || 91.9 GB || ||= T7450-4k =|| base commit || not tested || || || || || || + D1012 || 2.4 GB || 174.0 s || 235.0 s || 338.3 GB || || || + D1041 || 1.9 GB || 158.8 s || 219.3 s || 254.5 GB || ||= T7258 =|| base commit || 191 MB || 30.5 s || 42.0 s || 49.5 GB || || || + D1012 || 171 MB || 31.4 s || 41.3 s || 49.5 GB || || || + D1041 || 179 MB || 31.2 s || 43.0 s || 49.5 GB || Here the `T9696` testcase refers to the `Bar.hs` produced by `generate.hs` on this ticket. The `T7258` case is the `W2.hs` on #7458 which features a large number of fields in a single record constructor. The `T7450` case refers to program like that described in #7450(comment:18) defining a single type with 1024 constructors deriving `Read`. The `T7450-2k` case is identical to `T7450` but with 2096 constructors. `T7450-4k` is again identical but with 4096 constructors. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 00:00:19 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 00:00:19 -0000 Subject: [GHC] #9669: Long compile time/high memory usage for modules with many deriving clauses In-Reply-To: <047.d2e05ff2cf33283bc3e60e65402ecabf@haskell.org> References: <047.d2e05ff2cf33283bc3e60e65402ecabf@haskell.org> Message-ID: <062.7c8916b9ce74f57ad338deebd962fb5c@haskell.org> #9669: Long compile time/high memory usage for modules with many deriving clauses -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #75 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): From the above we can safely assume that my work on #7450 has not had any measureable impact on #9669 or #7258. Hrm. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 00:02:26 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 00:02:26 -0000 Subject: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? In-Reply-To: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> References: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> Message-ID: <060.374599416540bbfad8335439f0c5bc93@haskell.org> #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? -------------------------------------+------------------------------------- Reporter: iustin | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1012 -------------------------------------+------------------------------------- Comment (by bgamari): ticket:9669#comment:13 contains a summary of the performance impact of Phab:D1012 and Phab:D1040 on this and potentially-related ticket #7258. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 00:02:45 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 00:02:45 -0000 Subject: [GHC] #7258: Compiling DynFlags is jolly slow In-Reply-To: <046.5b0ca13f8e67074efa6f0020a75c7792@haskell.org> References: <046.5b0ca13f8e67074efa6f0020a75c7792@haskell.org> Message-ID: <061.860e285127bd31b51ab73bbc8fc0979b@haskell.org> #7258: Compiling DynFlags is jolly slow -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): ticket:9669#comment:13 contains a summary of the performance impact of Phab:D1012 and Phab:D1040 on this and potentially-related ticket #7450. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 00:03:18 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 00:03:18 -0000 Subject: [GHC] #9669: Long compile time/high memory usage for modules with many deriving clauses In-Reply-To: <047.d2e05ff2cf33283bc3e60e65402ecabf@haskell.org> References: <047.d2e05ff2cf33283bc3e60e65402ecabf@haskell.org> Message-ID: <062.a0951082952c1b3e0928188cf2bd10a4@haskell.org> #9669: Long compile time/high memory usage for modules with many deriving clauses -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * related: #75 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 00:07:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 00:07:27 -0000 Subject: [GHC] #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? In-Reply-To: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> References: <045.5b74d940dce176e76fe47859d9b698f8@haskell.org> Message-ID: <060.a5297a36de59664252cb8d91e3e9cc26@haskell.org> #7450: Regression in optimisation time of functions with many patterns (6.12 to 7.4)? -------------------------------------+------------------------------------- Reporter: iustin | Owner: bgamari Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1012 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b29633f5cf310824f3e34716e9261162ced779d3/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b29633f5cf310824f3e34716e9261162ced779d3" Bitmap: Fix thunk explosion Previously we would build up another `map (-N)` thunk for every word in the bitmap. Now we strictly accumulate the position and carry out a single ``map (`subtract` accum)``. `Bitmap.intsToBitmap` showed up in the profile while compiling a testcase of #7450 (namely a program containing a record type with large number of fields which derived `Read`). The culprit was `CmmBuildInfoTables.procpointSRT.bitmap`. On the testcase (with 4096 fields), the profile previously looked like, ``` total time = 307.94 secs (307943 ticks @ 1000 us, 1 processor) total alloc = 336,797,868,056 bytes (excludes profiling overheads) COST CENTRE MODULE %time %alloc lintAnnots CoreLint 17.2 25.8 procpointSRT.bitmap CmmBuildInfoTables 11.3 25.2 FloatOutwards SimplCore 7.5 1.6 flatten.lookup CmmBuildInfoTables 4.0 3.9 ... ``` After this fix it looks like, ``` total time = 256.88 secs (256876 ticks @ 1000 us, 1 processor) total alloc = 255,033,667,448 bytes (excludes profiling overheads) COST CENTRE MODULE %time %alloc lintAnnots CoreLint 20.3 34.1 FloatOutwards SimplCore 9.1 2.1 flatten.lookup CmmBuildInfoTables 4.8 5.2 pprNativeCode AsmCodeGen 3.7 4.3 simplLetUnfolding Simplify 3.6 2.2 StgCmm HscMain 3.6 2.1 ``` Signed-off-by: Ben Gamari Test Plan: Validate Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1041 GHC Trac Issues: #7450 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 00:53:44 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 00:53:44 -0000 Subject: [GHC] #10622: Rename Backpack packages to units Message-ID: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: backpack | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal package may contain MULTIPLE Cabal units, although old-style Cabal files will only define one unit. Here are some of the consequences: 1. We rename `PackageKey` to `UnitId`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit will be uniquely identified by an `InstalledUnitId`. 2. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 3. For backwards compatibility reasons, we'll sometimes arrange for `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to coincide. Specifically, the unit of a package which has the same `UnitName` as the `PackageName` is treated specially: its `InstalledUnitId` is guaranteed to be the same as the `InstalledPackageId` and it is what is "visible" when a user uses old concepts such as `-package foo-0.1` to select a package. 4. The installed package database is extended to record some number of units per an installed package: the public facing API is that you can register a package CONTAINING some number of units. For old-style packages, there will be only one unit with a matching `UnitName`, so this will be isomorphic to an old style package; however, GHC will grow some new APIs for selecting specific units to bring into scope. GHC really mostly only cares about units, but if a user asks for a package using, e.g. `-package` it will translate this request into a request for the appropriate unit. 5. For old-style packages, Cabal will continue to write and register a package configuration file which implicitly defines a single unit. However, the plan is to give GHC the capacity to generate unit description files (like package description files, but per unit), which Cabal can interpret and use to register packages in the global database using a `ghc-pkg` which can register units and "unitless" package description files which don't implicitly define a unit. (NB: we must create unit description files, because `ghc-pkg recache` is expected to be able to regenerate the database.) (NB: we want to be able to add units for a package separately, because this is how units for indefinite packages are created as they are instantiated with new implementations.) 6. Cabal could also finally grow the "multiple libraries per single Cabal file" support people have wanted; it's just a stylized use of the Backpack facilities. The work plan: 1. Modify `bin-package-db` to reflect the unit/package split, but otherwise keep ghc-pkg and GHC the same (so old-style package description still supported, and interpreted as a package containing one unit.) Source modifications to GHC assume that a package only has one unit. 2. Generalize GHC to work with packages with multiple units 3. Add capability to Cabal/ghc-pkg to register just units. For compilation of Backpack files, GHC will write out units which Cabal will then install to the real registry 4. Backpack! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 01:13:47 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 01:13:47 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.21a6b928f8f8add32e09ae381fe58897@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1056 -------------------------------------+------------------------------------- Changes (by ezyang): * differential: => Phab:D1056 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 01:18:42 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 01:18:42 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.ffb12a023d99898b372a3741928fd7e0@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1056 -------------------------------------+------------------------------------- Comment (by ezyang): Corresponding Cabal PR: https://github.com/haskell/cabal/pull/2685 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 01:45:07 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 01:45:07 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.6e2bbda4834140c0c13a3867265e4a3a@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | typeclass, auto Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by songzh): Yes you are right, this is can be one application of TH. However, I am only a newbie of TH, I find I cannot query whether type like `Eq a => List a` is an instance of `Eq` with TH. And there are also other problems for me to implement it, like the situation type synonym with type variables. Any Template Haskell expert would like to work this out? Replying to [comment:3 goldfire]: > To me, this looks like the perfect application of Template Haskell. Yes, this ''could'' be built into GHC, but this seems like one step too far. If you're keen on this being built-in, perhaps seek out support on mailing lists and such to see whether others agree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 01:51:50 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 01:51:50 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly In-Reply-To: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> References: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> Message-ID: <065.42f939b81c6ad6b83542848f4ffb6e95@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: dnusbaum Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Hooray! Let me know if I can be of help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 01:56:32 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 01:56:32 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.090343bd3130c3b63d88a134723eb80d@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): If it's working in HEAD and at the tip of the ghc-7.10 branch, I think it's safe to close the ticket with a regression test. Given the sensitivity of the bug, it might be worth the trouble to make sure that the regression test actually fails on, say, 7.10.2-rc1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 02:06:49 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 02:06:49 -0000 Subject: [GHC] #10607: Auto derive from top to bottom In-Reply-To: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> References: <045.e09b97a7eafdf9652cf786c0b3852657@haskell.org> Message-ID: <060.7ffd87c2cf993cee0548e899eb61a474@haskell.org> #10607: Auto derive from top to bottom -------------------------------------+------------------------------------- Reporter: songzh | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | typeclass, auto Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Yes -- TH struggles a bit with instance lookup and such. Implementing new querying features shouldn't be hard though, if you can suggest an API. Why do you need fancy querying capabilities for your use case? Where does `reifyInstances` fail for you? As for type synonyms, you can check out the `th-expand-syns` package. `th-desugar` also does (limited) type family expansion (among other, larger features). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 03:20:37 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 03:20:37 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.ecc032237a39d461a332c8de744a3dc9@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by ezyang: Old description: > After today's weekly Backpack call, we have come to the conclusion that > we have two different types of "packages" in the Backpack world: > > 1. Cabal packages, which have a single `.cabal` file and are a unit of > distribution which get uploaded to Hackage, and > > 2. Backpack packages, of which there may be multiple defined in a > Backpack file shipped with a Cabal package; and are the building blocks > for modular development in the small. > > It's really confusing to have both of these called packages: thus, we > propose to rename all occurrences of Backpack package to unit. A Cabal > package may contain MULTIPLE Cabal units, although old-style Cabal files > will only define one unit. Here are some of the consequences: > > 1. We rename `PackageKey` to `UnitId`, as it identifies a unit rather > than a Cabal package. (I think this actually makes the function of these > identifiers clearer.) We'll also distinguish Cabal-file level > `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit > will be uniquely identified by an `InstalledUnitId`. > > 2. The source-level syntax of Backpack files will use `unit` in place of > where `package` was used before. > > 3. For backwards compatibility reasons, we'll sometimes arrange for > `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to > coincide. Specifically, the unit of a package which has the same > `UnitName` as the `PackageName` is treated specially: its > `InstalledUnitId` is guaranteed to be the same as the > `InstalledPackageId` and it is what is "visible" when a user uses old > concepts such as `-package foo-0.1` to select a package. > > 4. The installed package database is extended to record some number of > units per an installed package: the public facing API is that you can > register a package CONTAINING some number of units. For old-style > packages, there will be only one unit with a matching `UnitName`, so this > will be isomorphic to an old style package; however, GHC will grow some > new APIs for selecting specific units to bring into scope. GHC really > mostly only cares about units, but if a user asks for a package using, > e.g. `-package` it will translate this request into a request for the > appropriate unit. > > 5. For old-style packages, Cabal will continue to write and register a > package configuration file which implicitly defines a single unit. > However, the plan is to give GHC the capacity to generate unit > description files (like package description files, but per unit), which > Cabal can interpret and use to register packages in the global database > using a `ghc-pkg` which can register units and "unitless" package > description files which don't implicitly define a unit. (NB: we must > create unit description files, because `ghc-pkg recache` is expected to > be able to regenerate the database.) (NB: we want to be able to add units > for a package separately, because this is how units for indefinite > packages are created as they are instantiated with new implementations.) > > 6. Cabal could also finally grow the "multiple libraries per single Cabal > file" support people have wanted; it's just a stylized use of the > Backpack facilities. > > The work plan: > > 1. Modify `bin-package-db` to reflect the unit/package split, but > otherwise keep ghc-pkg and GHC the same (so old-style package description > still supported, and interpreted as a package containing one unit.) > Source modifications to GHC assume that a package only has one unit. > > 2. Generalize GHC to work with packages with multiple units > > 3. Add capability to Cabal/ghc-pkg to register just units. For > compilation of Backpack files, GHC will write out units which Cabal will > then install to the real registry > > 4. Backpack! New description: After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal package may contain MULTIPLE Cabal units, although old-style Cabal files will only define one unit. Here are some of the consequences: 1. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit will be uniquely identified by an `InstalledUnitId`. 2. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 3. For backwards compatibility reasons, we'll sometimes arrange for `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to coincide. Specifically, the unit of a package which has the same `UnitName` as the `PackageName` is treated specially: its `InstalledUnitId` is guaranteed to be the same as the `InstalledPackageId` and it is what is "visible" when a user uses old concepts such as `-package foo-0.1` to select a package. 4. The installed package database is extended to record some number of units per an installed package: the public facing API is that you can register a package CONTAINING some number of units. For old-style packages, there will be only one unit with a matching `UnitName`, so this will be isomorphic to an old style package; however, GHC will grow some new APIs for selecting specific units to bring into scope. GHC really mostly only cares about units, but if a user asks for a package using, e.g. `-package` it will translate this request into a request for the appropriate unit. 5. For old-style packages, Cabal will continue to write and register a package configuration file which implicitly defines a single unit. However, the plan is to give GHC the capacity to generate unit description files (like package description files, but per unit), which Cabal can interpret and use to register packages in the global database using a `ghc-pkg` which can register units and "unitless" package description files which don't implicitly define a unit. (NB: we must create unit description files, because `ghc-pkg recache` is expected to be able to regenerate the database.) (NB: we want to be able to add units for a package separately, because this is how units for indefinite packages are created as they are instantiated with new implementations.) 6. Cabal could also finally grow the "multiple libraries per single Cabal file" support people have wanted; it's just a stylized use of the Backpack facilities. The work plan: 1. Modify `bin-package-db` to reflect the unit/package split, but otherwise keep ghc-pkg and GHC the same (so old-style package description still supported, and interpreted as a package containing one unit.) Source modifications to GHC assume that a package only has one unit. 2. Generalize GHC to work with packages with multiple units 3. Add capability to Cabal/ghc-pkg to register just units. For compilation of Backpack files, GHC will write out units which Cabal will then install to the real registry 4. Backpack! -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 05:15:28 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 05:15:28 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.746d2f98d95298d949b2b8358928dafb@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Changes (by ezyang): * differential: => Phab:D1057 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 06:30:43 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 06:30:43 -0000 Subject: [GHC] #10608: Compile error regression from GHC 7.10 to 7.11 In-Reply-To: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> References: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> Message-ID: <057.13936ae23948371d5d9bc3a21bfe081c@haskell.org> #10608: Compile error regression from GHC 7.10 to 7.11 -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:1 simonpj]: > I'll just reverse the change, which is easy to do. Two people have complained about the new behaviour and I don't think anyone complained about the old! Please don't count me yet as complaining... but rather as wondering :-) The new error message hint {{{ Could not deduce (IsString [t]) arising from the literal ?""? }}} is provides some additional information the previous message didn't. The only downside of the new message is that it doesn't also give the hint of what an explicit type-sig would look like or that `FlexibleContexts` may let GHC continue) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 06:55:56 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 06:55:56 -0000 Subject: [GHC] #10621: Handle annotations in hsig/boot files In-Reply-To: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> References: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> Message-ID: <060.d9a3784d678d8029c322d037b7545ab1@haskell.org> #10621: Handle annotations in hsig/boot files -------------------------------------+------------------------------------- Reporter: spinda | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: GHC API | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): I have a working patch for this that I can submit to Phabricator tomorrow. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 06:56:19 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 06:56:19 -0000 Subject: [GHC] #10621: Handle annotations in hsig/boot files In-Reply-To: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> References: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> Message-ID: <060.c6fdfd1b977592e7defa1a3bf0267e3b@haskell.org> #10621: Handle annotations in hsig/boot files -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: feature request | Status: new Priority: normal | Milestone: Component: GHC API | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by spinda): * owner: => spinda -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 07:28:23 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 07:28:23 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.aefdb527b9bd45f6ce15a4b50d5a608f@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Description changed by simonpj: Old description: > After today's weekly Backpack call, we have come to the conclusion that > we have two different types of "packages" in the Backpack world: > > 1. Cabal packages, which have a single `.cabal` file and are a unit of > distribution which get uploaded to Hackage, and > > 2. Backpack packages, of which there may be multiple defined in a > Backpack file shipped with a Cabal package; and are the building blocks > for modular development in the small. > > It's really confusing to have both of these called packages: thus, we > propose to rename all occurrences of Backpack package to unit. A Cabal > package may contain MULTIPLE Cabal units, although old-style Cabal files > will only define one unit. Here are some of the consequences: > > 1. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather > than a Cabal package. (I think this actually makes the function of these > identifiers clearer.) We'll also distinguish Cabal-file level > `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit > will be uniquely identified by an `InstalledUnitId`. > > 2. The source-level syntax of Backpack files will use `unit` in place of > where `package` was used before. > > 3. For backwards compatibility reasons, we'll sometimes arrange for > `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to > coincide. Specifically, the unit of a package which has the same > `UnitName` as the `PackageName` is treated specially: its > `InstalledUnitId` is guaranteed to be the same as the > `InstalledPackageId` and it is what is "visible" when a user uses old > concepts such as `-package foo-0.1` to select a package. > > 4. The installed package database is extended to record some number of > units per an installed package: the public facing API is that you can > register a package CONTAINING some number of units. For old-style > packages, there will be only one unit with a matching `UnitName`, so this > will be isomorphic to an old style package; however, GHC will grow some > new APIs for selecting specific units to bring into scope. GHC really > mostly only cares about units, but if a user asks for a package using, > e.g. `-package` it will translate this request into a request for the > appropriate unit. > > 5. For old-style packages, Cabal will continue to write and register a > package configuration file which implicitly defines a single unit. > However, the plan is to give GHC the capacity to generate unit > description files (like package description files, but per unit), which > Cabal can interpret and use to register packages in the global database > using a `ghc-pkg` which can register units and "unitless" package > description files which don't implicitly define a unit. (NB: we must > create unit description files, because `ghc-pkg recache` is expected to > be able to regenerate the database.) (NB: we want to be able to add units > for a package separately, because this is how units for indefinite > packages are created as they are instantiated with new implementations.) > > 6. Cabal could also finally grow the "multiple libraries per single Cabal > file" support people have wanted; it's just a stylized use of the > Backpack facilities. > > The work plan: > > 1. Modify `bin-package-db` to reflect the unit/package split, but > otherwise keep ghc-pkg and GHC the same (so old-style package description > still supported, and interpreted as a package containing one unit.) > Source modifications to GHC assume that a package only has one unit. > > 2. Generalize GHC to work with packages with multiple units > > 3. Add capability to Cabal/ghc-pkg to register just units. For > compilation of Backpack files, GHC will write out units which Cabal will > then install to the real registry > > 4. Backpack! New description: After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal ''package'' may contain MULTIPLE Backpack ''units'', although old-style Cabal files will only define one unit. A Cabal package remains * The unit of distribution * The unit that Hackage handles * The unit of versioning * The unit of ownership (who maintains it etc) Here are some of the consequences: 1. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit will be uniquely identified by an `InstalledUnitId`. 2. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 3. For backwards compatibility reasons, we'll sometimes arrange for `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to coincide. Specifically, the unit of a package which has the same `UnitName` as the `PackageName` is treated specially: its `InstalledUnitId` is guaranteed to be the same as the `InstalledPackageId` and it is what is "visible" when a user uses old concepts such as `-package foo-0.1` to select a package. 4. The installed package database is extended to record some number of units per an installed package: the public facing API is that you can register a package CONTAINING some number of units. For old-style packages, there will be only one unit with a matching `UnitName`, so this will be isomorphic to an old style package; however, GHC will grow some new APIs for selecting specific units to bring into scope. GHC really mostly only cares about units, but if a user asks for a package using, e.g. `-package` it will translate this request into a request for the appropriate unit. 5. For old-style packages, Cabal will continue to write and register a package configuration file which implicitly defines a single unit. However, the plan is to give GHC the capacity to generate unit description files (like package description files, but per unit), which Cabal can interpret and use to register packages in the global database using a `ghc-pkg` which can register units and "unitless" package description files which don't implicitly define a unit. (NB: we must create unit description files, because `ghc-pkg recache` is expected to be able to regenerate the database.) (NB: we want to be able to add units for a package separately, because this is how units for indefinite packages are created as they are instantiated with new implementations.) 6. Cabal could also finally grow the "multiple libraries per single Cabal file" support people have wanted; it's just a stylized use of the Backpack facilities. The work plan: 1. Modify `bin-package-db` to reflect the unit/package split, but otherwise keep ghc-pkg and GHC the same (so old-style package description still supported, and interpreted as a package containing one unit.) Source modifications to GHC assume that a package only has one unit. 2. Generalize GHC to work with packages with multiple units 3. Add capability to Cabal/ghc-pkg to register just units. For compilation of Backpack files, GHC will write out units which Cabal will then install to the real registry 4. Backpack! -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 07:40:32 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 07:40:32 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.7a185b43a02c6fb43ebb1b4bf50647da@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Comment (by thomasw): Actually, this limitation only applies to type splices. I had forgotten about declaration splices, which can also contain type signatures, until goldfire reminded me. My patch on Phabricator adds full support for partial type signatures in declaration splices in addition to support for anonymous wild cards in type splices. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 08:10:28 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 08:10:28 -0000 Subject: [GHC] #10606: avoid redundant stores to the stack when examining already-tagged data In-Reply-To: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> References: <047.87e47415860596bb28d3d6cc9eb67dbd@haskell.org> Message-ID: <062.d04ecbb1f7b4a68f5109535bbd82c4fc@haskell.org> #10606: avoid redundant stores to the stack when examining already-tagged data -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 (CodeGen) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by simonmar): This is basically the same as #8905. It's not hard to rearrange the code to optimise the already-evaluated path, but as you noticed it will increase code size due to not being able to share the saving code with the heap-check failure, and having to reload things from the stack in the unevaluated case. Things are rather delicately arranged at the moment to generate small code. I believe the reason that you get some duplication when sinking the return address is because there's a special case in the stack allocator to spot this. One thing I think it would be worth doing is having an option to tune the tradeoff between code size and speed (like gcc's -Os), and the code generated for case expressions would be a prime candidate to be altered by this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 11:23:59 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 11:23:59 -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.b684dd8c7109ad19dab610f83812af53@haskell.org> #2439: Missed optimisation with dictionaries and loops -------------------------------------+------------------------------------- Reporter: rl | Owner: simonpj Type: bug | Status: new Priority: lowest | Milestone: 7.12.1 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 Revisions: -------------------------------------+------------------------------------- Comment (by 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. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 11:44:54 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 11:44:54 -0000 Subject: [GHC] #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection Message-ID: <046.3a764cfd54e5a4e4443ef4864c8fddbf@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: T8958a | Related Tickets: #10298, #7695 Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Phab:D898 was primarily intended to fix hangs in the event that `iconv` was unavailable (namely #10298 and #7695). In addition to this fix, it also introduced self-contained handling of ANSI terminals to allow compiled executables to run in minimal environments lacking iconv. However, the behavior that the patch introduced is highly suspicious. Specifically, it gives the user a UTF-8 encoding even if they requested ASCII. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 11:46:34 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 11:46:34 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.95bf95699a8da2aa09f780a9ebd5db7f@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"889824dd5ea37adc0fbfe851f724ca9331278664/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="889824dd5ea37adc0fbfe851f724ca9331278664" Document RULES and class methods Relates to Trac #10595 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 11:47:31 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 11:47:31 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.5c9aa60c1380135b3bcb2f5baa612e77@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 11:53:01 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 11:53:01 -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.a5cdea869d1a9a01e6b840a2b2250380@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: T8958a Related Tickets: #10298, #7695 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > Phab:D898 was primarily intended to fix hangs in the event that `iconv` > was unavailable (namely #10298 and #7695). In addition to this fix, it > also introduced self-contained handling of ANSI terminals to allow > compiled executables to run in minimal environments lacking iconv. > > However, the behavior that the patch introduced is highly suspicious. > Specifically, it gives the user a UTF-8 encoding even if they requested > ASCII. New description: Phab:D898 was primarily intended to fix hangs in the event that `iconv` was unavailable (namely #10298 and #7695). In addition to this fix, it also introduced self-contained handling of ANSI terminals to allow compiled executables to run in minimal environments lacking iconv. However, the behavior that the patch introduced is highly suspicious. Specifically, it gives the user a UTF-8 encoding even if they requested ASCII. This has the potential to break quite a lot of code. At very least it breaks GHC's Unicode terminal detection logic, which attempts to catch an invalid character when encoding a pair of smart-quotes. Of course, this exception will never be thrown if a UTF-8 encoder is used. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:03:18 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:03:18 -0000 Subject: [GHC] #10608: Compile error regression from GHC 7.10 to 7.11 In-Reply-To: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> References: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> Message-ID: <057.42d2ff78bebcd5e4a38c9fffea5f2f85@haskell.org> #10608: Compile error regression from GHC 7.10 to 7.11 -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"b5aabfbdb96ba8abf2748d089f40c267c2131215/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b5aabfbdb96ba8abf2748d089f40c267c2131215" Infer types with flexible contexts Responding to Trac #10608 and Trac #10351, I've reverted to making type inference infer structured constraint like f :: C [t] => t -> t even if -XFlexibleContexts is not set. That elicits an error message suggesting the flag. The result is more helpful than the error message you get otherwise. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:03:18 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:03:18 -0000 Subject: [GHC] #10351: Inferred type is rejected In-Reply-To: <046.86ef5a0fea428f7b5f5c596d5fa38be9@haskell.org> References: <046.86ef5a0fea428f7b5f5c596d5fa38be9@haskell.org> Message-ID: <061.21830dddea09bc9046d38462fcbd83eb@haskell.org> #10351: Inferred type is rejected -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | typecheck/should_fail/T10351 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"b5aabfbdb96ba8abf2748d089f40c267c2131215/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b5aabfbdb96ba8abf2748d089f40c267c2131215" Infer types with flexible contexts Responding to Trac #10608 and Trac #10351, I've reverted to making type inference infer structured constraint like f :: C [t] => t -> t even if -XFlexibleContexts is not set. That elicits an error message suggesting the flag. The result is more helpful than the error message you get otherwise. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:03:57 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:03:57 -0000 Subject: [GHC] #10608: Compile error regression from GHC 7.10 to 7.11 In-Reply-To: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> References: <042.11522462d4a928bbcbcbc3f0257c4c97@haskell.org> Message-ID: <057.a142612c8208458ff5fc8f2714e1d8cb@haskell.org> #10608: Compile error regression from GHC 7.10 to 7.11 -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:28:14 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:28:14 -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.34228efe5924a03b8fa1cc12ab358d9c@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: T8958a Related Tickets: #10298, #7695 | Blocking: | Differential Revisions: Phab:1059 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:1059 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:30:16 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:30:16 -0000 Subject: [GHC] #10513: ghc 7.6.3 Compiler panic with Generics In-Reply-To: <051.c09e61e0961a632608f776aed9796e7c@haskell.org> References: <051.c09e61e0961a632608f776aed9796e7c@haskell.org> Message-ID: <066.07bb1d1ee42d2fa1fc38340f5cff84cd@haskell.org> #10513: ghc 7.6.3 Compiler panic with Generics -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): If this is 7.6 only then I'm afraid we are extremely unlikely to fix it unless there is pressure from a large constituency to do so. I assume it's ok with 7.10? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:31:04 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:31:04 -0000 Subject: [GHC] #4243: Make a proper options parser for the RTS In-Reply-To: <044.6ea5654174cc0120653bc110fe1a703c@haskell.org> References: <044.6ea5654174cc0120653bc110fe1a703c@haskell.org> Message-ID: <059.a5a373237d9afa1fd7c3bcb8992b9022@haskell.org> #4243: Make a proper options parser for the RTS -------------------------------------+------------------------------------- Reporter: igloo | Owner: carlostome Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Runtime System | Version: 6.13 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #9839 | Blocking: 7535 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) Comment: What keeps us from implementing RTS arg parser in Haskell? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:32:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:32:21 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.f051ab32d51c2c4cb46f279ffabcaa02@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a6359f2629024d67fc82a7d41c67d5d89d2d3a3d/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="a6359f2629024d67fc82a7d41c67d5d89d2d3a3d" Add testcase for #10602 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:38:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:38:40 -0000 Subject: [GHC] #10624: th/T10279 testcase is broken Message-ID: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> #10624: th/T10279 testcase is broken -------------------------------------+------------------------------------- Reporter: bgamari | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- On Debian 7, x86_64. {{{ Actual stderr output differs from expected: --- ./th/T10279.stderr 2015-07-06 17:16:38.923135777 -0400 +++ ./th/T10279.comp.stderr 2015-07-09 08:29:06.443205994 -0400 @@ -1,8 +1,7 @@ -T10279.hs:10:10: - Failed to load interface for ?A? - no package key matching ?rts-1.0? was found - (This package key looks like the source package ID; - the real package key is ?rts?) - In the expression: (rts-1.0:A.Foo) - In an equation for ?blah?: blah = (rts-1.0:A.Foo) +T10279.hs:10:8:ghc-stage2: panic! (the 'impossible' happened) + (GHC version 7.10.1.20150708 for x86_64-unknown-linux): + qual_pkg rts-1.0 + +Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug + *** unexpected failure for T10279(normal) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:40:11 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:40:11 -0000 Subject: [GHC] #10624: th/T10279 testcase is broken In-Reply-To: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> References: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> Message-ID: <061.d2acb63b6386e05db9c162c85ab39594@haskell.org> #10624: th/T10279 testcase is broken -------------------------------------+------------------------------------- Reporter: bgamari | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * version: 7.10.1 => 7.11 * milestone: => 7.12.1 Comment: I will mark this test as `expect_broken` on the `ghc-7.10` branch for the 7.10.2 release. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 12:47:57 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 12:47:57 -0000 Subject: [GHC] #10513: ghc 7.6.3 Compiler panic with Generics In-Reply-To: <051.c09e61e0961a632608f776aed9796e7c@haskell.org> References: <051.c09e61e0961a632608f776aed9796e7c@haskell.org> Message-ID: <066.58118534934dea3741489edb021fc442@haskell.org> #10513: ghc 7.6.3 Compiler panic with Generics -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by andreas.abel): Yes, only 7.6. I still reported it, as for Agda we support ghc>=7.6. We have to wait with Generics until we drop support for 7.6. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 14:04:22 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 14:04:22 -0000 Subject: [GHC] #10561: "deriving (Functor)" on a polykinded type produces ill-kinded instance In-Reply-To: <047.92b5c73d11a6ce75dd9ba55b0b432115@haskell.org> References: <047.92b5c73d11a6ce75dd9ba55b0b432115@haskell.org> Message-ID: <062.4908045aa8841c8b0f3a1bfcaa6401e2@haskell.org> #10561: "deriving (Functor)" on a polykinded type produces ill-kinded instance -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | deriving/should_compile/T10561 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => deriving/should_compile/T10561 * resolution: => fixed Comment: This patch makes GHC complain before generating ill-kinded code via `deriving`. #10524 contains the remaining open issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 14:28:03 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 14:28:03 -0000 Subject: [GHC] #10625: Spurious unused quantified type variable warning with ExistentialQuantification Message-ID: <050.bcfa2a8486244e674e467da363afe987@haskell.org> #10625: Spurious unused quantified type variable warning with ExistentialQuantification -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: Incorrect Architecture: | warning at compile-time Unknown/Multiple | Blocked By: Test Case: | Related Tickets: #5331 Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- When using an existentially quantified type variable that shadows another variable in a data declaration, {{{-Wall}}} produces more warnings than necessary: {{{ $ ghci -XExistentialQuantification -Wall GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help ?> data Ex a = forall a. Ex a :2:20: Warning: Unused quantified type variable ?a? In the definition of data constructor ?Ex? :2:20: Warning: This binding for ?a? shadows the existing binding bound at :2:9 }}} The unused quantified type variable warning seems wrong, since it ''is'' being used (as the shadowing warning indicates). Curiously, this warning doesn't seem to appear when doing something similar with {{{RankNTypes}}}: {{{ $ ghci -XRankNTypes -Wall GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help ?> data Ex a = Ex (forall a. a) :2:24: Warning: This binding for ?a? shadows the existing binding bound at :2:9 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 17:28:51 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 17:28:51 -0000 Subject: [GHC] #10624: th/T10279 testcase is broken In-Reply-To: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> References: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> Message-ID: <061.9f112cc3f0c9190432975448bad4f6eb@haskell.org> #10624: th/T10279 testcase is broken -------------------------------------+------------------------------------- Reporter: bgamari | Owner: ezyang Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1060 -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => patch * differential: => Phab:D1060 Comment: This can be fixed by cherry-picking the following commit from master: {{{ commit cf1d9751e7ca85e9b3284ad57882958b8dc73d16 Author: Edward Z. Yang Date: Tue Apr 7 09:08:54 2015 -0500 Don't repeat package key with -dppr-debug when package info is missing. Signed-off-by: Edward Z. Yang Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D802 }}} as well as applying the attached Phab diff. When I cherry-picked, I had to fix a minor parenthesization wibble: {{{ commit cbe0615b7d71d340f597032c2009ff771f1b91c8 Author: Edward Z. Yang Date: Thu Jul 9 10:21:28 2015 -0700 Parenthesization wibble in T10279. Signed-off-by: Edward Z. Yang diff --git a/testsuite/tests/th/T10279.stderr b/testsuite/tests/th/T10279.stderr index 9c72bf9..071ee45 100644 --- a/testsuite/tests/th/T10279.stderr +++ b/testsuite/tests/th/T10279.stderr @@ -1,8 +1,8 @@ -T10279.hs:10:10: +T10279.hs:10:8: Failed to load interface for ?A? no package key matching ?rts-1.0? was found (This package key looks like the source package ID; the real package key is ?rts?) - In the expression: (rts-1.0:A.Foo) - In an equation for ?blah?: blah = (rts-1.0:A.Foo) + In the expression: rts-1.0:A.Foo + In an equation for ?blah?: blah = rts-1.0:A.Foo }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 18:04:29 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 18:04:29 -0000 Subject: [GHC] #10624: th/T10279 testcase is broken In-Reply-To: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> References: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> Message-ID: <061.7b701da339771e6e9cf3f30c47467091@haskell.org> #10624: th/T10279 testcase is broken -------------------------------------+------------------------------------- Reporter: bgamari | Owner: ezyang Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1060 -------------------------------------+------------------------------------- Comment (by Edward Z. Yang ): In [changeset:"6f1c0766943cdb9a567c0e2b9d41c5e73c2ff5bc/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="6f1c0766943cdb9a567c0e2b9d41c5e73c2ff5bc" Make mkQualPackage more robust when package key is bad. Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1060 GHC Trac Issues: #10624 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 9 21:28:59 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 09 Jul 2015 21:28:59 -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.f83f14ac10b7d50d318f60894b2d7d09@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): Sorry for late response, I'm hoping to make progress on this, I was wondering if we can use a fallback mechanism in instance deriving. For example: If GND and DeriveAnyClass are enabled, we know DeriveAnyClass is tried first, but why not try GND when it fails? There are couple of things that are very inconvenient with the current approach: 1. If I want to derive two instances for my newtype, one needs GND and one needs DeriveAnyClass, I can't do that and I have to split things into modules which means orphan instances. 2. I'm tired of adding dozens of LANGUAGE pragmas in every single file, so I was hoping to move those to cabal file. But I can't do that easily because of problems like this. About the error message: What would be the correct message here? Also, even with just `DeriveAnyClass`, the error message is weird: {{{ ? deriveany_bug ghc --make -fforce-recomp Test.hs -XDeriveAnyClass [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:2:13: Can't make a derived instance of ?Functor MyMaybe?: You need DeriveFunctor to derive an instance for this class Try GeneralizedNewtypeDeriving for GHC's newtype-deriving extension In the newtype declaration for ?MyMaybe? }}} It first says that I need DeriveFunctor, but then says I should try GND. Is it trying to say that GND implies DeriveFunctor? (which shouldn't be the case according to the user manual) Otherwise which one should I try? This message is confusing IMO. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 00:51:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 00:51:56 -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.38c60843f0066d74458c97c2c45acf21@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): I'm a little confused here. Why is `DeriveAnyClass` failing here? From the user manual, it seems `DeriveAnyClass` should ''always'' succeed. I think the first step in understanding this all is to figure that out. I've hunted around (wiki:Commentary/Compiler/GenericDeriving#Usingstandardderivingforgenericfunctions and #5462) but I haven't found a proper specification of the feature. It certainly isn't in the user manual. Between those two links, one says that ''any'' class can be derived, and the other requires a default. Perhaps it's the latter. Does anyone out there know? Or do you want to go spelunking through the code? One way or the other, we should disentangle this and write up a specification. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 01:45:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 01:45:10 -0000 Subject: [GHC] #10224: Partial type signatures generate typed hole warnings In-Reply-To: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> References: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> Message-ID: <060.1ffd6780ac0839972f46eaa69339602d@haskell.org> #10224: Partial type signatures generate typed hole warnings -------------------------------------+------------------------------------- Reporter: quchen | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: closed => new * resolution: invalid => Comment: I find the warning message quite misleading. Here is my (uninteresting) case: {{{ foo :: _ -> Bool foo True = False foo False = True }}} I get this warning (with `-XPartialTypeSignatures`) {{{ Scratch.hs:18:8: warning: Found hole: _ :: Bool In the type signature for ?foo?: _ -> Bool }}} I think of "hole" as something in an expression instead of a type. In a type, I thought it was called a "wildcard". In any case, `_ :: Bool` is wrong. My `_` certainly does not have type `Bool`. It has '''value''' `Bool`. Here is my suggested output: {{{ Scratch.hs:18:8: warning: Found type wildcard: `_' standing in for `Bool' In the type signature for ?foo?: _ -> Bool }}} I'm reopening on the basis that, even if my hole vs. wildcard distinction is silly nitpicking, saying `_ :: Bool` is wrong and should be fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 02:16:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 02:16:32 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.d5ea5b1ebafd91483687d6780d35c7d6@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Description changed by ezyang: Old description: > After today's weekly Backpack call, we have come to the conclusion that > we have two different types of "packages" in the Backpack world: > > 1. Cabal packages, which have a single `.cabal` file and are a unit of > distribution which get uploaded to Hackage, and > > 2. Backpack packages, of which there may be multiple defined in a > Backpack file shipped with a Cabal package; and are the building blocks > for modular development in the small. > > It's really confusing to have both of these called packages: thus, we > propose to rename all occurrences of Backpack package to unit. A Cabal > ''package'' may contain MULTIPLE Backpack ''units'', although old-style > Cabal files will only define one unit. > > A Cabal package remains > * The unit of distribution > * The unit that Hackage handles > * The unit of versioning > * The unit of ownership (who maintains it etc) > > Here are some of the consequences: > > 1. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather > than a Cabal package. (I think this actually makes the function of these > identifiers clearer.) We'll also distinguish Cabal-file level > `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit > will be uniquely identified by an `InstalledUnitId`. > > 2. The source-level syntax of Backpack files will use `unit` in place of > where `package` was used before. > > 3. For backwards compatibility reasons, we'll sometimes arrange for > `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to > coincide. Specifically, the unit of a package which has the same > `UnitName` as the `PackageName` is treated specially: its > `InstalledUnitId` is guaranteed to be the same as the > `InstalledPackageId` and it is what is "visible" when a user uses old > concepts such as `-package foo-0.1` to select a package. > > 4. The installed package database is extended to record some number of > units per an installed package: the public facing API is that you can > register a package CONTAINING some number of units. For old-style > packages, there will be only one unit with a matching `UnitName`, so this > will be isomorphic to an old style package; however, GHC will grow some > new APIs for selecting specific units to bring into scope. GHC really > mostly only cares about units, but if a user asks for a package using, > e.g. `-package` it will translate this request into a request for the > appropriate unit. > > 5. For old-style packages, Cabal will continue to write and register a > package configuration file which implicitly defines a single unit. > However, the plan is to give GHC the capacity to generate unit > description files (like package description files, but per unit), which > Cabal can interpret and use to register packages in the global database > using a `ghc-pkg` which can register units and "unitless" package > description files which don't implicitly define a unit. (NB: we must > create unit description files, because `ghc-pkg recache` is expected to > be able to regenerate the database.) (NB: we want to be able to add units > for a package separately, because this is how units for indefinite > packages are created as they are instantiated with new implementations.) > > 6. Cabal could also finally grow the "multiple libraries per single Cabal > file" support people have wanted; it's just a stylized use of the > Backpack facilities. > > The work plan: > > 1. Modify `bin-package-db` to reflect the unit/package split, but > otherwise keep ghc-pkg and GHC the same (so old-style package description > still supported, and interpreted as a package containing one unit.) > Source modifications to GHC assume that a package only has one unit. > > 2. Generalize GHC to work with packages with multiple units > > 3. Add capability to Cabal/ghc-pkg to register just units. For > compilation of Backpack files, GHC will write out units which Cabal will > then install to the real registry > > 4. Backpack! New description: After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal ''package'' may contain MULTIPLE Backpack ''units'', although old-style Cabal files will only define one unit. A Cabal package remains * The unit of distribution * The unit that Hackage handles * The unit of versioning * The unit of ownership (who maintains it etc) Here are some of the consequences: 1. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit will be uniquely identified by an `InstalledUnitId`. 2. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 3. For backwards compatibility reasons, we'll sometimes arrange for `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to coincide. Specifically, the unit of a package which has the same `UnitName` as the `PackageName` is treated specially: its `InstalledUnitId` is guaranteed to be the same as the `InstalledPackageId` and it is what is "visible" when a user uses old concepts such as `-package foo-0.1` to select a package. 4. The installed package database is extended to record some number of units per an installed package: the public facing API is that you can register a package CONTAINING some number of units. For old-style packages, there will be only one unit with a matching `UnitName`, so this will be isomorphic to an old style package; however, GHC will grow some new APIs for selecting specific units to bring into scope. GHC really mostly only cares about units, but if a user asks for a package using, e.g. `-package` it will translate this request into a request for the appropriate unit. 5. For old-style packages, Cabal will continue to write and register a package configuration file which implicitly defines a single unit. However, the plan is to give GHC the capacity to generate unit description files (like package description files, but per unit), which Cabal can interpret and use to register packages in the global database using a `ghc-pkg` which can register units and "unitless" package description files which don't implicitly define a unit. (NB: we must create unit description files, because `ghc-pkg recache` is expected to be able to regenerate the database.) (NB: we want to be able to add units for a package separately, because this is how units for indefinite packages are created as they are instantiated with new implementations.) (NB: For BC purposes, since Cabal has to write old-style packages for old GHC, this is pretty irritating.) 6. Cabal could also finally grow the "multiple libraries per single Cabal file" support people have wanted; it's just a stylized use of the Backpack facilities. (Note: Actually, not QUITE: multiple libraries are likely to want separate sets of dependencies, whereas our units proposal has external dependencies shared over all units. If we want the multiple libraries, cabal-install has to learn about units.) The work plan: 1. Modify `bin-package-db` to reflect the unit/package split, but otherwise keep ghc-pkg and GHC the same (so old-style package description still supported, and interpreted as a package containing one unit.) Source modifications to GHC assume that a package only has one unit. 2. Generalize GHC to work with packages with multiple units 3. Add capability to Cabal/ghc-pkg to register just units. For compilation of Backpack files, GHC will write out units which Cabal will then install to the real registry 4. Backpack! -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 09:36:16 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 09:36:16 -0000 Subject: [GHC] #9238: Negative zero broken In-Reply-To: <047.56415c116f5d14a35293c7c7b01ed1ce@haskell.org> References: <047.56415c116f5d14a35293c7c7b01ed1ce@haskell.org> Message-ID: <062.53f3620afd561e39ae360f244f62be84@haskell.org> #9238: Negative zero broken -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #7858, #9451 | Differential Revisions: Phab:D1061 -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D1061 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 11:41:28 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 11:41:28 -0000 Subject: [GHC] #10626: Missed opportunity for SpecConstr Message-ID: <046.2ec00fd6c7f1ac3b0945088bcbe8d910@haskell.org> #10626: Missed opportunity for SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Look at `perf/should_run/T4830`. After `SpecConstr` and optimisation we finally get {{{ Rec { Main.foo_$s$wfoo1 [Occ=LoopBreaker] :: Int# -> Double -> Double -> Double# [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType ] Main.foo_$s$wfoo1 = \ (sc_s4eN :: Int#) (sc1_s4eO :: Double) (sc2_s4eP :: Double) -> case sc_s4eN of ds_X1SR { __DEFAULT -> case sc1_s4eO of wild_a1Tf { D# x_a1Th -> case sc2_s4eP of wild1_a1Tj { D# y_a1Tl -> case tagToEnum# @ Bool (<=## x_a1Th y_a1Tl) of _ [Occ=Dead] { False -> Main.foo_$s$wfoo1 (-# ds_X1SR 1#) wild1_a1Tj wild_a1Tf; True -> Main.foo_$s$wfoo1 (-# ds_X1SR 1#) wild_a1Tf wild1_a1Tj } } }; 0# -> case sc1_s4eO of _ [Occ=Dead] { D# x_a1UL -> case sc2_s4eP of _ [Occ=Dead] { D# y_a1UP -> +## x_a1UL y_a1UP } } } end Rec } }}} If we ran `SpecConstr` again we'd specialise this function, because the recursive calls both have boxed arguments. I looked into why `SpecConstr` didn't catch it, and it's because `SpecConstr`'s input looks like this {{{ case case tagToEnum# @ Bool (<=## x_a1Th y_a1Tl) of _ [Occ=Dead] { False -> (wild1_a1Tj, wild_a1Tf); True -> wild_X8 } of r_s4e0 { (ipv_s4e1, ipv_s4e2) -> $wfoo_s4db (I# (-# ds_X1SR 1#)) (Just @ (Double, Double) r_s4e0) }}} Notice the case-of-case which doesn't expose the `Double` boxes of arguments to `$wfoo`. Why is that case-of-case still there? Because of `Note [Single- alternative cases]` in Simplify. Which is clearly a delicate spot so I don't want to meddle with it today. But it's intriguing. Maybe Sequent Core will do better. Note that late demand analysis also catches this case, yielding the (rather good) {{{ Rec { Main.$w$s$wfoo [InlPrag=[0], Occ=LoopBreaker] :: Int# -> Double# -> Double# -> Double# [GblId, Arity=3, Caf=NoCafRefs, Str=DmdType ] Main.$w$s$wfoo = \ (w_s4gW :: Int#) (ww_s4h1 :: Double#) (ww1_s4h5 :: Double#) -> case w_s4gW of ds_X1SW { __DEFAULT -> case tagToEnum# @ Bool (<=## ww_s4h1 ww1_s4h5) of _ [Occ=Dead] { False -> Main.$w$s$wfoo (-# ds_X1SW 1#) ww1_s4h5 ww_s4h1; True -> Main.$w$s$wfoo (-# ds_X1SW 1#) ww_s4h1 ww1_s4h5 }; 0# -> +## ww_s4h1 ww1_s4h5 } end Rec } }}} I'm pretty sure that late-demand-analysis should be on with `-O2` but someone should do a nofib run to check. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 11:43:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 11:43:36 -0000 Subject: [GHC] #7782: flag to run the demand analysis a second time In-Reply-To: <046.1ec01ebe7149b378f35843d2bc9ef200@haskell.org> References: <046.1ec01ebe7149b378f35843d2bc9ef200@haskell.org> Message-ID: <061.aac275694f9f8a417f16ee9f5daf30a9@haskell.org> #7782: flag to run the demand analysis a second time -------------------------------------+------------------------------------- Reporter: nfrisby | Owner: Type: task | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #4941, #5302, | Blocking: #6087, #4962 | Differential Revisions: -------------------------------------+------------------------------------- Description changed by simonpj: Old description: > There are some tickets documenting runtime bugs that can be cleaned up by > running the demand analyzer (followed by a simplifier run) a second time > at the end of the pipeline: #4941, #5302, #6087. #6070 ? Others? > > The -flate-dmd-anal flag has been committed to HEAD (cf comment:10 > below). > > The remaining task is to determine if `-O2` should imply `-flate-dmd- > anal`. It currently does not: late demand analysis is ''off'' by default. > > See LateDmd for more info. New description: There are some tickets documenting runtime bugs that can be cleaned up by running the demand analyzer (followed by a simplifier run) a second time at the end of the pipeline: #4941, #5302, #6087, #6070. #10626 ? Others? The -flate-dmd-anal flag has been committed to HEAD (cf comment:10 below). The remaining task is to determine if `-O2` should imply `-flate-dmd- anal`. It currently does not: late demand analysis is ''off'' by default. See LateDmd for more info. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 11:53:29 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 11:53:29 -0000 Subject: [GHC] #10224: Partial type signatures generate typed hole warnings In-Reply-To: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> References: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> Message-ID: <060.eb4211a5e64c3470eb11ec6fb99328b7@haskell.org> #10224: Partial type signatures generate typed hole warnings -------------------------------------+------------------------------------- Reporter: quchen | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"9e86bf1b346934e04ccc17ec50ea7e7d906f25e2/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="9e86bf1b346934e04ccc17ec50ea7e7d906f25e2" Better type wildcard errors Adopts sugggestion in Trac #10224, comment:3 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 11:58:14 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 11:58:14 -0000 Subject: [GHC] #10224: Partial type signatures generate typed hole warnings In-Reply-To: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> References: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> Message-ID: <060.e550fe11ef5d5428bf019438df11c879@haskell.org> #10224: Partial type signatures generate typed hole warnings -------------------------------------+------------------------------------- Reporter: quchen | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Good idea -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 12:20:37 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 12:20:37 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.dd08e23979db76044b253d3754cba738@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Hmm. I think it'd be easy to send GHC into an infinite loop using this; i.e. the current implementation is over-liberal. {{{ type instance FieldScalar x = Field x }}} Is it true that you expect `Scalar (Scalar a) ~ Scalar a)` (cf #10318). If so, you could make it better behaved by saying {{{ class (Scalar (Scalar a) ~ Scalar a, Field (Scalar a)) => Vector a class Vector x => Field x }}} This still isn't accepted but could be under comment:6 of #10318 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 14:35:37 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 14:35:37 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.1bd638eaad9cf9c3025e13a9f5e0ce91@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Test still fails when `base` is compiled with -O2 (as it is in a perf or default/release build). {{{ $ make TEST=T10602 TEST_HC=ghc-7.10.1.20150710 ... =====> T10602(optasm) 92 of 92 [0, 0, 0] cd . && "/opt/ghc/7.10.2/bin/ghc-7.10.1.20150710" -c T10602.hs -fforce- recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts -fno-warn-tabs -fno-ghci-history -O -fasm -O2 > T10602.comp.stderr 2>&1 Compile failed (status 256) errors were: ghc: panic! (the 'impossible' happened) (GHC version 7.10.1.20150710 for x86_64-unknown-linux): Template variable unbound in rewrite rule sg_s5zh [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] [sc_s5zf, sc_s5zg, sg_s5zh, sg_s5zi] [: @ a_a3fj sc_s5zf sc_s5zg] [: @ a_a3fj sc_s5zb sc_s5zc] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 14:49:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 14:49:32 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.6ccf001862d2348ead4c98014b6f7173@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): I attached an alternative test that also fails with a devel2 build. `-fno- spec-constr` makes the problem go away, as do a few other things (see `T10602.hs`). Maybe this debug message is of help to someone: {{{ $ ./ghc-devel2/inplace/bin/ghc-stage2 T10602.hs [2 of 2] Compiling T10602 ( T10602.hs, T10602.o ) SpecConstr Function ?$wgo_s13x? has one call pattern, but the limit is 0 Use -fspec-constr-count=n to set the bound Use -dppr-debug to see specialisations ghc-stage2: panic! (the 'impossible' happened) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 15:07:51 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 15:07:51 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.f8782a93a26fa4b59d71bb852daf0bcb@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, this is very odd. thomie, I suppose your alternate test case still on reproduces with the `ghc-stage2` binary? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 15:15:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 15:15:42 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.c32179fb9601ade844421970f9f81351@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): I'm not sure what you're asking. For me, it fails with both `ghc-stage1` and `ghc-stage2` from a devel2 build of HEAD, as well as with `ghc-7.10.1.20150710` from hvr's ppa. If it wasn't clear: you need both `T10602.hs` and `T10602b.hs`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 15:26:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 15:26:15 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.59df85c888b3f472316de74a0bc730ff@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: infoneeded Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): OK I'm on it. Thank you for a simple repro case. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 15:30:34 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 15:30:34 -0000 Subject: [GHC] #10570: Terrible error message with fundeps and PolyKinds In-Reply-To: <046.4466b015687c38c71e7a50b843a82b42@haskell.org> References: <046.4466b015687c38c71e7a50b843a82b42@haskell.org> Message-ID: <061.54d9ee507b74388def06095c0ce05bae@haskell.org> #10570: Terrible error message with fundeps and PolyKinds -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"2d06a9f19d5b3ab8c3ff0b24f508c15bedae99d2/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="2d06a9f19d5b3ab8c3ff0b24f508c15bedae99d2" Improve error message for fundeps Improve error message fundeps, especially when PolyKinds means that the un-determined variables are (invisible) kind variables. See Trac #10570. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 16:45:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 16:45:27 -0000 Subject: [GHC] #10570: Terrible error message with fundeps and PolyKinds In-Reply-To: <046.4466b015687c38c71e7a50b843a82b42@haskell.org> References: <046.4466b015687c38c71e7a50b843a82b42@haskell.org> Message-ID: <061.510802002466fd65c82b56512d9b7f18@haskell.org> #10570: Terrible error message with fundeps and PolyKinds -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 17:54:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 17:54:55 -0000 Subject: [GHC] #10298: Infinite loop when shared libraries are unavailable In-Reply-To: <047.ac4f2671f8ae23d583742150fb22d7b0@haskell.org> References: <047.ac4f2671f8ae23d583742150fb22d7b0@haskell.org> Message-ID: <062.dfeed9e623a4676f749704a76bfcd6aa@haskell.org> #10298: Infinite loop when shared libraries are unavailable -------------------------------------+------------------------------------- Reporter: snoyberg | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Runtime System | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime crash | (amd64) Blocked By: | Test Case: Related Tickets: #7695 | Blocking: | Differential Revisions: Phab:D898 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d69dfba4e27c4ec33459906fd87c9a56a371f510/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d69dfba4e27c4ec33459906fd87c9a56a371f510" Fix self-contained handling of ASCII encoding D898 was primarily intended to fix hangs in the event that iconv was unavailable (namely #10298 and #7695). In addition to this fix, it also introduced self-contained handling of ANSI terminals to allow compiled executables to run in minimal environments lacking iconv. However, the behavior that the patch introduced is highly suspicious. Specifically, it gives the user a UTF-8 encoding even if they requested ASCII. This has the potential to break quite a lot of code. At very least it breaks GHC's Unicode terminal detection logic, which attempts to catch an invalid character when encoding a pair of smart-quotes. Of course, this exception will never be thrown if a UTF-8 encoder is used. Here we use the `char8` encoding to handle requests for ASCII encodings in the event that we find iconv to be non-functional. Fixes #10623. Test Plan: Validate with T8959a Reviewers: rwbarton, hvr, austin, hsyl20 Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1059 GHC Trac Issues: #10623 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 17:54:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 17:54: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.b5be4855eb5d5a6cbf20b973dd13fa5e@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: T8958a Related Tickets: #10298, #7695 | Blocking: | Differential Revisions: Phab:1059 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d69dfba4e27c4ec33459906fd87c9a56a371f510/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d69dfba4e27c4ec33459906fd87c9a56a371f510" Fix self-contained handling of ASCII encoding D898 was primarily intended to fix hangs in the event that iconv was unavailable (namely #10298 and #7695). In addition to this fix, it also introduced self-contained handling of ANSI terminals to allow compiled executables to run in minimal environments lacking iconv. However, the behavior that the patch introduced is highly suspicious. Specifically, it gives the user a UTF-8 encoding even if they requested ASCII. This has the potential to break quite a lot of code. At very least it breaks GHC's Unicode terminal detection logic, which attempts to catch an invalid character when encoding a pair of smart-quotes. Of course, this exception will never be thrown if a UTF-8 encoder is used. Here we use the `char8` encoding to handle requests for ASCII encodings in the event that we find iconv to be non-functional. Fixes #10623. Test Plan: Validate with T8959a Reviewers: rwbarton, hvr, austin, hsyl20 Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1059 GHC Trac Issues: #10623 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 17:54:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 17:54:55 -0000 Subject: [GHC] #7695: Hang when locale-archive and gconv-modules are not there In-Reply-To: <042.96ea14c731f7f52fd1ea0cef77ce2267@haskell.org> References: <042.96ea14c731f7f52fd1ea0cef77ce2267@haskell.org> Message-ID: <057.88a88baa317c9fce42e79c165506b72c@haskell.org> #7695: Hang when locale-archive and gconv-modules are not there -------------------------------------+------------------------------------- Reporter: hpd | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: None | Version: 7.8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #8977, #10298 | Blocking: | Differential Revisions: Phab:D898 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d69dfba4e27c4ec33459906fd87c9a56a371f510/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d69dfba4e27c4ec33459906fd87c9a56a371f510" Fix self-contained handling of ASCII encoding D898 was primarily intended to fix hangs in the event that iconv was unavailable (namely #10298 and #7695). In addition to this fix, it also introduced self-contained handling of ANSI terminals to allow compiled executables to run in minimal environments lacking iconv. However, the behavior that the patch introduced is highly suspicious. Specifically, it gives the user a UTF-8 encoding even if they requested ASCII. This has the potential to break quite a lot of code. At very least it breaks GHC's Unicode terminal detection logic, which attempts to catch an invalid character when encoding a pair of smart-quotes. Of course, this exception will never be thrown if a UTF-8 encoder is used. Here we use the `char8` encoding to handle requests for ASCII encodings in the event that we find iconv to be non-functional. Fixes #10623. Test Plan: Validate with T8959a Reviewers: rwbarton, hvr, austin, hsyl20 Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1059 GHC Trac Issues: #10623 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 17:56:19 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 17:56:19 -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.36371531c8d9cfa900a7cb7655d1be4e@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: T8958a Related Tickets: #10298, #7695 | Blocking: | Differential Revisions: Phab:1059 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: A version of this is also present in the ghc-7.10 branch as 677552f21690761b89255d05e42976679be4d374. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 18:03:54 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 18:03:54 -0000 Subject: [GHC] #10613: Mechanism for checking that we only enter single-entry thunks once In-Reply-To: <046.787816a81f7da40c6d0ca0afdcdd9dbb@haskell.org> References: <046.787816a81f7da40c6d0ca0afdcdd9dbb@haskell.org> Message-ID: <061.2acdc7154f87c442ad10d1dc26ad93e1@haskell.org> #10613: Mechanism for checking that we only enter single-entry thunks once -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Simonmar, could you confirm that there are no blatant inaccuracies in this description? If not, do you have an opinion on which approach is preferable? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 18:10:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 18:10:12 -0000 Subject: [GHC] #7810: make show VALUE=VAR depends on ghc-stage1 In-Reply-To: <046.882d6e4c467938612df87a18a7ab7d09@haskell.org> References: <046.882d6e4c467938612df87a18a7ab7d09@haskell.org> Message-ID: <061.78c8b2c2cbe19e56c6b252d00a929a4c@haskell.org> #7810: make show VALUE=VAR depends on ghc-stage1 -------------------------------------+------------------------------------- Reporter: kgardas | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1064 -------------------------------------+------------------------------------- Changes (by thomie): * owner: thoughtpolice => thomie * differential: => Phab:D1064 Comment: I have a patch that adds a `make show!` command. From the commit message: A normal `make show` starts a build of the ghc-stage1 compiler, to create package-data.mk files. This version doesn't read those, so it will work right after ./configure. Does that sound reasonable to add? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 18:36:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 18:36:35 -0000 Subject: [GHC] #8709: `make 1` does not work (well) In-Reply-To: <047.74dec05c27dff19fcb1196415db32998@haskell.org> References: <047.74dec05c27dff19fcb1196415db32998@haskell.org> Message-ID: <062.c8fbba3d4d395003cb2d885e58be643a@haskell.org> #8709: `make 1` does not work (well) -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 7.7 Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => worksforme Comment: I think this bug is fixed in 092082e7583c8170ae41ef8d01a554db34f91bb3. Or at least it won't give an error anymore when `libraries/integer- gmp/gmp/config.mk` can't be found. {{{ --- a/libraries/integer-gmp/gmp/ghc.mk +++ b/libraries/integer-gmp/gmp/ghc.mk @@ -47,7 +47,10 @@ endif ifeq "$(phase)" "final" ifneq "$(CLEANING)" "YES" -include libraries/integer-gmp/gmp/config.mk +# Hack. The file gmp/config.mk doesn't exist yet after running ./configure in +# the toplevel (ghc) directory. To let some toplevel make commands such as +# sdist go through, right after ./configure, don't consider this an error. +-include libraries/integer-gmp/gmp/config.mk endif }}} Those 'No such file or directory' lines are perfectly normal. Please reopen if you're still having problems. Ideally with a way to reproduce. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 18:46:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 18:46:47 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.ed917fb94b4f4640baab8f747012809e@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Simon has written another patch addressing this issue which I have merged to the `ghc-7.10` branch. This still needs a fix on `master`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 19:21:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 19:21:33 -0000 Subject: [GHC] #10627: cabal install of numeric-prelude hangs Message-ID: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> #10627: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: MacOS X Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- While trying to do cabal install species with 7.10.2rc2 I discovered that it hangs compiling numeric-prelude in src/Algebra/RealRing.h. It doesn't seem to be busy computing as cpu usage is 0% {{{ ghc -V The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150630 cabal install --verbose=3 numeric-prelude ... [39 of 97] Compiling Algebra.RealRing ( src/Algebra/RealRing.hs, dist/build/Algebra/RealRing.o ) ... Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = True}) = {terms: 3,506, types: 3,224, coercions: 4} *** Common sub-expression: Result size of Common sub-expression }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 19:28:38 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 19:28:38 -0000 Subject: [GHC] #10627: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.b712eff6d7f85e8001b841ba866e940a@haskell.org> #10627: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Did you try installing the same version of numeric-prelude with ghc-7.10.1. As in: is this a regression? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 19:51:51 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 19:51:51 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.4f480de77018d961a2ddbcfa5ed12a83@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Comment (by ezyang): Here is a counter-proposal, organized around avoiding changing the package database format: Cabal already has limited support for multiple "packages" in a distribution unit, namely with its support for testing libraries. These libraries are never installed for other users to use, but internally, they can be installed and used like extra libraries. In this model, the database has a separate entry for each unit. The downside is that the package database will no longer be organized by distribution units. But this was already the case: if I install a package multiple times with different dependencies, it will occur multiple times in the database. The big upside is that the changes we have to make are now much smaller. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 20:08:29 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 20:08:29 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs (was: cabal install of numeric-prelude hangs) In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.fdf9319bcd199c4f3921c72d32c8ca5a@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by George: Old description: > While trying to do cabal install species with 7.10.2rc2 I discovered that > it hangs compiling numeric-prelude in src/Algebra/RealRing.h. It doesn't > seem to be busy computing as cpu usage is 0% > {{{ > ghc -V > The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150630 > cabal install --verbose=3 numeric-prelude > ... > [39 of 97] Compiling Algebra.RealRing ( src/Algebra/RealRing.hs, > dist/build/Algebra/RealRing.o ) > ... > > Result size of Float out(FOS {Lam = Just 0, > Consts = True, > OverSatApps = True}) > = {terms: 3,506, types: 3,224, coercions: 4} > *** Common sub-expression: > Result size of Common sub-expression > }}} New description: While trying to do cabal install species with HP 7.10.2rc2 I discovered that it hangs compiling numeric-prelude in src/Algebra/RealRing.h. It doesn't seem to be busy computing as cpu usage is 0%. It also hangs with HP 7.10.1.20150612 but works with HP 7.10.1.20150601 {{{ ghc -V The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150630 cabal install --verbose=3 numeric-prelude ... [39 of 97] Compiling Algebra.RealRing ( src/Algebra/RealRing.hs, dist/build/Algebra/RealRing.o ) ... Result size of Float out(FOS {Lam = Just 0, Consts = True, OverSatApps = True}) = {terms: 3,506, types: 3,224, coercions: 4} *** Common sub-expression: Result size of Common sub-expression }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 20:09:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 20:09:42 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.f8a69878e054477b70a5c2f8c63218dd@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:1 thomie]: > Did you try installing the same version of numeric-prelude with ghc-7.10.1. As in: is this a regression? Thanks for asking me to check that, it is a regression as noted in the description which I just modified -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 20:41:19 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 20:41:19 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.eaa4c300c4739d61e760666abbbe43b9@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Ok. The next thing to do would be to reduce the test. No packages, no cabal, just a single file that fails to build with ghc. Sometimes this is not so easy, but without it these type of bugs don't get fixed easily either. Maybe you want to give it a try? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 20:51:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 20:51:02 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.5e261bea798533ea65f54a65ddac72bd@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Sorry, I don't think I can, I will however send mail to the package maintainer, Henning Thielemann and cc Brent Yorgey whose species package depends on numeric prelude. I set the priority as high as it seems that shipping a release that can't compile a package it could previously is not a good thing. The impact of the bug is not clear. However, I personally don't need this fix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:16:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:16:44 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.10bfabb09121db11029f58b66fd00b39@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Lemming): My first interesting observation is that GHCi (run by `cabal repl`) can load all modules. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:18:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:18:33 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.54bfc3af5ae1ca1285fed7e2e798e3ac@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Lemming): * cc: ghc@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:19:38 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:19:38 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.d2327288db52981c025618021b2a3a01@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:6 Lemming]: > My first interesting observation is that GHCi (run by `cabal repl`) can load all modules. Thanks Lemming, what version of ghc are you using? What platform? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:21:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:21:44 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.0144c9950b226ee586eaf999333edea6@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Lemming): Replying to [comment:8 George]: > Thanks Lemming, what version of ghc are you using? What platform? GHC-7.10.1.20150630 from the Ubuntu-HVR-PPA package ghc-7.10.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:25:14 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:25:14 -0000 Subject: [GHC] #10628: clang's cpp causes incorrect line numbers in type errors Message-ID: <049.49ac6081ec1ed294f564c94326c7489b@haskell.org> #10628: clang's cpp causes incorrect line numbers in type errors -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: MacOS X Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- If I run GHC on {{{ {-# LANGUAGE CPP #-} module Foo where foo :: String foo = True }}} I get an error {{{ Foo.hs:7:7: Couldn't match type ?Bool? with ?[Char]? Expected type: String Actual type: Bool In the expression: True In an equation for ?foo?: foo = True }}} but the type error is on line 6, not line 7. It seems to have something to do with the fact that line 2 starts with a `#` since the error is reported correctly if I make the language pragma a single line. GHC on linux reports the correct location, as does GHC on OS X if I use any other language pragma, so I'm pretty sure this is another instance of clang's `cpp` causing problems for us. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:36:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:36:39 -0000 Subject: [GHC] #10628: clang's cpp causes incorrect line numbers in type errors In-Reply-To: <049.49ac6081ec1ed294f564c94326c7489b@haskell.org> References: <049.49ac6081ec1ed294f564c94326c7489b@haskell.org> Message-ID: <064.c60e873ce2a0149511c4fdaee8d1b3d4@haskell.org> #10628: clang's cpp causes incorrect line numbers in type errors -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by mpickering): Here is the preprocessed source. There is an extra line inserted after the pragma. {{{ {-# LINE 1 "test.hs" #-} # 1 "test.hs" # 1 "" 1 # 16 "" # 1 "/Users/matt/Downloads/ghc-7.10.1.app/Contents/lib/ghc-7.10.1/include/ghcversion.h" 1 # 17 "" 2 # 1 "test.hs" 2 {-# LANGUAGE CPP #-} module Foo where foo :: String foo = True }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:36:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:36:39 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.76261712ba3d9bc3d851a4d28538f6a5@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:9 Lemming]: > Replying to [comment:8 George]: > > > Thanks Lemming, what version of ghc are you using? What platform? > > GHC-7.10.1.20150630 from the Ubuntu-HVR-PPA package ghc-7.10.2 Can you confirm that you can reproduce the bug with cabal install? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:47:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:47:44 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.b1104135eee01df30a845676e8dbb6fc@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Lemming): I attached a minimal example that you can run with: {{{ $ ghc-7.10.1.20150630 -O RealRing.hs [1 of 1] Compiling RealRing ( RealRing.hs, RealRing.o ) RealRing.hs:11:6: Warning: Rule "NP.roundSimple :: a -> Word" may never fire because ?roundSimple? might inline first Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ?roundSimple? ^C }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 21:59:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 21:59:56 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.dc7897f1e2435aa4ea6577a3425711fc@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:6 Lemming]: > My first interesting observation is that GHCi (run by `cabal repl`) can load all modules. Yes, cabal repl works for me also {{{ ghc -V The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150630 cabal get -s numeric-prelude cd numeric-prelude cabal sandbox init cabal install --only-dependencies cabal repl }}} However after quitting out of the repl, cabal build fails cabal build Building numeric-prelude-0.4.2... ... It hangs after emitting the following {{{ src/Algebra/RealRing.hs:369:6: Warning: Rule "NP.roundSimple :: a -> Word64" may never fire because ?roundSimple? might inline first Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ?roundSimple? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:03:48 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:03:48 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.a952dd50946549b1ab10b9d6adbca160@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Lemming): Replying to [comment:6 Lemming]: > My first interesting observation is that GHCi (run by `cabal repl`) can load all modules. I think it is because GHCi does not optimize and the problem seems to be the rewrite rule. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:06:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:06:06 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.7344118a4f2219089e6191ac828a44f2@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): I actually tried the technique on my current code base and it did appear GHC went into an infinite loop. I didn't report it here though because I wasn't sure exactly what was going on and I haven't had a chance to look into it more fully. I'm not sure what you mean by this could be accepted with regards to comment:6 of #10318. There's a lot going on in that thread, and it's hard for me to get a good grasp of what's relevant. I basically know nothing about how type inference actually works, I'm just a big fan of using it :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:06:54 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:06:54 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.54269bea0fb3787b4bb4e66d95c21e5a@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Replying to [comment:11 Lemming]: > I attached a minimal example that you can run with: > {{{ > $ ghc-7.10.1.20150630 -O RealRing.hs > [1 of 1] Compiling RealRing ( RealRing.hs, RealRing.o ) > > RealRing.hs:11:6: Warning: > Rule "NP.roundSimple :: a -> Word" may never fire > because ?roundSimple? might inline first > Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ?roundSimple? > ^C > }}} Thanks! That fails for me also. It works if I compile without the -O -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:10:37 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:10:37 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.6415601d5f42b5497924d67d1800e638@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by George): * cc: george (added) * os: MacOS X => Unknown/Multiple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:20:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:20:12 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar Message-ID: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime | Operating System: Linux System | Type of failure: Incorrect result Keywords: | at runtime concurrency sockets | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- In a project using the network-transport-tcp package, I'm observing {{{threadWaitRead}}} throw the exception {{{BlockedIndefinitelyOnMVar}}}. The call stack is roughly: {{{ ... n-t-tcp:Network.Transport.TCP.handleIncomingMessages n-t-tcp:Network.Transport.TCP.Internal.recvInt32 n-t-tcp:Network.Transport.TCP.Internal.recvExact network:Network.Socket.ByteString:recv network:Network.Socket.ByteString:recvInner network:Network.Socket.Internal:throwSocketErrorWaitRead base:Control.Concurrent:threadWaitRead }}} IIUC this would be an RTS bug. The socket file descriptor is healthy and works fine if the exception is caught and {{{threadWaitRead}}} is retried. Unfortunately, I can only reproduce this in a particular machine and with a rather complex test case. I'd appreciate any advice on inspecting the RTS code to scan for the cause of {{{BlockedIndefinitelyOnMVar}}} being thrown. Of course, if someone can help explaining this behavior I'll be most thankful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:27:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:27:17 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.d9ed511ee4003fac16e08604200fb13d@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by facundo.dominguez: Old description: > In a project using the network-transport-tcp package, I'm observing > {{{threadWaitRead}}} throw the exception {{{BlockedIndefinitelyOnMVar}}}. > > The call stack is roughly: > > {{{ > ... > n-t-tcp:Network.Transport.TCP.handleIncomingMessages > n-t-tcp:Network.Transport.TCP.Internal.recvInt32 > n-t-tcp:Network.Transport.TCP.Internal.recvExact > network:Network.Socket.ByteString:recv > network:Network.Socket.ByteString:recvInner > network:Network.Socket.Internal:throwSocketErrorWaitRead > base:Control.Concurrent:threadWaitRead > }}} > > IIUC this would be an RTS bug. The socket file descriptor is healthy and > works fine if the exception is caught and {{{threadWaitRead}}} is > retried. > > Unfortunately, I can only reproduce this in a particular machine and with > a rather complex test case. > > I'd appreciate any advice on inspecting the RTS code to scan for the > cause of {{{BlockedIndefinitelyOnMVar}}} being thrown. > > Of course, if someone can help explaining this behavior I'll be most > thankful. New description: In a project using the network-transport-tcp package, I'm observing {{{threadWaitRead}}} throw the exception {{{BlockedIndefinitelyOnMVar}}}. The call stack is roughly: {{{ ... n-t-tcp:Network.Transport.TCP.handleIncomingMessages n-t-tcp:Network.Transport.TCP.Internal.recvInt32 n-t-tcp:Network.Transport.TCP.Internal.recvExact network:Network.Socket.ByteString:recv network:Network.Socket.ByteString:recvInner network:Network.Socket.Internal:throwSocketErrorWaitRead base:Control.Concurrent:threadWaitRead }}} IIUC this would be an RTS bug. The socket file descriptor is healthy and works fine if the exception is caught and {{{threadWaitRead}}} is retried. Unfortunately, I can only reproduce this in a particular cluster and with a rather complex test case while using the threaded runtime. I'd appreciate any advice on inspecting the RTS code to scan for the cause of {{{BlockedIndefinitelyOnMVar}}} being thrown. Of course, if someone can help explaining this behavior I'll be most thankful. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:31:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:31:35 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.f4cb0d886b99a0dfa2baabcc0a980f24@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: MacOS X | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: ghc@?, george (removed) * os: Unknown/Multiple => MacOS X Comment: Amazing. I couldn't resist looking at this, and it seems to be a very long-standing bug, introduced I think by {{{ commit 30c17e7096919c55218083c8fcb98e6287552058 Author: simonpj at microsoft.com Date: Thu Nov 25 17:23:56 2010 +0000 Substitution should just substitute, not optimise This was causing Trac #4524, by optimising (e |> co) to e on the LHS of a rule. Result, the template variable 'co' wasn't bound any more. Now that substition doesn't optimise, it seems sensible to call simpleOptExpr rather than substExpr when substituting in the RHS of rules. Not a big deal either way. }}} The last para says "optimise the RHS of rules when substituting", but that is too strict in the `IdInfo` of an `Id` if the RULE refers to the same `Id`. I don't know how this ever worked. Patch coming. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:43:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:43:32 -0000 Subject: [GHC] #10628: clang's cpp causes incorrect line numbers in type errors In-Reply-To: <049.49ac6081ec1ed294f564c94326c7489b@haskell.org> References: <049.49ac6081ec1ed294f564c94326c7489b@haskell.org> Message-ID: <064.15e0c12c63d1fe012e7f0889ad6255b1@haskell.org> #10628: clang's cpp causes incorrect line numbers in type errors -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: cpp Operating System: MacOS X | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #10044 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => cpp * status: new => closed * resolution: => duplicate * related: => #10044 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 22:48:37 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 22:48:37 -0000 Subject: [GHC] #10044: Wrong line number reported with CPP and line beginning with # In-Reply-To: <047.a0bfc7b37bebfe567d7611d66867f0e2@haskell.org> References: <047.a0bfc7b37bebfe567d7611d66867f0e2@haskell.org> Message-ID: <062.f5692ab6760f4ae5ebe5b7f645ee8a45@haskell.org> #10044: Wrong line number reported with CPP and line beginning with # -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.1-rc2 Resolution: | Keywords: cpp Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by gridaphobe): * cc: gridaphobe (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 23:21:03 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 23:21:03 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.2d14d10a41c21eb4ff7cb93d58259499@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): The stuff in #10318 is speculation about a possible feature. But the question remains: in your application If {{{ class (Scalar (Scalar a) ~ Scalar a, Field (Scalar a)) => Vector a class Vector x => Field x }}} was accepted by GHC, would it serve your purpose? That means that in any instance of `Vector t`, GHC will need to prove that `Scalar (Scalar t) ~ Scalar t`. Will that be true, in your application? If so, that makes the speculation in #10318 more persuasive. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 23:35:34 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 23:35:34 -0000 Subject: [GHC] #10592: Allow cycles in class declarations In-Reply-To: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> References: <050.6ec91d55766f7dba414220a7b67bdbfd@haskell.org> Message-ID: <065.f721e109c9b8db4c52fde2f3761da8c9@haskell.org> #10592: Allow cycles in class declarations -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): My current implementation has constraints that look exactly like this, plus a lot more related to other aspects of the class hierarchy. So supporting this would be a necessary condition for me cyclic class declarations for me, but I can't say for sure if it would be sufficient (but my guess is probably). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 10 23:48:53 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 10 Jul 2015 23:48:53 -0000 Subject: [GHC] #10068: Make the runtime reflection API for names, modules, locations more systematic In-Reply-To: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> References: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> Message-ID: <061.3f6cc6ec34f9ec18796a86a36ce5d539@haskell.org> #10068: Make the runtime reflection API for names, modules, locations more systematic -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): `GHC.Stack.CostCentreStack` has yet another representation of source locations, as `CString`s. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 03:36:49 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 03:36:49 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.99c7a4e359cb70dffb85f5fad23dd266@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Comment (by ezyang): And here is a counter-counter-proposal, where simply REDUCE sharing: 1. The basic idea is to defer making libraries/bundles of hi files until we have a complete, definite package that has been Cabalized. So if we have something like: {{{ package p where signature H module P package q where module H include p }}} distributed with a `q.cabal`, `p` NEVER SHOWS UP in the installed package database; not even the version of it instantiated with `q`. 2. This obviously breaks type-checking, since when we build `p` will still be compiled to a specific package key `p(Q -> q:H)`, but this package key won't be anywhere in our installed package database. So libraries like `q` will get a new type of entry in the installed package database: they are **fat installed packages** which can contain files for more than one package key. These keys are enumerated in the entry installed package database, and you just look in `import-dirs/key` to find the relevant interface files. So `p`'s interface files will live in something like `q -install-dir/p_KEY`. Cabal also records the ABI hash of each of the sub- packages in a fat package. 3. Suppose `p` is an indefinite package with a `p.cabal` of its own. Neither the generic `p` nor the instantiated versions of `p` have direct entries in the package database: you will only file `hi` files/libraries under the fat installs of other definite packages with used `p`. 4. What happens in this situation, when `q1` and `q2` are built in parallel? (Suppose each package has its own Cabal file) {{{ package p where signature H module P package h where module H package q1 where include h include p module Q1 package q2 where include h include p module Q2 }}} `h` is a normal package and can get installed as usual. `q1` and `q2` are FAT installed packages, they get installed with hi files and libraries for `p(H -> h:H)`. In particular, this means that means that `p` instantiated with `h` is DUPLICATED in these two fat installed packages. To avoid disaster from incompatible duplicate packages, we verify that for every duplicated package key in the package database, the ABI hashes are the same. This will work great if we have deterministic builds, and not so great if they are nondeterministic. 5. Let's say we instantiate a package, and we discover that a fat package which we don't directly depend on instantiated it already. What do we do? It should be OK to reuse it, but when Cabal goes and installs, it must copy the interface files and libraries from the other fat package into our new fat package. 6. This makes the story great for distribution packagers: they don't have to worry about two (morally separate) packages depending on common files/libraries which need to be installed in the same location. This would require a subpackage, but Debian is unlikely to want to create lots and lots of little packages to get the sharing we're aiming for here. I actually kind of suspect this is what Simon wanted to do from the beginning; apologies for not figuring it out sooner. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 07:15:37 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 07:15:37 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.e67becdd474b2418008ad5fc8b1387a4@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Lemming): * cc: ghc@?, george (added) * os: MacOS X => Unknown/Multiple -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 16:27:02 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 16:27:02 -0000 Subject: [GHC] #10630: Template variable unbound in rewrite rule (GHC 7.10.1) Message-ID: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> #10630: Template variable unbound in rewrite rule (GHC 7.10.1) -------------------------------------+------------------------------------- Reporter: Otini | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Keywords: panic, | Operating System: Linux template, bitmap | Type of failure: GHC rejects Architecture: x86_64 | valid program (amd64) | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I read this bug had been fixed in GHC 7.10, and yet I get this when trying to compile bitmap : {{{ $ cabal install bitmap Resolving dependencies... Configuring bitmap-0.0.2... Building bitmap-0.0.2... Failed to install bitmap-0.0.2 Build log ( /home/olivier/.cabal/logs/bitmap-0.0.2.log ): Configuring bitmap-0.0.2... Building bitmap-0.0.2... Preprocessing library bitmap-0.0.2... [ 1 of 10] Compiling Data.Bitmap.Internal ( Data/Bitmap/Internal.hs, dist/build/Data/Bitmap/Internal.o ) [ 2 of 10] Compiling Data.Bitmap.Base ( Data/Bitmap/Base.hs, dist/build/Data/Bitmap/Base.o ) [ 3 of 10] Compiling Data.Bitmap.IO ( Data/Bitmap/IO.hs, dist/build/Data/Bitmap/IO.o ) Data/Bitmap/IO.hs:1248:1: Warning: SPECIALISE pragma for non-overloaded function ?myPlusPtr? Data/Bitmap/IO.hs:1249:1: Warning: SPECIALISE pragma for non-overloaded function ?myPlusPtr? ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): Template variable unbound in rewrite rule $fPixelComponentFloat3_X2Rc [$fPixelComponentFloat3_X2Rc] [$fPixelComponentFloat3_X2Rc] [] [] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug cabal: Error: some packages failed to install: bitmap-0.0.2 failed during the building phase. The exception was: ExitFailure 1 $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.10.1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 16:40:33 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 16:40:33 -0000 Subject: [GHC] #10630: Template variable unbound in rewrite rule (GHC 7.10.1) In-Reply-To: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> References: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> Message-ID: <059.63f53f6a4ddfe7501581383c71709b21@haskell.org> #10630: Template variable unbound in rewrite rule (GHC 7.10.1) -------------------------------------+------------------------------------- Reporter: Otini | Owner: Type: bug | Status: new Priority: high | Milestone: ? Component: Compiler | Version: 7.10.1 Resolution: | Keywords: panic, Operating System: Linux | template, bitmap Type of failure: GHC rejects | Architecture: x86_64 valid program | (amd64) Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Otini): * milestone: => ? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 16:50:51 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 16:50:51 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.4441b200b11be9d0dd8f2d6045761e82@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by slyfox): * cc: slyfox (added) Comment: It's unclear which runtime you are using: threaded or non-threaded? Can you grab an '+RTS -Ds' dump for a process that crashed like that? Trac #10590 might or might not be relevant. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 17:01:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 17:01:15 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.a7a216dd7ceae3afe60ace349873fc80@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): The RTS throws that exception in a single place in resurrectThreads: https://github.com/ghc/ghc/blob/9b1ebba2af060fef90dcd722313d3f8041ec5a97/rts/Schedule.c#L2847 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 11 21:28:43 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 11 Jul 2015 21:28:43 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.ed71becf73f6283e7e8fe8d1eef95bf3@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1056 -------------------------------------+------------------------------------- Comment (by ezyang): I was thinking about this situation some more, and I realized that we can actually avoid having to have Cabal query GHC for the package key, if we adopt a convention: the version hash of a package is the SAME as the package key, if the package is definite. I've repushed the pull request with this in mind. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 02:31:40 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 02:31:40 -0000 Subject: [GHC] #9571: nofib should use criterion-style bootstrapping/sampling In-Reply-To: <045.5455eab068db49e1d11638c2709a378d@haskell.org> References: <045.5455eab068db49e1d11638c2709a378d@haskell.org> Message-ID: <060.a59dc87d3cccd31698bf4482cb6c1a5f@haskell.org> #9571: nofib should use criterion-style bootstrapping/sampling -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 7.9 suite | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5793 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kanetw): Is it possible to just use criterion to run the benchmarks, or does GHC have special requirements that would require an own implementation? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 03:28:54 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 03:28:54 -0000 Subject: [GHC] #10631: Report of GHC Panic Message-ID: <048.0d7915ea1be06d70aee5e73f020551d8@haskell.org> #10631: Report of GHC Panic -------------------------------------+------------------------------------- Reporter: seewalker | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: MacOS X Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I'll just copy here the error message; I wouldn't say I have the judgement to interpret it: ''ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-apple-darwin): Loading temp shared object failed: dlopen(/var/folders/84/5rj51n8x70g4km60lfh_ds1m0000gt/T/ghc22694_0/libghc22694_107.dylib, 5): Symbol not found: _AlexSzuELoZZpfyhWUk8IXGTl3Kiel_ModulesziDBTypes_zdfPersistFieldLinkTag_closure Referenced from: /var/folders/84/5rj51n8x70g4km60lfh_ds1m0000gt/T/ghc22694_0/libghc22694_107.dylib Expected in: flat namespace in /var/folders/84/5rj51n8x70g4km60lfh_ds1m0000gt/T/ghc22694_0/libghc22694_107.dylib Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug'' This occurred while interactively developing a website with "yesod devel". After the compiler crashed, I killed the program, invoked "yesod devel" again without changing anything in my source code. This next time, no error occurred. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 08:10:33 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 08:10:33 -0000 Subject: [GHC] #10630: Template variable unbound in rewrite rule (GHC 7.10.1) In-Reply-To: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> References: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> Message-ID: <059.880456f58bbab17dfa854c89d0093bb1@haskell.org> #10630: Template variable unbound in rewrite rule (GHC 7.10.1) -------------------------------------+------------------------------------- Reporter: Otini | Owner: Type: bug | Status: new Priority: high | Milestone: ? Component: Compiler | Version: 7.10.1 Resolution: | Keywords: panic, Operating System: Linux | template, bitmap Type of failure: GHC rejects | Architecture: x86_64 valid program | (amd64) Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): Should be fixed in 7.10.2 as part of #10251 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 10:37:20 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 10:37:20 -0000 Subject: [GHC] #10565: GHC 7.10.2 RC: the impossible happened on hPDB-examples-1.2.0.2 In-Reply-To: <047.3ffddb89eb8d6f97040b05fb569a18d7@haskell.org> References: <047.3ffddb89eb8d6f97040b05fb569a18d7@haskell.org> Message-ID: <062.86a099af4c8dc6a29ece8d6554c4f591@haskell.org> #10565: GHC 7.10.2 RC: the impossible happened on hPDB-examples-1.2.0.2 ---------------------------------+----------------------------------------- Reporter: snoyberg | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: wontfix | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix Comment: As described above I'm not convinced that we can do much better on the code as-written. I'll send a patch suggesting an alternate implementation upstream. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 13:06:59 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 13:06:59 -0000 Subject: [GHC] #10632: ImplicitParams: GHC does not warn about unused implicit parameters Message-ID: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> #10632: ImplicitParams: GHC does not warn about unused implicit parameters -------------------------------------+------------------------------------- Reporter: mwnx | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.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 Revisions: | -------------------------------------+------------------------------------- When using -XImplicitParams, and an implicit parameter is not used within a function which accepts said parameter, no warning is issued (with -Wall turned on). Example: {{{#!hs {-# LANGUAGE ImplicitParams #-} f :: (?file1 :: String) => IO () f = putStrLn $ "f2: " main :: IO () main = let ?file1 = "A" in f }}} Here, I would expect a warning about ?file1 being unused in f. As far as I can tell (but I'm quite the layman in these matters), issuing a warning here would be desirable, possible, and quite easy. Sorry for the bug report if there's a reason for the status quo. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 13:11:57 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 13:11:57 -0000 Subject: [GHC] #10633: GHCi segfaults on arm Message-ID: <045.ce30a9b63cbcf433a0315ff9f9caf317@haskell.org> #10633: GHCi segfaults on arm ---------------------------------+------------------------------- Reporter: Thra11 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: arm | Type of failure: GHCi crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | ---------------------------------+------------------------------- I define a data type: {{{#!hs data Tree a = Leaf a | Tree { left :: Tree a , right :: Tree a } deriving Show }}} Then I create a few named trees: {{{#!hs testTree0 = Leaf 0 testTree1 = Tree (Leaf 0) (Leaf 0) testTree2 = Tree testTree0 testTree0 testTree3 = Tree testTree1 testTree1 testTree4 = Tree (Tree (Leaf 0) (Leaf 0)) (Tree (Leaf 0) (Leaf 0)) }}} This segfaults in GHCi (works fine with non-interactive GHC): {{{#!hs main = print testTree3 }}} == Notes == * testTree3 and testTree4 represent the same tree, constructed in different ways. However, testTree3 segfaults when it tries to print the second testTree1; testTree4 does not. * entering 'print testTree1' twice segfaults, but only if it is twice in a row. * strangely enough, printing testTree4 repeatedly does not segfault. * printing testTree0 many times in a row doesn't segfault either. * printing testTree2 segfaults. It seems to be something to do with repetition or reevaluation of the same named structure. I haven't yet managed to determine whether the print is relevant or whether it's forcing the evaluation of the data structure that causes the segfault (Can't remember how to force a list but discard the result). I have attached the the output from running ghci with +RTS -Di. Let me know if there's anything else I should try. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 12 16:27:00 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 12 Jul 2015 16:27: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.e51e63cd7c1b053b2aab0d9f7d189add@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): Oh you're right. I forgot that DeriveAnyClass should never fail, so maybe there are multiple bugs involved. I managed to modify GHC to make this program work: {{{ ? deriveany_bug cat Test.hs newtype MyMaybe a = MyMaybe (Maybe a) deriving (Functor, Show) main = print $ MyMaybe $ Just (10 :: Int) ? deriveany_bug ghc-stage1 --make Test.hs -fforce-recomp -XDeriveAnyClass [1 of 1] Compiling Main ( Test.hs, Test.o ) Linking Test ... ? deriveany_bug ./Test MyMaybe (Just 10) ? deriveany_bug ghc-stage1 --make Test.hs -fforce-recomp -XDeriveAnyClass -XGeneralizedNewtypeDeriving [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:2:13: warning: Both DeriveAnyClass and GeneralizedNewtypeDeriving are enabled Defaulting to the DeriveAnyClass strategy for instantiating Functor In the newtype declaration for ?MyMaybe? Test.hs:2:22: warning: Both DeriveAnyClass and GeneralizedNewtypeDeriving are enabled Defaulting to the DeriveAnyClass strategy for instantiating Show In the newtype declaration for ?MyMaybe? Linking Test ... ? deriveany_bug ./Test MyMaybe (Just 10) }}} `mkNewTypeEqn` function has some error handling for the cases where we have both GND and DeriveAnyClass, but the logic is buggy, I think. It's easy to fix. (I didn't run the whole test suite though, I'm not 100% sure I didn't break anything) Should I send a patch for reviews or do you think the problem is something else? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 07:47:14 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 07:47:14 -0000 Subject: [GHC] #10634: Type class with bijective type functions Message-ID: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> #10634: Type class with bijective type functions -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- See the attached module. {{{ $ cat TypeFunctionBijection.hs {-# LANGUAGE TypeFamilies #-} module TypeFunctionBijection where import Data.Int (Int8, Int16, Int32) type family Up a type instance Up Int8 = Int16 type instance Up Int16 = Int32 class (Up (Down a) ~ a) => Convert a where type Down a down :: a -> Down a instance Convert Int16 where type Down Int16 = Int8 down = fromIntegral instance Convert Int32 where type Down Int32 = Int16 down = fromIntegral x :: Int8 x = down 8 }}} {{{ $ ghci-7.8.4 -Wall TypeFunctionBijection.hs GHCi, version 7.8.4: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling TypeFunctionBijection ( TypeFunctionBijection.hs, interpreted ) Ok, modules loaded: TypeFunctionBijection. *TypeFunctionBijection> :q Leaving GHCi. }}} {{{ $ ghci-7.10.1 -Wall TypeFunctionBijection.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling TypeFunctionBijection ( TypeFunctionBijection.hs, interpreted ) TypeFunctionBijection.hs:24:5: Couldn't match expected type ?Int8? with actual type ?Down a0? The type variable ?a0? is ambiguous In the expression: down 8 In an equation for ?x?: x = down 8 Failed, modules loaded: none. Prelude> :q Leaving GHCi. }}} Up to GHC-7.8.4 I could make a type function like `Down` a bijection by adding equality constraints to the `Convert` class. In GHC-7.10.1 this fails. Is this a bug or a feature? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 08:54:26 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 08:54:26 -0000 Subject: [GHC] #10068: Make the runtime reflection API for names, modules, locations more systematic In-Reply-To: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> References: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> Message-ID: <061.e0f6bab9a51d9d14b40370dddc9b58ce@haskell.org> #10068: Make the runtime reflection API for names, modules, locations more systematic -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Old description: > Currently in `base` we have > > * `GHC.SrcLoc`: the data type `SrcLoc` contains `srcLocPackage` and > `srcLocModule` > > * `Data.Typeable.Internals`: the data type `TyCon` contains > `tyConPackage`, `tyConModule` and `tyConName`. > > * `GHC.Generics`: the data type `Datatype` contains `dataTypePackage`, > `dataTypeModule` and `dataTypeName` > > * `Data.Data`: the data type `DataType` (yes the capitalisation > differs!) contains a field `tycon :: String`, and there are functions > `tyconModule :: String -> String`, and `tyconUQname :: String -> String`, > for parsing that string and extracting the module name and tycon name. > > * `GHC.StaticPtr`: the data type `StaticPtrInfo` contains > `spInfoPackageKey`, `spInfoModuleName`, `spInfoName` (all `String`s). > Oh, and `spInfoSrcLoc :: (Int,Int)` too! > > This is madness! Five different representations for the same information > in one package! > > Let's fix this by defining some shared data types, for > > * `Module` = `ModuleName` + package > * `Entity` = `Module` + unqualified name > > There would be a tiresome changeover period; but `Typeable` and > `StaticPtr` are in flux anyway. > > Would anyone be willing to lead on this? New description: Currently in `base` we have * `GHC.SrcLoc`: the data type `SrcLoc` contains `srcLocPackage` and `srcLocModule` * `Data.Typeable.Internals`: the data type `TyCon` contains `tyConPackage`, `tyConModule` and `tyConName`. * `GHC.Generics`: the data type `Datatype` contains `dataTypePackage`, `dataTypeModule` and `dataTypeName` * `Data.Data`: the data type `DataType` (yes the capitalisation differs!) contains a field `tycon :: String`, and there are functions `tyconModule :: String -> String`, and `tyconUQname :: String -> String`, for parsing that string and extracting the module name and tycon name. * `GHC.StaticPtr`: the data type `StaticPtrInfo` contains `spInfoPackageKey`, `spInfoModuleName`, `spInfoName` (all `String`s). Oh, and `spInfoSrcLoc :: (Int,Int)` too! * `GHC.Stack.ccSrcSpan :: Ptr CostCentre -> IO CString` stores a source location in a C structure, and returns it as a `CString`. This is madness! Six different representations for the same information in one package! Let's fix this by defining some shared data types, for * `Module` = `ModuleName` + package * `Entity` = `Module` + unqualified name There would be a tiresome changeover period; but `Typeable` and `StaticPtr` are in flux anyway. Would anyone be willing to lead on this? -- Comment (by simonpj): Well spotted. Do you feel like helping out with this?! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 09:07:10 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 09:07:10 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.7a9b3144516a954323678329fec5992f@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Comment (by simonpj): This sounds plausible to me, though as usual with cabal/backpack I am not 100% sure of my ground. I think of it like this: * Cabal concerns itself with Cabal packages (units of distribution and versioning), including choosing version numbers, downloading them, and figuring out if that particular package (instantiated with its transitive dependencies) is already installed. * GHC concerns itself with Backpack units. Both share a single "installed package database". But they use it in a different way. For GHC at least, it's just a cache: a place to record the result of previous work (including typechecking indefinite packages), so that we don't need to repeat it. There is no harm in repeating it, but it's a waste of time. So Cabal need never see the previously-compiled indefinite packages; they are just a way for GHC to save time. Maybe that is what you are saying. Another way to attack this is to ask "what questions does Cabal ask the installed package database?" and "what questions does GHC ask?". I think the two are different. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 09:38:16 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 09:38:16 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.3cd1cfbfc2c574f5527e86b6859b44ee@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"d073c770209d3e7208059b3be8187a47c9181a3e/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d073c770209d3e7208059b3be8187a47c9181a3e" Do not optimise RULE lhs in substRule This was causing Trac #10627. See Note [Substitute lazily] in CoreSubst. The bug was introduced by commit 30c17e7096919c55218083c8fcb98e6287552058 Author: simonpj at microsoft.com Date: Thu Nov 25 17:23:56 2010 +0000 Substitution should just substitute, not optimise The fix is not to optimise the RHS as well as not-optimising the LHS! The simplifier does the right thing in Simplify.simplRule }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 09:40:02 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 09:40:02 -0000 Subject: [GHC] #10634: Type class with bijective type functions In-Reply-To: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> References: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> Message-ID: <061.7c396133d593e4af7920d79f306d9bd0@haskell.org> #10634: Type class with bijective type functions -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10009 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jstolarek): * status: new => closed * resolution: => duplicate * related: => #10009 Comment: It's a bug. See #10009. As a side note: I don't think it is correct to call this a bijection. Bijection means that we have injectivity (which is true) and surjectivity (which is not true). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 09:50:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 09:50:48 -0000 Subject: [GHC] #10634: Type class with injective type functions (was: Type class with bijective type functions) In-Reply-To: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> References: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> Message-ID: <061.561ee99ea4e163075c95d4da6a9d9688@haskell.org> #10634: Type class with injective type functions -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10009 | Differential Revisions: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 09:54:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 09:54:53 -0000 Subject: [GHC] #10009: type inference regression when faking injective type families In-Reply-To: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> References: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> Message-ID: <060.2e2ecb3c1ddd730840fd12a03689196c@haskell.org> #10009: type inference regression when faking injective type families -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1-rc1 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10226, #10634 | -------------------------------------+------------------------------------- Changes (by jstolarek): * related: #10226 => #10226, #10634 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 09:59:20 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 09:59:20 -0000 Subject: [GHC] #10009: type inference regression when faking injective type families In-Reply-To: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> References: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> Message-ID: <060.3c9ac26960948c2ffeaae3e9ab652e27@haskell.org> #10009: type inference regression when faking injective type families -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1-rc1 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10226 | -------------------------------------+------------------------------------- Changes (by Lemming): * related: #10226, #10634 => #10226 Comment: I was hit by this bug in `hmm-hmatrix` but I remember that I used this pattern in more places. I added #10634, which however is much abstracted from the original code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 10:00:39 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 10:00:39 -0000 Subject: [GHC] #10009: type inference regression when faking injective type families In-Reply-To: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> References: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> Message-ID: <060.d4bd0027af185e14a16927a3636b3499@haskell.org> #10009: type inference regression when faking injective type families -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1-rc1 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10226, #10634 | -------------------------------------+------------------------------------- Changes (by Lemming): * cc: Lemming (added) * related: #10226 => #10226, #10634 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 10:02:08 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 10:02:08 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.40a0de559723fe000c5b87bbc863ee3d@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | simplCore/should_compile/T10627 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge * testcase: => simplCore/should_compile/T10627 Comment: OK, fixed now. Thanks for reporting. Worth merging to 7.10.2 Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 10:26:50 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 10:26:50 -0000 Subject: [GHC] #10009: type inference regression when faking injective type families In-Reply-To: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> References: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> Message-ID: <060.253505f690d1280bdeb64b74510ace5c@haskell.org> #10009: type inference regression when faking injective type families -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1-rc1 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: #10226, #10634 | -------------------------------------+------------------------------------- Comment (by Lemming): Replying to [comment:27 kosmikus]: > Re `hlist`: I'm surprised this ever worked. What I usually do is to define the `UnPrime`-equivalent outside of the class (as a type family), and `Prime` within. I hadn't considered that there may have been GHC versions that would have allowed both to be defined within the class. I used that technique several times after I found out that it worked. I expected that GHC knows what it does. :-) I am now reverting the affected definitions. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 11:45:03 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 11:45:03 -0000 Subject: [GHC] #10635: -fwarn-redundant-constraints should not be part of -Wall Message-ID: <046.37bc7c73c7a26deffb461f9d58ce3c42@haskell.org> #10635: -fwarn-redundant-constraints should not be part of -Wall -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.11 Component: Compiler | Operating System: Unknown/Multiple (Type checker) | Type of failure: Incorrect Keywords: | warning at compile-time Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- When I compile existing code with GHC-7.11.20150707 I get lot of "redundant constraints" warnings. Generally I think that this warning can be very useful for minimizing constraints, nonetheless there are good reasons not choose minimal constraints for a type signature. E.g. if I have to implement `Data.Map.singleton` I do not need the `Ord k` constraint for the key type. However, I might add it anyway in order to be able to change the implementation in future such that it uses `Ord k` dictionary. Thus I suggest to exclude `-fwarn-redundant-constraints` from `-Wall`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 11:49:10 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 11:49:10 -0000 Subject: [GHC] #10635: -fwarn-redundant-constraints should not be part of -Wall In-Reply-To: <046.37bc7c73c7a26deffb461f9d58ce3c42@haskell.org> References: <046.37bc7c73c7a26deffb461f9d58ce3c42@haskell.org> Message-ID: <061.84b02c21645f50a627440895d67c5905@haskell.org> #10635: -fwarn-redundant-constraints should not be part of -Wall -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.11 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | Blocking: Blocked By: | Differential Revisions: Related Tickets: #9939, #9973, | #10100, #10183 | -------------------------------------+------------------------------------- Changes (by Lemming): * related: => #9939, #9973, #10100, #10183 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:04:26 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:04:26 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.ca6a087c34175882abe936c00e7a396e@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: merge Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | simplCore/should_compile/T10602 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: infoneeded => merge * testcase: => simplCore/should_compile/T10602 Comment: Fixed by {{{ commit 7da7b0e48598af7df25e1129772b42cb31649c74 Author: Simon Peyton Jones Date: Mon Jul 13 12:58:34 2015 +0100 Make sure rule LHSs are simplified SpecConstr was generating a rule LHS with nested casts, which the simplifier then optimised away. Result: unbound template variables. Easily fixed. See Note [SpecConstr call patterns] >--------------------------------------------------------------- 7da7b0e48598af7df25e1129772b42cb31649c74 compiler/specialise/SpecConstr.hs | 25 ++++++++++-- testsuite/tests/simplCore/should_compile/T10602.hs | 46 +++++++++------------- .../tests/simplCore/should_compile/T10602b.hs | 20 ++++++++++ testsuite/tests/simplCore/should_compile/all.T | 2 +- 4 files changed, 61 insertions(+), 32 deletions(-) diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs }}} I forgot to mention the ticket in the commit message. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:20:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:20:48 -0000 Subject: [GHC] #10463: Wrong warning with PartialTypeSignatures In-Reply-To: <047.c9ed6af0d80ddd0588b394ac97106388@haskell.org> References: <047.c9ed6af0d80ddd0588b394ac97106388@haskell.org> Message-ID: <062.08696479a9b65cf2ab880120cdd3cf84@haskell.org> #10463: Wrong warning with PartialTypeSignatures -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: partial- Related Tickets: | sigs/should_compile/T10463 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => partial-sigs/should_compile/T10463 * resolution: => fixed Comment: Was fixed along with #10224 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:21:16 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:21:16 -0000 Subject: [GHC] #10224: Partial type signatures generate typed hole warnings In-Reply-To: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> References: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> Message-ID: <060.bb4a491be346b49350d1ffbd165d3cb2@haskell.org> #10224: Partial type signatures generate typed hole warnings -------------------------------------+------------------------------------- Reporter: quchen | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"d7335f74744a78bb468326b13fdd8b0c471eb71f/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d7335f74744a78bb468326b13fdd8b0c471eb71f" Test Trac #10463 was fixed along with Trac #10224 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:21:16 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:21:16 -0000 Subject: [GHC] #10463: Wrong warning with PartialTypeSignatures In-Reply-To: <047.c9ed6af0d80ddd0588b394ac97106388@haskell.org> References: <047.c9ed6af0d80ddd0588b394ac97106388@haskell.org> Message-ID: <062.f533b2702a3c8d8041e5de3a9ae1a01d@haskell.org> #10463: Wrong warning with PartialTypeSignatures -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: partial- Related Tickets: | sigs/should_compile/T10463 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"d7335f74744a78bb468326b13fdd8b0c471eb71f/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="d7335f74744a78bb468326b13fdd8b0c471eb71f" Test Trac #10463 was fixed along with Trac #10224 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:23:27 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:23:27 -0000 Subject: [GHC] #10009: type inference regression when faking injective type families In-Reply-To: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> References: <045.3dd09f45a408c20b5f0ae041319c4a61@haskell.org> Message-ID: <060.5c6a8c5888604ffb9ab58bdad76d8201@haskell.org> #10009: type inference regression when faking injective type families -------------------------------------+------------------------------------- Reporter: aavogt | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1-rc1 checker) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | typecheck/should_compile/T10009 Blocked By: | Blocking: Related Tickets: #10226, #10634 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => typecheck/should_compile/T10009 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:24:26 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:24:26 -0000 Subject: [GHC] #10226: Regression in constraint solver from 7.8 to 7.10 In-Reply-To: <044.82bc8202e2a2f838b899ceb019365912@haskell.org> References: <044.82bc8202e2a2f838b899ceb019365912@haskell.org> Message-ID: <059.ed07ff5394832a633cc044ec9f046036@haskell.org> #10226: Regression in constraint solver from 7.8 to 7.10 -------------------------------------+------------------------------------- Reporter: edsko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: duplicate | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: indexed- Blocked By: | types/should_compile/T10226 Related Tickets: #10009 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => indexed-types/should_compile/T10226 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:28:09 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:28:09 -0000 Subject: [GHC] #10634: Type class with injective type functions In-Reply-To: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> References: <046.d71414e34b5bda9c37dd4a62236b6422@haskell.org> Message-ID: <061.daaf4fd865cedbab68d3fe62f0e54467@haskell.org> #10634: Type class with injective type functions -------------------------------------+------------------------------------- Reporter: Lemming | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10009 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"02a6b29cc85b2820016fb66ae426dee7ecd36895/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="02a6b29cc85b2820016fb66ae426dee7ecd36895" Test Trac #10634 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:29:45 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:29:45 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.0449f20e2a8e75966e9239140afc9d66@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | simplCore/should_compile/T10627 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): That's great! Do we understand why this worked as recently as June 1st? Also, why would the compiler hang without this fix? Just curious. Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:34:21 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:34:21 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.7e63535bb4977da094c87063a6cdeec4@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | simplCore/should_compile/T10627 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:20 George]: > Do we understand why this worked as recently as June 1st? No, I'm not sure. > Also, why would the compiler hang without this fix? Just curious. It's the knot-tying in `CoreSubst.simplRecBndrs`. Did you read `Note [Substitute lazily]` referred to in the commit message? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 12:45:29 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 12:45:29 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.6f54d87697007219f05c87722bfc47c0@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | simplCore/should_compile/T10627 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by George): Yes, in between posting the comment and reading your reply. :) Thanks for explaining! Sorry to bother you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 16:21:19 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 16:21:19 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.a3dc157ee738f4b6be02f9fa60149a34@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by facundo.dominguez): I'm attaching the eventlog produced with {{{-Ds}}}. It can be uncompressed with: {{{ cat test.eventlog.xz.00 test.eventlog.xz.01 | unxz > test.eventlog }}} Had to split it to comply with the upload limits of trac. It contains an entry produced with {{{ traceEventIO "threadWaitRead: failed with BlockedIndefinitelyOnMVar" }}} At the point where {{{threadedWaitRead}}} fails. I couldn't reproduce the bug with GHC HEAD. I'm using the threaded runtime. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 16:34:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 16:34:48 -0000 Subject: [GHC] #10578: ghci line numbers are off by one In-Reply-To: <047.babcd43e2857d19107b478b8249a9812@haskell.org> References: <047.babcd43e2857d19107b478b8249a9812@haskell.org> Message-ID: <062.daee33ac03769dd3d19b756a246d272e@haskell.org> #10578: ghci line numbers are off by one -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: osa1 Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1067 -------------------------------------+------------------------------------- Changes (by osa1): * owner: => osa1 * differential: => D1067 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 16:54:01 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 16:54:01 -0000 Subject: [GHC] #10578: ghci line numbers are off by one In-Reply-To: <047.babcd43e2857d19107b478b8249a9812@haskell.org> References: <047.babcd43e2857d19107b478b8249a9812@haskell.org> Message-ID: <062.cf6b030c18b7467efe7dd2f7d8ba137f@haskell.org> #10578: ghci line numbers are off by one -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: osa1 Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1067 -------------------------------------+------------------------------------- Comment (by osa1): This bug should be there for a long time. We have at least 34 GHCi tests with wrong location reporting, e.g. test.run.stderr locations are different than test.stderr for those tests. I fixed this bug in my patch and now I'm going over GHCi tests and fixing expected outputs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 19:08:57 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 19:08:57 -0000 Subject: [GHC] #7810: make show VALUE=VAR depends on ghc-stage1 In-Reply-To: <046.882d6e4c467938612df87a18a7ab7d09@haskell.org> References: <046.882d6e4c467938612df87a18a7ab7d09@haskell.org> Message-ID: <061.cdf8e74a4a4988185a07ec408df36c0f@haskell.org> #7810: make show VALUE=VAR depends on ghc-stage1 -------------------------------------+------------------------------------- Reporter: kgardas | Owner: thomie Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1064 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"ec197d390e18a6cfaa420009f5c5f143237f5a9f/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="ec197d390e18a6cfaa420009f5c5f143237f5a9f" Build system: add `make show!` command (#7810) A normal `make show` starts a build of the ghc-stage1 compiler, to create package-data.mk files. This version doesn't read those, so it will work right after ./configure. Differential Revision: https://phabricator.haskell.org/D1064 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 19:10:07 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 19:10:07 -0000 Subject: [GHC] #7810: make show VALUE=VAR depends on ghc-stage1 In-Reply-To: <046.882d6e4c467938612df87a18a7ab7d09@haskell.org> References: <046.882d6e4c467938612df87a18a7ab7d09@haskell.org> Message-ID: <061.57e14c03b9cf1f33f47d0ffa6326d8af@haskell.org> #7810: make show VALUE=VAR depends on ghc-stage1 -------------------------------------+------------------------------------- Reporter: kgardas | Owner: thomie Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1064 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: I added documentation to [wiki:Building/Modifying] as well as to `make help`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 21:21:11 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 21:21:11 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.f3088742299d677d19d14475188c751a@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): '''-Ds''' should output scheduling log to stderr (might require '''-debug''' link option as well). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 13 21:56:08 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 13 Jul 2015 21:56:08 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.26f27c55305dcace6f964785f9295f3d@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Indeed. But I redirected it to the eventlog with {{{-l}}} as it is suggested to reduce the overhead of tracing. If the stderr output is needed instead, let me know and I'll try it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 03:18:37 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 03:18: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.5f1dc5fdb986ba6d14e4d52b144744bb@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * cc: jpm@? (added) Comment: I'm less worried about implementing the correct behavior than figuring out what the correct behavior should be. You're saying that `DeriveAnyClass` should never fail... but is that different from what 7.10.1 actually does? I think issuing a warning in this case is a great step. But I'd still love to see a specification (preferably in the user manual) of how all this works. In any case, submitting a patch for review via Phab is never the wrong thing to do. (And, of course, thanks for writing the patch!) I'm cc'ing Pedro, who (if memory serves) wrote this feature. (Full disclosure: I was involved in the design of `DeriveAnyClass`, and I'm sure that at some point in history, I knew the answers to the questions I'm asking. But it's all lost now, and I'm hoping Pedro can fill in the details.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 05:58:07 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 05:58:07 -0000 Subject: [GHC] #10068: Make the runtime reflection API for names, modules, locations more systematic In-Reply-To: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> References: <046.e24e266e9d617fc4224d115c2a203db8@haskell.org> Message-ID: <061.27a05ba3ae0348c05b95518b56e1e5bd@haskell.org> #10068: Make the runtime reflection API for names, modules, locations more systematic -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): I'm afraid I don't have a lot of free cycles at the moment, I just happened to notice the extra representation while working on https://phabricator.haskell.org/D861. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 06:27:03 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 06:27:03 -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.2abd2b98f7b6578d6e8b26b5cf424c8b@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kosmikus): Ok, here's my take on this. The behaviour is clearly inconsistent. Let's compare ghc-7.8.4 and ghc-7.10.1. There are three flags that play a role here, namely `GeneralizedNewtypeDeriving` (GND), `DeriveFunctor` (DF), and `DeriveAnyClass` (DAC). The DAC flag ist not supported by ghc-7.8.4. We have the following results: || || ghc-7.8.4 || ghc-7.10.1 || || no flags || error (GND) || error (GND) || || GND || ok (GND) || ok (GND) || || DF || ok (DF) || ok (DF) || || GND + DF || ok (GND) || ok (GND) || || DAC || unsupported || error (GND) || || DAC + GND || unsupported || error (GND') || || DAC + DF || unsupported || ok (DF) || || DAC + GND + DF || unsupported || warning (??) || So the good news is that without the use of DAC, both GHC versions behave the same. However, in the presence of DAC, several things go wrong. In the DAC case, an error is reported suggesting the use of GND instead. That's strange, because doing the same thing for a user-defined `MyFunctor` class will actually happily work. I know we've had a long discussion about the conditions for using DAC in the past. In principle, I'd like it if it wouldn't work on "any" class, but instead would require the presence of defaults. It doesn't make much sense to derive partial class definitions with missing methods. I'm not entirely sure what the reason may have been to lift this restriction. The DAC + GND case is probably the worst. We get a completely unhelpful error message, saying that GND doesn't work yet suggesting to enable GND. Also, it's a case where the mere presence of DAC makes things break all of a sudden, because removing DAC will happily make GHC use GND and succeed. In the DAC + DF, we silently prefer the built-in functor deriving, which at least in this case seems useful, because DAC for the built-in functor would yield a partial class definition. The DAC + GND + DF case yields a warning that indicates that both DAC and GND are available to derive the `Functor` instance, and that it is defaulting to DAC! Yet it then seems to use DF to derive the actual `Functor` instance. So again, the outcome isn't too bad, but the warning is clearly misleading. What to do about all this? I think there are the following issues: * Should `DAC` work only if defaults are present for all methods, or should it work also in other situations? I cannot think of a good reason not to require defaults for all methods right now? * I think that if, given by the flags and imposed restrictions, only one of the three deriving methods is available, that one should clearly be taken. * If several deriving methods are available, we might still choose one. I think the natural thing is to choose built-in deriving before GND before DAC. In all such cases, it should probably produce a warning. * I very much like Richard's idea to allow PRAGMAs to explicitly indicate the desired deriving method in a deriving clause. This would be both a way to change default behaviour used by GHC and to remove warnings, because you'd explicitly document intent. * If no deriving method is available but a deriving clause is used, we should suggest both GND or DAC as options, but only if they're actually available. It's entirely possible that I've overlooked important cases. Suggestions welcome. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 07:48:17 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 07:48: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.aa31bcc44049e0d8e7863a8357c72b8e@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Your list sounds plausible to me, Andres. Re "I cannot think of a good reason not to require defaults for all methods right now?", I agree, but I assume you mean "either a generic default method or a polymorphic default method is provided". Remember there are those two forms of default method. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 08:22:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 08:22:59 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.f53329d7fc9a8d3f75aec6bf6918d569@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): stderr is preferred as it shows MVar addresses and thread states on each GC cycle (I wonder if it's a logging bug or feature): {{{ all threads: threads on capability 0: other threads: thread 4 @ 0x7f526d10b388 is blocked on an MVar @ 0x7f526d10aa50 (TSO_DIRTY) thread 3 @ 0x7f526d105d20 ["TimerManager"] is blocked on an external call (TSO_DIRTY) thread 2 @ 0x7f526d1058f0 ["IOManager on cap 0"] is blocked on an external call (TSO_DIRTY) }}} I hope to see file descriptor ID/MVar history for thread killed by BlockedIndefinitelyOnMVar. Human readable thread names are set with '''labelThread'''. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 08:24:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 08:24:51 -0000 Subject: [GHC] #8919: Why is xhtml library installed but not exported to users? In-Reply-To: <045.ff43846276358ed8eb8ece32c648e51e@haskell.org> References: <045.ff43846276358ed8eb8ece32c648e51e@haskell.org> Message-ID: <060.424fb6d6b306448cea53f775bad85241@haskell.org> #8919: Why is xhtml library installed but not exported to users? -------------------------------------+--------------------------------- Reporter: simons | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.8.3 Component: Build System | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------+--------------------------------- Comment (by Thomas Miedema ): In [changeset:"47ebe267e8f78eee68333ba12a83d4fa6d763c3b/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="47ebe267e8f78eee68333ba12a83d4fa6d763c3b" Build system: delete REGULAR_INSTALL_DYNLIBS and INSTALL_DYNLIBS Ever since we ship xhtml, terminfo and haskeline (#8919), commit 4caadb7cbee5c176abb99df25c4cc1657ae57f40, REGULAR_INSTALL_DYNLIBS is always empty. REGULAR_INSTALL_PACKAGES = PACKAGES_STAGE1 + compiler + PACKAGES_STAGE2 REGULAR_INSTALL_DYNLIBS = PACKAGES_STAGE1 + PACKAGES_STAGE2 - REGULAR_INSTALL_PACKAGES So we can delete it, and all the places where it is used. This simplifies ghc.mk a bit. Differential Revision: https://phabricator.haskell.org/D1062 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 08:42:53 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 08:42:53 -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.2fe525348fdadd89e820af4bd7bc02ae@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kosmikus): Yes, I think it makes sense to require at least any sort of default definition for all class methods, regardless of whether it is a normal default or a generic default. It might also be sensible to take MINIMAL pragmas into account. If an explicit non-empty MINIMAL pragma is specified, then I think the intent of the author is to say that it doesn't make sense to give an empty class instance, and similarly, it would then also not make sense to derive it. But I'm open to suggestions. Even if we allow DeriveAnyClass for classes that have e.g. mutually recursive defaults and a non-empty MINIMAL pragma, I guess we'd at least still get a warning reported for the derived instance. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 08:53:35 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 08:53:35 -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.5b9bdec67776195dffeccd999dbae244@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Usually the MINIMAL thing means "you must give non-default definitions for at least these methods". That's easy to understand in the absence of generic-default methods, because the normal (or polymorphic) default methods invariably work by invoking other methods in the same class or superclass. But given generic-default methods, it's not so clear to me. I suspect that MINIMAL should ''not'' complain if you fail to give explicit code for a method that has a generic default, because the generic default is capable of doing type-specific stuff. (I have not checked what really happens.) The manual entry for MINIMAL does not cover this, and it jolly well should. Once that is nailed down, it'll become clear what to do for `DeriveAnyClass`, I think. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 10:49:19 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 10:49:19 -0000 Subject: [GHC] #8131: T7571 with WAY=llvm fails, but not WAY=optllvm In-Reply-To: <052.22eb4f882263987206e929bacae5db28@haskell.org> References: <052.22eb4f882263987206e929bacae5db28@haskell.org> Message-ID: <067.9912a75884985a52d1ec049b0881bc64@haskell.org> #8131: T7571 with WAY=llvm fails, but not WAY=optllvm -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | llvm/should_compile/T8131 | Blocking: | Differential Revisions: Phab:D624 -------------------------------------+------------------------------------- Changes (by thomie): * owner: rwbarton => * resolution: fixed => * status: closed => new * os: Unknown/Multiple => Windows Comment: This test is failing hard on Windows. {{{ +ghc: panic! (the 'impossible' happened) + (GHC version 7.11.20150713 for x86_64-unknown-mingw32): + <> + +Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug \ No newline at end of file *** unexpected failure for T8131(normal) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 10:59:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 10:59:47 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.8d51bda0bfcba883036e94d3722da178@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => plugins/T10294 Comment: The test `plugins/T10294` is failing on Windows with the same error as above: {{{ ghc-stage2.exe: panic! (the 'impossible' happened) (GHC version 7.11.20150713 for x86_64-unknown-mingw32): Static flags have not been initialised! Please call GHC.parseStaticFlags early enough. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 11:03:10 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 11:03:10 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.d6f434822d7f80bc07615a627456e173@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10596 Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by thomie): * status: merge => new * testcase: => th/T10596 Comment: This test is failing on Windows, and also on Travis (https://s3.amazonaws.com/archive.travis-ci.org/jobs/70789702/log.txt). {{{ Actual stderr output differs from expected: --- ./th/T10596.stderr.normalised 2015-07-13 19:47:37.667428464 +0000 +++ ./th/T10596.comp.stderr.normalised 2015-07-13 19:47:37.667428464 +0000 @@ -1 +0,0 @@ -Just 100 \ No newline at end of file *** unexpected failure for T10596(normal) }}} Note that Windows and Travis don't build dynamic libraries. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 11:22:07 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 11:22:07 -0000 Subject: [GHC] #10636: Clear up difference between `WayDyn` and `Opt_Static` Message-ID: <045.a1abb18f844e8c03a0e9193959190437@haskell.org> #10636: Clear up difference between `WayDyn` and `Opt_Static` -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- There are currently 2 different ways to test for a static or dynamic build: 1. Test if `WayDyn` is in `ways` 2. Test if `Opt_Static` is set Unless there's a use-case for setting `WayDyn`/`Opt_Static` inconsistently (if so, please add a `Note` somewhere), it should be possible to replace all queries of `Opt_Static` with an equivalent query of `WayDyn`. That would have prevented bug #8294. See the comments in Phab:D1017. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 11:31:06 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 11:31:06 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.112d9b325947ec1ce7b74cc6bed1a88e@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Also on travis. Shall we mark the test case as known_broken on this bug? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 15:26:30 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 15:26:30 -0000 Subject: [GHC] #10001: GHC crash trying to build a project within Nix-shell In-Reply-To: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> References: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> Message-ID: <062.592b6ffef745c0ab2414203f502614c7@haskell.org> #10001: GHC crash trying to build a project within Nix-shell -------------------------------------+------------------------------------- Reporter: wolftune | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: 9825 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by siddhanathan): This example does fail outside a Nix-shell. I just had the same issue with GHC 7.10.1 Reproducing should be simple. Just install the nix package manager ([http://nixos.org/nix/]), copy the files in the gist to a new folder, run `nix-shell` in the folder, and then `cabal sandbox init && cabal install`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 16:28:26 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 16:28:26 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.019500ead6c97806f33299df629cd8d4@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by facundo.dominguez): I failed to reproduce the bug without redirecting with {{{-l}}}. I updated the attached eventlog and also the stderr output I get. Hopefully, they both sum up all the interesting information. Let me know if the split eventlog/stderr is still unhelpful. I'm using {{{labelThread tid "handleIncomingMessages"}}} to mark the dying thread. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 17:00:44 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 17:00:44 -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.fabbe34178831a615b01a427ca277288@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): Sorry if this is a digression, but DAC just doesn't make sense to me. I think the only place it's mentioned in the user manual is here: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/deriving.html and it's just saying "With -XDeriveAnyClass you can derive any other class. The compiler will simply generate an empty instance." What I found confusing is: 1. It says "derive any other class", which to me means that GHC first tries other mechanisms to derive implementations, and uses DAC as a last resort, because of the word "other". E.g. if we have DF and DAC and we're trying to derive Functor, DF should always be used. If we're trying to derive something that's not supported by any other enabled extension, we should try DAC. 2. It says "the compiler will simply generate an empty instance". This works for all typeclasses, so in a sense this is most general deriving mechanism. So to me it seems like this should be tried last, not first, when we have multiple deriving mechanisms that we can use for a particular `deriving (..)` statement. E.g. it should start with most specific deriving mechanism and move to more general ones as they fail. --- @simonpj, > Once that is nailed down, it'll become clear what to do for DeriveAnyClass, I think. If I understand correctly, you mean we should do something like this: 1. Update semantics of MINIMAL to make generic implementations counted. 2. Modify DAC to make working iff all MINIMALs have definitions. 3. Also fix problems with docs and warnings on the way. Does that sound right? Also, it seems like DeriveAnyClass is broken in some other ways(#9821, #9968). Maybe I can fix those on the way. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 17:29:02 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 17:29:02 -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.c67fbd7326342ab72e58d92d781060e4@haskell.org> #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. -------------------------------------+------------------------------------- Reporter: jpbernardy | Owner: osa1 Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | newcomer Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D978 -------------------------------------+------------------------------------- Comment (by osa1): How should we proceed about this? Like @rwbarton mentioned in #10577, none of these is a part of the standard, so I think we can change behavior of standalone deriving to introduce an empty case, and then also change EmptyDataDecls deriving to make the behavior consistent. Should we move this discussion to the mailing list for feedbacks? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 17:34:45 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 17:34:45 -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.cc1f3705aa25bfe60633cd66856f4788@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by dreixel): Note that we initially thought of taking MINIMAL pragmas into account for DAC, but eventually decided against that. More background here: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#Usingstandardderivingforgenericfunctions -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 17:48:46 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 17:48:46 -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.d0e5b636e43954d15cc04db61fcd47a8@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): I can't see anything about why MINIMALs are not taken into account in that link, where can I learn about this? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 19:39:07 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 19:39:07 -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.160b4097f3e96df5eda4c09c41c83b9c@haskell.org> #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. -------------------------------------+------------------------------------- Reporter: jpbernardy | Owner: osa1 Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | newcomer Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D978 -------------------------------------+------------------------------------- Comment (by simonpj): This ticket has a long thread, which is discouraging for anyone approaching it for the first time. My suggestion: write a wiki page proposing a particular design. Advertise it on the Haskell and libraries mailing list (this is practically a core- libraries committee issue). Drive the discussion to a consensus. Implement it. It's very much a corner case so what we really need is a well documented decision rather than a long debate. It just that it's hard to see the wood for the trees now. Thanks! Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 19:54:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 19:54:51 -0000 Subject: =?utf-8?q?=5BGHC=5D_=2310637=3A_Cannot_suppress_=22Warning=3A_?= =?utf-8?q?=7B-=23_SOURCE_=23-=7D_unnecessary_in_import_of__?= =?utf-8?b?4oCYQeKAmSI=?= Message-ID: <046.5119908e23481708e117e58b6fa1ab97@haskell.org> #10637: Cannot suppress "Warning: {-# SOURCE #-} unnecessary in import of ?A?" -----------------------------------------+--------------------------------- Reporter: phischu | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -----------------------------------------+--------------------------------- Consider the following three files: {{{#!hs -- A.hs module A where }}} {{{#!hs -- A.hs-boot module A where }}} {{{#!hs -- B.hs module B where import {-# SOURCE #-} A }}} When compiling these three files GHC emits a warning and rightly so: {{{ >ghc B.hs B.hs:3:23: Warning: {-# SOURCE #-} unnecessary in import of ?A? [1 of 3] Compiling A[boot] ( A.hs-boot, A.o-boot ) [2 of 3] Compiling A ( A.hs, A.o ) [3 of 3] Compiling B ( B.hs, B.o ) }}} When on the other hand compiling with `-w` I expect the warning to go away but it doesn't. {{{ >ghc -w B.hs B.hs:3:23: Warning: {-# SOURCE #-} unnecessary in import of ?A? [1 of 3] Compiling A[boot] ( A.hs-boot, A.o-boot ) [2 of 3] Compiling A ( A.hs, A.o ) [3 of 3] Compiling B ( B.hs, B.o ) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 20:40:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 20:40:25 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken Message-ID: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- In GHC 7.10.1, Template Haskell support was added for all calling conventions. Unfortunately a few cases are unhandled, which makes the TH code treat the `prim` and `javascript` calling conventions as if they were C calling conventions, adding the `static` keyword and running them through `parseCImport`. This is particularly bad for `javascript` imports, since most JS imports aren't valid C imports, so they get rejected. I'm testing a fix for this that I'll submit later today. I hope this is in time for 7.10.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 20:48:27 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 20:48:27 -0000 Subject: [GHC] #10639: Optimization changes concurrent program's behaviour Message-ID: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> #10639: Optimization changes concurrent program's behaviour -------------------------------------+------------------------------------- Reporter: gizmo.mk0 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Windows Architecture: x86_64 | Type of failure: Incorrect result (amd64) | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Here is a program that spawns a thread from the main thread, which tries to constantly write out a message to the console. {{{#!hs module Main where import Control.Concurrent (forkIO) main :: IO () main = do _ <- forkIO $ runForever $ putStrLn "Hey" runForever $ return () runForever :: IO () -> IO () runForever action = action >> runForever action }}} If you compile it with 'ghc main', it works correctly - it prints out the message continuously, and you can terminate it by pressing Ctrl-C. However, if you compile it with 'ghc -O main' (or -O2, or -O3...), it doesn't print out anything, and the only way to exit is to kill the process from Task Manager. This was reproducable with GHC 7.10.1, on a Windows 7 x64 machine, with an AMD A4-5300 APU. ''(Disclaimer: this is my first bugreport, and I'm not sure what else can I do to investigate this issue.)'' -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 14 22:06:04 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 14 Jul 2015 22:06:04 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.fe6efa6172fbb92464a1a660112fa36d@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Changes (by luite): * differential: => Phab:D1070 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 05:21:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 05:21:34 -0000 Subject: [GHC] #10639: Optimization changes concurrent program's behaviour In-Reply-To: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> References: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> Message-ID: <063.baddf2aab774f5a7201bcd38081b0830@haskell.org> #10639: Optimization changes concurrent program's behaviour -------------------------------------+------------------------------------- Reporter: gizmo.mk0 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by gizmo.mk0: Old description: > Here is a program that spawns a thread from the main thread, which tries > to constantly write out a message to the console. > > {{{#!hs > module Main where > > import Control.Concurrent (forkIO) > > main :: IO () > main = do > _ <- forkIO $ runForever $ putStrLn "Hey" > runForever $ return () > > runForever :: IO () -> IO () > runForever action = action >> runForever action > }}} > > If you compile it with 'ghc main', it works correctly - it prints out the > message continuously, and you can terminate it by pressing Ctrl-C. > However, if you compile it with 'ghc -O main' (or -O2, or -O3...), it > doesn't print out anything, and the only way to exit is to kill the > process from Task Manager. > > This was reproducable with GHC 7.10.1, on a Windows 7 x64 machine, with > an AMD A4-5300 APU. > > ''(Disclaimer: this is my first bugreport, and I'm not sure what else can > I do to investigate this issue.)'' New description: Here is a program that spawns a thread from the main thread, which tries to constantly write out a message to the console. {{{#!hs module Main where import Control.Concurrent (forkIO) main :: IO () main = do _ <- forkIO $ runForever $ putStrLn "Hey" runForever $ return () runForever :: IO () -> IO () runForever action = action >> runForever action }}} If you compile it with 'ghc main', it works correctly - it prints out the message continuously, and you can terminate it by pressing Ctrl-C. However, if you compile it with 'ghc -O main' (or -O2, or -O3...), it doesn't print out anything, and the only way to exit is to kill the process from Task Manager. This was reproducable with GHC 7.10.1, on a Windows 7 x64 machine, with an AMD A4-5300 APU. ''EDIT: As it turns out, using "yield" instead of "return ()" solves the problem. It seems I misunderstood how forkIO works. However, I'm not sure if the current working is intentional or not, so I think I should leave this ticket open - just to be on the safe side.'' -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 05:23:15 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 05:23:15 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.dadf7b08a6c6fe049a71a5e968035923@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Changes (by hvr): * priority: normal => highest -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 05:23:38 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 05:23:38 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.ebc93811069b74a6751bf9d6343d323c@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: patch Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Changes (by hvr): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 06:41:41 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 06:41:41 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.cc57d86dc72ca413443944da3c91d3a3@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by trommler): Replying to [comment:6 rwbarton]: > We should probably just go ahead with that fix anyways since this breakage is rather severe. Let's keep this ticket open after doing so though, to see whether it causes any issues like #8935 and perhaps take a moment to see if we can find a simpler way to handle this whole situation. The issue in #8935 was that we did not search the global context (the executable) first when resolving a symbol. The issue were certain relocations used for global variables (the process environment in the case of #8935). To solve the issue here we have two options: 1. Load C libraries with RTLD_GLOBAL, the symbols cannot be overridden by Haskell code. Is there a reasonable use case where we would override the definition of a symbol in a C library during one run of GHCi? 1. Append all `-lfoo` to every link command of a temporary shared library. If a symbol is defined in a library mentioned earlier in the link command it will override the symbol in `libfoo`. The second option is probably easier to implement whereas the performance of the first option will most likely be better (fewer libraries to open and fewer symbols to look at). I would say we go for option two for now and create a new ticket for a complete redesign of dynamic linking for 7.12. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:05:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:05:32 -0000 Subject: [GHC] #10640: Document prim-ops Message-ID: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> #10640: Document prim-ops -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Currently documentation is quite scarce for many primops (particularly the BCO operations). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:07:28 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:07:28 -0000 Subject: [GHC] #9439: LlvmCodegen: Overzealous mangler incorrectly transforms user code In-Reply-To: <046.9a4e1bc549a42d7dea911589e68836d0@haskell.org> References: <046.9a4e1bc549a42d7dea911589e68836d0@haskell.org> Message-ID: <061.20a5c2bab3949de1d874b4154f3b26e7@haskell.org> #9439: LlvmCodegen: Overzealous mangler incorrectly transforms user code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.8.4 Component: Compiler (LLVM) | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: 9268 | Differential Revisions: Phab:D150 -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: 7.8 is quite old and this is fixed in 7.10. Closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:11:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:11:34 -0000 Subject: [GHC] #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 In-Reply-To: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> References: <044.0d20d012b4759c978b1b34e772ddf019@haskell.org> Message-ID: <059.2f65a6d4277b5d059e2aca61baadca4c@haskell.org> #10602: ghc panic: Template variable unbound in rewrite rule when compiling with -O2 -------------------------------------+------------------------------------- Reporter: pacak | Owner: bgamari Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | simplCore/should_compile/T10602 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-7.10` in 3cadf440c490abc1c8d5d45f5d034809c8912815. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:26:56 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:26:56 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.1aded5c96e011736c9b10250765b3056@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): BTW, this could be due to `DYNAMIC_GHC_PROGRAMS = NO`, couldn?t it? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:27:06 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:27:06 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.53ec72393e76b73698fad1075534a79b@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"4ee658a02ccc6d3aa0b6a0a5f2f5934a593f1356/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="4ee658a02ccc6d3aa0b6a0a5f2f5934a593f1356" Mark test case for #10294 expect_broken on #10301 as it is broken on Travis, and in #10301 others have reported the same error. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:27:06 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:27:06 -0000 Subject: [GHC] #10294: Missing instances if compiling with -fplugin In-Reply-To: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> References: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> Message-ID: <061.ffcfdeb00db333b339fe438415f8aa48@haskell.org> #10294: Missing instances if compiling with -fplugin -------------------------------------+------------------------------------- Reporter: jscholl | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: duplicate | Architecture: x86_64 Operating System: Linux | (amd64) Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: 10420 | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"4ee658a02ccc6d3aa0b6a0a5f2f5934a593f1356/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="4ee658a02ccc6d3aa0b6a0a5f2f5934a593f1356" Mark test case for #10294 expect_broken on #10301 as it is broken on Travis, and in #10301 others have reported the same error. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:29:06 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:29:06 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.25e04d0419838cec983c0bda8d3ac51d@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10596 Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"0a402785c9c5ab4be9487518790d24af9d211a8b/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="0a402785c9c5ab4be9487518790d24af9d211a8b" Flush stdout in test case for #10596 which might help, as it has helped with lots of other TH-related test cases in the past. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:35:18 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:35:18 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.737ef16849acb6057daf8a4a2f53b9fe@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Replying to [comment:10 nomeata]: > Also on travis. Shall we mark the test case as known_broken on this bug? Well, then Phabricator's build will fail. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:41:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:41:32 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.3197d180f6702cbaba747f7f89af5317@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"8e6a50339a4a61d4f2cbec645c78abc85098a294/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="8e6a50339a4a61d4f2cbec645c78abc85098a294" Mark test case for #10294 conditionally expect_broken on #10301 the hypothesis is that it only breaks with `DYNAMIC_GHC_PROGRAMS = NO`, so use `unless(have_dynamic(),expect_broken(10301))` to not break the Phabricator build. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:41:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:41:32 -0000 Subject: [GHC] #10294: Missing instances if compiling with -fplugin In-Reply-To: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> References: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> Message-ID: <061.19993c2ca9f6b138a02144065aef1ab3@haskell.org> #10294: Missing instances if compiling with -fplugin -------------------------------------+------------------------------------- Reporter: jscholl | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: duplicate | Architecture: x86_64 Operating System: Linux | (amd64) Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: 10420 | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"8e6a50339a4a61d4f2cbec645c78abc85098a294/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="8e6a50339a4a61d4f2cbec645c78abc85098a294" Mark test case for #10294 conditionally expect_broken on #10301 the hypothesis is that it only breaks with `DYNAMIC_GHC_PROGRAMS = NO`, so use `unless(have_dynamic(),expect_broken(10301))` to not break the Phabricator build. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:43:19 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:43:19 -0000 Subject: [GHC] #10639: Optimization changes concurrent program's behaviour In-Reply-To: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> References: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> Message-ID: <063.089a9f0422bf04fdb03e72775ffe3464@haskell.org> #10639: Optimization changes concurrent program's behaviour -------------------------------------+------------------------------------- Reporter: gizmo.mk0 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by slyfox): * cc: slyfox (added) Comment: It's a result of cooperative multitasking in ghc: Trac #367 In short: non-allocating threads can starve other threads, can be worked- around by -fno-omit-yields -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 08:44:24 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 08:44:24 -0000 Subject: [GHC] #10639: Tight (non-allocating) loop freezes the scheduler (was: Optimization changes concurrent program's behaviour) In-Reply-To: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> References: <048.3130b8c9dae40d4cc95f52d78c185152@haskell.org> Message-ID: <063.45d59dbe7240cf4bea61d8507cccfdb4@haskell.org> #10639: Tight (non-allocating) loop freezes the scheduler -------------------------------------+------------------------------------- Reporter: gizmo.mk0 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 Type of failure: Incorrect result | (amd64) at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: slyfox (removed) Comment: My guess is this. With optimisation the `runForever (return ())` turns into a tight loop that does not allocate. Once that loop gets control of the CPU, it never gives it up. Without optimisation, the loop does allocation. This is really a long-standing bug, just a rather rare one. Usually we check whether a thread's time quantum has expired when checking for heap- allocation overflow. If there is no allocation we don't check. I'm pretty sure this is it, so I'll change the title of the ticket. It should be documented though. Would someone feel able to add a bullet to the [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/bugs.html bugs section] of the user manual? Fixing it properly is tricky, because we don't want to add zillions of checks, and identifying all the risky points is hard. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 09:34:42 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 09:34:42 -0000 Subject: [GHC] #9049: Expose srcLoc from the assertion architecture to allow better error messages In-Reply-To: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> References: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> Message-ID: <057.87cb025475fc11fabb18a9ffd3360492@haskell.org> #9049: Expose srcLoc from the assertion architecture to allow better error messages -------------------------------------+------------------------------------- Reporter: nh2 | Owner: gridaphobe Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D578 -------------------------------------+------------------------------------- Comment (by bgamari): This has been merged to `ghc-7.10` as e3dc28046373f3183dda56b096dbebec865e3be7. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 10:30:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 10:30:03 -0000 Subject: [GHC] #10641: Gekonnt abnehmen mit Calriphen und Petoximol Message-ID: <051.5c2fdd8536acfc13ca82b33e2915197a@haskell.org> #10641: Gekonnt abnehmen mit Calriphen und Petoximol -------------------------------------+------------------------------------- Reporter: | Owner: luisagombach | Status: new Type: bug | Milestone: Priority: lowest | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Calriphen und Petoximol Calriphen und Petoximol sind meisterhafte Fett-Killer und heute die erfolgsversprechendsten Di?tpillen, die es zu finden gibt. Mit der Di?t k?nnen Anwender in 5 bis 12 Wochen bis zu 16 Kilo Fett weg bekommen, ohne zus?tzlich ?berhaupt Sport zu treiben. Das sehr ?berzeugende Konzept konnte bis jetzt viele Menschen davon ?berzeugen, bei einer Di?tmethode in erster Linie auf [http://abnehmen-mit.com/calriphen-phenoxin/ Calriphen] und Petoximol zur?ckzukommen. Auch in den Medien ist das neue Konzept hoch frequentiert, denn das Konzept ?berschwemmt den kompletten Gesundheitsbereich. Die interessante Wirkformel bezieht sich auf viele hoch wirksame Pflanzenstoffe, die in Calriphen und Petoximol vereint eine bisher ungesehene Wirkweise entfalten. Somit ist es kein Wunder, dass diese Di?tpillen bei den Anwendern so prima anschlagen. Auch wir konnten festellen, dass diese Di?tpillen vor allem kombiniert die Pfunde so richtig purzeln lassen. Petoximol und Calriphen Erfahrung Durch Nutzerrezensionen kriegt man ein realistisches und durchweg gute Eindr?cke von Calriphen und Petoximol. Viele Personen konnten ihre l?stigen Kilos loswerden und die Wunschvorstellungen zu dem Gewicht enorm maximieren. Noch dazu wird erz?hlt, dass die Di?t auch die Gem?tsverfassung optimiert und die Stimmung hebt. Auch die Nahrungsumwandlung soll sich mit den Di?tpillen wesentlich verbessern. Beinahe ausschlie?lich alle Interessenten hatten ?ber Werbung im WWW und Fernsehen von diesen Di?tmitteln erfahren, viele sind auf Internetseiten darauf gesto?en und einge haben davon ?ber die Bekannte erfahren, dass die Produktkombination ein gutes Ergebnis hervorbringt. Berichte bezeugen, dass Menschen in nur wenigen Wochen mehr als 18 Kilo K?rperfett verlieren konnten ? Ergebnisse, welche f?r sich sprechen. Dabei ist die Anwendung gesund und den K?rper schonend, aber dennoch ?beraus effektiv. Petoximol und Calriphen Inhaltsstoffe Die Di?tpillen bekommen erst mit ihrer Zusammensetzung eine solch starke Wirkung. Dabei blockiert die Stoffkombination die Fett-Synthese, beschleunigt die Fettumwandlung und sch?tzt den K?rper vor sch?dlichen Stoffen. Au?erdem modulieren die Produkte den Verdauungsapparat zum Positiven und dies hilft zus?tzlich, eine Gewichtsabnahme voranzutreiben. Haupts?chlich die Goji-Beere und Riboflavin sind die wirkungsvollen Stoffe der Produkte. Sie beschleunigen die Fettreduktion und geben unserem Stoffwechsel das Zeichen, abzunehmen. Dadurch ist die sichere Gewichtsreduktion gewiss. Petoximol und Calriphen Test In unserem exklusiven Test wirkten die Di?tpillen au?erordentlich gut. Die Testerin schaffte es, 20 Kilo in gerade einmal 5 Wochen loszuwerden. Keine anderen Di?tpillen schaffen solche Ergebnisse. In ihrer Di?tphase nahm unsere Testerin ?ber den geschilderten Zeitraum immer morgens und abends Calriphen und Petoximol und konnte schon nach einigen Tagen positive Ver?nderungen feststellen. Dabei war die anf?ngliche Zielsetzung, in 7 Wochen bis zu 18 kg abzunehmen. Dieses Ziel wurde sogar weit ?bertroffen. Petoximol und Calriphen kaufen Wir k?nnen best?tigen, dass es am g?nstigsten ist, wenn man Calriphen und Petoximol direkt ?ber den Fabrikant kauft. Im WWW bietet der Hersteller die Pillen auf seiner Webseite an. Da kann man auch ab und zu die Pillen mit einem Rabatt bestellen. So sind die Di?tpillen bis zu 40 % g?nstiger als wenn man sie zum Ladenpreis erwirbt. Eine tolle Einzigartigkeit ist die Petoximol und Calriphen Geld-zur?ck-Garantie, welche verlangt werden kann, wenn man mit den Di?tmitteln nicht klar kommt. [http://abnehmen- mit.com/] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 11:30:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 11:30:25 -0000 Subject: [GHC] #10301: Plugins/dynamic loading subtly broken (it seems) In-Reply-To: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> References: <052.1efd9612b96733295747c4ea13bc0951@haskell.org> Message-ID: <067.afa6bda3b52753d0d9b5f8322528c904@haskell.org> #10301: Plugins/dynamic loading subtly broken (it seems) -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | plugins/T10294 Related Tickets: #8276 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"b1063b1b64989749292d156b189eb64a73fb329a/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="b1063b1b64989749292d156b189eb64a73fb329a" Testsuite: mark T10294 conditionally expect_broken on #10301 Fix 8e6a50339a4a61d4f2cbec645c78abc85098a294. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 12:27:42 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 12:27:42 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD Message-ID: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This started out with code that compiled on 7.10, but fails on HEAD (20150711): {{{ {-# LANGUAGE TypeFamilies, StandaloneDeriving, UndecidableInstances #-} module StandaloneDeriving where type family F a newtype D a = D (F a) -- | This works on 7.10.1 and HEAD (20150711) deriving instance Eq (F a) => Eq (D a) -- | This works on 7.10.1, but fails on HEAD (20150711) deriving instance Bounded (F a) => Bounded (D a) }}} which fails on HEAD with: {{{ GHCi, version 7.11.20150711: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling StandaloneDeriving ( StandaloneDeriving.hs, interpreted ) StandaloneDeriving.hs:12:1: error: Couldn't match representation of type ?a0? with that of ?F a? arising from a use of ?coerce? Relevant bindings include minBound :: D a (bound at StandaloneDeriving.hs:12:1) In the expression: coerce (minBound :: F a) :: D a In an equation for ?minBound?: minBound = coerce (minBound :: F a) :: D a When typechecking the code for ?minBound? in a derived instance for ?Bounded (D a)?: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ?Bounded (D a)? StandaloneDeriving.hs:12:1: error: Couldn't match representation of type ?a1? with that of ?F a? arising from a use of ?coerce? Relevant bindings include maxBound :: D a (bound at StandaloneDeriving.hs:12:1) In the expression: coerce (maxBound :: F a) :: D a In an equation for ?maxBound?: maxBound = coerce (maxBound :: F a) :: D a When typechecking the code for ?maxBound? in a derived instance for ?Bounded (D a)?: To see the code I am typechecking, use -ddump-deriv In the instance declaration for ?Bounded (D a)? Failed, modules loaded: none. }}} Which I managed to reduce to: {{{ {-# LANGUAGE TypeFamilies, FlexibleContexts #-} module CoerceFail where import Data.Coerce type family F a newtype D a = D (F a) -- | This works on 7.10.1, but fails on HEAD (20150711) coerceD :: Coercible (F a) (D a) => F a -> D a coerceD = coerce }}} Which also works on 7.10.1 but fails on HEAD with: {{{ GHCi, version 7.11.20150711: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling CoerceFail ( CoerceFail.hs, interpreted ) CoerceFail.hs:12:11: error: Couldn't match representation of type ?a0? with that of ?F a? arising from a use of ?coerce? Relevant bindings include coerceD :: F a -> D a (bound at CoerceFail.hs:12:1) In the expression: coerce In an equation for ?coerceD?: coerceD = coerce }}} I don't know if this was never supposed to work, and the behaviour on HEAD is correct, or, if this is truly a regression from 7.10 to HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 12:37:27 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 12:37:27 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.29d5ce09b615e22630579a720e4bc42d@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by darchon): The example can be even further simplified to: {{{ {-# LANGUAGE TypeFamilies #-} module CoerceFail where import Data.Coerce type family F a newtype D a = D (F a) -- | This works on 7.10.1, but fails on HEAD (20150711) coerceD :: F a -> D a coerceD = coerce }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 13:04:45 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 13:04:45 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder Message-ID: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: subfolder | Operating System: Unknown/Multiple import submodule cd | Type of failure: GHC rejects Architecture: | valid program Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I'm taking a huge risk in looking like an idiot, but it's worth trying to attack the elephant in the room. The first response I expect is ''"This is expected behaviour!"''. This is what intuition says, but I disagree. It's a simple problem and the fix should be easy, unless there's some advanced import mechanism that would conflict with the solution that I don't know about. That is exactly where I'm taking the risk in reporting this issue. The problem is simple: 1. Create a folder called "Yes". 2. Create Yes/A.hs with the following code: {{{#!hs module Yes.A where import Yes.B }}} 3. Create Yes/B.hs with the following code: {{{#!hs module Yes.B where }}} 4. Open a terminal in the folder that contains "Yes" and run: {{{ $ ghc Yes/A.hs }}} '''This works fine'''. Now try the following: {{{ $ cd Yes Yes/ $ ghc A.hs }}} You'll be greeted with the beautiful error: {{{ A.hs:3:8: Could not find module ?Yes.B? Use -v to see a list of the files searched for. }}} A screenshot is worth the above thousand words: http://i.imgur.com/8AxRa0K.png '''This is silly'''. Running with the -v option shows that ghc is not looking for Yes/B.hs, but Yes/Yes/B.hs. I can understand ''why'' it looks there, but not why ghc isn't just this ''tiny'' bit more intelligent in knowing where to look. After all, the module name tells ghc ''exactly'' in which subfolder it is located: {{{#!hs module Yes.A where -- This module is very likely to be in Yes/, because otherwise a name inconsistency error is thrown. }}} '''Proposed solution:''' The module name tells ghc exactly where it is located. If Yes.A imports Yes.B, then you know that they're in the same subfolder. Simple as that. Instead of ignoring that information and looking for Yes/Yes/B.hs, it should simply look for Yes/B.hs. Relative to ghc (which is run from Yes/) this would be ./B.hs. This solution is scalable. Imagine a module Ding.Dong.Biddly.Bong that imports Ding.Dong.Doodle.Bell. Running "ghc Bong.hs" from Ding/Dong/Biddly/ should '''not''' make it look for "Ding/Dong/Biddly/Ding/Dong/Doodle/Bell.hs", but for Ding/Dong/Doodle/Bell.hs. Relative to ghc (run from Ding/Dong/Biddly/), this would be ../Doodle/Bell.hs. So yeah, right now ghc is arbitrarily restricted to run from the root of the source directory. This '''looks''' like intended behaviour until you realise that the silly bug mentioned here is probably the only thing that prevents ghc from running from ''any'' subfolder. Of course there are the -i and :set options for ghc that allows one to work around this, but one should not be expected to jump through all the -iFile hoops to be allowed to run ghc from any arbitrary subdirectory of the source folder. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 13:13:48 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 13:13:48 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.5891ff4080fa7dafb052e531fbd85244@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire * priority: normal => highest * milestone: => 7.12.1 Comment: Happily, this works with the tip of the ghc-7.10 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 14:13:58 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 14:13:58 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.d3d8b3158c73b0656ad7f3894dfe760b@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): What if there ''is'' a file `Yes/Yes/B.hs` containing `module Yes.B where`? Currently, `cd Yes; ghc A.hs` would work then. There was another ticket on the same subject recently, but I can't find it at the moment. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 14:37:36 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 14:37:36 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.3fa0f3bede6507de095b402b45a14449@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by FPtje): {{{ falco ~/Downloads/Yes$ mkdir Yes falco ~/Downloads/Yes$ mv B.hs Yes/ falco ~/Downloads$ find Yes Yes Yes/Yes Yes/Yes/B.hs Yes/A.hs falco ~/Downloads/Yes$ ghci A.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help [1 of 2] Compiling Yes.B ( Yes/B.hs, interpreted ) [2 of 2] Compiling Yes.A ( A.hs, interpreted ) Ok, modules loaded: Yes.A, Yes.B. }}} Yes, like I said, it looks for Yes/Yes/B.hs. Puting B.hs in Yes/Yes will make ghc work with loading A.hs from Yes/, but that will break running ghc in the root of the source: {{{ falco ~/Downloads/Yes$ cd .. falco ~/Downloads$ ghci Yes/A.hs GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Yes/A.hs:3:8: Could not find module ?Yes.B? Use -v to see a list of the files searched for. Failed, modules loaded: none. Prelude> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 14:39:47 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 14:39:47 -0000 Subject: [GHC] #10596: Template Haskell : getQ and putQ doesn't work In-Reply-To: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> References: <046.c146d1bd7b74286ed3cadc42554eb201@haskell.org> Message-ID: <061.f9d621b41fc7498287871fac16cbddca@haskell.org> #10596: Template Haskell : getQ and putQ doesn't work -------------------------------------+------------------------------------- Reporter: kiripon | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: getQ putQ Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10596 Related Tickets: | Blocking: | Differential Revisions: Phab:D1026 -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => merge Comment: According to [https://travis-ci.org/ghc/ghc/builds/71040095 Travis], this fix works. Thanks for thinking of this, Joachim! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 15:06:59 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 15:06:59 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.7ad314c5388261d8a81aea929cdc089e@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: Runtime System | Keywords: Resolution: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonmar): `BlockedIndefinitelyOnMVar` is thrown when the thread is blocked on an `MVar` that isn't reachable from anywhere else, which means that it will never be woken up. There are two possibilities: - the exception is being thrown erroneously (unlikely, I'd guess) - the IO manager has somehow lost the `MVar` that the thread is waiting on. You could proceed by instrumenting code below `GHC.Event` to find out what happens to the `MVar` the thread is waiting on. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 15:41:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 15:41:03 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2310637=3A_Cannot_suppress_=22Warning?= =?utf-8?q?=3A_=7B-=23_SOURCE_=23-=7D_unnecessary_in_import_of__?= =?utf-8?b?4oCYQeKAmSI=?= In-Reply-To: <046.5119908e23481708e117e58b6fa1ab97@haskell.org> References: <046.5119908e23481708e117e58b6fa1ab97@haskell.org> Message-ID: <061.a16f059fd5a293e8842ce292e26459df@haskell.org> #10637: Cannot suppress "Warning: {-# SOURCE #-} unnecessary in import of ?A?" ---------------------------------+----------------------------------------- Reporter: phischu | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by simonpj): Good catch! Currently -w simply makes the "set of active warning flags" empty. But in fact there is no flag to control this particular warning (see `DynFlags.WarningFlag`). So we must choose: * Invent a new flag `-fwarn-unnecesary-source-imports", or * Re-use an existing flag, such as `-fwarn-unused-imports`. I'm inclined to do the latter; it's hardly a hot topic. Then * Modify `GhcMake.warnUnnecessarySourceImports` to check this flag, and do nothing unless it is set. This is easy. Would someone like to do it? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 15:46:51 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 15:46:51 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2310637=3A_Cannot_suppress_=22Warning?= =?utf-8?q?=3A_=7B-=23_SOURCE_=23-=7D_unnecessary_in_import_of__?= =?utf-8?b?4oCYQeKAmSI=?= In-Reply-To: <046.5119908e23481708e117e58b6fa1ab97@haskell.org> References: <046.5119908e23481708e117e58b6fa1ab97@haskell.org> Message-ID: <061.65c685892cf623f44d41b0cfa6511118@haskell.org> #10637: Cannot suppress "Warning: {-# SOURCE #-} unnecessary in import of ?A?" ---------------------------------+----------------------------------------- Reporter: phischu | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by thomie): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 15:57:00 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 15:57:00 -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.ce9ea0731ae2723e8b009dc56b78a313@haskell.org> #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. -------------------------------------+------------------------------------- Reporter: jpbernardy | Owner: osa1 Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | newcomer Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D978 -------------------------------------+------------------------------------- Comment (by osa1): Sent an email to libraries mailing list: https://mail.haskell.org/pipermail/libraries/2015-July/025959.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 16:02:35 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 16:02:35 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.6f27787d87555ed0d6cb46cf09abdf37@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Richard Eisenberg ): In [changeset:"9f978b67212a51fa34ef44db463351b959ff15e4/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="9f978b67212a51fa34ef44db463351b959ff15e4" Fix #10642. Representational equalities cannot discharge nominal ones. Even if, somehow, this didn't cause a type error (as reported in the ticket), it would surely cause a core lint error. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 16:03:46 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 16:03:46 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.b0338d1341d9e47ed69ed725332aabf9@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | typecheck/should_compile/T10642 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * testcase: => typecheck/should_compile/T10642 * resolution: => fixed Comment: All fixed now. Thanks for the report! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 16:56:47 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 16:56:47 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.5abd63bd491f58dd8a33897345a56743@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | typecheck/should_compile/T10642 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I know it wasn't the point of the ticket, but I'm surprised that the derived instance for Bounded (a Haskell 2010-derivable class) uses coerce rather than just using the data constructor D. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 16:58:00 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 16:58:00 -0000 Subject: [GHC] #10632: ImplicitParams: GHC does not warn about unused implicit parameters In-Reply-To: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> References: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> Message-ID: <058.8d3cf65d660a07ac3c7fb8db84712b1a@haskell.org> #10632: ImplicitParams: GHC does not warn about unused implicit parameters -------------------------------------+------------------------------------- Reporter: mwnx | Owner: Type: bug | Status: new Priority: lowest | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I think it works fine in HEAD. Can others verify? {{{ T10632.hs:5:6: warning: Redundant constraint: ?file1::String In the type signature for: f :: (?file1::String) => IO () }}} If so, can someone add this as a regression test? I don't think it's worth messing with 7.10. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 17:01:55 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 17:01:55 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.061e047c10c29dc553f5bc9bdca6f673@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | typecheck/should_compile/T10642 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): For reasons I'm not quite sure of (performance, probably), the following classes are always derived using GND when derived for newtypes: `Eq`, `Ord`, `Ix`, `Bounded`. This is true in a file with no extensions enabled. I don't know precisely why `Eq` didn't trigger this bug, but it wasn't worth exploring. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 17:24:26 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 17:24:26 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.bed36622a2ca1eea72a3b32d86f25736@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | typecheck/should_compile/T10642 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by darchon): `Bounded` is not derivable in the standard way for the `D` type, it needs `StandaloneDeriving`, which for newtypes seems to *always* use `coerce`. As to why `Eq` didnt trigger the bug, is has to do with the fact that: {{{ coerceDF :: (F a -> Int) -> (D a -> Int) coerceDF = coerce }}} also didn't trigger the bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 18:22:57 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 18:22:57 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.2618ce6eb3cce6d2811510f534c2b323@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: patch Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1073 -------------------------------------+------------------------------------- Changes (by niteria): * status: new => patch * differential: => D1073 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 19:47:09 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 19:47:09 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.edbdf1dfb2baf0b750449c4807deafdd@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: patch Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1073 -------------------------------------+------------------------------------- Changes (by slyfox): * differential: D1073 => Phab:D1073 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 20:30:20 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 20:30:20 -0000 Subject: [GHC] #10644: Option GADTs invalidates a rank-2 function. Message-ID: <044.cea8b59ff0253a5be2360b5015d264ac@haskell.org> #10644: Option GADTs invalidates a rank-2 function. -------------------------------------+------------------------------------- Reporter: bales | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: GHC rejects (amd64) | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This module typechecks WITHOUT the extension GADTs and doesn't typecheck WITH the extension GADTs Since it has nothing to do with GADTs, the consequence of using the option is surprising. I witnessed this behaviour on GHC versions 7.6.3, 7.8.3, 7.8.4, 7.10.1 {{{#!hs {-# LANGUAGE RankNTypes , GADTs #-} module GADTMonomorphism where problem :: (forall x . () -> x) -> (a,b) problem f = (p, p) where p = f () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 20:34:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 20:34:34 -0000 Subject: [GHC] #10644: Option GADTs specialises a polymorphic value in local bindings (was: Option GADTs invalidates a rank-2 function.) In-Reply-To: <044.cea8b59ff0253a5be2360b5015d264ac@haskell.org> References: <044.cea8b59ff0253a5be2360b5015d264ac@haskell.org> Message-ID: <059.1b9f4600b110962281f2c725ef598217@haskell.org> #10644: Option GADTs specialises a polymorphic value in local bindings -------------------------------------+------------------------------------- Reporter: bales | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 22:09:43 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 22:09:43 -0000 Subject: [GHC] #10294: Missing instances if compiling with -fplugin In-Reply-To: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> References: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> Message-ID: <061.609623dd0af64a40a6e583bdff59ee10@haskell.org> #10294: Missing instances if compiling with -fplugin -------------------------------------+------------------------------------- Reporter: jscholl | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: x86_64 Operating System: Linux | (amd64) Type of failure: GHC rejects | Test Case: valid program | plugins/T10294, plugins/T10294a Blocked By: 10420 | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * testcase: => plugins/T10294, plugins/T10294a * resolution: duplicate => Comment: The `pre_cmd` of T10294 and T10294a generates the following warning with a devel2 build: {{{ $ make -s --no-print-directory -C annotation-plugin package.T10294 WARNING: file compiler/specialise/Specialise.hs, line 722 specImport discarding: mapM_ :: forall a_a5Mh (m_a5Mi :: * -> *) b_a5Mj (t_a5Mk :: * -> *). (Foldable t_a5Mk, Monad m_a5Mi) => (a_a5Mh -> m_a5Mi b_a5Mj) -> t_a5Mk a_a5Mh -> m_a5Mi () want: False stable: False calls: mapM_ _ @ CoreM _ @ [] $fFoldable[] $fMonadCoreM }}} This makes the test fail for me, even when DYNAMIC_GHC_PROGRAMS=YES (my timeout program stops working for some reason when it sees unexpected output). I don't know if the warning can be ignored, so I'm reopening this ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 15 22:18:28 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 15 Jul 2015 22:18:28 -0000 Subject: [GHC] #10644: Option GADTs specialises a polymorphic value in local bindings In-Reply-To: <044.cea8b59ff0253a5be2360b5015d264ac@haskell.org> References: <044.cea8b59ff0253a5be2360b5015d264ac@haskell.org> Message-ID: <059.c2b1e8ac857901f9b8b3a34f02d461fd@haskell.org> #10644: Option GADTs specialises a polymorphic value in local bindings -------------------------------------+------------------------------------- Reporter: bales | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: This is just a consequence of `MonoLocalBinds`, as specified in [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/other- type-extensions.html#mono-local-binds 7.13.9.3 of the user manual]. GADTs switches on `MonoLocalBinds`, so the definition of `p` is not generalised, and that in turn leads to the error you encountered. You might reasonably think that GADTs have nothing do to with generalisation, but alas they do, as the papers mentioned in the manual describe. I'm not saying it's brilliant behaviour, just that I don't know how to do better. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 01:45:48 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 01:45:48 -0000 Subject: [GHC] #10642: Coercible regression from 7.10 to HEAD In-Reply-To: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> References: <046.c46d2b7dd776baef2d9178bdbce8ff5d@haskell.org> Message-ID: <061.7183ca75af1be2dd0773a35bb13fa189@haskell.org> #10642: Coercible regression from 7.10 to HEAD -------------------------------------+------------------------------------- Reporter: darchon | Owner: goldfire Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | typecheck/should_compile/T10642 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): `StandaloneDeriving` and normal `deriving` use the same mechanisms. So `StandaloneDeriving` is no more likely to use `coerce` than normal `deriving`. This can most easily be seen when deriving `Show`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 07:52:05 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 07:52:05 -0000 Subject: [GHC] #10645: Fix Data.List.sortOn documentation Message-ID: <042.73e5e4056be5a499a396a6aaa190cb5b@haskell.org> #10645: Fix Data.List.sortOn documentation -------------------------------------+------------------------------------- Reporter: spl | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.10.2-rc2 libraries/base | Operating System: Unknown/Multiple Keywords: | Type of failure: Documentation Architecture: | bug Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The {{{sortOn}}} documentation says: {{{ @sortOn f@ is equivalent to @sortBy . comparing f@ }}} but this is not correct (it does not type-check). It should say: {{{ @sortOn f@ is equivalent to @sortBy (comparing f)@ }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 07:54:45 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 07:54:45 -0000 Subject: [GHC] #10645: Fix Data.List.sortOn documentation In-Reply-To: <042.73e5e4056be5a499a396a6aaa190cb5b@haskell.org> References: <042.73e5e4056be5a499a396a6aaa190cb5b@haskell.org> Message-ID: <057.b15e8b189f385839b5920cd2af11e172@haskell.org> #10645: Fix Data.List.sortOn documentation -------------------------------------+------------------------------------- Reporter: spl | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spl): I would submit a patch myself, but it will take me time to set everything up and it's such a small change, I'm hoping it's easy enough for somebody else to do it. If not, let me know, and I'll do it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 08:12:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 08:12:27 -0000 Subject: [GHC] #10645: Fix Data.List.sortOn documentation In-Reply-To: <042.73e5e4056be5a499a396a6aaa190cb5b@haskell.org> References: <042.73e5e4056be5a499a396a6aaa190cb5b@haskell.org> Message-ID: <057.bb07f8a6e09294f12d7fe5f11eecd6d2@haskell.org> #10645: Fix Data.List.sortOn documentation -------------------------------------+------------------------------------- Reporter: spl | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 7.12.1 Comment: Fixed in commit 504c2aeb8bf36e031c0751e33b85bab58680542e: {{{ Author: Thomas Miedema <> Date: Thu Jul 16 10:10:18 2015 +0200 Docs: `sortOn = sortBy (comparing f)` [skip ci] }}} Thanks for the report. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 09:45:08 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 09:45:08 -0000 Subject: [GHC] #10047: inconsistency in name binding between splice and quasiquotation In-Reply-To: <047.467ed7feed46ef69006cfd30a0e1c7fb@haskell.org> References: <047.467ed7feed46ef69006cfd30a0e1c7fb@haskell.org> Message-ID: <062.429c57e57f5670c6cdf00d26a0605ce0@haskell.org> #10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by spinda): Regarding what I wrote earlier about the splicing restriction: There's an essential conflict between having module-local declarations in scope for the reification environment and avoiding the splitting of declaration groups on splices. For some splices, such as {{{makeLenses}}}, reification takes precedence. But not all splices need to reify module- local declarations: for those, giving that up would be worth avoiding the splicing restriction. In 7.10, the first use case for splices is covered by the {{{$(...)}}} syntax, and the second by quasiquoters. After this change, only the first is represented. This can be rectified by providing some way to mark splices as falling into the second category, then processing them along with the other declarations in the group instead of splitting on them. To accomplish this, an additional {{{$$(...)}}} syntax (or similar) could be added. In the top-level declaration context, these splices would be marked as not to be split on. For consistency, the same syntax would yield the same result as {{{$(...)}}} in all other contexts (types, etc). Quasiquoters would then gain a similar additional syntax, {{{[:name| ... |]}}} or such. Since this would actually emulate the current behavior of quasiquoters, perhaps the effect should be reversed here for compatibility, with the second syntax ''enabling'' splitting. I'm not sure. Alternately, we could forgo the additional syntax and simply mark all splices arising from quasiquoters as not causing a split. This would accomplish the end goal of preserving compatibility. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 09:51:50 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 09:51:50 -0000 Subject: [GHC] #10311: package name returned from tyConPackage is garbled In-Reply-To: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> References: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> Message-ID: <064.273061e21f5c48a3d7697ad19de58496@haskell.org> #10311: package name returned from tyConPackage is garbled -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by j.waldmann): "Moreover there is a reason ..." I understand that but that reason applies to (standalone-)haddock-generated URLs as well. Are you implying that they also should contain the package key (instead of the name)? Of course that would solve my problem as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 10:46:48 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 10:46:48 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.cc9c40518dd93f0d63ac8182ea158317@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by svenpanne): I think the current behavior is not silly at all, and the proposed solution will very probably lead to confusion in non-trivial settings: Assume that you have the following directory/file structure: Foo/Yes/A.hs Bar/Yes/B.hs with the same contents as in the OP. GHC(i) can happily load this if you set the right import paths and give the module name, not the file name: {{{ $ ghci -iFoo:Bar Yes.A GHCi, version 7.10.1.20150630: http://www.haskell.org/ghc/ :? for help [1 of 2] Compiling Yes.B ( Bar/Yes/B.hs, interpreted ) [2 of 2] Compiling Yes.A ( Foo/Yes/A.hs, interpreted ) Ok, modules loaded: Yes.A, Yes.B. }}} So the assumption that a module name tells GHC exactly the location of the subfolder is wrong, the import path effectively overlays several directories. This is standard behavior for lots of compilers/interpreters which is needed for more complicated projects, and I don't think we should change that. As it is, it is already complicated enough, putting some "clever" magic into GHC just to avoid a single commandline option is not the way to go. How does your proposal interact with the import path? How can one avoid accidentally finding the wrong module? Should filenames on the commandline be handled differently from module names? IMHO the answers to these questions are far from obvious and the potential gain (saving a single commandline flag) doesn't outweigh the introduced complexity. P.S.: What do you mean by "name inconsistency error"? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 12:14:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 12:14:40 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.26a06fe75e5a07c9a1216fe267b8c539@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by FPtje): Shouldn't the -i problem you mention be resolved simply by giving those folder the highest priority? Standard behaviour for lots of compilers and interpreters? Haskell is a different language altogether. Rules from other compilers do not necesarily apply. The extra search paths aren't "clever magic", just an extra place to look for modules. It doesn't have to make anything more complicated. Finding wrong modules shouldn't happen, at least not in the example you provided. Especially when -i paths have priority over the other paths. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 12:49:05 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 12:49:05 -0000 Subject: [GHC] #10047: inconsistency in name binding between splice and quasiquotation In-Reply-To: <047.467ed7feed46ef69006cfd30a0e1c7fb@haskell.org> References: <047.467ed7feed46ef69006cfd30a0e1c7fb@haskell.org> Message-ID: <062.b1da940e3cf7170a4d6ac43e63f54b99@haskell.org> #10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: th/T10047 Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:13 slyfox]: > I skimmed through testsuite failures on full validate today and found qq007 and qq008 failures: These failures are indeed due to this ticket -- we need to fix them up. But first, we have to decide what to do with this ticket in general. I have to say I find @spinda's arguments convincing. The idea that `[q|blah|]` is identical to `$(quoteDec q "blah")` is nice, but perhaps there is a reason for two separate mechanisms here. The splitting that @spinda is so worried about happens only for ''declaration'' splice/quasiquotes, so we could have the splices/quasiquote consistency for other contexts. With some careful documentation in the manual, I think it's not hard for users to understand this difference. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 12:51:06 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 12:51:06 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.2b91efa1aef11f95e978df16e47fb27a@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by svenpanne): I think the point where we disagree is what you call the ''"-i problem"'': For me it's not a problem at all, it's as easy as it gets without being too clever and confusing, and it's standard behavior (compare with e.g. C/C++'s include path handling). And ''"ghc is arbitrarily restricted to run from the root of the source directory"'' is not correct, either: It is just the case (again standard behavior) that the default search path just contains "." (https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/separate- compilation.html#search-path). Regarding finding wrong modules: Extend your example Yes/A.hs (containing module Yes.A) Yes/B.hs (containing module Yes.b) with Yes/Yes/B.hs (containing module Yes.Yes.B) With your proposal when your cwd is the top-level "Yes", "ghc A.hs" would pick up the file containing Yes.Yes.B, which is not what you want, although it's in the perfectly right location. Another problem is: No build system of any kind should blindly go upwards in the directory hierarchy because of symbolic links, only downwards. And finally: In any non-toy program, having a single -i option is your least problem, so you will have a .cabal file, anyway. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 13:28:05 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 13:28:05 -0000 Subject: [GHC] #10646: Adding GADTs extension makes RankNTypes code fail to compile. Message-ID: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> #10646: Adding GADTs extension makes RankNTypes code fail to compile. -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Type checker) | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The failing example: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} data I a = I a example :: String -> I a -> String example str x = withContext x s where s i = "Foo" ++ str withContext :: I a -> (forall b. I b -> c) -> c withContext x f = f x }}} '''Without''' `GADTs`, this compiles and works fine: {{{ ? *Main > example "bar" (P 'a' "quux") "Foobar" }}} '''With''' `GADTs` the code fails to compile with an error: {{{ ex.hs:7:31: Couldn't match type ?t0? with ?I b? because type variable ?b? would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: I b -> String at ex.hs:7:17-31 Expected type: I b -> String Actual type: t0 -> [Char] Relevant bindings include s :: t0 -> [Char] (bound at ex.hs:9:5) In the second argument of ?withContext?, namely ?s? In the expression: withContext x s Failed, modules loaded: none. }}} '''Yet''', if I add type annotation for `s`, everything seems to be fine: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} data I a = I a example :: String -> I a -> String example str x = withContext x s where s :: I a -> String s i = "Foo" ++ str withContext :: I a -> (forall b. I b -> c) -> c withContext x f = f x }}} ---- I tried to make the failing example smaller, but seems that every bit participates. The use of `str` inside `s` especially. Is there some bug hiding inside GADTs related stuff? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 13:29:44 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 13:29:44 -0000 Subject: [GHC] #10646: Adding GADTs extension makes RankNTypes code fail to compile. In-Reply-To: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> References: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> Message-ID: <060.710c441f90e59fd03b4e54262f48c103@haskell.org> #10646: Adding GADTs extension makes RankNTypes code fail to compile. -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Old description: > The failing example: > > {{{#!hs > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE GADTs #-} > > data I a = I a > > example :: String -> I a -> String > example str x = withContext x s > where > s i = "Foo" ++ str > > withContext :: I a -> (forall b. I b -> c) -> c > withContext x f = f x > }}} > > '''Without''' `GADTs`, this compiles and works fine: > > {{{ > ? *Main > example "bar" (P 'a' "quux") > "Foobar" > }}} > > '''With''' `GADTs` the code fails to compile with an error: > > {{{ > ex.hs:7:31: > Couldn't match type ?t0? with ?I b? > because type variable ?b? would escape its scope > This (rigid, skolem) type variable is bound by > a type expected by the context: I b -> String > at ex.hs:7:17-31 > Expected type: I b -> String > Actual type: t0 -> [Char] > Relevant bindings include s :: t0 -> [Char] (bound at ex.hs:9:5) > In the second argument of ?withContext?, namely ?s? > In the expression: withContext x s > Failed, modules loaded: none. > }}} > > '''Yet''', if I add type annotation for `s`, everything seems to be fine: > > {{{#!hs > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE GADTs #-} > > data I a = I a > > example :: String -> I a -> String > example str x = withContext x s > where > s :: I a -> String > s i = "Foo" ++ str > > withContext :: I a -> (forall b. I b -> c) -> c > withContext x f = f x > }}} > > ---- > > I tried to make the failing example smaller, but seems that every bit > participates. The use of `str` inside `s` especially. > > Is there some bug hiding inside GADTs related stuff? New description: The failing example: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} data I a = I a example :: String -> I a -> String example str x = withContext x s where s i = "Foo" ++ str withContext :: I a -> (forall b. I b -> c) -> c withContext x f = f x }}} '''Without''' `GADTs`, this compiles and works fine: {{{ ? *Main > example "bar" (P 'a' "quux") "Foobar" }}} '''With''' `GADTs` the code fails to compile with an error: {{{ ex.hs:7:31: Couldn't match type ?t0? with ?I b? because type variable ?b? would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: I b -> String at ex.hs:7:17-31 Expected type: I b -> String Actual type: t0 -> [Char] Relevant bindings include s :: t0 -> [Char] (bound at ex.hs:9:5) In the second argument of ?withContext?, namely ?s? In the expression: withContext x s Failed, modules loaded: none. }}} '''Yet''', if I add type annotation for `s`, everything seems to be fine: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} data I a = I a example :: String -> I a -> String example str x = withContext x s where s :: I a -> String s i = "Foo" ++ str withContext :: I a -> (forall b. I b -> c) -> c withContext x f = f x }}} ---- I tried to make the failing example smaller, but seems that every bit participates. The use of `str` inside `s` especially. Is there some bug hiding inside GADTs related stuff? Tried with 7.8.4 and 7.10.1 -- Comment (by phadej): Happens -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 13:57:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 13:57:21 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.f38c50aeffef838f54cde0e2128f3b1c@haskell.org> #10181: Lint check: arity invariant -------------------------------------+------------------------------------- Reporter: nomeata | Owner: nomeata Type: task | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:751 -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"02897c586f091de5ba2b73bbef4c6054b28955d4/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="02897c586f091de5ba2b73bbef4c6054b28955d4" Failing test case: idArity invariant check, #10181 This was found Thomas Miedema. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 14:00:42 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 14:00:42 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.cd7379f2da9742f8e8a7c5ef065fc473@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: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:751 -------------------------------------+------------------------------------- Changes (by nomeata): * cc: thomie (added) * owner: nomeata => * status: closed => new * resolution: fixed => Comment: thomie notified me of a a case of this lint check firing, triggered by simply `t a = t a`. Here is what?s happening: {{{ ==================== Simplifier ==================== Max iterations = 4 SimplMode {Phase = 2 [main], inline, rules, eta-expand, case-of-case} Result size of Simplifier = {terms: 2, types: 4, coercions: 0} Rec { t [Occ=LoopBreaker] :: forall t_ans t_ant. t_ans -> t_ant [LclIdX, Arity=1, Str=DmdType] t = t end Rec } [...] ==================== Demand analysis ==================== Result size of Demand analysis = {terms: 2, types: 4, coercions: 0} Rec { t [Occ=LoopBreaker] :: forall t_ans t_ant. t_ans -> t_ant [LclIdX, Arity=1, Str=DmdType b] t = t end Rec } *** Core Linted result of Demand analysis: *** Core Lint errors : in result of Demand analysis *** T10181.hs:3:1: warning: [RHS of t :: forall t_ans t_ant. t_ans -> t_ant] idArity 1 exceeds arity imposed by the strictness signature DmdType b: t }}} So there are several possibilities: * The simplifier should not set the `idArity` of `t` if after simplification, it does not have that arity. * `idArtiy t = 1` is correct, as that is the arity provided by the programmer. In that case, the lint check is bogus. * The demand analysis should enforce the the invariant if it adds a bottoming signature. This requires some insight with someone with the big picture in mind. Simon? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 14:13:01 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 14:13:01 -0000 Subject: [GHC] #10646: Adding GADTs extension makes RankNTypes code fail to compile. In-Reply-To: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> References: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> Message-ID: <060.ece68123c235f78c24afc24b80b79057@haskell.org> #10646: Adding GADTs extension makes RankNTypes code fail to compile. -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: invalid | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: This is not-a-bug. See #10644, which, by some strange coincidence, was posted yesterday. Thanks for reporting, however! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 14:35:37 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 14:35:37 -0000 Subject: [GHC] #10646: Adding GADTs extension makes RankNTypes code fail to compile. In-Reply-To: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> References: <045.2348b72dd405b74e9e39d97f27a62f17@haskell.org> Message-ID: <060.0060168935df9f6de7f478e56f813618@haskell.org> #10646: Adding GADTs extension makes RankNTypes code fail to compile. -------------------------------------+------------------------------------- Reporter: phadej | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: invalid | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by phadej): Thanks to you for the explanation! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 15:03:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 15:03:38 -0000 Subject: [GHC] #10577: Use empty cases where appropriate when deriving instances for empty types In-Reply-To: <047.96e36644fa4dc515076cb2f2c2be615c@haskell.org> References: <047.96e36644fa4dc515076cb2f2c2be615c@haskell.org> Message-ID: <062.428c08a84b34e835d68405e8b07927e6@haskell.org> #10577: Use empty cases where appropriate when deriving instances for empty types -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 15:03:57 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 15:03:57 -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.5afa6394450c84cc53f623eb613c3763@haskell.org> #7401: Can't derive instance for Eq when datatype has no constructor, while it is trivial do do so. -------------------------------------+------------------------------------- Reporter: jpbernardy | Owner: osa1 Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: deriving, Operating System: Unknown/Multiple | newcomer Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D978 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 15:43:56 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 15:43:56 -0000 Subject: [GHC] #10529: hpc: Improve error messages in readMix In-Reply-To: <042.190bab483c0a9360715a797a8a3385e1@haskell.org> References: <042.190bab483c0a9360715a797a8a3385e1@haskell.org> Message-ID: <057.e4191e8cc493a2e9c69e5d8bf87f3908@haskell.org> #10529: hpc: Improve error messages in readMix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Code Coverage | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | simple/tixs/T10529{a,b,c} | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * testcase: => simple/tixs/T10529{a,b,c} * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 17:44:22 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 17:44:22 -0000 Subject: [GHC] #10311: package name returned from tyConPackage is garbled In-Reply-To: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> References: <049.befe981d27d5c4c24d07557f283ecb8b@haskell.org> Message-ID: <064.967c8da133f1e738236d8ba55885b958@haskell.org> #10311: package name returned from tyConPackage is garbled -------------------------------------+------------------------------------- Reporter: j.waldmann | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): The issue with Haddock is an interesting one which we have not really adequately discussed yet. I think in principle, Haddock documentation should be placed in a URL `packagename-0.1`, on the principle that the documentation for a package is somehow invariant of what versions you picked for its dependencies. If I want to know what the API of `containers-0.5.6.3` is, I don't care that it was compiled against `base-4.2` or `base-4.3`. But in practice, Haddock documentation (1) must be built with respect to a specific version resolution, and (2) contains links to other packages, the particular versions of which depend on the resolution from (1). So even if I in principle don't care what version of `base` I compiled against, if I click a hyperlink to `Int`, I'm going to have to end up with some version of `base` documentation! But I think this will not solve your problem, because even if Haddock URLs started recording package keys, they would want to record an expanded form, `foo-0.1-47ajk3tbda43DFWyeF3oHQ`. So you will still have to bang on the installed package database to get this from `47ajk3tbda43DFWyeF3oHQ`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 17:52:58 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 17:52:58 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.caafc301e44e8eb83087fd03e1989bd9@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime crash | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D407 -------------------------------------+------------------------------------- Comment (by thomie): For posterity, other commits in this series: * 33ed16bd8b3d95dd18e401a3d64435d8675b5f86 {{{ Author: Merijn Verstraaten <> Date: Wed Jul 24 19:00:42 2013 +0100 *Really* RTS crash due to bad coercion. Previous commit only moved the coercion mistake to a different architecture (i.e. underflow could still occur on platforms where Int is smaller than CInt). This patch should definitively deal with all possible combinations. Signed-off-by: Austin Seipp <> }}} * 00e04e81fb127d716719a85d9387a98b664b7176 {{{ Author: Merijn Verstraaten <> Date: Wed Jul 24 14:37:25 2013 +0100 Fix OSX RTS crash due to bad coercion. The code coerces Int to CInt, which causes an overflow if Int is bigger than CInt (for example, Int 64bit, CInt 32 bit). This results in a negative value being passed to c_poll. On Linux all negative values are treated as infinite timeouts, which gives subtly wrong semantics, but is unlikely to produce actual bugs. OSX insists that only -1 is a valid value for infinite timeout, any other negative timeout is treated as an invalid argument. This patch replaces the c_poll call with a loop that handles the overflow gracefully by chaining multiple calls to poll to obtain the proper semantics. Signed-off-by: Austin Seipp <> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 19:10:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 19:10:38 -0000 Subject: [GHC] #9618: Undocument ImpredicativeTypes In-Reply-To: <045.05901419138923a568c2731a51d0dcf7@haskell.org> References: <045.05901419138923a568c2731a51d0dcf7@haskell.org> Message-ID: <060.d7af30f6e923f07d3e834e96bb7a9eda@haskell.org> #9618: Undocument ImpredicativeTypes -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Documentation | Version: 7.8.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: #8808 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: In #10325, SPJ updated the User's guide and the error message: "GHC doesn't yet support impredicative polymorphism". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 19:50:20 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 19:50:20 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.50fc4c61352656c477fc07cd77129d96@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Comment (by ezyang): Duncan and I had a chat about this, which in particular clarified "What questions Cabal asks the installed package database." cabal-install currently queries the installed package database in order so determine what the installed packages are when it is making an install plan. However, this is going to soon not be the case with Nix style versioning: Cabal will make an install plan using purely source package info, and then query the database to find out what products it already has installed. So the key idea is: **the installed package database is a database of units**! There may be more junk in the database than you would expect from the packages you have installed, but in a Nix world where there will be many many installs of the same package, ghc-pkq is already going to not be so useful for finding info about packages. I'll update the top level description with the final plan. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 20:07:16 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 20:07:16 -0000 Subject: [GHC] #9049: Expose srcLoc from the assertion architecture to allow better error messages In-Reply-To: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> References: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> Message-ID: <057.de0359eae474da8b2787af6d11a04682@haskell.org> #9049: Expose srcLoc from the assertion architecture to allow better error messages -------------------------------------+------------------------------------- Reporter: nh2 | Owner: gridaphobe Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D578 -------------------------------------+------------------------------------- Comment (by bgamari): Unfortunately 00cd6173a620ef99739d97ac843258fee8e2dee9, which e3dc28046373f3183dda56b096dbebec865e3be7 depends upon, changes an existing interface, which we try very hard to avoid in minor releases. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 20:07:36 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 20:07:36 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.10e202f1d84aad843c6e7bcff1a02b21@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Description changed by ezyang: Old description: > After today's weekly Backpack call, we have come to the conclusion that > we have two different types of "packages" in the Backpack world: > > 1. Cabal packages, which have a single `.cabal` file and are a unit of > distribution which get uploaded to Hackage, and > > 2. Backpack packages, of which there may be multiple defined in a > Backpack file shipped with a Cabal package; and are the building blocks > for modular development in the small. > > It's really confusing to have both of these called packages: thus, we > propose to rename all occurrences of Backpack package to unit. A Cabal > ''package'' may contain MULTIPLE Backpack ''units'', although old-style > Cabal files will only define one unit. > > A Cabal package remains > * The unit of distribution > * The unit that Hackage handles > * The unit of versioning > * The unit of ownership (who maintains it etc) > > Here are some of the consequences: > > 1. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather > than a Cabal package. (I think this actually makes the function of these > identifiers clearer.) We'll also distinguish Cabal-file level > `PackageName`s from Backpack-file `UnitName`s. Finally, any given unit > will be uniquely identified by an `InstalledUnitId`. > > 2. The source-level syntax of Backpack files will use `unit` in place of > where `package` was used before. > > 3. For backwards compatibility reasons, we'll sometimes arrange for > `PackageName`/`UnitName` and `InstalledUnitId`/`InstalledPackageId` to > coincide. Specifically, the unit of a package which has the same > `UnitName` as the `PackageName` is treated specially: its > `InstalledUnitId` is guaranteed to be the same as the > `InstalledPackageId` and it is what is "visible" when a user uses old > concepts such as `-package foo-0.1` to select a package. > > 4. The installed package database is extended to record some number of > units per an installed package: the public facing API is that you can > register a package CONTAINING some number of units. For old-style > packages, there will be only one unit with a matching `UnitName`, so this > will be isomorphic to an old style package; however, GHC will grow some > new APIs for selecting specific units to bring into scope. GHC really > mostly only cares about units, but if a user asks for a package using, > e.g. `-package` it will translate this request into a request for the > appropriate unit. > > 5. For old-style packages, Cabal will continue to write and register a > package configuration file which implicitly defines a single unit. > However, the plan is to give GHC the capacity to generate unit > description files (like package description files, but per unit), which > Cabal can interpret and use to register packages in the global database > using a `ghc-pkg` which can register units and "unitless" package > description files which don't implicitly define a unit. (NB: we must > create unit description files, because `ghc-pkg recache` is expected to > be able to regenerate the database.) (NB: we want to be able to add units > for a package separately, because this is how units for indefinite > packages are created as they are instantiated with new implementations.) > (NB: For BC purposes, since Cabal has to write old-style packages for old > GHC, this is pretty irritating.) > > 6. Cabal could also finally grow the "multiple libraries per single Cabal > file" support people have wanted; it's just a stylized use of the > Backpack facilities. (Note: Actually, not QUITE: multiple libraries are > likely to want separate sets of dependencies, whereas our units proposal > has external dependencies shared over all units. If we want the multiple > libraries, cabal-install has to learn about units.) > > The work plan: > > 1. Modify `bin-package-db` to reflect the unit/package split, but > otherwise keep ghc-pkg and GHC the same (so old-style package description > still supported, and interpreted as a package containing one unit.) > Source modifications to GHC assume that a package only has one unit. > > 2. Generalize GHC to work with packages with multiple units > > 3. Add capability to Cabal/ghc-pkg to register just units. For > compilation of Backpack files, GHC will write out units which Cabal will > then install to the real registry > > 4. Backpack! New description: After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal ''package'' may contain MULTIPLE Backpack ''units'', and old-style Cabal files will only define one unit. Every Cabal package has a distinguished unit (with the same name as the package) that serves as the publically visible unit. A Cabal package remains * The unit of distribution * The unit that Hackage handles * The unit of versioning * The unit of ownership (who maintains it etc) Here are some of the consequences: 1. The "installed package database" no longer maintains a one-to-one mapping between Cabal packages and entries in the database. This invariant is being dropped for two reasons: (1) With a Nix-style database, a package `foo-0.1` may be installed many times with different dependencies / source code, all of which live in the installed package database. (2) With Backpack, a package containing a Backpack file may install multiple units. To avoid having to rename *everything*, we'll keep calling this the installed package database, but really it's more like an installed *unit* database. 2. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Installed units continue to be identified by `InstalledPackageId`. 3. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 4. For old-style packages, Cabal will continue to write and register a single entry in the installed package database. For Backpack packages, Cabal will register as many entries as is necessary to install a package. The entry with the same `UnitName` as `PackageName` is publically visible to other packages. If a Backpack file defines other packages, those packages are registered with different `UnitName`s (giving them different `InstalledPackageId`s) which are not publically visible. The non- publically visible packages will have their description/URL/etc fields blank, and have a pointer to the "real" package. 5. If when installing a unit, we discover that it is already present in the database, we check if the ABI hashes are the same. If they are, we simply skip installing the unit but otherwise proceed. If the ABI hashes are not the same, we error: the units we are installing need to be recompiled against the unit present in the database. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 20:09:14 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 20:09:14 -0000 Subject: [GHC] #10196: Regression regarding Unicode subscript characters in identifiers In-Reply-To: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> References: <045.6ee5899f7586f6a7c7c268a3fffc6086@haskell.org> Message-ID: <060.e9db32d22f2af49bb20b69d26c31b00e@haskell.org> #10196: Regression regarding Unicode subscript characters in identifiers -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 (Parser) | Keywords: Resolution: fixed | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Phab:D969 Related Tickets: #5108 | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: This has been merged to `ghc-7.10` as 358e0a8d4cb49baa29cf6b001eaa9d4ac428bb2d. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 20:11:28 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 20:11:28 -0000 Subject: [GHC] #9049: Expose srcLoc from the assertion architecture to allow better error messages In-Reply-To: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> References: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> Message-ID: <057.9eefabade6b6624a0d09d0a3c085e7a0@haskell.org> #9049: Expose srcLoc from the assertion architecture to allow better error messages -------------------------------------+------------------------------------- Reporter: nh2 | Owner: gridaphobe Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D578 -------------------------------------+------------------------------------- Comment (by gridaphobe): Does it actually break any client packages? There was talk of building stackage with the backport to investigate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 20:12:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 20:12:38 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.b57fd3bfd63f87557ebe3a7fa69a7457@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: patch Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Comment (by bgamari): The backported patch has been merged to `ghc-7.10` as 98587f0c34b15ed307a9a6f8ebc50fb5339b4042. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 21:13:48 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 21:13:48 -0000 Subject: [GHC] #9049: Expose srcLoc from the assertion architecture to allow better error messages In-Reply-To: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> References: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> Message-ID: <057.41251e3ae1db4fcfa5e96c29e2fe13ed@haskell.org> #9049: Expose srcLoc from the assertion architecture to allow better error messages -------------------------------------+------------------------------------- Reporter: nh2 | Owner: gridaphobe Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D578 -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:37 gridaphobe]: > Does it actually break any client packages? There was talk of building stackage with the backport to investigate. Yeah, one single package from Stackage seems to be affected by this: {{{ [11 of 14] Compiling HsWalk ( HsWalk.hs, dist/build/ide-backend- server/ide-backend-server-tmp/HsWalk.o ) HsWalk.hs:136:35: Couldn't match expected type ?SrcSpan? with actual type ?RealSrcSpan? In the first argument of ?go?, namely ?span? In the second argument of ?($)?, namely ?go span? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 22:07:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 22:07:40 -0000 Subject: [GHC] #7478: setSessionDynFlags does not always work In-Reply-To: <044.a3899b7bd6c11925eee15996dee68777@haskell.org> References: <044.a3899b7bd6c11925eee15996dee68777@haskell.org> Message-ID: <059.d587a5d04b65191ed75eb71cac415275@haskell.org> #7478: setSessionDynFlags does not always work -------------------------------------+------------------------------------- Reporter: edsko | Owner: bherzog Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: ghc- Related Tickets: | api/T7478 | Blocking: | Differential Revisions: Phab:D1017 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"415351a938e86c4def60228552f121d91bbe7e59/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="415351a938e86c4def60228552f121d91bbe7e59" Put Opt_Static into defaultFlags if not pc_DYNAMIC_BY_DEFAULT (#7478) The test for Trac issue #7478 fails on some systems due to inconsistent default flags for dynamic vs. static linking. Test Plan: validate Reviewers: austin, thomie Reviewed By: thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1017 GHC Trac Issues: #7478 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 22:07:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 22:07:40 -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.6ae599f96593bf6a67fa4fe1562aa375@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1016 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"ae96c751c869813ab95e712f8daac8516bb4795f/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="ae96c751c869813ab95e712f8daac8516bb4795f" Implement -fprint-expanded-synonyms Add a flag to print type-synonyms-expanded versions of types in type error messages (in addition to old error messages with synonyms) * Mailing list discussion: https://mail.haskell.org/pipermail/ghc- devs/2015-June/009247.html * Wiki page: https://wiki.haskell.org/Expanding_type_synonyms_in_error_messages_proposal * Trac: https://ghc.haskell.org/trac/ghc/ticket/10547 Test Plan: * I'll find some examples and add tests. Reviewers: austin, simonpj, goldfire, bgamari Reviewed By: austin, simonpj, goldfire, bgamari Subscribers: rodlogic, thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1016 GHC Trac Issues: #10547 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 22:07:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 22:07:40 -0000 Subject: [GHC] #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter In-Reply-To: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> References: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> Message-ID: <065.4a3a945fd8be851316240fd6001fd658@haskell.org> #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | RyanGlScott Priority: normal | Status: new Component: Template Haskell | Milestone: Resolution: | Version: 7.10.1 Operating System: Unknown/Multiple | Keywords: Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #4168, #5218, | Blocking: #5877, | Differential Revisions: Phab:D1054 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2c9de9c9a3df8e855c883139b0cb2fd41801bd67/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="2c9de9c9a3df8e855c883139b0cb2fd41801bd67" Handle Char#, Addr# in TH quasiquoter (fixes #10620) DsMeta does not attempt to handle quasiquoted Char# or Addr# values, which causes expressions like `$([| 'a'# |])` or `$([| "abc"# |])` to fail with an `Exotic literal not (yet) handled by Template Haskell` error. To fix this, the API of `template-haskell` had to be changed so that `Lit` now has an extra constructor `CharPrimL` (a `StringPrimL` constructor already existed, but it wasn't used). In addition, `DsMeta` has to manipulate `CoreExpr`s directly that involve `Word8`s. In order to do this, `Word8` had to be added as a wired-in type to `TysWiredIn`. Actually converting from `HsCharPrim` and `HsStringPrim` to `CharPrimL` and `StringPrimL`, respectively, is pretty straightforward after that, since both `HsCharPrim` and `CharPrimL` use `Char` internally, and `HsStringPrim` uses a `ByteString` internally, which can easily be converted to `[Word8]`, which is what `StringPrimL` uses. Reviewers: goldfire, austin, simonpj, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1054 GHC Trac Issues: #10620 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 22:07:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 22:07:40 -0000 Subject: [GHC] #10447: DeriveFoldable rejects instances with constraints in last argument of data type In-Reply-To: <050.655803d4d5fe3ef1b8f5abc5e3585493@haskell.org> References: <050.655803d4d5fe3ef1b8f5abc5e3585493@haskell.org> Message-ID: <065.28634ec9c30e1500c62e7d959c915d80@haskell.org> #10447: DeriveFoldable rejects instances with constraints in last argument of data type -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8678 | Differential Revisions: Phab:D1031 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"2c5c29722c78e089eda0baa7ff89154b58f23165/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="2c5c29722c78e089eda0baa7ff89154b58f23165" DeriveFoldable for data types with existential constraints (#10447) Reviewers: dolio, shachaf, ekmett, austin, #core_libraries_committee, simonpj, bgamari Reviewed By: simonpj, bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1031 GHC Trac Issues: #10447 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 16 22:07:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 16 Jul 2015 22:07:40 -0000 Subject: [GHC] #10578: ghci line numbers are off by one In-Reply-To: <047.babcd43e2857d19107b478b8249a9812@haskell.org> References: <047.babcd43e2857d19107b478b8249a9812@haskell.org> Message-ID: <062.3031e7a1c60655f175797e18f47c69a1@haskell.org> #10578: ghci line numbers are off by one -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: osa1 Type: bug | Status: new Priority: low | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1067 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"a5e9da8feb5110ab8ee8fe3821e6b6d53946f983/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="a5e9da8feb5110ab8ee8fe3821e6b6d53946f983" Fix off-by-one error in GHCi line reporting (Trac #10578) Test Plan: I couldn't add tests because apparently line number reporting was already working correctly when loading script files. I don't know how to test by running commands using stdin, is this supported? Reviewers: austin, thomie, bgamari Reviewed By: thomie, bgamari Subscribers: hvr, thomie Differential Revision: https://phabricator.haskell.org/D1067 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 01:23:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 01:23:36 -0000 Subject: [GHC] #10647: Notice about lack of SIMD support. Message-ID: <044.41ea1589882067bc6ce5e3c65bf3dab1@haskell.org> #10647: Notice about lack of SIMD support. -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- In some cases, when SIMD primitives are used without the `-fllvm` flag, instead of giving the friendly `SIMD vector instructions require the LLVM back-end.`, GHC crashes with varying messages. The simplest example is {{{#!hs {-# LANGUAGE MagicHash #-} module Foo where import GHC.Prim data V = V Int8X16# }}} In 7.8.4 this crashes with {{{ ghc: panic! (the 'impossible' happened) (GHC version 7.8.4 for x86_64-unknown-linux): Size.intSize W128 }}} According to osa1, in HEAD this still crashes, but with {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): Format.intFormat W128 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 02:16:13 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 02:16:13 -0000 Subject: [GHC] #10647: Notice about lack of SIMD support. In-Reply-To: <044.41ea1589882067bc6ce5e3c65bf3dab1@haskell.org> References: <044.41ea1589882067bc6ce5e3c65bf3dab1@haskell.org> Message-ID: <059.a8859598347082f788ce19c2509d97e0@haskell.org> #10647: Notice about lack of SIMD support. -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: omeragacan@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 02:25:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 02:25:47 -0000 Subject: [GHC] #10648: Some 64-vector SIMD primitives are absolutely useless Message-ID: <044.c060f468a7f7b3021db9c517bef50f1b@haskell.org> #10648: Some 64-vector SIMD primitives are absolutely useless -------------------------------------+------------------------------------- Reporter: mniip | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- The primitives `packInt8X64#`, `packWord8X64#`, `unpackInt8X64#`, `unpackWord8X64#` cannot be used because their types include unboxed 64-tuples, but any haskell code using them does not compile due to the 62-tuple limitation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 10:22:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 10:22:55 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.02feda96cdb5a4a958b532a33f6a0acf@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Comment (by simonpj): > Installed units continue to be identified by `InstalledPackageId` Wouldn't `InstalledUnitId` be clearer? Indeed wouldn't `InstalledPackageId` be positively misleading? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 10:37:24 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 10:37:24 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.b85ff2ae014145a84fbbe5f53bf52ccd@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by FPtje): > With your proposal when your cwd is the top-level "Yes", "ghc A.hs" would pick up the file containing Yes.Yes.B, which is not what you want I'm not sure what you mean exactly, but I tried this with current ghc, and it already does find the module. However, since the Yes/Yes/B.hs contains Yes.Yes.B, and A.hs tries to import Yes.B, a module name mismatch error occurs (see screenshot: http://i.imgur.com/hQuh8dx.png). It doesn't seem like this would be a problem. The screenshot also shows that the behaviour is the same when I append the search path that I request to be added by default. I'm not saying that "." in the search path should be ''replaced'' by my proposition, rather, I suggest that a path needs to be added with the lowest priority. That way, all previous behaviour should remain unchanged, with the exception that it should find modules that it arguably should have in the first place. '''About why this problem in general should be fixed:''' > In any non-toy program, having a single -i option is your least problem, so you will have a .cabal file, anyway. This issue is generalised to just compiling, because that is where this bug lies. The bug makes development a huge nuisance. Personally I like working on a single file, having it loaded in ghci. The power of ghci is that it can load any single haskell file and work with it, executing single functions. However, simply going to the folder containing the haskell file, opening up a terminal and running ghci will often have you run into this bug, forcing you to either cd to the root folder or give the root folder to -i. This is annoying, but it also makes writing linters unnecessarily difficult. This linter (https://github.com/SublimeLinter/SublimeLinter- ghc) for example simply runs ghc -Wall on any haskell file open in the Sublime text editor. Since ghc is run from some arbitrary location, it gives a meaningless result when it hits this bug. The same happens when pressing the "Build" button in sublime, which just runs "runhaskell $file". The only way for Sublime and sublimelinter-ghc to solve this problem is to try to find out the root path of the source and either give that to ghc/runhaskell or put that in an -i option. This would involve searching for cabal files, parsing haskell files, having the user set it manually or other things that go way beyond the idea of ''"tools that run a command on a file and show a pretty output in the text editor"''. The responsibility of this issue lies with the source of the problem: ghc not realising that the source file containing Yes.B might just very well be right next to the source file of Yes.A. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 10:49:47 2015 From: ghc-devs at haskell.org (GHC-PGTEST) Date: Fri, 17 Jul 2015 10:49:47 -0000 Subject: [GHC-PGTEST] #10649: test - plz ignore Message-ID: <042.6af7a9ebe6a5a8973a884b8c60b732d5@haskell.org> #10649: test - plz ignore -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- -- Ticket URL: GHC-PGTEST The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 11:27:07 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 11:27:07 -0000 Subject: [GHC] #10649: Performance issue with unnecessary reboxing Message-ID: <044.4cf844fad84f7356a087aa89ed9fcd46@haskell.org> #10649: Performance issue with unnecessary reboxing -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Depending on number of fields in a structure (A and F), $fBA_$cfoo or $fBF_$cfoo will or will not be using $w$cfoo for 16 fields it uses it, for 12 - not With lazy fields behaviour, it starts using $w$cfoo around 100-200 fields. Adding -funfolding-use-threshold=90 helps in this case, but given enough fields (about 50 of them, of different types) value of 1000000000 is not helping and with very cheap operation (like addition or allocation of cons-like structure) overhead from sending those parameters via stack into worker becomes very significant - I have code that works ~3-5 times slower. This issue is not specific to generics, I can provide more examples if necessary {{{#!hs {-# LANGUAGE FlexibleContexts, FlexibleInstances, DeriveGeneric, DefaultSignatures #-} {-# LANGUAGE TypeOperators, BangPatterns #-} {-# OPTIONS -funbox-strict-fields -ddump-to-file -ddump-simpl -ddump-stg -dsuppress-all -ddump-asm #-} import Data.Word import GHC.Generics data A = A !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word deriving Generic data F = F !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word !Word deriving Generic class B a where foo :: a -> Word {-# INLINE foo #-} default foo :: (Generic a, GB (Rep a)) => a -> Word foo !x = gfoo (from x) class GB f where gfoo :: (f a) -> Word instance GB x => GB (M1 D d (M1 C c x)) where {-# INLINE gfoo #-} gfoo (M1 (M1 x)) = gfoo x instance (GB a, GB b) => GB (a :*: b) where {-# INLINE gfoo #-} gfoo (a :*: b) = gfoo a + gfoo b instance GB (M1 S s (Rec0 Word)) where {-# INLINE gfoo #-} gfoo (M1 (K1 x)) = x instance B A instance B F main :: IO () main = return () }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 11:29:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 11:29:18 -0000 Subject: [GHC] #10578: ghci line numbers are off by one In-Reply-To: <047.babcd43e2857d19107b478b8249a9812@haskell.org> References: <047.babcd43e2857d19107b478b8249a9812@haskell.org> Message-ID: <062.c6b203ab77ac8eb72d7463cfa4fdf330@haskell.org> #10578: ghci line numbers are off by one -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: osa1 Type: bug | Status: new Priority: low | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1067 -------------------------------------+------------------------------------- Changes (by hvr): * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 11:57:45 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 11:57:45 -0000 Subject: [GHC] #10649: Performance issue with unnecessary reboxing In-Reply-To: <044.4cf844fad84f7356a087aa89ed9fcd46@haskell.org> References: <044.4cf844fad84f7356a087aa89ed9fcd46@haskell.org> Message-ID: <059.4c6a6615ee2103c74a125bf8940b4463@haskell.org> #10649: Performance issue with unnecessary reboxing -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by pacak): using both -funfolding-use-threshold=10000 -funfolding-creation- threshold=10000 - seems to help in all cases -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 12:07:26 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 12:07:26 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.6cc6b19d29b5fa34850313d3240766bf@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by svenpanne): Simply trying to run ''"ghc -Wall"'' (plus a few warning/error-related flags) is just way to naive to be helpful for any non-toy program: Apart from being agnostic about the project root, this way you don't have a clue about which additional packages are needed and must be specified on the commandline, too. Furthermore, you might need to enable some GHC extensions, define some preprocessor symbols etc. This is exactly what .cabal files are for and why they are declarative, and any non-toy tool should use these as a basis. This situation is not much different from other language environments/IDEs, which all have some kind of "project file" (under varying names). Linting Java without setting the right CLASSPATH? No way... Linting C/C++ without setting the right include search paths and preprocessor symbols? No way... Perhaps you might want to have a look at the haskell-mode for Emacs, it does exactly what you want in a saner way, i.e. by looking at a potential .cabal file. Before I sound even more like Grumpy Cat on a really bad day, I'd like to hear from others what they think about this proposal. ;-) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 14:30:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 14:30:17 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.45da5f33d038158c891c01178ac2554a@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by FPtje): > Simply trying to run "ghc -Wall" (plus a few warning/error-related flags) is just way to naive to be helpful for any non-toy program Nonsense! ''ghc -Wall'' works fine when this issue is fixed/worked around! http://i.imgur.com/CxHO2S5.png Besides, even if there are ''other'' hurdles that would make ghc -Wall not work for single files in bigger projects, that does not mean that this issue should not be resolved. > [...] other language environments/IDEs > [...] haskell-mode for Emacs, it does exactly what you want in a saner way At the risk of sounding even grumpier, the core of this issue lies with ghc not finding modules that it arguably should. Therefore, the responsibility lies with ghc to solve it. You can tell me to use emacs and you can tell me that IDE's for other languages need more information before they can lint code, but that won't make the problem go away for ghc. The proposed fix isn't that difficult, makes proper sense given how the folder structure vs. module name works and should (AFAIK) not break any backwards compatibility. I don't see why you would want to throw this away at face value before expecting everyone who uses runhaskell, ghci and ghc to just work around it while stating "that's how IDEs/haskell linters do it". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 15:50:31 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 15:50: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.de1d9c1e2408925315b1c1c6fd0acfa5@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: patch Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1073 -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"3448f9827d2364b91bc60134aa38b74849b9d54e/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="3448f9827d2364b91bc60134aa38b74849b9d54e" Reduce non-determinism in ABI hashes with RULES and instance decls Summary: Before this change the `RULES` would be attached to one for the names from the module that appear on the left hand side. The choice depended on the `uniq` that was generated, which are known to be non-deterministic (a separate, bigger problem). Now we use `OccName`s which should be stable. Analogously for instance declarations, but they are attached to one of the types involved. Test Plan: contbuild it made `Data.Text.Internal.Fusion.Common` interface stable, previously stream fusion rule would be attached either to `streamList` or `unstreamList` depending on if the module was compiled after `cabal clean` or after `find | grep '\.o$' | xargs rm`. Reviewers: simonpj, austin, bgamari, simonmar Subscribers: puffnfresh, thomie Differential Revision: https://phabricator.haskell.org/D1073 GHC Trac Issues: #4012 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 15:59:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 15:59:32 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.3e513fb0fd8be6a189113337ea6da00c@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by svenpanne): Simply saying "nonsense" is... well, nonsense. :-) As I already said several times: For very simple programs you might get away without specifying non-exposed packages, GHC extensions, preprocessor defines etc. on the commandline, but in general you simply don't, just take a look at a few packages on Hackage. So any tool not looking at a .cabal file (or somewhere else where similar information is stored, wherever that may be) is fundamentally flawed and restricted to toy problems. And there's still the problem that in general tools which go up in the directory hierarchy have problems when symbolic links are involved: `cd Yes; cd ..` is not always a no-op. I still fail to see what's wrong with using runghc/ghc/ghci from the top directory of your project or why that's considered to be so complicated... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 16:02:09 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 16:02:09 -0000 Subject: [GHC] #10650: Can't define GHCi :def macro with NoImplicitPrelude on Message-ID: <050.a9004b0bba20a10488d32b9b9c069466@haskell.org> #10650: Can't define GHCi :def macro with NoImplicitPrelude on -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Status: new Type: bug | Milestone: Priority: normal | Version: 7.10.1 Component: GHCi | Operating System: Unknown/Multiple Keywords: | Type of failure: GHC rejects Architecture: | valid program Unknown/Multiple | Blocked By: Test Case: | Related Tickets: #8640 Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- GHCi is unusually prohibitive in typechecking {{{:def}}} macros when {{{NoImplicitPrelude}}} is enabled. Here's an example to illustrate what I mean: {{{ $ ghci -XNoImplicitPrelude GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help ?> :def pf \str -> Prelude.return Prelude.$ ":! pointfree \"" Prelude.++ str Prelude.++ "\"" :1:111: Not in scope: type constructor or class ?String? :1:121: Not in scope: type constructor or class ?IO? :1:124: Not in scope: type constructor or class ?String? }}} I can understand the functions being out-of-scope when {{{NoImplicitPrelude}}} is on, but the type errors don't make any sense to me, especially since {{{:t}}} seems to pick up on the types just fine: {{{ ?> :t Prelude.return Prelude.return :: GHC.Base.Monad m => a -> m a ?> :t "\"" "\"" :: [GHC.Types.Char] }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 16:08:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 16:08:42 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.f92472e8de130323db0d7adab52b6c3d@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder Operating System: Unknown/Multiple | import submodule cd Type of failure: GHC rejects | Architecture: valid program | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by FPtje): > Simply saying "nonsense" is... well, nonsense. That's why I provided a screenshot. Please see my explanation on '''other hurdles''' on why that is no reason to not fix that issue > I still fail to see what's wrong with using runghc/ghc/ghci from the top directory of your project or why that's considered to be so complicated... The complicated bit is having your linter find out where that directory is. To repeat myself: > The only way for Sublime and sublimelinter-ghc to solve this problem is to try to find out the root path of the source and either give that to ghc/runhaskell or put that in an -i option. This would involve searching for cabal files, parsing haskell files, having the user set it manually or other things that go way beyond the idea of "tools that run a command on a file and show a pretty output in the text editor". Symbolic links should be looked at. Depending on how ghc mounts its libraries, that might be doable. I don't know the specifics, but even if that's the next bug, it's much better to not be able to deal with symbolic links than this issue. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 16:25:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 16:25:17 -0000 Subject: [GHC] #10651: Type checking issue with existential quantification, rank-n types and constraint kinds Message-ID: <046.13e821c10925b9eff72404016930e9cc@haskell.org> #10651: Type checking issue with existential quantification, rank-n types and constraint kinds -------------------------------------+------------------------------------- Reporter: Roboguy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Type checker) | Operating System: Unknown/Multiple Keywords: | Type of failure: GHC rejects Architecture: | valid program Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- I'm trying to create a library for working with lists with existentially quantified types and I ran into an issue implementing `mapM_` for my type (note that the `map` and `mapM` implementations both work fine): {{{#!hs {-# LANGUAGE RankNTypes, ExistentialQuantification, ConstraintKinds #-} data ConstrList c = forall a. c a => a :> ConstrList c | CNil infixr :> constrMap :: (forall a. c a => a -> b) -> ConstrList c -> [b] constrMap f (x :> xs) = f x : constrMap f xs constrMap f CNil = [] constrMapM :: Monad m => (forall a. c a => a -> m b) -> ConstrList c -> m [b] constrMapM f = sequence . constrMap f -- Doesn't work, even with the definition as undefined (?) constrMapM_ :: Monad m => (forall a. c a => a -> m b) -> ConstrList c -> m () constrMapM_ = undefined }}} It fails with this error message: {{{ /users/dyoung/Test.hs:16:16: Couldn't match type ?b0? with ?b? ?b0? is untouchable inside the constraints (c a) bound by the type signature for constrMapM_ :: c a => a -> m b0 at /users/dyoung/Test.hs:16:16-77 ?b? is a rigid type variable bound by the type signature for constrMapM_ :: Monad m => (forall a. c a => a -> m b) -> ConstrList c -> m () at /users/dyoung/Test.hs:16:16 Expected type: a -> m b0 Actual type: a -> m b In the ambiguity check for the type signature for ?constrMapM_?: constrMapM_ :: forall (c :: * -> Constraint) (m :: * -> *) b. Monad m => (forall a. c a => a -> m b) -> ConstrList c -> m () To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ?constrMapM_?: constrMapM_ :: Monad m => (forall a. c a => a -> m b) -> ConstrList c -> m () Failed, modules loaded: none. }}} If I add `AllowAmbiguousTypes`, it works when the definition is `undefined` but it doesn't work if I put the real definition in. I believe that this is accepted and works as I had intended on 7.8.3 (with the correct definition as well) after talking to some people on IRC, but I haven't personally tested it. bitemyapp on IRC noticed that it does compile on 7.10.1 if we add an extra argument of type `b` to both `constrMap_` and `constrMapM` and pass that value from `constrMapM_` to `constrMap` (I think all of those things must happen in order for this to work): {{{#!hs constrMapM :: Monad m => b -> (forall a. c a => a -> m b) -> ConstrList c -> m [b] constrMapM ignoredB f = sequence . constrMap f constrMapM_ :: Monad m => b -> (forall a. c a => a -> m b) -> ConstrList c -> m () constrMapM_ b f xs = fmap (const ()) (constrMapM b f xs) }}} Is this expected behavior? I don't fully understand the new ambiguity check. This kind of reminds me of linear types (or a relevant type system) in a way: we must make explicit use of the `b` to "discharge" it in order to have a valid type. Also, I notice that this works fine as well, which makes me think it the type error above is related to `ConstraintKinds`: {{{#!hs data AnyList f = forall a. (f a) :| (AnyList f) | Nil infixr :| anyMap :: (forall a. f a -> b) -> AnyList f -> [b] anyMap f (x :| xs) = f x : anyMap f xs anyMap _ Nil = [] anyMapM :: Monad m => (forall a. f a -> m b) -> AnyList f -> m [b] anyMapM f xs = sequence (anyMap f xs) anyMapM_ :: Monad m => (forall a. f a -> m b) -> AnyList f -> m () anyMapM_ f xs = fmap (const ()) (anyMapM f xs) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 16:27:37 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 16:27:37 -0000 Subject: [GHC] #3134: encodeFloat . decodeFloat In-Reply-To: <045.24712bc58e93c54f33f4f129effc8533@haskell.org> References: <045.24712bc58e93c54f33f4f129effc8533@haskell.org> Message-ID: <060.90034c489019ad0639da9af29007ce13@haskell.org> #3134: encodeFloat . decodeFloat -------------------------------------+------------------------------------- Reporter: roland | Owner: Type: bug | Status: new Priority: normal | Milestone: ? Component: Prelude | Version: 6.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): daniel.is.fischer, perhaps you would like to have another look now? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 16:32:38 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 16:32:38 -0000 Subject: [GHC] #10543: MacOS: validate fails on \u In-Reply-To: <047.a887440a0df817cb06caf9fc53c8c2c9@haskell.org> References: <047.a887440a0df817cb06caf9fc53c8c2c9@haskell.org> Message-ID: <062.8fd6e3b0b4ca42e003c91fd0d27e4b1f@haskell.org> #10543: MacOS: validate fails on \u -------------------------------------+------------------------------------- Reporter: trommler | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: invalid | Keywords: cpp Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1004 -------------------------------------+------------------------------------- Comment (by rodlogic): For what is worth, I have created an issue with Homebrew [https://github.com/Homebrew/homebrew/issues/41777 here]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 17:01:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 17:01:47 -0000 Subject: [GHC] #10652: Better cache performance in Array# Message-ID: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: | Owner: MikeIzbicki | Status: new Type: feature | Milestone: request | Version: 7.10.1 Priority: normal | Operating System: Unknown/Multiple Component: Compiler | Type of failure: None/Unknown Keywords: | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- A common use case for arrays is to loop over them, performing an operation on each element of the array. For `ByteArray#`s, this is guaranteed to have good cache performance: When element `i` is accessed, the CPU's prefetcher will ensure that the element `i+1` is already sitting in cache, so the next loop will not suffer a cache miss. Currently, the `Array#` and `SmallArray#` types do not significantly benefit from the prefetcher. This feature request asks for a few new primops that would improve the situation. My understanding is that the "raw" element in an `Array#` is actually a pointer to the region in memory associated with the "logical" element of the array. When looping, the subsequent pointers are guaranteed to get prefetched, but the subsequent logical element is not guaranteed to be prefetched. In particular, if we'll only get the benefits of prefetching on the logical elements if we're lucky enough that the memory manager happened to allocate these logical elements on the heap next to each other. I don't know enough about GHC internals to check the source code, but my experiments demonstrate that this is not currently happening in my use case, resulting in rather significant performance degradations. (The experiments are rather complicated, so I'm not attaching them.) I propose adding the primops: {{{ packArray# :: Array# a -> b -> b packSmallArray# :: SmallArray# a -> b -> b packMutableArray# :: MutableArray# s a -> State# s -> State# s packSmallMutableArray# :: SmallMutableArray# s a -> State# s -> State# s }}} These operations would have the semantic effect of noops, with the exception that they request that the logical elements in the arrays be arranged adjacently in memory. Thus, future loops over the arrays would benefit from CPU prefetching. There are a number of ways the memory manager could handle these requests, and I don't particular care which is chosen. For example, the memory manager could rearrange the memory immediately or wait until the next garbage collection pass and do it then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 17:35:16 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 17:35:16 -0000 Subject: [GHC] #8131: T7571 with WAY=llvm fails, but not WAY=optllvm In-Reply-To: <052.22eb4f882263987206e929bacae5db28@haskell.org> References: <052.22eb4f882263987206e929bacae5db28@haskell.org> Message-ID: <067.b50cb7c0af0929e49e412834643175ef@haskell.org> #8131: T7571 with WAY=llvm fails, but not WAY=optllvm -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Windows | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | llvm/should_compile/T8131 | Blocking: | Differential Revisions: Phab:D624 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: thomie, this looks like a much different failure mode than what this bug described (which was due to our inability to guarantee that alignments that were passed to LLVM were constant). Could you open a new bug describing this new failure? I'm going to close this. Feel free to add a reference to the new bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 18:02:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 18:02:17 -0000 Subject: [GHC] #8583: Associated pattern synonyms In-Reply-To: <045.39184734af9bc44765e305261b59a6ed@haskell.org> References: <045.39184734af9bc44765e305261b59a6ed@haskell.org> Message-ID: <060.b61dd61bd645eb5dd77ea4ac00ee913e@haskell.org> #8583: Associated pattern synonyms -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | PatternSynonyms Type of failure: None/Unknown | Architecture: Blocked By: 5144 | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > The PatternSynonyms wiki page has a section on (typeclass-)associated > pattern synonyms: > > {{{ > class ListLike l where > pattern Nil :: l a > pattern Cons :: a -> l a -> a > isNil :: l a -> Bool > isNil Nil = True > isNil (Cons _ _) = False > append :: l a -> l a -> l a > > instance ListLike [] where > pattern Nil = [] > pattern Cons x xs = x:xs > append = (++) > > headOf :: (ListLike l) => l a -> Maybe a > headOf Nil = Nothing > headOf (Cons x _) = Just x > }}} New description: The PatternSynonyms wiki page has a section on (typeclass-)associated pattern synonyms: {{{#!hs class ListLike l where pattern Nil :: l a pattern Cons :: a -> l a -> a isNil :: l a -> Bool isNil Nil = True isNil (Cons _ _) = False append :: l a -> l a -> l a instance ListLike [] where pattern Nil = [] pattern Cons x xs = x:xs append = (++) headOf :: (ListLike l) => l a -> Maybe a headOf Nil = Nothing headOf (Cons x _) = Just x }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 18:02:40 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 18:02:40 -0000 Subject: [GHC] #8583: Associated pattern synonyms In-Reply-To: <045.39184734af9bc44765e305261b59a6ed@haskell.org> References: <045.39184734af9bc44765e305261b59a6ed@haskell.org> Message-ID: <060.6f2806b4895856bcff4e96d5afcd24b7@haskell.org> #8583: Associated pattern synonyms -------------------------------------+------------------------------------- Reporter: cactus | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | PatternSynonyms Type of failure: None/Unknown | Architecture: Blocked By: 5144 | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > The PatternSynonyms wiki page has a section on (typeclass-)associated > pattern synonyms: > > {{{#!hs > class ListLike l where > pattern Nil :: l a > pattern Cons :: a -> l a -> a > isNil :: l a -> Bool > isNil Nil = True > isNil (Cons _ _) = False > append :: l a -> l a -> l a > > instance ListLike [] where > pattern Nil = [] > pattern Cons x xs = x:xs > append = (++) > > headOf :: (ListLike l) => l a -> Maybe a > headOf Nil = Nothing > headOf (Cons x _) = Just x > }}} New description: The PatternSynonyms wiki page has a section on (typeclass-)associated pattern synonyms: {{{#!hs class ListLike l where pattern Nil :: l a pattern Cons :: a -> l a -> a isNil :: l a -> Bool isNil Nil = True isNil (Cons _ _) = False append :: l a -> l a -> l a instance ListLike [] where pattern Nil = [] pattern Cons x xs = x:xs append = (++) headOf :: (ListLike l) => l a -> Maybe a headOf Nil = Nothing headOf (Cons x _) = Just x }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 18:30:45 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 18:30:45 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation Message-ID: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature | Status: new request | Milestone: 7.12.1 Priority: normal | Version: 7.11 Component: Compiler | Operating System: Unknown/Multiple Keywords: pattern | Type of failure: None/Unknown synonyms | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Suppose I have the following two modules. {{{#!hs {-# LANGUAGE PatternSynonyms #-} module A where data A = A2 Int Int pattern A1 a <- A2 a _ where A1 a = A2 a 0 }}} {{{#!hs module B where import A ( A(..) ) a = A1 0 }}} When I try to compile `B.hs` I get an error because `A1` is unbound in module `B`. {{{ $ ghc --make B.hs [1 of 2] Compiling A ( A.hs, A.o ) [2 of 2] Compiling B ( B.hs, B.o ) B.hs:5:5: Not in scope: data constructor ?A1? Perhaps you meant ?A2? (imported from A) }}} The issue is that the import `A(..)` brings all of `A`s data constructors and accessors into scope, but not any associated pattern synonyms. Instead I have to enable `PatternSynonyms` in module `B` (or just import everything from `A`). {{{#!hs {-# LANGUAGE PatternSynonyms #-} module B where import A ( A(..), pattern A1 ) a = A1 0 }}} I'd like to propose that we extend the semantics of the `A(..)` import/export notation to include any associated pattern synonyms. I think this is in line with the spirit of `PatternSynonyms`, that the extension should allow internal refactoring without causing API breakage, and that the extension should only need to be enabled to *define* pattern synonyms. FYI, this issue does appear in the wild, I ran into it while working on https://phabricator.haskell.org/D861 and had to modify two import lists in Cabal. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 18:39:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 18:39:58 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.a1dcd48253b7ec4266397e3b0d7aff61@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern Operating System: Unknown/Multiple | synonyms Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I don't really agree. What would you say for {{{ pattern P x = Tree (Just x) }}} would you put it in list or Maybe? What about this? {{{ pattern Q x = (x, True) }}} Would you export it with pairs? Pattern synonyms inherently do not belong to one type in the way that data constructors do. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 18:43:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 18:43:05 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.b41d7a79bce7b7dd281aabd90646d781@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Getting better cache behaviour would be a good thing! I don't know the impl in detail either, but I'm pretty sure that all you need to do is to use unboxed arrays. Certainly before even beginning to think about new primops we need to understand ''in detail'' what the current implementation does, and why it has poor cache behaviour. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 19:59:16 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 19:59:16 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.2e9f3627099815751a7a7cd126b7b938@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern Operating System: Unknown/Multiple | synonyms Type of failure: None/Unknown | Architecture: Blocked By: | Unknown/Multiple Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): I would argue that `P` belongs to whatever type `Tree` constructs (but not `Maybe`), and that `Q` belongs to pairs. More generally, https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/syntax- extns.html#idp23521760 says that pattern synonyms have a type `C => t1 -> t2 -> ... -> t`; I would argue that a pattern synonym belongs to the outermost type constructor of `t`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 20:10:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 20:10:10 -0000 Subject: [GHC] #10654: Better error message regarding type synonyms and PolyKinds Message-ID: <047.a210a64784e6d31cfc284639bd72d82d@haskell.org> #10654: Better error message regarding type synonyms and PolyKinds -------------------------------------+------------------------------------- Reporter: abbradar | Owner: Type: feature | Status: new request | Milestone: Priority: low | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: Other Architecture: | Blocked By: Unknown/Multiple | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Followup of https://mail.haskell.org/pipermail/haskell- cafe/2015-July/120505.html {{{ ghci> :set -XPolyKinds ghci> type Test a = a ghci> type Huh = Test :6:1: Type synonym ?Test? should have 2 arguments, but has been given 1 In the type declaration for ?Huh? }}} (Notice the number of arguments reported) Jonas Scholl at haskell-cafe suggested that the additional invisible argument is a kind argument, which indeed looks to be the case, as he demonstrated: {{{ Prelude> :set -XPolyKinds -XDataKinds -XKindSignatures Prelude> type Test a = a Prelude> type Huh a = Test (a :: Bool) Prelude> type Bar = Huh :5:1: Type synonym ?Huh? should have 1 argument, but has been given none In the type declaration for ?Bar? }}} A better error message may be desirable here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 20:56:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 20:56:15 -0000 Subject: [GHC] #10655: Add wildcards (from partial type signatures) to template-haskell Message-ID: <047.377e7ec79ced4344fe833b9b8e6ee665@haskell.org> #10655: Add wildcards (from partial type signatures) to template-haskell -------------------------------------+------------------------------------- Reporter: abbradar | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.10.1 Component: Template | Operating System: Unknown/Multiple Haskell | Type of failure: None/Unknown Keywords: | Blocked By: Architecture: | Related Tickets: Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Ditto. I imagine `WildcardT` added to the `Language.Haskell.TH.Syntax.Type`, though I have no idea of exact volume of needed work. Looking at [https://github.com/ghc/ghc/blob/master/libraries/template- haskell/Language/Haskell/TH/Syntax.hs#L1465], this is unresolved in HEAD, too. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 21:32:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 21:32:36 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.49f19c20b2bd7fa22586328ca5b7b839@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1057 -------------------------------------+------------------------------------- Old description: > After today's weekly Backpack call, we have come to the conclusion that > we have two different types of "packages" in the Backpack world: > > 1. Cabal packages, which have a single `.cabal` file and are a unit of > distribution which get uploaded to Hackage, and > > 2. Backpack packages, of which there may be multiple defined in a > Backpack file shipped with a Cabal package; and are the building blocks > for modular development in the small. > > It's really confusing to have both of these called packages: thus, we > propose to rename all occurrences of Backpack package to unit. A Cabal > ''package'' may contain MULTIPLE Backpack ''units'', and old-style Cabal > files will only define one unit. Every Cabal package has a distinguished > unit (with the same name as the package) that serves as the publically > visible unit. > > A Cabal package remains > * The unit of distribution > * The unit that Hackage handles > * The unit of versioning > * The unit of ownership (who maintains it etc) > > Here are some of the consequences: > > 1. The "installed package database" no longer maintains a one-to-one > mapping between Cabal packages and entries in the database. This > invariant is being dropped for two reasons: (1) With a Nix-style > database, a package `foo-0.1` may be installed many times with different > dependencies / source code, all of which live in the installed package > database. (2) With Backpack, a package containing a Backpack file may > install multiple units. To avoid having to rename *everything*, we'll > keep calling this the installed package database, but really it's more > like an installed *unit* database. > > 2. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather > than a Cabal package. (I think this actually makes the function of these > identifiers clearer.) We'll also distinguish Cabal-file level > `PackageName`s from Backpack-file `UnitName`s. Installed units continue > to be identified by `InstalledPackageId`. > > 3. The source-level syntax of Backpack files will use `unit` in place of > where `package` was used before. > > 4. For old-style packages, Cabal will continue to write and register a > single entry in the installed package database. For Backpack packages, > Cabal will register as many entries as is necessary to install a package. > The entry with the same `UnitName` as `PackageName` is publically visible > to other packages. If a Backpack file defines other packages, those > packages are registered with different `UnitName`s (giving them different > `InstalledPackageId`s) which are not publically visible. The non- > publically visible packages will have their description/URL/etc fields > blank, and have a pointer to the "real" package. > > 5. If when installing a unit, we discover that it is already present in > the database, we check if the ABI hashes are the same. If they are, we > simply skip installing the unit but otherwise proceed. If the ABI hashes > are not the same, we error: the units we are installing need to be > recompiled against the unit present in the database. New description: After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal ''package'' may contain MULTIPLE Backpack ''units'', and old-style Cabal files will only define one unit. Every Cabal package has a distinguished unit (with the same name as the package) that serves as the publically visible unit. A Cabal package remains * The unit of distribution * The unit that Hackage handles * The unit of versioning * The unit of ownership (who maintains it etc) Here are some of the consequences: 1. The "installed package database" no longer maintains a one-to-one mapping between Cabal packages and entries in the database. This invariant is being dropped for two reasons: (1) With a Nix-style database, a package `foo-0.1` may be installed many times with different dependencies / source code, all of which live in the installed package database. (2) With Backpack, a package containing a Backpack file may install multiple units. To avoid having to rename *everything*, we'll keep calling this the installed package database, but really it's more like an installed *unit* database. 2. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Installed units are identified by an `InstalledUnitId` instead of an `InstalledPackageId`. 3. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 4. For old-style packages, Cabal will continue to write and register a single entry in the installed package database. For Backpack packages, Cabal will register as many entries as is necessary to install a package. The entry with the same `UnitName` as `PackageName` is publically visible to other packages. If a Backpack file defines other packages, those packages are registered with different `UnitName`s (giving them different `InstalledPackageId`s) which are not publically visible. The non- publically visible packages will have their description/URL/etc fields blank, and have a pointer to the "real" package. 5. If when installing a unit, we discover that it is already present in the database, we check if the ABI hashes are the same. If they are, we simply skip installing the unit but otherwise proceed. If the ABI hashes are not the same, we error: the units we are installing need to be recompiled against the unit present in the database. -- Comment (by ezyang): OK. (I was thinking about BC for Cabal users but I guess it should not be too bad. We'll see.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 21:38:19 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 21:38:19 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.6d9b0d8e253ffb23c6692782667fecef@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): In my specific use case, unboxed arrays are not possible because each element does not have a fixed size (think something like `Integer`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 23:45:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 23:45:15 -0000 Subject: [GHC] #10651: Type checking issue with existential quantification, rank-n types and constraint kinds In-Reply-To: <046.13e821c10925b9eff72404016930e9cc@haskell.org> References: <046.13e821c10925b9eff72404016930e9cc@haskell.org> Message-ID: <061.824594ee40a10cd694784f05766b23c9@haskell.org> #10651: Type checking issue with existential quantification, rank-n types and constraint kinds -------------------------------------+------------------------------------- Reporter: Roboguy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Keywords: Resolution: | Architecture: Operating System: Unknown/Multiple | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | Blocking: Blocked By: | Differential Revisions: Related Tickets: | -------------------------------------+------------------------------------- Comment (by mniip): > I believe that this is accepted and works as I had intended on 7.8.3 (with the correct definition as well) after talking to some people on IRC, but I haven't personally tested it It only works with `undefined` in 7.8.3. The proper implementation fails. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 23:56:49 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 23:56:49 -0000 Subject: [GHC] #9243: Recompilation avoidance doesn't work for -fno-code/-fwrite-interface In-Reply-To: <045.eb0d37b8e28f9b0d21ba7b721e124a6b@haskell.org> References: <045.eb0d37b8e28f9b0d21ba7b721e124a6b@haskell.org> Message-ID: <060.996a070ae7241d465a2bbd2fdfb8d8c6@haskell.org> #9243: Recompilation avoidance doesn't work for -fno-code/-fwrite-interface -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: closed Priority: high | Milestone: 7.10.1 Component: Compiler | Version: 7.9 Resolution: fixed | Keywords: backpack Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D596 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"bc604bdb0144010e8582caa6ea159ca0446c04f2/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="bc604bdb0144010e8582caa6ea159ca0446c04f2" Update assert to fix retc001 and retc002 (#9243) Since 2223e196b2dc5340d70e58be011c279d381b4319, maybe_old_linkable can be Nothing even with an up-to-date interface file. This happens when compiling with --make -fno-code -fwrite-interface. See also Note [Recompilation checking when typechecking only] in GhcMake.hs. This fixes retc001 and retc002 when ghc_debugged. Differential Revision: https://phabricator.haskell.org/D1077 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 17 23:56:49 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 17 Jul 2015 23:56:49 -0000 Subject: [GHC] #10224: Partial type signatures generate typed hole warnings In-Reply-To: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> References: <045.c9ae412f65588bd6476cb40ffda876e8@haskell.org> Message-ID: <060.c12fc3a465b8768ead1545abdecca548@haskell.org> #10224: Partial type signatures generate typed hole warnings -------------------------------------+------------------------------------- Reporter: quchen | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"f607393b7ffa8a06417e3f1263d2610d6bfe8279/ghc"]: {{{ #!CommitTicketReference repository="ghc" revision="f607393b7ffa8a06417e3f1263d2610d6bfe8279" Testsuite: accept new stderr for T9497{a,b,c}-run (#10224) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 00:09:43 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 00:09:43 -0000 Subject: [GHC] #10654: Better error message regarding type synonyms and PolyKinds In-Reply-To: <047.a210a64784e6d31cfc284639bd72d82d@haskell.org> References: <047.a210a64784e6d31cfc284639bd72d82d@haskell.org> Message-ID: <062.be8aa67a6b91496039641aa76d3ba069@haskell.org> #10654: Better error message regarding type synonyms and PolyKinds -------------------------------------+------------------------------------- Reporter: abbradar | Owner: Type: feature request | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #10516 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #10516 Comment: Thanks for the report. A fix is underway in #10516. {{{ ?:1> :set -XPolyKinds ?:2> type Test a = a ?:3> type Huh = Test :3:1: error: The type synonym ?Test? should have 1 argument, but has been given none In the type synonym declaration for ?Huh? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 00:56:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 00:56:36 -0000 Subject: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules In-Reply-To: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> References: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> Message-ID: <066.15eca773096c9f3da4eff95749ce0959@haskell.org> #10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: dreixel Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1081 -------------------------------------+------------------------------------- Changes (by osa1): * cc: omeragacan@? (added) * differential: => D1081 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 00:57:18 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 00:57:18 -0000 Subject: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules In-Reply-To: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> References: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> Message-ID: <066.d328c60f961e6fd513496f5c9d03dbe5@haskell.org> #10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1081 -------------------------------------+------------------------------------- Changes (by osa1): * owner: dreixel => osa1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 04:09:51 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 04:09:51 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.d29041d2c4c93af04ea71e05ec105145@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by carter): Mike: have you looked at how the gc arranges values only reachable via a boxed array? I guess one problem I can think of off hand is that your primops get tricky when a value is shared across Multiple boxed arrays! A valid and interesting idea would be to just make sure that the gc places unshared values reachable only via a boxed array continuously when doing a copying gc. I should try to look into this myself. Relatedly: bob Harper et all did prove a few years ago that certain gc strategies do result in cache optimal memory layouts. But I don't know if ghc does a traversal order that maps to their specific proof. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 04:27:59 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 04:27:59 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.ebd1d4f593bb8871d94963df3e1908cc@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by MikeIzbicki): Replying to [comment:3 carter]: > Mike: have you looked at how the gc arranges values only reachable via a boxed array? I wouldn't even know where to look for this. My only evidence that things aren't aligned is the huge number of cache misses I'm getting. But I suppose these cache misses could be caused by something else. > I guess one problem I can think of off hand is that your primops get tricky when a value is shared across Multiple boxed arrays! My proposal doesn't run into this problem. I'm specifically not proposing that GHC try to find a "globally optimal" memory allocation scheme. Instead, all I want is that immediately after these operations are called memory is aligned. A subsequent call to these primops on another array with the same elements in a different order would destroy that alignment. > A valid and interesting idea would be to just make sure that the gc places unshared values reachable only via a boxed array continuously when doing a copying gc. I should try to look into this myself. I think this would work for me, and probably be better in general performance-wise. I was just (maybe naively) imagining this would be harder to implement. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 05:10:23 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 05:10:23 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.e30b1c1db03d99e4cd65ba6e9c9cc28d@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by carter): I actually think that it'd be easier/safe space safety wise to provide the latter (eg, preserve sharing!). your proposed alternative operations requires doing a GC style movement of the values held in the underlying array to have the right semantics I'm not sure where to look in the GC myself, but i think https://github.com/ghc/ghc/blob/master/rts/sm/Evac.c#L711-L725 is probably a good starting point -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 05:17:21 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 05:17:21 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.e5c389c814538691fcf6ec6288a1f3df@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by carter): roughly: as long as the GC does a *breadth first* copy of the values reachable through a boxed array, in left to right order, you should have the behavior you want. i *believe* ghc roughly does this in a depth first order, but i could be wrong likewise, https://ghc.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/GC/Copying provides some more information about the rough flavor of the copying algorithms. one challenge might be that the underlying storage layer of the GC is block oriented, and i believe the GC can promote a block of memory between generations instead of just copying -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 05:46:59 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 05:46:59 -0000 Subject: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules In-Reply-To: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> References: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> Message-ID: <066.49fbe0530e5919c68852695a6504d405@haskell.org> #10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: D1081 -------------------------------------+------------------------------------- Changes (by hvr): * cc: kosmikus (added) Comment: Replying to [comment:6 simonpj]: > Andres Loh has offered to take over `Generic` and `DeriveAnyClass`, but only at the end of the summer. > > I'm not sure what his Trac alias is. It's `kosmikus` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 09:10:38 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 09:10:38 -0000 Subject: [GHC] #10654: Better error message regarding type synonyms and PolyKinds In-Reply-To: <047.a210a64784e6d31cfc284639bd72d82d@haskell.org> References: <047.a210a64784e6d31cfc284639bd72d82d@haskell.org> Message-ID: <062.4b850fe80347a6c6542201e01dbf61c6@haskell.org> #10654: Better error message regarding type synonyms and PolyKinds -------------------------------------+------------------------------------- Reporter: abbradar | Owner: Type: feature request | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Other | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #10516 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by abbradar): Thanks and sorry for the duplicate, I will search better next time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 09:14:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 09:14:36 -0000 Subject: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules In-Reply-To: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> References: <051.f823b016355f38c348182e98da9d4ae1@haskell.org> Message-ID: <066.cfcbc74ee38a77d7b660b7169ad58c36@haskell.org> #10487: DeriveGeneric breaks when the same data name is used in different modules -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: osa1 Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: Phab:D1081 -------------------------------------+------------------------------------- Changes (by thomie): * differential: D1081 => Phab:D1081 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 09:16:13 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 09:16:13 -0000 Subject: [GHC] #10655: Add wildcards (from partial type signatures) to template-haskell In-Reply-To: <047.377e7ec79ced4344fe833b9b8e6ee665@haskell.org> References: <047.377e7ec79ced4344fe833b9b8e6ee665@haskell.org> Message-ID: <062.b2fee66d0f82fca101b8fdbc9800a2cf@haskell.org> #10655: Add wildcards (from partial type signatures) to template-haskell -------------------------------------+------------------------------------- Reporter: abbradar | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by abbradar): * status: new => closed * resolution: => duplicate Comment: A more thorough search revealed #10548, sorry for the noise. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 09:33:51 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 09:33:51 -0000 Subject: [GHC] #10656: Ability to get stack traces from Haskell code Message-ID: <046.afad267b86c2cf45e3280bfe1e22e59b@haskell.org> #10656: Ability to get stack traces from Haskell code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Tarrasch Type: feature | Status: new request | Milestone: 7.12.1 Priority: normal | Version: 7.10.1 Component: Compiler | Operating System: Unknown/Multiple Keywords: | Type of failure: None/Unknown Architecture: | Blocked By: Unknown/Multiple | Related Tickets: #3693 Test Case: | Blocking: | Differential Revisions: Phab:D963 | -------------------------------------+------------------------------------- With the merge of Phab:D169 and Phab:D396 (included in GHC 7.10.1) GHC now has the ability to produce DWARF debugging information in compiled binaries. It would be nice if Haskell programs could request stack backtraces from the RTS. Tarrasch has some work in this direction in Phab:D963 however there are a number of questions that remain outstanding, * do we want to rely on an external library for parsing DWARF information? If so, how do we address portability concerns? * What should the Haskell-land interfaces look like? Writing down some concrete use-cases would help here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 09:34:22 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 09:34:22 -0000 Subject: [GHC] #3693: Show stack traces In-Reply-To: <043.7c288f8e774d3806292d73b1513892ec@haskell.org> References: <043.7c288f8e774d3806292d73b1513892ec@haskell.org> Message-ID: <058.b02b27908917acbabef71c55467e7fad@haskell.org> #3693: Show stack traces -------------------------------------+------------------------------------- Reporter: jpet | Owner: Tarrasch Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Runtime System | Version: 6.10.4 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #10656 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * related: => #10656 Comment: Currently this is being worked on in D963. I am going to close this ticket as the original issue of GHC binaries lacking debug information has been resolved. I have opened #10656 to track the process of exposing this debug information to Haskell programs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 10:23:22 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 10:23:22 -0000 Subject: [GHC] #10656: Ability to get stack traces from Haskell code In-Reply-To: <046.afad267b86c2cf45e3280bfe1e22e59b@haskell.org> References: <046.afad267b86c2cf45e3280bfe1e22e59b@haskell.org> Message-ID: <061.2fb01f6d0eacfb37c6f18537b3452154@haskell.org> #10656: Ability to get stack traces from Haskell code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Tarrasch Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: #3693 | Blocking: | Differential Revisions: Phab:D963 -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > With the merge of Phab:D169 and Phab:D396 (included in GHC 7.10.1) GHC > now has the ability to produce DWARF debugging information in compiled > binaries. > > It would be nice if Haskell programs could request stack backtraces from > the RTS. Tarrasch has some work in this direction in Phab:D963 however > there are a number of questions that remain outstanding, > > * do we want to rely on an external library for parsing DWARF > information? If so, how do we address portability concerns? > > * What should the Haskell-land interfaces look like? Writing down some > concrete use-cases would help here. New description: With the merge of Phab:D169 and Phab:D396 (included in GHC 7.10.1, see #3693 for details) GHC now has the ability to produce DWARF debugging information in compiled binaries. It would be nice if Haskell programs could request stack backtraces from the RTS. Tarrasch has some work in this direction in Phab:D963 however there are a number of questions that remain outstanding, * do we want to rely on an external library for parsing DWARF information? If so, how do we address portability concerns? * What should the Haskell-land interfaces look like? Writing down some concrete use-cases would help here. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 14:22:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 14:22:28 -0000 Subject: [GHC] #10656: Ability to get stack traces from Haskell code In-Reply-To: <046.afad267b86c2cf45e3280bfe1e22e59b@haskell.org> References: <046.afad267b86c2cf45e3280bfe1e22e59b@haskell.org> Message-ID: <061.0e490d442e0c34d93da0ce29bf05b98c@haskell.org> #10656: Ability to get stack traces from Haskell code -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Tarrasch Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3693 | Differential Revisions: Phab:D963 -------------------------------------+------------------------------------- Comment (by Tarrasch): Thanks for the rescoping @bgmari! Once we've merged something like Phab:D963. Then we can create new tickets for (i) getting it to use DWARF and a ticket for (ii) giving stack traces to Haskell land exception handlers. Phab:D963 does actually not even use the DWARF stuff. See the abandoned patch Phab:D662 for an implementation using that. Phab:D662 got abandoned since it did too much at once. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 16:56:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 16:56:15 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted Message-ID: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: typecheck/should_compile/T2497 | Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- {{{ $ make TEST=T2497 WAY=optasm EXTRA_HC_OPTS=-fsimpl-tick-factor=10000 TEST_HC=ghc-7.11.20150711 ... T2497.hs:18:1: warning: Defined but not used: ?beq? ghc: panic! (the 'impossible' happened) (GHC version 7.11.20150711 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired rule 1 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: 40000 ... }}} The test is very small: {{{ module ShouldCompile() where eq :: Eq a => a -> a -> Bool eq = (==) {-# RULES "rule 1" forall x y. x == y = y `eq` x #-} }}} The problem does not occur with ghc-7.10.1. Curiously the problem goes away when I change the module header to `module ShouldCompile where`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:26:10 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:26:10 -0000 Subject: [GHC] #10294: Missing instances if compiling with -fplugin In-Reply-To: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> References: <046.47fd486c7f73b488b5247db11cbe3c48@haskell.org> Message-ID: <061.168fb535c32ecdf57ea0c74b0d76fa89@haskell.org> #10294: Missing instances if compiling with -fplugin -------------------------------------+------------------------------------- Reporter: jscholl | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: GHC rejects | Test Case: valid program | plugins/T10294, plugins/T10294a Blocked By: 10420 | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 7.12.1 Comment: Nevermind, that warning only shows up when ghc is compiled with `-DDEBUG`, and is not related to this ticket at all. Closing as duplicate again. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:49:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:49:28 -0000 Subject: [GHC] #7919: Heap corruption (segfault) from large 'let' expression In-Reply-To: <045.3707d678a38441ef54b667e63e238d84@haskell.org> References: <045.3707d678a38441ef54b667e63e238d84@haskell.org> Message-ID: <060.ea4cd4b9adf11634139a3806990f20c8@haskell.org> #7919: Heap corruption (segfault) from large 'let' expression -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: bug | Status: infoneeded Priority: high | Milestone: 7.12.1 Component: Runtime System | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"dcaa4865a4ee99888e90a80b7f09e11e71689f6c/ghc" dcaa4865/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dcaa4865a4ee99888e90a80b7f09e11e71689f6c" Testsuite: mark T7919 expect_broken_for(#7919, ['optasm','dyn','optllvm']) It fails with a segmentation fault. Occasionally also for WAY=threaded2. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:49:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:49:28 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.d89ef8b3aa6aa64574140ab85aac579f@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"dc6e55626cf25bcda1cab52f92591e16bddd101d/ghc" dc6e556/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dc6e55626cf25bcda1cab52f92591e16bddd101d" Testsuite: mark T2497 expect_broken_for(#10657, ['optasm', 'optllvm']) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:49:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:49:28 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.14a34c77b8b4bd43386836b1abfdbe36@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 Revisions: Phab:751 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"11f86125d7fda92d1d9962ef5c07a58eb9a2901f/ghc" 11f86125/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="11f86125d7fda92d1d9962ef5c07a58eb9a2901f" Testsuite: mark 3 tests expect_broken_for(#10181, ['optasm', 'optllvm']) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:49:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:49:28 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.e64f87a9632237312f823f388d6601ab@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 Revisions: Phab:751 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"16a87397295fa92bcbe7a2c6277f938622b93969/ghc" 16a87397/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="16a87397295fa92bcbe7a2c6277f938622b93969" Testsuite: mark qq007 and qq008 expect_broken(#10181) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:56:17 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:56:17 -0000 Subject: [GHC] #10181: Lint check: arity invariant In-Reply-To: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> References: <046.f8da9bf8eb8c5c91d5a26d3f26e33176@haskell.org> Message-ID: <061.26775b2fb44512b9608512fd9efbfd0c@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 Revisions: Phab:751 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"cbb4d7887e6ff039c9a482178435a688b4c5d4f8/ghc" cbb4d788/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cbb4d7887e6ff039c9a482178435a688b4c5d4f8" Testsuite: mark qq007 and qq008 expect_broken(#10047) This fixes the wrong ticket number in 16a87397295fa92bcbe7a2c6277f938622b93969 (#10181). }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 18:56:17 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 18:56:17 -0000 Subject: [GHC] #10047: inconsistency in name binding between splice and quasiquotation In-Reply-To: <047.467ed7feed46ef69006cfd30a0e1c7fb@haskell.org> References: <047.467ed7feed46ef69006cfd30a0e1c7fb@haskell.org> Message-ID: <062.398bd3d25424a5ea31219b02e1b1d2d0@haskell.org> #10047: inconsistency in name binding between splice and quasiquotation -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T10047 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"cbb4d7887e6ff039c9a482178435a688b4c5d4f8/ghc" cbb4d788/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="cbb4d7887e6ff039c9a482178435a688b4c5d4f8" Testsuite: mark qq007 and qq008 expect_broken(#10047) This fixes the wrong ticket number in 16a87397295fa92bcbe7a2c6277f938622b93969 (#10181). }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 19:21:48 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 19:21:48 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.df4b51d10c02b5d959f3dcee15e57773@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder | import submodule cd Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Chiming in here at Sven's request (at the end of comment:7), though I don't feel strongly: I think the original request is reasonable, well-specified, backward compatible, and straightforward to implement. I also think that the objections raised here are reasonable, in that users experienced in other languages would find the proposed behavior unexpected and that the limitation in GHC described here seems unlikely to bite in non-trivial situations. So I think the best way around this impasse is to see what other users think. After all, I think the burden lies with the requester of a new feature to ensure that public opinion agrees with the request before anyone considers implementing. This is especially true with simple user- facing changes like this one. So, @FPtje, gather a groundswell of support for this feature request, and it will be given more consideration. In any case, thanks to both of you for your impassioned arguments above -- users who care about their software is what makes open-source software great. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 19:23:29 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 19:23:29 -0000 Subject: [GHC] #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds Message-ID: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: gadt/termination | Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- See attachment for the result of running `make TEST=termination WAY=optasm TEST_HC=ghc-7.11.20150711`. It starts with: {{{ *** Core Lint errors : in result of Worker Wrapper binds *** : warning: In a case alternative: (Equal ww_sRe :: Apply Omega Omega ~# t_asc) Non term variable ww_sRe *** Offending Program *** }}} The problem does not occur with ghc-7.10.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 19:24:45 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 19:24:45 -0000 Subject: [GHC] #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds In-Reply-To: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> References: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> Message-ID: <060.3ff0910c5bc549ca8ba14a238735e5c7@haskell.org> #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | gadt/termination Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * Attachment "gadt-termination-core-lint-error.txt" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 19:36:26 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 19:36:26 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.cfaa41214ed77c57f6ff27deab5ddff1@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): If `Q` belongs to pairs, then is it ever imported with `(..)` attached to some type? I would guess "no". I agree that the attachment of patterns to datatypes like this is fishy, but I see gridaphobe's point that it would be nice to shield the use of synonyms from clients. What if there were a way to declare that a pattern is attached to a type? For example: {{{ module A ( A(.., pattern A1) ) where ... }}} By adding `A1` to the export list of the type `A`, then it is imported with `A` as well. We would probably want a check that `A1`'s result type is indeed headed by `A`. This seems to make sense in re-exports as well, in case the pattern synonyms and original datatype are defined in different modules. (The use of the `pattern` keyword in there is redundant, but I like it anyway. Others may disagree.) gridaphobe, does this address your need? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 19:44:10 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 19:44:10 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.6a90d77c7672a54cc1afde46e215f95c@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * priority: high => highest * version: 7.11 => 7.10.2-rc2 * milestone: 7.12.1 => 7.10.2 Comment: Same problem with `ghc-7.10.1.20150715`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 19:50:55 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 19:50:55 -0000 Subject: [GHC] #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds In-Reply-To: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> References: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> Message-ID: <060.f68c056ba0d3149780b10e5388f0c3e2@haskell.org> #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | gadt/termination Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by thomie: Old description: > See attachment for the result of running `make TEST=termination > WAY=optasm TEST_HC=ghc-7.11.20150711`. It starts with: > > {{{ > *** Core Lint errors : in result of Worker Wrapper binds *** > : warning: > In a case alternative: (Equal ww_sRe :: Apply Omega Omega ~# t_asc) > Non term variable ww_sRe > *** Offending Program *** > }}} > > The problem does not occur with ghc-7.10.1. New description: See attachment for the result of running `make TEST=termination WAY=optasm TEST_HC=ghc-7.11.20150711`. It starts with: {{{ *** Core Lint errors : in result of Worker Wrapper binds *** : warning: In a case alternative: (Equal ww_sRe :: Apply Omega Omega ~# t_asc) Non term variable ww_sRe *** Offending Program *** }}} The problem does not occur with ghc-7.10.1 or ghc-7.10.2-rc2. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 20:14:52 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 20:14:52 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.38bdf977dc841b4d741fc0e0bfd636c1@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:3 goldfire]: > If `Q` belongs to pairs, then is it ever imported with `(..)` attached to some type? I would guess "no". Well I suppose it would be possible, since {{{ import GHC.Tuple ((,)(..)) }}} is a valid import declaration. Here's how I imagine this working, if a module `M` exports a type `T` and a pattern `P` whose result type is headed by `T`, e.g. {{{ module M (T(..), pattern P) where data T = T Int Int pattern P x = T x 0 }}} then a client module that uses a wildcard import, e.g. {{{ module B where import M ( T(..) ) }}} should see `P` as well. This rule would avoid any sort of spooky action at a distance, where `T` and `P` are defined in separate modules, because the wildcard would only depend on a single interface file. That being said, I'm perfectly happy with goldfire's suggestion too :) > What if there were a way to declare that a pattern is attached to a type? For example: > > {{{ > module A ( A(.., pattern A1) ) where ... > }}} > > By adding `A1` to the export list of the type `A`, then it is imported with `A` as well. We would probably want a check that `A1`'s result type is indeed headed by `A`. This seems to make sense in re-exports as well, in case the pattern synonyms and original datatype are defined in different modules. One question though, if I have a client module {{{ module B ( A(..) ) where import A ( A(..) ) }}} does `B` now export `A1` under your scheme, or does it need to explicitly add `pattern A1` to the export declaration? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 20:16:57 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 20:16:57 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier Message-ID: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: concurrent/conc034 | Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This is a regression from 7.10.1 to 7.10.2-rc2. See attachment for the result of running `make TEST=conc034 WAY=optasm TEST_HC=ghc-7.10.1.20150715`. It starts with: {{{ *** Core Lint errors : in result of Simplifier *** : Warning: In the expression: seq @ e10_a20g @ (# State# RealWorld, () #) e2_a20o (# eta_B1, () #) Kinds don't match in type application: Type variable: b_13 :: * Arg type: (# State# RealWorld, () #) :: # xx # *** Offending Program *** }}} ghc-7.10.1 is fine. Same problem with ghc-7.11.20150711 (HEAD). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 20:17:21 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 20:17:21 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier In-Reply-To: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> References: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> Message-ID: <060.b0fe162ac46c18e009010b4e24608c32@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/conc034 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * Attachment "concurrent-conc034-core-lint-errors.txt" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 20:36:45 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 20:36:45 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier In-Reply-To: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> References: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> Message-ID: <060.ad044957eb9536135e57f8acbf018412@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/conc034 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"34bb4605d4ec5b131df57ca4c91d6840b7539194/ghc" 34bb4605/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="34bb4605d4ec5b131df57ca4c91d6840b7539194" Testsuite: mark array001 and conc034 expect_broken_for(#10659, ['optasm',...]) Update submodule array. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 20:36:45 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 20:36:45 -0000 Subject: [GHC] #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds In-Reply-To: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> References: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> Message-ID: <060.41f4e13936a77b55360ca1890e9c207c@haskell.org> #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | gadt/termination Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"43dafc93b201e193e83792d2461bf4e45805b5c3/ghc" 43dafc9/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="43dafc93b201e193e83792d2461bf4e45805b5c3" Testsuite: mark gadt/termination expect_broken_for(#10658, ['optasm','optllvm']) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 18 21:00:52 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 18 Jul 2015 21:00:52 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier In-Reply-To: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> References: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> Message-ID: <060.4daff055ce1075f00eb5ff1c2a4f2f4c@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/conc034, | libraries/array/tests/array001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * testcase: concurrent/conc034 => concurrent/conc034, libraries/array/tests/array001 Comment: The test `array001` in `libraries/array/tests` fails in the same way. Curiously it also fails for WAY=hpc (which means `'-O -fhpc'`), while `con034` doesn't. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 00:24:19 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 00:24:19 -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.08ad7e72309894b5437ebcca9db0e76f@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Changes (by oerjan): * cc: oerjan (added) Comment: Replying to [comment:3 goldfire]: > Now, the user chooses what facility provides the instances. Note that I've done something currently impossible: I've used GND for the `Read` class. Normally, we don't want this behavior, and (to my knowledge) there's no way to convince GHC to use GND to derive a `Read` or `Show` instance. But maybe some user out there does want it. I can think of at least one such use case that seems to make sense: Deriving `Read` and `Show` for newtypes around standard numeric types. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 02:50:56 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 02:50:56 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.f12b0fcac763fc786cb7aeedbc84d2b9@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:4 gridaphobe]: > Replying to [comment:3 goldfire]: > > If `Q` belongs to pairs, then is it ever imported with `(..)` attached to some type? I would guess "no". > > Well I suppose it would be possible, since > > {{{ > import GHC.Tuple ((,)(..)) > }}} > > is a valid import declaration. Yes, but no pattern synonyms are defined in `GHC.Tuple`. > One question though, if I have a client module > > {{{ > module B ( A(..) ) where > import A ( A(..) ) > }}} > > does `B` now export `A1` under your scheme, or does it need to explicitly add `pattern A1` to the export declaration? Good point. I think it would make sense to re-export the patterns, but I see how this is perhaps problematic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 04:11:39 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 04:11:39 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.8faf7f7d8f3c5b17dc1b6f6b0e0e79bd@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:5 goldfire]: > > > If `Q` belongs to pairs, then is it ever imported with `(..)` attached to some type? I would guess "no". > > > > Well I suppose it would be possible, since > > > > {{{ > > import GHC.Tuple ((,)(..)) > > }}} > > > > is a valid import declaration. > > Yes, but no pattern synonyms are defined in `GHC.Tuple`. Right, you would need a module that re-exported `(,)` in addition to a pattern synonym, e.g. {{{ module A ( (,)(..), pattern Q ) }}} so it's very unlikely to happen in practice. But, if you are re-exporting `(,)` from your module, I think it would be reasonable to attach the pattern synonyms that belong to `(,)`. I see this as module `A` providing its own view of pairs. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 08:22:30 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 08:22:30 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.c68bc86d52c215874e41ac0f699f8997@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I can see the point, but I'm not enthusiastic myself * It would mean that a programmer (and GHC) would need to do type inference even to figure out what the export `T(..)` meant. That is, lexical scoping depends on type inference. Currently Haskell never requires type inference to figure out scoping. Changing this would entail some fairly radical changes in the compiler. * It's not clear why you might dignify smart patterns, but not smart constructors. We often use "smart constructors" and it would make the same kind of sense to export those too with `T(..)`. Perhaps any function whose result type was `T`? I just don't see a good place to stop with this line of thought. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 08:30:00 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 08:30:00 -0000 Subject: [GHC] #8123: GHCi warns about -eventlog even though it's sometimes necessary In-Reply-To: <043.6d79c34e9438338948ab4ac93632c1d6@haskell.org> References: <043.6d79c34e9438338948ab4ac93632c1d6@haskell.org> Message-ID: <058.081a0459e6e9300663b1e07b34ad4a7d@haskell.org> #8123: GHCi warns about -eventlog even though it's sometimes necessary -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect | (amd64) warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by akio): * status: infoneeded => new Comment: Here is a test session (with GHC 7.10.1): {{{ % cat Test.hs main = return () % ghc -c -eventlog Test.hs % ghci Test.hs GHCi, version 7.10.1.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( Test.hs, interpreted ) [flags changed] Ok, modules loaded: Main. *Main> Leaving GHCi. % ghci Test.hs -eventlog GHCi, version 7.10.1.1: http://www.haskell.org/ghc/ :? for help Warning: -debug, -threaded and -ticky are ignored by GHCi Ok, modules loaded: Main. Prelude Main> Leaving GHCi. }}} So GHCi decides to re-use the object file only when it's given `-eventlog`. Perhaps the recompilation checker should ignore this flag, if the flag doesn't actually affect how a module is compiled? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 09:25:45 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 09:25:45 -0000 Subject: [GHC] #10660: .dyn_o isn't generated for .hsig files with -dynamic-too Message-ID: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> #10660: .dyn_o isn't generated for .hsig files with -dynamic-too -------------------------------------+------------------------------------- Reporter: spinda | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This causes the linker to error out later on, as it expects a .dyn_o file to exist for each .hsig file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 09:25:59 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 09:25:59 -0000 Subject: [GHC] #10660: .dyn_o isn't generated for .hsig files with -dynamic-too In-Reply-To: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> References: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> Message-ID: <060.99c8fa2444f487ae2d49cab03b06540e@haskell.org> #10660: .dyn_o isn't generated for .hsig files with -dynamic-too -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by spinda): * owner: => spinda -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 09:59:13 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 09:59:13 -0000 Subject: [GHC] #10660: .dyn_o isn't generated for .hsig files with -dynamic-too In-Reply-To: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> References: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> Message-ID: <060.125290671e8225d1dd2847ed500239bd@haskell.org> #10660: .dyn_o isn't generated for .hsig files with -dynamic-too -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1084 -------------------------------------+------------------------------------- Changes (by spinda): * differential: => Phab:D1084 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 11:02:48 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 11:02:48 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.6ceff33e60b8ddf7f3c4d5f2d64782a8@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder | import submodule cd Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Miloan): Just like @FPtje, I have experienced this problem. For me it is counter- intuitive to have to compile the code from the root folder. Maybe this origins from my experience with other compilers. While I do agree that GHC is not your average compiler, it would not hurt to conform to some standards. The proposed solution is exactly how I imagined the compiler worked when I started programming Haskell. That's why I believe it would be a great addition to GHC. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 15:35:47 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 15:35:47 -0000 Subject: [GHC] #10643: GHC cannot import submodules when run from subfolder In-Reply-To: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> References: <044.3c9adfa0c2ca70fe317024c4892ed64f@haskell.org> Message-ID: <059.7b230996f37f5a5f8416c3ecf40709e4@haskell.org> #10643: GHC cannot import submodules when run from subfolder -------------------------------------+------------------------------------- Reporter: FPtje | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: subfolder | import submodule cd Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rodlogic): It would surprise me, should I see something like the following: {{{ src/Yes/A.hs (module Yes.A ...) src/Yes/B.hs (module Yes.B ...) src/Yes/Yes/B.hs (module Yes.B ...) }}} Maybe the above structure is useful to deal with conditionally compiled modules such as platform specific ones? Or some other use case that can't be achieved with a less surprising structure? Even in those cases why not keep the structure normalized? Such as: {{{ src/Yes/A.hs (module Yes.A ...) src/Yes/B.hs (module Yes.B ...) src/Yes/Windows/B.hs (module Yes.Windows.B ...) }}} Or even a completely separate include path for the platform specific modules assuming the module names don't clash. The above is clearer and simpler to me. That assumes: 1. The module structure must match the file system structure (WYSIWYG) - what is the value we get from this variability here? Another similar example of this is the fact that Cabal doesn't complain that a file {{{../xyz.cabal}}} may have a cabal package named {{{MyYesPackage}}}. 2. No clever nesting of module tree within module tree making thing more complicated. There is probably not much GHC can do here since it is more of a best practice that not everyone may agree with. If we can agree on (1) above, then I find this proposal quite reasonable. As I understand it, this would mean that GHC should be able to infer an include path based on the current module file and that this include path would take precedence over the current path, which seems to be already an implicit include dir (?). I would go even further and have GHC outright reject, or at least warn first then completely reject after a couple of releases, a module structure that doesn't match the file system structure. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 19:20:52 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 19:20:52 -0000 Subject: [GHC] #10661: Regression: hp2ps reports `integer unexpected` on new style package keys Message-ID: <045.9c4a37e2fa0ae7c34e598ac5ff3e0cab@haskell.org> #10661: Regression: hp2ps reports `integer unexpected` on new style package keys -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Profiling | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: concurrent/prog002/concprog002 | Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- hp2ps reports `integer unexpected` when run on a profile file created with HEAD. The profile file contains entries such as the following: {{{ $ grep System.Random Test.hp 9Kgekc9yEaLHLNUuw6paWL:System.Random.StdGen 24 9Kgekc9yEaLHLNUuw6paWL:System.Random.StdGen 24 9Kgekc9yEaLHLNUuw6paWL:System.Random.StdGen 24 9Kgekc9yEaLHLNUuw6paWL:System.Random.StdGen 24 }}} To reproduce, first install random (there might be a simpler way, but this one is required to run `make TEST=concprog002 WAY=threaded2_hT`, which is failing at the moment): {{{ $ cabal install random==1.1 --with-ghc=ghc-7.11.20150711 -v0 }}} Note the package key for random starts with a number: {{{ $ ghc-pkg --package-db=.ghc/x86_64-linux-7.11.20150711/package.conf.d/ describe random | grep key key: 9Kgekc9yEaLHLNUuw6paWL }}} Then create a heap profile for the following program with `-hT`, and try to run `hp2ps` on it: {{{ $ cat Test.hs import System.Random main = sequence $ replicate 1000 (randomIO :: IO Int) $ ghc-7.11.20150711 Test.hs -rtsopts -fforce-recomp -v0 $ ./Test +RTS -hT -i0.001 $ hp2ps Test.hp hp2ps: Test.hp, line 12: integer unexpected }}} Note that in the profile file the entries for libraries like `base`, `ghc- prim` and `integer-gmp` don't contain package keys (maybe the entries for random shouldn't either?): {{{ base:Data.Dynamic.Dynamic 24 integer-gmp:GHC.Integer.Type.Jp# 16 ghc-prim:GHC.Types.: 24 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 19:34:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 19:34:28 -0000 Subject: [GHC] #10661: Regression: hp2ps reports `integer unexpected` on new style package keys In-Reply-To: <045.9c4a37e2fa0ae7c34e598ac5ff3e0cab@haskell.org> References: <045.9c4a37e2fa0ae7c34e598ac5ff3e0cab@haskell.org> Message-ID: <060.22394a9563365d7779c80ac5938dbc79@haskell.org> #10661: Regression: hp2ps reports `integer unexpected` on new style package keys -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Profiling | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/prog002/concprog002 Blocked By: | Blocking: Related Tickets: #10550 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * related: => #10550 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 20:30:48 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 20:30:48 -0000 Subject: [GHC] #8123: GHCi warns about -eventlog even though it's sometimes necessary In-Reply-To: <043.6d79c34e9438338948ab4ac93632c1d6@haskell.org> References: <043.6d79c34e9438338948ab4ac93632c1d6@haskell.org> Message-ID: <058.f5453585162bdd74b0691a107fc0d04e@haskell.org> #8123: GHCi warns about -eventlog even though it's sometimes necessary -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect | (amd64) warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): akio, you seem to have something special about your environment (`DYNAMIC_BY_DEFAULT`?) I had to add `-dynamic` to the `ghc` invocations to reproduce. But a simpler test is {{{ rwbarton at morphism:/tmp$ ghc -c Test.hs rwbarton at morphism:/tmp$ ghc -c Test.hs -threaded compilation IS NOT required rwbarton at morphism:/tmp$ ghc -c Test.hs -debug compilation IS NOT required rwbarton at morphism:/tmp$ ghc -c Test.hs -eventlog rwbarton at morphism:/tmp$ }}} Technically the eventlog way is not actually RTS-only because it adds `-DTRACING` to the C compiler and C preprocessor options. If you had CPP in Test.hs that checked whether `TRACING` was defined, then recompiling the module to an object file (either in ghci or by ghc) really would have been necessary. So, there are a few possible resolutions: 1. Make `WayEventLog` a non-RTS only way in `wayRTSOnly`, which would suppress this ghci warning, on the grounds that modules can detect (via CPP) whether they were built with `-eventlog`. I think this would prevent linking `-eventlog` object files with non-`-eventlog` ones, though. 2. Don't change `wayRTSOnly`, and just change the test for that ghci warning to check something other than `wayRTSOnly` (e.g., treat `WayEventLog` specially). However this leaves us in the current mildly inconsistent state of affairs that `-eventlog` is considered in some sense (and is documented to be) a link-time only option, when in fact it affects compilation as well. 3. Implement `WayEventLog` in the same manner as `WayThreaded` and `WayDebug`. I don't know exactly what is (perhaps thomie can comment) but the latter two ways are not built by automatically enabling CPP options in ghc, even though the RTS is in fact full of `#ifdef THREADED` and `#ifdef DEBUG`. I assume there is some special logic in the build system for these. This potentially breaks people who were using `#ifdef TRACING` in their Haskell source, but hopefully there aren't any (it is undocumented after all). Personally I lean towards 3 if it isn't technically difficult to implement. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 19 21:49:19 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 19 Jul 2015 21:49:19 -0000 Subject: [GHC] #8123: GHCi warns about -eventlog even though it's sometimes necessary In-Reply-To: <043.6d79c34e9438338948ab4ac93632c1d6@haskell.org> References: <043.6d79c34e9438338948ab4ac93632c1d6@haskell.org> Message-ID: <058.15f99f31fe5f16207935a03cb8107edd@haskell.org> #8123: GHCi warns about -eventlog even though it's sometimes necessary -------------------------------------+------------------------------------- Reporter: akio | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Incorrect | (amd64) warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by akio): Replying to [comment:3 rwbarton]: > akio, you seem to have something special about your environment (`DYNAMIC_BY_DEFAULT`?) I had to add `-dynamic` to the `ghc` invocations to reproduce. Oops, yes, I was using a `ghc` with `("GHC Dynamic","NO")`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 00:14:56 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 00:14:56 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.4747bd9db90bba4becb89ebf9320fa8e@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): If the values pointed to by your array don't themselves contain pointers (and assuming nothing else on the heap points to them) then either a BFS or a DFS traversal will visit them all sequentially. But in many cases if your values don't contain pointers then you could find a way to store them in an unboxed array with higher memory density anyways. (Using a boxed array costs you two words per element up front, one for the pointer in the array and one for the info pointer of the If your values do themselves contain pointers then it does matter whether the traversal is BFS or DFS, but which one you want depends on how you plan to use the values, which the GC can't know without further hints. For example a large Integer contains a pointer to a ByteArray# containing the actual integer data, which you will need for most (but not all) operations on the Integer. If you have an array with a lot of large Integers, you may or may not want to put the ByteArray# after its corresponding Integer (even ignoring the possibility of the ByteArray#s being shared). My potential concerns about the original feature request are - It sounds like a lot of extra complexity in the GC - Existing programs gain nothing from this added complexity unless they are modified to use the new primops - Consequently the implementation of the new primops must have zero cost for programs that do not use them - A fairly narrow range of programs stand to benefit from the new primops - It's unclear how much there is to be gained in the best case, especially compared to user-space alternatives like explicitly prefetching the next value of the array before processing the current one You might be better off just implementing your own memory management (e.g. allocate variable-length representations of your data sequentially from a mutable ByteArray, then store offsets into this storage in your array and access the data through short-lived Haskell values, Storable-style). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 00:46:34 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 00:46:34 -0000 Subject: [GHC] #10650: Can't define GHCi :def macro with NoImplicitPrelude on In-Reply-To: <050.a9004b0bba20a10488d32b9b9c069466@haskell.org> References: <050.a9004b0bba20a10488d32b9b9c069466@haskell.org> Message-ID: <065.f931b0d65449a4c5c718acb8db1a97e8@haskell.org> #10650: Can't define GHCi :def macro with NoImplicitPrelude on -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #8640 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * keywords: => newcomer Comment: These references to `String` and `IO` are from the expression that is built in `InteractiveUI.defineMacro`, see the comment: {{{ -- > ghciStepIO . definition :: String -> IO String }}} `RdrName` is a name that is not necessarily bound to a particular module. In this setting in ghci it only makes sense to use the `String` from the real `Prelude`. I'm not terribly familiar with this part of the compiler, but I imagine it is an easy local fix in `defineMacro`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 00:57:50 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 00:57:50 -0000 Subject: [GHC] #10001: GHC crash trying to build a project within Nix-shell In-Reply-To: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> References: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> Message-ID: <062.642923cd2419c76be2b0fb01927a36da@haskell.org> #10001: GHC crash trying to build a project within Nix-shell -------------------------------------+------------------------------------- Reporter: wolftune | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: 9825 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Can we get instructions to reproduce that do not include "Just install the nix package manager"? The panic must depend on some feature of the environment. At a guess, perhaps TMPDIR is pointing at a filesystem (`/run`) that is mounted with noexec? That won't work (#10131). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 01:07:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 01:07:48 -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.059f4c0bd0f992156d7cc610e069824f@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I'm confused by a lot of this thread. As I mentioned in comment:2, `DeriveAnyClass` will never derive `Functor`, even when it is the only deriving extension enabled. So I would expect the presence of `DeriveAnyClass` to be irrelevant to any attempt to derive `Functor`, whatever other deriving extensions are enabled. And I think this behavior is (poorly) documented, by the word "other" in the description of `DeriveAnyClass`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 01:13:30 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 01:13:30 -0000 Subject: [GHC] #9571: nofib should use criterion-style bootstrapping/sampling In-Reply-To: <045.5455eab068db49e1d11638c2709a378d@haskell.org> References: <045.5455eab068db49e1d11638c2709a378d@haskell.org> Message-ID: <060.6d440f48828a89b77d93664e682086a7@haskell.org> #9571: nofib should use criterion-style bootstrapping/sampling -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: NoFib benchmark | Version: 7.9 suite | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 5793 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:2 kanetw]: > Is it possible to just use criterion to run the benchmarks, or does GHC have special requirements that would require an own implementation? This is discussed a bit in the comments on #5793. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 01:18:02 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 01:18:02 -0000 Subject: [GHC] #10578: ghci line numbers are off by one In-Reply-To: <047.babcd43e2857d19107b478b8249a9812@haskell.org> References: <047.babcd43e2857d19107b478b8249a9812@haskell.org> Message-ID: <062.54b564709b4ab39003aa2d02f8011927@haskell.org> #10578: ghci line numbers are off by one -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: osa1 Type: bug | Status: closed Priority: low | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1067 -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 01:22:30 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 01:22:30 -0000 Subject: [GHC] #8131: T7571 with WAY=llvm fails, but not WAY=optllvm In-Reply-To: <052.22eb4f882263987206e929bacae5db28@haskell.org> References: <052.22eb4f882263987206e929bacae5db28@haskell.org> Message-ID: <067.8978a696234f8ee15fb319bf08973889@haskell.org> #8131: T7571 with WAY=llvm fails, but not WAY=optllvm -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | llvm/should_compile/T8131 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D624 -------------------------------------+------------------------------------- Comment (by rwbarton): This panic is quite interesting though, since there is in fact some new loopy stuff in the Cmm parser. Too bad it is only on Windows... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 02:28:00 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 02:28:00 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.faaffb92168ad4f442a8e2f007915225@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): I'm not in strong favor of any proposal of this sort, but I also haven't used pattern synonyms much, so my opinion is not well informed. But I do think my proposal answers Simon's first point: the programmer says explicitly what should be included by any import of a datatype. This choice is checked in my proposal, but I don't imagine that would be a challenge to implement. The interface file would indicate what pattern synonyms are included with a datatype. It all doesn't seem very complicated. As for smart constructors: I think that pattern synonyms subsume traditional "smart constructors". They should really be pattern synonyms now! With the change proposed in this ticket, clients might not even know the difference between a real constructor and a smart one. Here might be a motivation and a design principle for this feature: a library should be able to refactor a concrete data type without affecting client code. This refactoring would require exporting pattern synonyms mimicking the old behavior. But it's conceivable a client would never know. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 02:35:51 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 02:35:51 -0000 Subject: [GHC] #10632: ImplicitParams: GHC does not warn about unused implicit parameters In-Reply-To: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> References: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> Message-ID: <058.6e840eb8c9af3ef1fa6a248fea9e7860@haskell.org> #10632: ImplicitParams: GHC does not warn about unused implicit parameters -------------------------------------+------------------------------------- Reporter: mwnx | Owner: Type: bug | Status: new Priority: lowest | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Reid Barton ): In [changeset:"9834fea4d8fa00eb55f864287aa323ec7412e578/ghc" 9834fea4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9834fea4d8fa00eb55f864287aa323ec7412e578" Add regression test for unused implicit parameter warning (#10632) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 02:36:19 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 02:36:19 -0000 Subject: [GHC] #10632: ImplicitParams: GHC does not warn about unused implicit parameters In-Reply-To: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> References: <043.e43a281629468e7ea1a3cf04b358b377@haskell.org> Message-ID: <058.abae6d7cd2ac4d2899f6410f26cee5bd@haskell.org> #10632: ImplicitParams: GHC does not warn about unused implicit parameters -------------------------------------+------------------------------------- Reporter: mwnx | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 04:22:34 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 04:22:34 -0000 Subject: [GHC] #3744: Comparisons against minBound/maxBound not optimised for (Int|Word)(8|16|32) In-Reply-To: <041.2169b48b8108c3b700385a622d1921fe@haskell.org> References: <041.2169b48b8108c3b700385a622d1921fe@haskell.org> Message-ID: <056.3a37db662456910d8a2a900de4a39fc9@haskell.org> #3744: Comparisons against minBound/maxBound not optimised for (Int|Word)(8|16|32) -------------------------------------+------------------------------------- Reporter: rl | Owner: Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 6.13 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * cc: rwbarton (added) Comment: I just ran into this too. Perhaps the thing to do is to generate rules in PrelRules like {{{ narrow8IntOp x < 127 = True }}} etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 04:43:33 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 04:43:33 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.8482de5a4a179dd57b60d00d26d462d0@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:8 goldfire]: > But I do think my proposal answers Simon's first point: the programmer says explicitly what should be included by any import of a datatype. This choice is checked in my proposal, but I don't imagine that would be a challenge to implement. The interface file would indicate what pattern synonyms are included with a datatype. It all doesn't seem very complicated. > > As for smart constructors: I think that pattern synonyms subsume traditional "smart constructors". They should really be pattern synonyms now! With the change proposed in this ticket, clients might not even know the difference between a real constructor and a smart one. > > Here might be a motivation and a design principle for this feature: a library should be able to refactor a concrete data type without affecting client code. This refactoring would require exporting pattern synonyms mimicking the old behavior. But it's conceivable a client would never know. I agree on all accounts. We should strive to enable client code to be oblivious to library refactorings. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 07:44:36 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 07:44:36 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.1cc98aa1e6327b623bb6130068a6031a@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Well I certainly agree with the goal of being oblivious to library refactorings. I don't yet understand Richard's proposal. Perhaps you mean this: * Let's say that the data constructors of a type `T` are "associated with `T`". * When you say `T(..)` in an export or import list, you mean `T` plus all its in-scope associated constructors. * In the defining module of a data type (''and nowhere else'') you can list pattern synonyms in the export list thus `T( ..., pattern A1 )`, and that permanently associates `A1` with `T`. Is that what you intended? Well that is certainly better. It means that there is one place to go to find out the full list of what `T(..)` might mean, namely the module where `T` is defined. But I dislike that you have to look (a) at the definition of `T` and (b) at the exports of the module. Somehow the definition of `T` should tell you everything. Something like {{{ data T = A Int | B [Bool] with( P, Q, R ) pattern P x = B [x] ...etc... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 09:19:47 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 09:19:47 -0000 Subject: [GHC] #10662: GHC warning shows technical summary of AST instead of the user's code Message-ID: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> #10662: GHC warning shows technical summary of AST instead of the user's code -------------------------------------+------------------------------------- Reporter: kolmodin | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I got a warning for some code I wrote; {{{#!hs forkIO (....) }}} Naturally GHC warns me that I'm throwing away the result, and should write like this; {{{#!hs _ <- forkIO (...) }}} However, the warning is expressed in a somewhat confusing way, not sure this is intentional. {{{ examples/route_guide_client.hs:84:5: Warning: A do-notation statement discarded a result of type ?ThreadId? Suppress this warning by saying ?_ <- ($) forkIO let AbsBinds [] [] {Exports: [go <= go <>] Exported types: go :: [L.ByteString] -> IO () [LclId, Str=DmdType] Binds: go acc = ...} in go []? or by using the flag -fno-warn-unused-do-bind }}} I find it confusing that the warning mentions AbsBinds, exports and types. I'd expect a snippet of my code in the warning. However, doesn't look like this is a (recent) regression. The same happens GHC 7.8.4 and 7.10.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 09:35:38 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 09:35:38 -0000 Subject: [GHC] #10560: -f and -O options interact in non-obvious, order dependent ways In-Reply-To: <046.4b383b5f0fce35e0e7803ffe12bdc717@haskell.org> References: <046.4b383b5f0fce35e0e7803ffe12bdc717@haskell.org> Message-ID: <061.5c4ab04965a56c42ba4b5fce18d2e7c3@haskell.org> #10560: -f and -O options interact in non-obvious, order dependent ways -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): A similar [https://mail.haskell.org/pipermail/haskell- cafe/2015-June/120047.html discussion] for language pragmas: `{-# LANGUAGE GADTs, NoMonoLocalBinds #-}` vs `{-# LANGUAGE NoMonoLocalBinds, GADTs #-}`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 09:51:06 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 09:51:06 -0000 Subject: [GHC] #10408: The behavior of -ignore-dot-ghci and -ghci-script are weird In-Reply-To: <046.9a385a1c8826dd0a905fd10c48159e27@haskell.org> References: <046.9a385a1c8826dd0a905fd10c48159e27@haskell.org> Message-ID: <061.205c523ba3468dd5bf362a943b8507a1@haskell.org> #10408: The behavior of -ignore-dot-ghci and -ghci-script are weird -------------------------------------+------------------------------------- Reporter: watashi | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86 Type of failure: Incorrect result | Test Case: at runtime | Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D887 -------------------------------------+------------------------------------- Comment (by mboes): Any chance this fix could be backported to the 7.10 branch? It's affecting the safety of distributing GHCi wrappers to users for building custom GHCi based interactive environments. These need to turn off reading the user's ~/.ghci just in case there's funny stuff in there, while still convincing GHCi to read a custom script.ghci during initialization. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 09:53:12 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 09:53:12 -0000 Subject: [GHC] #10543: MacOS: validate fails on \u In-Reply-To: <047.a887440a0df817cb06caf9fc53c8c2c9@haskell.org> References: <047.a887440a0df817cb06caf9fc53c8c2c9@haskell.org> Message-ID: <062.9534878dd8f7cddfc6b0b3eaf7ee8b0b@haskell.org> #10543: MacOS: validate fails on \u -------------------------------------+------------------------------------- Reporter: trommler | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: invalid | Keywords: cpp Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1004 -------------------------------------+------------------------------------- Comment (by geoff): So, I was the one to add this line ? overriding `-Wno-invalid-pp-token -Wno-unicode -Wno-trigraphs` ? because these flags are not universally supported by clang. If anyone could help me understand this better, it would be appreciated. https://github.com/Homebrew/homebrew/issues/41777#issuecomment-122826887 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 10:47:49 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 10:47:49 -0000 Subject: [GHC] #9832: Get rid of PERL dependency of `ghc-split` In-Reply-To: <042.a80d180822707ef08b1350d4a542cee3@haskell.org> References: <042.a80d180822707ef08b1350d4a542cee3@haskell.org> Message-ID: <057.7657f30036c760de58ec93e90c304a37@haskell.org> #9832: Get rid of PERL dependency of `ghc-split` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Phyx- Type: task | Status: new Priority: high | Milestone: 7.12.1 Component: Driver | Version: Resolution: | Keywords: perl Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: simonmar (added) Comment: > Ended up inlining one of the PCRE bindings since rewriting this without Perl Regex would have ended up in something a lot bigger and complexer. I [https://github.com/Mistuke/ghc/tree/trac-9832-replace-split-perl- script-with-haskell noticed] that this adds 30.000 lines of C and 1700 lines of Haskell. Not sure if that's any better than just bundling Perl on Windows + a 300 line Perl script. What is the problem we're trying so solve here? If it's binary size: we've been shipping Python and fortran compilers as well, maybe start with stripping those (#9014). Perhaps we can get rid of split-objs completely? I found the following quote by @simonmar in SharedLibraries: "Shared libs also completely eliminates the need for the ?split objs? hack that GHC uses to reduce the size of statically linked programs. This should make our link times a bit quicker." -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 10:50:34 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 10:50:34 -0000 Subject: [GHC] #9832: Get rid of PERL dependency of `ghc-split` In-Reply-To: <042.a80d180822707ef08b1350d4a542cee3@haskell.org> References: <042.a80d180822707ef08b1350d4a542cee3@haskell.org> Message-ID: <057.0d4fc33463edb0680951762db6a3d9f9@haskell.org> #9832: Get rid of PERL dependency of `ghc-split` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Phyx- Type: task | Status: new Priority: high | Milestone: 7.12.1 Component: Driver | Version: Resolution: | Keywords: perl Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: duncan (added) Comment: Sorry, that quote should have been attributed to @duncan. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 11:55:56 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 11:55:56 -0000 Subject: [GHC] #10662: GHC warning shows technical summary of AST instead of the user's code In-Reply-To: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> References: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> Message-ID: <062.46510c72fba63f85958f53c32f0e6800@haskell.org> #10662: GHC warning shows technical summary of AST instead of the user's code -------------------------------------+------------------------------------- Reporter: kolmodin | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Quite right! Reason: this message is generated by the desugarer, which only has typechecked code to print. Solution: when printing typechecked code, suppress details generated by the type checker itself. Details: * Sometimes we want to see those details, certainly during compiler debugging. And just conceivably for savvy users. So we need a flag to control it. * Quite a lot of supression goes on already. Example: `pprHsWrapper` uses `-dppr-debug` to control whether a `HsWrapper` get printed. But the `-dppr-debug` flag is a pretty low level thing that controls a lot of other debug-printing stuff too. * Nowadays we have `-fprint-explicit-foralls` and `-fprint-explicit- kinds`, so it might be better to add a new flat `-fprint-evidence` (or something) which shows you the extra evidence generated by the type checker. Nothing hard here, if someone would like to take it on. I can advise. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 14:30:56 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 14:30:56 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.45e9b8cd87b8b566c9de433c42961719@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 14:36:14 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 14:36:14 -0000 Subject: [GHC] #10649: Performance issue with unnecessary reboxing In-Reply-To: <044.4cf844fad84f7356a087aa89ed9fcd46@haskell.org> References: <044.4cf844fad84f7356a087aa89ed9fcd46@haskell.org> Message-ID: <059.b1f6ab7257b4efcf285649b1531bd089@haskell.org> #10649: Performance issue with unnecessary reboxing -------------------------------------+------------------------------------- Reporter: pacak | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => worksforme Comment: Replying to [comment:1 pacak]: > using both -funfolding-use-threshold=10000 -funfolding-creation- threshold=10000 - seems to help in all cases Closing as worksforme, since you found the right flags to tweak. Please reopen if you think this is a mistake. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 14:40:03 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 14:40:03 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.254dd7f4280d2d7146ef33ef55815e2a@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:10 simonpj]: > * In the defining module of a data type (''and nowhere else'') you can list pattern synonyms in the export list thus `T( ..., pattern A1 )`, and that permanently associates `A1` with `T`. Hmm, I understood Richard's proposal to mean that ''any'' module can associate pattern synonyms with a data type in the export list. In this case the association would not be permanent, as client modules could always choose to break the association or associate different pattern synonyms, by changing their export list. So in my interpretation you would have to to chase the import chain to figure out precisely what `T(..)` means, and there would be no "maximal" meaning. I can see the argument against that. If we go with your interpretation and say that ''only'' the defining module can associate pattern synonyms with a data type, I agree that it would be better to declare the association alongside the data type. I guess the real question is this: do we want to allow modules to associate pattern synonyms with data types that they have imported from somewhere else? I can see one situation where this would be handy. Suppose a package `p` changes one of its core data types, but does not export pattern synonyms to provide backwards compatibility. A client could write a new package `p-compat` that provides the necessary patterns and associates them with `p`s data types, thus seamlessly recreating the old API. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:05:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:05:53 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.2e9d1b87b37cb25d5ad22e23edf99c14@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"82ffc80df573512f788524c4616db3c08fc9f125/ghc" 82ffc80d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="82ffc80df573512f788524c4616db3c08fc9f125" LlvmCodeGen: add support for MO_U_Mul2 CallishMachOp This adds support MO_U_Mul2 to the LLVM backend by simply using 'mul' instruction but operating at twice the bit width (e.g., for 64 bit words we will generate mul that operates on 128 bits and then extract the two 64 bit values for the result of the CallishMachOp). Test Plan: validate Reviewers: rwbarton, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1068 GHC Trac Issues: #9430 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:05:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:05:53 -0000 Subject: [GHC] #7861: deferred type error with rankNTypes In-Reply-To: <044.e95c47f81beabe531ae3af1e8fe9b301@haskell.org> References: <044.e95c47f81beabe531ae3af1e8fe9b301@haskell.org> Message-ID: <059.3755500391352b66720d4dcc07e26407@haskell.org> #7861: deferred type error with rankNTypes -------------------------------------+------------------------------------- Reporter: guest | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.2 Resolution: wontfix | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: Compile-time | Test Case: crash | typecheck/should_run/T7861 Blocked By: | Blocking: Related Tickets: | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"4c96e7cf56fc67ad09efaf8c5de1c8d7a0f5cedd/ghc" 4c96e7cf/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4c96e7cf56fc67ad09efaf8c5de1c8d7a0f5cedd" Testsuite: add ImpredicativeTypes to T7861 (#7861) The test was failing with: T7861: T7861.hs:15:13: Cannot instantiate unification variable ?t0? with a type involving foralls: A a0 -> a0 GHC doesn't yet support impredicative polymorphism In the first argument of ?seq?, namely ?f? In a stmt of a 'do' block: f `seq` print "Hello 2" It requires ImpredicativeTypes, at least since 7.8, because we instantiate seq's type (c->d->d) with f's type (c:= (forall b. a) -> a), which is polymorphic (it has foralls). I simplified the test a bit by removing the type synonym, and verified that ghc-7.6.3 still panics on this test. Reviewers: simonpj, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1080 GHC Trac Issues: #7861 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:05:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:05:53 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.c53c6843074449c45a0a048b853e84ab@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"49373ffe4cbc87b46468d2372e850138e151a9ae/ghc" 49373ffe/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="49373ffe4cbc87b46468d2372e850138e151a9ae" Support wild cards in TH splices - Declaration splices: partial type signatures are fully supported in TH declaration splices. For example, the wild cards in the example below will unify with `Eq a` and `a -> a -> Bool`, as expected: ``` [d| foo :: _ => _ foo x y = x == y |] ``` - Expression splices: anonymous and named wild cards are supported in expression signatures, but extra-constraints wild cards aren't. Just as is the case for regular expression signatures. ``` [e | Just True :: _a _ |] ``` - Typed expression splices: the same wildcards as in (untyped) expression splices are supported. - Pattern splices: TH doesn't support type signatures in pattern splices, consequently, partial type signatures aren't supported either. - Type splices: partial type signatures are only partially supported in type splices, specifically: only anonymous wild cards are allowed. So `[t| _ |]`, `[t| _ -> Maybe _ |]` will work, but `[t| _ => _ |]` or `[| _a |]` won't (without `-XNamedWildCards`, the latter will work as the named wild card is treated as a type variable). Normally, named wild cards are collected before renaming a (partial) type signature. However, TH type splices are run during renaming, i.e. after the initial traversal, leading to out of scope errors for named wild cards. We can't just extend the initial traversal to collect the named wild cards in TH type splices, as we'd need to expand them, which is supposed to happen only once, during renaming. Similarly, the extra-constraints wild card is handled right before renaming too, and is therefore also not supported in a TH type splice. Another reason not to support extra-constraints wild cards in TH type splices is that a single signature can contain many TH type splices, whereas it mustn't contain more than one extra-constraints wild card. Enforcing would this be hard the way things are currently organised. Anonymous wild cards pose no problem, because they start without names and are given names during renaming. These names are collected right after renaming. The names generated for anonymous wild cards in TH type splices will thus be collected as well. With a more invasive refactoring of the renaming, partial type signatures could be fully supported in TH type splices. As only anonymous wild cards have been requested so far, these small changes satisfying this request will do for now. Also don't forget that a TH declaration splices support all kinds of wild cards. - Extra-constraints wild cards were silently ignored in expression and pattern signatures, appropriate error messages are now generated. Test Plan: run new tests Reviewers: austin, goldfire, adamgundry, bgamari Reviewed By: goldfire, adamgundry, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1048 GHC Trac Issues: #10094, #10548 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:05:54 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:05:54 -0000 Subject: [GHC] #10640: Document prim-ops In-Reply-To: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> References: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> Message-ID: <061.ae3dc2892dec1f27aea1a5df58ffb948@haskell.org> #10640: Document prim-ops -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"c526e095c5762cc6feb3066779c2f919d66d40e5/ghc" c526e095/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="c526e095c5762cc6feb3066779c2f919d66d40e5" primops: Add haddocks to BCO primops Test Plan: none Reviewers: simonmar, austin, hvr Subscribers: hvr, thomie Differential Revision: https://phabricator.haskell.org/D1082 GHC Trac Issues: #10640 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:05:54 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:05:54 -0000 Subject: [GHC] #10094: Template Haskell cannot represent type wildcards In-Reply-To: <049.6629ff791e291b2d66323173df5c56f5@haskell.org> References: <049.6629ff791e291b2d66323173df5c56f5@haskell.org> Message-ID: <064.7b64f20ddad2b04b2422f0c6eaa7eeab@haskell.org> #10094: Template Haskell cannot represent type wildcards -------------------------------------+------------------------------------- Reporter: adamgundry | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1-rc1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #9879, #10548 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"49373ffe4cbc87b46468d2372e850138e151a9ae/ghc" 49373ffe/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="49373ffe4cbc87b46468d2372e850138e151a9ae" Support wild cards in TH splices - Declaration splices: partial type signatures are fully supported in TH declaration splices. For example, the wild cards in the example below will unify with `Eq a` and `a -> a -> Bool`, as expected: ``` [d| foo :: _ => _ foo x y = x == y |] ``` - Expression splices: anonymous and named wild cards are supported in expression signatures, but extra-constraints wild cards aren't. Just as is the case for regular expression signatures. ``` [e | Just True :: _a _ |] ``` - Typed expression splices: the same wildcards as in (untyped) expression splices are supported. - Pattern splices: TH doesn't support type signatures in pattern splices, consequently, partial type signatures aren't supported either. - Type splices: partial type signatures are only partially supported in type splices, specifically: only anonymous wild cards are allowed. So `[t| _ |]`, `[t| _ -> Maybe _ |]` will work, but `[t| _ => _ |]` or `[| _a |]` won't (without `-XNamedWildCards`, the latter will work as the named wild card is treated as a type variable). Normally, named wild cards are collected before renaming a (partial) type signature. However, TH type splices are run during renaming, i.e. after the initial traversal, leading to out of scope errors for named wild cards. We can't just extend the initial traversal to collect the named wild cards in TH type splices, as we'd need to expand them, which is supposed to happen only once, during renaming. Similarly, the extra-constraints wild card is handled right before renaming too, and is therefore also not supported in a TH type splice. Another reason not to support extra-constraints wild cards in TH type splices is that a single signature can contain many TH type splices, whereas it mustn't contain more than one extra-constraints wild card. Enforcing would this be hard the way things are currently organised. Anonymous wild cards pose no problem, because they start without names and are given names during renaming. These names are collected right after renaming. The names generated for anonymous wild cards in TH type splices will thus be collected as well. With a more invasive refactoring of the renaming, partial type signatures could be fully supported in TH type splices. As only anonymous wild cards have been requested so far, these small changes satisfying this request will do for now. Also don't forget that a TH declaration splices support all kinds of wild cards. - Extra-constraints wild cards were silently ignored in expression and pattern signatures, appropriate error messages are now generated. Test Plan: run new tests Reviewers: austin, goldfire, adamgundry, bgamari Reviewed By: goldfire, adamgundry, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1048 GHC Trac Issues: #10094, #10548 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:05:54 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:05:54 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.7aee3b2ad321f4ea66e935795b6abbde@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: patch Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"4cd008b6c1751c5533ab7eac32d17c9749e4758e/ghc" 4cd008b6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4cd008b6c1751c5533ab7eac32d17c9749e4758e" Do not treat prim and javascript imports as C imports in TH and QQ Reviewers: austin, hvr, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1070 GHC Trac Issues: #10638 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:08:24 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:08:24 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.904ee9c4fa588ed6319dbd62af7c521c@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:43:35 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:43:35 -0000 Subject: [GHC] #10624: th/T10279 testcase is broken In-Reply-To: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> References: <046.c3031a14463ec6e81aac9ce75089e55e@haskell.org> Message-ID: <061.d4bbf7f1ae58d700498fa1fab5525d78@haskell.org> #10624: th/T10279 testcase is broken -------------------------------------+------------------------------------- Reporter: bgamari | Owner: ezyang Type: bug | Status: closed Priority: normal | Milestone: 7.12.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 Revisions: Phab:D1060 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:45:09 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:45:09 -0000 Subject: [GHC] #7478: setSessionDynFlags does not always work In-Reply-To: <044.a3899b7bd6c11925eee15996dee68777@haskell.org> References: <044.a3899b7bd6c11925eee15996dee68777@haskell.org> Message-ID: <059.153f650c0c3ba00fb55cdbde02e57800@haskell.org> #7478: setSessionDynFlags does not always work -------------------------------------+------------------------------------- Reporter: edsko | Owner: bherzog Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: ghc- | api/T7478 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1017 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: T7478 is marked as expect_broken for darwin. Should that be changed now? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:46:39 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:46:39 -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.56d15bb70a2dd9a1081b1b4c755b5424@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: closed Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1016 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * differential: D1016 => Phab:D1016 * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:48:12 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:48:12 -0000 Subject: [GHC] #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter In-Reply-To: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> References: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> Message-ID: <065.ab1efd737397e73aaa3e3ec161c0af3a@haskell.org> #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: th/T10620 Blocked By: | Blocking: Related Tickets: #4168, #5218, | Differential Revisions: Phab:D1054 #5877, | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => th/T10620 * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:52:31 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:52:31 -0000 Subject: [GHC] #10447: DeriveFoldable rejects instances with constraints in last argument of data type In-Reply-To: <050.655803d4d5fe3ef1b8f5abc5e3585493@haskell.org> References: <050.655803d4d5fe3ef1b8f5abc5e3585493@haskell.org> Message-ID: <065.81a7bac4e7302aaffa33fa048badb59b@haskell.org> #10447: DeriveFoldable rejects instances with constraints in last argument of data type -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.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_run/T10447 Blocked By: | Blocking: Related Tickets: #8678 | Differential Revisions: Phab:D1031 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * testcase: => deriving/should_run/T10447 * resolution: => fixed * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:54:39 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:54:39 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.5822e8f1a3d7fe46b543933180ed05b5@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler (LLVM) | Version: 7.9 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | primops/should_run/T9430 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => primops/should_run/T9430 * status: new => closed * resolution: => fixed * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:56:30 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:56:30 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.e2a1928a662f6571ebd8b9f3f9a84028@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 15:57:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 15:57:55 -0000 Subject: [GHC] #10640: Document prim-ops In-Reply-To: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> References: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> Message-ID: <061.b129b8ccfbd3a47e9e2a536625820a07@haskell.org> #10640: Document prim-ops -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1082 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * differential: => Phab:D1082 * resolution: => fixed * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 16:11:04 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 16:11:04 -0000 Subject: [GHC] #10510: Testsuite driver does not run tests in parallel on Windows In-Reply-To: <045.f7051a2be634cd79e52b8850db4fc44f@haskell.org> References: <045.f7051a2be634cd79e52b8850db4fc44f@haskell.org> Message-ID: <060.37db29d59954236ad868b1749b97e5cb@haskell.org> #10510: Testsuite driver does not run tests in parallel on Windows -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Test Suite | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Phyx-: It would be *great* if you could fix this. We would like to validate all patches on Windows as well Linux at some point, but it's sort of a problem when a single validate (--slow) takes hours. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 16:17:03 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 16:17:03 -0000 Subject: [GHC] #10498: "if ... then \case -> else ..." causes a "missing else clause" error In-Reply-To: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> References: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> Message-ID: <065.e1ee511bda3c075b1b14db867ee65634@haskell.org> #10498: "if ... then \case -> else ..." causes a "missing else clause" error -------------------------------------+------------------------------------- Reporter: dramforever | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 17:04:06 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 17:04:06 -0000 Subject: [GHC] #10662: GHC warning shows technical summary of AST instead of the user's code In-Reply-To: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> References: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> Message-ID: <062.6943b68dca0f785e55383acd57427dd5@haskell.org> #10662: GHC warning shows technical summary of AST instead of the user's code -------------------------------------+------------------------------------- Reporter: kolmodin | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * milestone: 7.10.2 => 7.12.1 Comment: kolmodin: can you please update your example to a working test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 17:18:27 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 17:18:27 -0000 Subject: [GHC] #10640: Document prim-ops In-Reply-To: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> References: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> Message-ID: <061.c69d0db72acec03e9f55ff1cc61cdb97@haskell.org> #10640: Document prim-ops -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1082 -------------------------------------+------------------------------------- Changes (by thomie): * owner: bgamari => * status: closed => new * resolution: fixed => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 17:18:40 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 17:18:40 -0000 Subject: [GHC] #10640: Document prim-ops In-Reply-To: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> References: <046.4e817e7df8d2c783e102d23f1eac2c40@haskell.org> Message-ID: <061.45e9bcb38fbbbf4980b2a853a5a69c92@haskell.org> #10640: Document prim-ops -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1082 -------------------------------------+------------------------------------- Changes (by thomie): * owner: => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 17:28:25 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 17:28:25 -0000 Subject: [GHC] #9049: Expose srcLoc from the assertion architecture to allow better error messages In-Reply-To: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> References: <042.a0d4c757be085a0284ebca147547b4f3@haskell.org> Message-ID: <057.b9d79634f1643079178c1be334f45042@haskell.org> #9049: Expose srcLoc from the assertion architecture to allow better error messages -------------------------------------+------------------------------------- Reporter: nh2 | Owner: gridaphobe Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D578 -------------------------------------+------------------------------------- Comment (by gridaphobe): FWIW, LiquidHaskell is also broken by 00cd6173a620ef99739d97ac843258fee8e2dee9, but as a maintainer I can deal with it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 18:17:14 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 18:17:14 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.68995a5268f75769d5623224162da80d@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | primops/should_run/T9430 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by michalt): * status: closed => new * owner: michalt => * resolution: fixed => * milestone: 7.12.1 => Comment: I was also planning to add support for MO_U_QuotRem2 (using `udiv` and `urem`), so let's not close this just yet. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 18:17:23 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 18:17:23 -0000 Subject: [GHC] #9430: implement more arithmetic operations natively in the LLVM backend In-Reply-To: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> References: <047.5faa8daf1edcacef61c9001ac8b43152@haskell.org> Message-ID: <062.763d3e8eecdaf8a2bd2cf468245cf16e@haskell.org> #9430: implement more arithmetic operations natively in the LLVM backend -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: michalt Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | primops/should_run/T9430 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by michalt): * owner: => michalt -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 20:53:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 20:53:48 -0000 Subject: [GHC] #10661: Regression: hp2ps reports `integer unexpected` on new style package keys In-Reply-To: <045.9c4a37e2fa0ae7c34e598ac5ff3e0cab@haskell.org> References: <045.9c4a37e2fa0ae7c34e598ac5ff3e0cab@haskell.org> Message-ID: <060.d0ba31a18b715f64b0f1572290e96201@haskell.org> #10661: Regression: hp2ps reports `integer unexpected` on new style package keys -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Profiling | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/prog002/concprog002 Blocked By: | Blocking: Related Tickets: #10550 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"2f18b19784fba161b143d8961d805ffb94a5be0a/ghc" 2f18b197/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2f18b19784fba161b143d8961d805ffb94a5be0a" Testsuite: mark concprog002 expect_broken_for(#10661, ['threaded2_hT']) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 20:53:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 20:53:48 -0000 Subject: [GHC] #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion In-Reply-To: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> References: <045.7e2f7bf1f77ecf8607cd3966531ffeb1@haskell.org> Message-ID: <060.1e66f1c5d205632a0a0046cdb1af54f2@haskell.org> #8089: Implementation of GHC.Event.Poll.poll is broken due to bad coercion -------------------------------------+------------------------------------- Reporter: merijn | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: libraries/base | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D407 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"d0cf8f1a41957a0d30475f7220facdec9efaa3a0/ghc" d0cf8f1/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d0cf8f1a41957a0d30475f7220facdec9efaa3a0" Testsuite: simplify T8089 (#8089) The previous implementation wasn't working for the `ghci` test way, causing a fulltest failure. Differential Revision: https://phabricator.haskell.org/D1075 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 20:53:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 20:53:48 -0000 Subject: [GHC] #10529: hpc: Improve error messages in readMix In-Reply-To: <042.190bab483c0a9360715a797a8a3385e1@haskell.org> References: <042.190bab483c0a9360715a797a8a3385e1@haskell.org> Message-ID: <057.cf08462ebed6967b4afc865e787fc074@haskell.org> #10529: hpc: Improve error messages in readMix -------------------------------------+------------------------------------- Reporter: nh2 | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Code Coverage | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simple/tixs/T10529{a,b,c} Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"b4ef8b8badaa43872a843778e8fa9da943955d38/ghc" b4ef8b8b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b4ef8b8badaa43872a843778e8fa9da943955d38" Update submodule hpc with fix for #10529 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 21:08:23 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 21:08:23 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.ef3da3104d997fe0965a1deaeaaad0aa@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Comment (by simonpj): Are there some feature tests for this? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 21:08:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 21:08:52 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.f1e05a68879f0907b62680c1891a99a3@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Comment (by simonpj): Is there a regression test for this? Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 21:16:05 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 21:16:05 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.2a8ca3443cf5ec6e2d37bdbb397993a1@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Comment (by luite): Yes it's part of D1070, but it's not backported to the 7.10 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 22:19:50 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 22:19:50 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.3fd68dc67a9318bdd395f8d0f5f8f6f6@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Comment (by thomasw): Replying to [comment:14 simonpj]: > Are there some feature tests for this? Yes, I think I added tests for all splices, including the scenarios in which wild cards aren't supported. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 22:29:21 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 22:29:21 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.4b63d6af9e3e0d6beaa33391ebb04e2d@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Comment (by simonpj): Terrific. So can you add them to the "Test case" field of this ticket? Or if too many, list them in a comment, and in the "Test case" field say "see comment:23" of whatever? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 22:39:04 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 22:39: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.651d002a3952934a97a8995ed139440f@haskell.org> #10547: feature request: expanding type synonyms in error messages -------------------------------------+------------------------------------- Reporter: osa1 | Owner: osa1 Type: feature request | Status: closed Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: checker) | Resolution: fixed | 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 Revisions: Phab:D1016 -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => typecheck/should_fail/ExpandSynsFail1,2,3,4 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 22:41:03 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 22:41:03 -0000 Subject: [GHC] #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken In-Reply-To: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> References: <044.f628d91a6d3fea6e78ba64e848c2026b@haskell.org> Message-ID: <059.34d6a6acafea9d2f53534eefddba4da3@haskell.org> #10638: quoting and Template Haskell handling for prim and javascript foreign imports broken -------------------------------------+------------------------------------- Reporter: luite | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: th/T10638 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1070 -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => th/T10638 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 22:48:30 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 22:48:30 -0000 Subject: [GHC] #10548: Support PartialTypeSignatures in Template Haskell In-Reply-To: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> References: <045.2df5e13492bce560a66b130aa6f59e92@haskell.org> Message-ID: <060.fe7f02b8f8af9d4ec0db9bb14a1c9a03@haskell.org> #10548: Support PartialTypeSignatures in Template Haskell -------------------------------------+------------------------------------- Reporter: spinda | Owner: thomasw Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: comment:17 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1048 -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => comment:17 Comment: D1048 included the following tests, * `ExtraConstraintsWildcardInExpressionSignature` * `ExtraConstraintsWildcardInPatternSignature` * `ExtraConstraintsWildcardInPatternSplice` * `ExtraConstraintsWildcardInTypeSplice` * `ExtraConstraintsWildcardInTypeSplice2` * `ExtraConstraintsWildcardInTypeSpliceUsed` * `NamedWildcardInTypeSplice` * `WildcardInTypeBrackets` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 20 23:27:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 20 Jul 2015 23:27: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.50debacbc67332c4a11f1f3a917d243a@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T8958a Blocked By: | Blocking: Related Tickets: #10298, #7695 | Differential Revisions: | Phab:D1059, Phab:D1085 -------------------------------------+------------------------------------- Changes (by rwbarton): * status: closed => new * priority: normal => high * differential: Phab:1059 => Phab:D1059, Phab:D1085 * resolution: fixed => * milestone: => 7.10.2 Comment: I realized that at least hsyl20 and perhaps others actually intend to run their programs in the (what I would consider to be broken) setting of a chroot without a working iconv installation. In that case we really shouldn't use `char8` when asked for an ASCII locale. If the programmer wants `char8` they can use it explicitly. I implemented an ASCII encoding in Phab:D1085. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 01:36:23 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 01:36:23 -0000 Subject: [GHC] #10663: ghci ignores stuff after an import command and a semicolon Message-ID: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> #10663: ghci ignores stuff after an import command and a semicolon -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Keywords: newcomer | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC accepts Unknown/Multiple | invalid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I can put a semicolon and then an expression or declaration after an import command in ghci, and the expression or declaration is simply ignored. {{{ rwbarton at morphism:~/ghc$ ghci-7.10.1 GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Prelude> import Data.List; x Prelude Data.List> }}} The stuff after the semicolon does have to parse, but then is discarded. Pretty confusing. It's especially confusing when using `ghc -e` {{{ rwbarton at morphism:~/ghc$ ghc-7.10.1 -e "import Data.List; sort [2,1]" rwbarton at morphism:~/ghc$ echo $? 0 }}} The command is wrong (in general you cannot give multiple commands separated by semicolons, you must use multiple `-e` options), but GHC fails to complain in any way and silently ignores the "second command". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 03:35:48 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 03:35:48 -0000 Subject: [GHC] #10613: Mechanism for checking that we only enter single-entry thunks once In-Reply-To: <046.787816a81f7da40c6d0ca0afdcdd9dbb@haskell.org> References: <046.787816a81f7da40c6d0ca0afdcdd9dbb@haskell.org> Message-ID: <061.437927ee2b46e17562d6056af0719ce2@haskell.org> #10613: Mechanism for checking that we only enter single-entry thunks once -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): For what it's worth, while investigating #10414, I ran the whole test suite with `-feager-blackholing`, which (at the time) caused all single- entry thunks to be overwritten with a black hole on entry. There were no test failures, which gives me a reasonably high degree of confidence that the "single-entry thunks are entered only once" invariant is maintained, outside of the situations involving multiple threads entering a closure simultaneously discussed in #10414. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 03:46:33 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 03:46:33 -0000 Subject: [GHC] #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture In-Reply-To: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> References: <056.5868cbe156b7bc338ff1b131da89abc1@haskell.org> Message-ID: <071.a425c53d55fba80dce6f7885ee662305@haskell.org> #10610: Issues face while building glassgow haskell compiler package on power - ppc64le - architecture --------------------------------------+--------------------------------- Reporter: amitkumar_ghatwal | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Other Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: --------------------------------------+--------------------------------- Comment (by rwbarton): In any event `configure --enable-hc-boot --enable-hc-boot-unregisterised` has not worked for a very, very long time. You should follow the instructions at Building/CrossCompiling instead, either using the native code generator that is new in HEAD, or using the C backend via `--enable- unregisterised`. You will require a system that can run both GHC and a cross-compiler to ppc64le. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 04:00:31 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 04:00:31 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.4dff8acd078af5468ba585b99c91aff5@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): gridaphobe's interpretation of my proposal is more accurate. I do mean to allow the reassociation of pattern synonyms in any module. This means that you have to "chase the import chain" to figure out what `T(..)` means. But this is ''already'' true! {{{ module A ( T(MkT1,MkT2) ) where data T = MkT1 | MkT2 | MkT3 module B ( T(..) ) where import A ( T(MkT1) ) module C ( T(..) ) where import B ( T(..) ) module D where import C ( T(..) ) }}} Figuring out what is in scope in `D` requires chasing a module chain. My proposal makes this no different. Indeed, I believe (if we drop the redundant `pattern` keyword in the parenthesized list after a datatype) my proposal makes it so that data constructors are no longer privileged at all. For example: {{{ module E ( T( Pat ), pattern Mk ) where data T = Mk pattern Pat = Mk }}} This means that `Pat` is imported with `T(..)` but `Mk` has to be imported separately. Is this confusing? Perhaps. But perhaps it is also sensible if done for backward compatibility. I'm not really against putting all of this in the datatype declaration instead of in an export list. (Actually, I quite like `data T = PublicMk | abstract PrivateMk` or similar.) But aiming to avoid module chasing to understand `T(..)` is a red herring. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 04:12:06 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 04:12:06 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.1a5020056d22d5cf7cc3cf39c20750da@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I think Richard's proposal already allows this, but I would add that there is likely some real value in allowing a module to associate a pattern synonym with a type constructor even when the module is not the one in which the type constructor is defined. It's a common organization to put a bunch of types in a single, sometimes "internal", module (to avoid import loops) and then define functions involving those types in many different modules (to avoid having one giant module of doom). Pattern synonyms can involve nontrivial functions if they use view patterns (think of Data.Seq for instance) so it would be useful to associate a pattern synonym with a data type in a top-level module that consists of re-exports. On the subject of requiring pattern synonyms attached to type constructors to have that type constructor in outermost position in their type, what about polymorphic pattern synonyms? Doesn't it make sense to write something like {{{ pattern Nil = (Foldable.null -> True) }}} where `Nil` matches an expression of type `Foldable t => t a`? What is the rule then? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 04:20:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 04:20:24 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.84fee71887e705cd8b6005b165db0bdc@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Replying to [comment:12 goldfire]: > But aiming to avoid module chasing to understand `T(..)` is a red herring. Sorry Richard, I should have been clearer. I know that the precise meaning of `T(..)` already depends on the full import chain. What I meant what that I can see the argument for `T(..)` to have a maximal meaning. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 04:20:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 04:20:47 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.fa2fffebda50fc429a619ee5ca375876@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Comment (by rwbarton): Replying to [comment:8 trommler]: > Replying to [comment:5 rwbarton]: > My understanding of what we want to be able to override is very hazy. Do we have a wiki page that describes the semantics of loading packages and libraries into ghci? > > Possibly we only need to use RTLD_LOCAL when building the ghci linker statically? Then we could revert the other changes like #10322 and #10110 and #10058. > What does it mean "building the ghci linker statically"? I mean when compiling the RTS (specifically Linker.c) for eventual inclusion into a static library rather than a dynamic library. I thought that we already used some mechanism to check for this somewhere in the RTS, but now I can't find it so maybe I imagined it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 04:49:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 04:49:47 -0000 Subject: [GHC] #10535: Float out causes major space leak In-Reply-To: <045.805dcb016f0fb85535fb7bc68c72dcaf@haskell.org> References: <045.805dcb016f0fb85535fb7bc68c72dcaf@haskell.org> Message-ID: <060.ed69b1bae4f00c6f1e8e4c9a25bcfacf@haskell.org> #10535: Float out causes major space leak -------------------------------------+------------------------------------- Reporter: AlexET | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #7367 #7206 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): This is a frequently reported issue. The original is #917, and other tickets (#1945, #3273, #4276, #5729) have been closed as duplicates of it. #8457 has a recapitulation of the subject. Should we close this ticket as a duplicate too? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 05:48:02 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 05:48:02 -0000 Subject: [GHC] #10630: Template variable unbound in rewrite rule (GHC 7.10.1) In-Reply-To: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> References: <044.2348e1502d5a9ad5de551838409efa1d@haskell.org> Message-ID: <059.4535129482db6691260c2572f6d8f080@haskell.org> #10630: Template variable unbound in rewrite rule (GHC 7.10.1) -------------------------------------+------------------------------------- Reporter: Otini | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: panic, | template, bitmap Operating System: Linux | Architecture: x86_64 Type of failure: GHC rejects | (amd64) valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => fixed * milestone: ? => 7.10.2 Comment: I confirmed that this is fixed in the ghc-7.10 branch. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 07:46:02 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 07:46:02 -0000 Subject: [GHC] #10522: Add UInfixT, like UInfixE or UInfixP but for types In-Reply-To: <045.117758279834e73fff10891f1400af9d@haskell.org> References: <045.117758279834e73fff10891f1400af9d@haskell.org> Message-ID: <060.1f2fb4462c81ede91967f26aeb0a270d@haskell.org> #10522: Add UInfixT, like UInfixE or UInfixP but for types -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1088 -------------------------------------+------------------------------------- Changes (by spinda): * owner: => spinda * differential: => Phab:D1088 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 09:35:39 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 09:35:39 -0000 Subject: [GHC] #10653: PatternSynonyms should be imported/exported as part of the wildcard notation In-Reply-To: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> References: <049.0e5a3c33a167308dc99ecaed5730df14@haskell.org> Message-ID: <064.d4acdc5d9fe05f9f1468265ca085ad63@haskell.org> #10653: PatternSynonyms should be imported/exported as part of the wildcard notation -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: pattern | synonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes, you do have to import-chase to figure out which ''subset'' of data constructors are imported by `T(..)`. But there's an upper bound: it can import no more than all the constructors. With the new proposal, ''any'' old new pattern synonym could be brought into scope by `T(..)`. That is new. Maybe it's not terrible, but it's new. Maybe one would want to associate more things with `T`? Such as a family of functions over `T`, whether or not they are pattern synonyms? Anyway I don't feel terribly strongly about all this ''provided'' it can all be resolved by the renamer (ie not involving type inference). By all means write a wiki page, seek feedback etc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 09:41:31 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 09:41:31 -0000 Subject: [GHC] #10535: Float out causes major space leak In-Reply-To: <045.805dcb016f0fb85535fb7bc68c72dcaf@haskell.org> References: <045.805dcb016f0fb85535fb7bc68c72dcaf@haskell.org> Message-ID: <060.0bb3a988281dfb9944387e553b1b5c2c@haskell.org> #10535: Float out causes major space leak -------------------------------------+------------------------------------- Reporter: AlexET | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #7367 #7206 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => duplicate Comment: Yes, that makes sense. I wish I knew what to do about the full-laziness space leak problem! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 09:42:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 09:42:14 -0000 Subject: [GHC] #8457: -ffull-laziness does more harm than good In-Reply-To: <044.229777d98aeb2cc7741c2bcf36225fde@haskell.org> References: <044.229777d98aeb2cc7741c2bcf36225fde@haskell.org> Message-ID: <059.5d7bc5dc86e0861a9446d6b1b0a4cfcf@haskell.org> #8457: -ffull-laziness does more harm than good -------------------------------------+------------------------------------- Reporter: errge | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): See also #917, #1945, #3273, #4276, #5729, #10535 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 11:46:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 11:46:51 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.6ca1301af736e70ab85b3ea7c67ec6ea@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | simplCore/should_compile/T10627 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged into `ghc-7.10` as 3794b597896e1138e23043de5646e60e3d011b27. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 11:47:40 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 11:47:40 -0000 Subject: [GHC] #10527: Panic Simplifier ticks exhausted with type families In-Reply-To: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> References: <045.3e1b7beda71c6891caa1dc0451a59ca1@haskell.org> Message-ID: <060.d3588157390f3a1d1bcaf3047a5d05a4@haskell.org> #10527: Panic Simplifier ticks exhausted with type families -------------------------------------+------------------------------------- Reporter: sopvop | Owner: simonpj Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.10.2 => 7.12.1 Comment: As this is fixed in 7.10.2 I'm going to re-milestone to 7.12.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 11:49:16 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 11:49:16 -0000 Subject: [GHC] #10530: Update transformers library In-Reply-To: <052.0c31d10f46f9c718da9cede6af3f558b@haskell.org> References: <052.0c31d10f46f9c718da9cede6af3f558b@haskell.org> Message-ID: <067.7dc700ff7d1691c4ec03b5ed73c56f68@haskell.org> #10530: Update transformers library -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.2 Component: libraries | Version: 7.10.2-rc2 (other) | Keywords: Resolution: wontfix | transformers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => wontfix Comment: We decided against this bump a few weeks ago. Closing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 11:50:11 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 11:50:11 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.d608d34c49e454d9ebc29ad889b2fa43@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by bgamari): * milestone: 7.10.2 => 7.12.1 Comment: As we are going to punt on this in 7.10.2 I'm going to re-milestone this for 7.12.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 11:53:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 11:53:47 -0000 Subject: [GHC] #10597: Linking of binaries fails on OpenBSD due to PIE support In-Reply-To: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> References: <046.bbef59da3b2fc0658a122f249ffe1800@haskell.org> Message-ID: <061.b061a704b06579fd37f97889cb0b8cf7@haskell.org> #10597: Linking of binaries fails on OpenBSD due to PIE support -------------------------------------+------------------------------------- Reporter: kgardas | Owner: kgardas Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: Merged to `ghc-7.10` as 0cfee536e5261af873485e7150be4a4ac26cd0e3. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 12:13:16 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 12:13:16 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.1ecdf76be8efa09d1abc84f78d99e8e8@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.10.2 => 7.12.1 Comment: `T2497` passes with the current state of the `ghc-7.10` branch (likely due to the fix for #10527). Re-milestoning for 7.12.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 12:16:08 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 12:16:08 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.496d4eda0c5d72eee20be64aa795b48f@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.12.1 => 7.10.2 Comment: Never mind, I was testing with the wrong `WAY`. It appears to still fail on 7.10. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 12:20:32 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 12:20:32 -0000 Subject: [GHC] #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds In-Reply-To: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> References: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> Message-ID: <060.eaae726275d22a660f4666719fcc4420@haskell.org> #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | gadt/termination Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"8f48fdc8f97c1f6f59e12a703e380d27760810b1/ghc" 8f48fdc/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="8f48fdc8f97c1f6f59e12a703e380d27760810b1" Use varToCoreExpr in mkWWcpr_help Lacking this cuased Trac #10658. The fix is easy; it was a simple omission. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 12:28:54 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 12:28:54 -0000 Subject: [GHC] #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds In-Reply-To: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> References: <045.3f2e26428d1f872a69bf0fec38cbfcef@haskell.org> Message-ID: <060.68e721864d41b38e9b2af8f65d554fbe@haskell.org> #10658: Regression gadt/termination -O Core Lint errors : in result of Worker Wrapper binds -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | gadt/termination Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 12:52:28 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 12:52:28 -0000 Subject: [GHC] #10651: Type checking issue with existential quantification, rank-n types and constraint kinds In-Reply-To: <046.13e821c10925b9eff72404016930e9cc@haskell.org> References: <046.13e821c10925b9eff72404016930e9cc@haskell.org> Message-ID: <061.919f88cab1ab016d726799ac6750c1d7@haskell.org> #10651: Type checking issue with existential quantification, rank-n types and constraint kinds -------------------------------------+------------------------------------- Reporter: Roboguy | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): The error message is not great, but I think it's right. To show that the type of `constrMap_` is unambiguous, GHC needs to prove that {{{ (forall a. c a => a -> m b) ~ (forall a. c a => a -> m beta) }}} where `beta` is a unification variable. If GHC guessed (unified) `beta := b`, all would be well, but `beta` is "untouchable" underneath the constraint `c a`. Why? Because what if `c a` later got instantiate to `b ~ Int`; then `beta := Int` might be a valid substitution. In general, GHC doesn't unify underneath an equality, ''or'' something that might turn into an equality. See Section 5 in the [http://research.microsoft.com/~simonpj/papers/constraints/jfp- outsidein.pdf OutsideIn paper]. I don't know how to improve this. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 13:05:31 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 13:05:31 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.1882ae7746ac73ff2558eb799790a4ff@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: This is hardly suprising. Inlining `(==)` we get {{{ {-# RULES "rule 1" forall x y. x == y = y == x #-} }}} So rewriting using the rule yields a new opportunity for using the rule. What did you expect? Re-open if you disagree. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 13:20:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 13:20:47 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.df6343e5ab2f7fb6b89859f803567f74@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"3c44a46b352a4eb7ff72eb3aa5495b25dee8351f/ghc" 3c44a46b/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="3c44a46b352a4eb7ff72eb3aa5495b25dee8351f" Refactor self-boot info This patch is a simple refactoring that prepares for a later one, related to Trac #10083. * Add a field tcg_self_boot :: SelfBootInfo to TcGblEnv, where SelfBootInfo is a new data type, describing the hi-boot file, if any, for the module being compiled. * Make tcHiBootIface return SelfBootInfo, a new data type * Make other functions get SelfBootInfo from the monad. * Remove tcg_mod_name from TcGblEnv; it was barely used and simpler to pass around explicitly. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 13:20:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 13:20:47 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.5e4d5371adc6efc308a4654d0855a729@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"efa7b3a474bc373201ab145c129262a73c86f959/ghc" efa7b3a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="efa7b3a474bc373201ab145c129262a73c86f959" Add NOINLINE for hs-boot functions This fixes Trac #10083. The key change is in TcBinds.tcValBinds, where we construct the prag_fn. With this patch we add a NOINLINE pragma for any functions that were exported by the hs-boot file for this module. See Note [Inlining and hs-boot files], and #10083, for details. The commit touches several other files becuase I also changed the representation of the "pragma function" from a function TcPragFun to an environment, TcPragEnv. This makes it easer to extend during construction. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 13:33:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 13:33:24 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.1fa931d4a9925074f99ef2cd9a86a120@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): simonpj, well, the real question is "what is was the author of the testcase expecting?" It seems that the intention of this test is to verify that scoping in RULES works correctly, not exercise the simplifier (although it's a bit difficult reconstructing this from the cited tickets). In light of this, it seems like the right solution here is to fix the testcase. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 13:38:46 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 13:38:46 -0000 Subject: [GHC] #10506: SourceNotes are not applied to all identifiers In-Reply-To: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> References: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> Message-ID: <064.5036471f714f1c84144a724583903d17@haskell.org> #10506: SourceNotes are not applied to all identifiers -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): scpmw, any updates here? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 14:48:40 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 14:48:40 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.c31b901545d5681d4b27b18ce2f56bb1@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => new * resolution: invalid => * milestone: 7.10.2 => 7.10.3 Comment: Simon is working on a new testcase. In the meantime we'll mark this as broken in 7.10.2. Reopening so we don't loose track of this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 15:20:51 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 15:20:51 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier In-Reply-To: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> References: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> Message-ID: <060.7452ee8f620a579c06fe14f394a32f06@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/conc034, | libraries/array/tests/array001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.10.2 => 7.12.1 Comment: We discussed this in the GHC call today. SPJ is working on a fix although isn't concerned that the issue found by Core lint jeopardizes real-world programs. Indeed the binary produced by compiling without `-dcore-lint` runs as expected. Marked on `ghc-7.10` as broken in dc771a80c2222e4843c71af09d78fef35fba9b06. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 15:24:00 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 15:24:00 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.335d00a7ce8b69f88c2629d4c11e8f5f@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.10.3 => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 15:36:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 15:36:25 -0000 Subject: [GHC] #10543: MacOS: validate fails on \u In-Reply-To: <047.a887440a0df817cb06caf9fc53c8c2c9@haskell.org> References: <047.a887440a0df817cb06caf9fc53c8c2c9@haskell.org> Message-ID: <062.bb243e36a7e265de3cadf2e02def76e9@haskell.org> #10543: MacOS: validate fails on \u -------------------------------------+------------------------------------- Reporter: trommler | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: invalid | Keywords: cpp Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1004 -------------------------------------+------------------------------------- Comment (by rodlogic): Replying to [comment:5 geoff]: > So, I was the one to add this line ? overriding `-Wno-invalid-pp-token -Wno-unicode -Wno-trigraphs` ? because these flags are not universally supported by clang. If anyone could help me understand this better, it would be appreciated. https://github.com/Homebrew/homebrew/issues/41777#issuecomment-122826887 I am not that familiar with GHC's build system, so I can't answer that. Hopefully someone else can? Here is the question, inlined: {{{ @rodlogic Is there a reason why the stage 0 bootstrap has to be built with -Werror? These warnings are pretty benign (indeed, more benign than the flags to suppress them). And what exactly is the significance of the \u in the source file, in this particular case? Support for unicode literals are not mandatory in POSIX in many places, and Mac OS X being a certified UNIX system, this is unlikely to change. The only way to reliably encode an arbitrary Unicode character in ASCII is is to use the octal sequences that comprise the glyph. Or, you could simply use the actual glyph, treating the source file as UTF-8, of course. But this seems particularly odd to me here, since the character that follows is t! So why is this needed here at all? What am I missing? }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 16:09:00 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 16:09:00 -0000 Subject: [GHC] #10083: ghc: panic! (the 'impossible' happened) In-Reply-To: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> References: <047.98ab68675b5fd7aadd4f473d218b6ef3@haskell.org> Message-ID: <062.d7c1bb3880bedbae9f27d9e5d75aa5a0@haskell.org> #10083: ghc: panic! (the 'impossible' happened) -------------------------------------+------------------------------------- Reporter: hedayaty | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Actually comment:17 does '''not''' fix #10083, because I found that the fix made the compiler go slower: {{{ Unexpected stat failures: perf/compiler T1969 [stat not good enough] (normal) perf/compiler T9872a [stat not good enough] (normal) perf/compiler T9872b [stat not good enough] (normal) perf/compiler T9872c [stat not good enough] (normal) perf/compiler T9872d [stat not good enough] (normal) bytes allocated value is too high: Deviation T1969(normal) bytes allocated: 7.5 % Deviation T9872d(normal) bytes allocated: 9.3 % Deviation T9872c(normal) bytes allocated: 8.4 % }}} by about 8% allocation overall. So the patch has all the code, but the key bit is commented out. See `Note [Inlining and hs-boot files]` in `TcBinds`. Presumably disabling inlining of functions exported by a `hs-boot` file really kills GHC's performance somewhere, implausible though it sounds. I suppose the next thing to do is to find out why, but I just don't have time to do that now, so I'm parking the whole thing. Sigh. Does anyone want to help? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 16:42:38 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 16:42:38 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier In-Reply-To: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> References: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> Message-ID: <060.33bced753cf54ad12f744b793d77a45e@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/conc034, | libraries/array/tests/array001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"00f3187a615813b5dbc870f0477124c9cf76c9f2/ghc" 00f3187/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="00f3187a615813b5dbc870f0477124c9cf76c9f2" Make seq-of-cast rule generate a case Previously it generated another call to seq, which triggered a lint failure (Trac #10659) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 16:44:12 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 16:44:12 -0000 Subject: [GHC] #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted In-Reply-To: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> References: <045.e07d83ab55eb2ec279004215c7074423@haskell.org> Message-ID: <060.7bb6d1e84476f75a1576adfab860c3fe@haskell.org> #10657: Regression T2497 WAY=optasm: Simplifier ticks exhausted -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T2497 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: This {{{ commit 55754ea34bd42ae88121311e9d0f29e90cce8166 Author: Simon Peyton Jones Date: Tue Jul 21 14:39:17 2015 +0100 Fix test T2497 to avoid infinite loop in RULES }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 16:44:52 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 16:44:52 -0000 Subject: [GHC] #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier In-Reply-To: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> References: <045.10fe039339e194e959bbf9b0c552a3d4@haskell.org> Message-ID: <060.b5f0ddc899f3159ac200693e832840bd@haskell.org> #10659: Regression concurrent/conc034 -O Core Lint errors : in result of Simplifier -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/conc034, | libraries/array/tests/array001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => fixed Comment: Both crashes are fixed by this. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 17:06:46 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 17:06:46 -0000 Subject: [GHC] #10662: GHC warning shows technical summary of AST instead of the user's code In-Reply-To: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> References: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> Message-ID: <062.173ad32281ba60e6aa5e7b59a34271e1@haskell.org> #10662: GHC warning shows technical summary of AST instead of the user's code -------------------------------------+------------------------------------- Reporter: kolmodin | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by kolmodin: Old description: > I got a warning for some code I wrote; > > {{{#!hs > forkIO (....) > }}} > > Naturally GHC warns me that I'm throwing away the result, and should > write like this; > > {{{#!hs > _ <- forkIO (...) > }}} > > However, the warning is expressed in a somewhat confusing way, not sure > this is intentional. > > {{{ > examples/route_guide_client.hs:84:5: Warning: > A do-notation statement discarded a result of type ?ThreadId? > Suppress this warning by saying > ?_ <- ($) > forkIO > let > AbsBinds [] [] > {Exports: [go <= go > <>] > Exported types: go :: [L.ByteString] -> IO () > [LclId, Str=DmdType] > Binds: go acc = ...} > in go []? > or by using the flag -fno-warn-unused-do-bind > > }}} > > I find it confusing that the warning mentions AbsBinds, exports and > types. > I'd expect a snippet of my code in the warning. > > However, doesn't look like this is a (recent) regression. The same > happens GHC 7.8.4 and 7.10.1. New description: Have a look at this code and the warning it generates; {{{#!hs -- T10662.hs main :: IO () main = do return $ let a = "hello" in a return () }}} We compile it with {{{ghc --make -Wall T10662.hs}}} {{{ [1 of 1] Compiling Main ( T10662.hs, T10662.o ) T10662.hs:3:3: Warning: A do-notation statement discarded a result of type ?[Char]? Suppress this warning by saying ?_ <- ($) return let AbsBinds [] [] {Exports: [a <= a <>] Exported types: a :: [Char] [LclId, Str=DmdType] Binds: a = "hello"} in a? or by using the flag -fno-warn-unused-do-bind Linking T10662 ... $ }}} Naturally GHC warns me that I'm throwing away the result, and should write like this; {{{#!hs main :: IO () main = do _ <- return $ let a = "hello" in a return () }}} I find it confusing that the warning mentions AbsBinds, exports and types. I'd expect a snippet of my code in the warning. It doesn't look like this is a (recent) regression. The same happens GHC 7.8.4 and 7.10.1. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 17:07:15 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 17:07:15 -0000 Subject: [GHC] #10662: GHC warning shows technical summary of AST instead of the user's code In-Reply-To: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> References: <047.fe5b14891f46efc740c72fc5c88bcc32@haskell.org> Message-ID: <062.46e93e038388fdee6d5ef2ccbbedcda2@haskell.org> #10662: GHC warning shows technical summary of AST instead of the user's code -------------------------------------+------------------------------------- Reporter: kolmodin | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by kolmodin): * Attachment "T10662.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 17:10:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 17:10:47 -0000 Subject: [GHC] #10664: T8131 times out on master Message-ID: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> #10664: T8131 times out on master -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The testsuite test `codeGen/should_fail/T8131` appears to time out on the `master` branch as of today. This isn't counted as a testsuite failure as it is a should-fail test, but nevertheless something is not right as it doesn't terminate despite being allowed to run for several minutes. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 17:14:20 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 17:14:20 -0000 Subject: [GHC] #10664: T8131 times out on master In-Reply-To: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> References: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> Message-ID: <061.2fb4067db7d7673c7fd3c0e49f30e19f@haskell.org> #10664: T8131 times out on master -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): I should note that there is no CPU usage while the test is running. It appears to be deadlocked. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 17:14:47 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 17:14:47 -0000 Subject: [GHC] #10664: T8131 times out on master In-Reply-To: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> References: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> Message-ID: <061.eee448573099595f2cb1b97f05eab51f@haskell.org> #10664: T8131 times out on master -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): The test runs for five minutes before being killed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 17:15:16 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 17:15:16 -0000 Subject: [GHC] #10664: T8131 times out on master In-Reply-To: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> References: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> Message-ID: <061.145e2c76eef73dcdbdb8d829531474a3@haskell.org> #10664: T8131 times out on master -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Oh good, then the <> mentioned at ticket:8131#comment:17 is not hopeless to debug after all :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 19:19:10 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 19:19:10 -0000 Subject: [GHC] #10416: GHC 7.10.1 User Guide profiling section 5.4 missing images In-Reply-To: <044.0e4dde9e3a0324f18f8091c422680492@haskell.org> References: <044.0e4dde9e3a0324f18f8091c422680492@haskell.org> Message-ID: <059.0c58a99c0d41d87c1aee093646664583@haskell.org> #10416: GHC 7.10.1 User Guide profiling section 5.4 missing images -------------------------------------+------------------------------------- Reporter: alanz | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Documentation | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D958, | Phab:D970 -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.10.2 => 7.10.3 Comment: I think we may need to punt on this for 7.10.2. I spent several hours on this today and have been entirely unable to get even the an `` tag to be produced in the HTML, much less a rendered image. Sadly DocBook appears to be an antiquated disaster. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 19:42:09 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 19:42:09 -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.ae5e212f49d43726f6a892165710a5d0@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T8958a Blocked By: | Blocking: Related Tickets: #10298, #7695 | Differential Revisions: | Phab:D1059, Phab:D1085 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"dbe6dac96543f426297a59d8d16c3f5afacf42d4/ghc" dbe6dac/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dbe6dac96543f426297a59d8d16c3f5afacf42d4" When iconv is unavailable, use an ASCII encoding to encode ASCII D898 and D1059 implemented a fallback behavior to handle the case that the end user's iconv installation is broken (typically due to running inside a chroot in which the necessary locale files and/or gconv modules have not been installed). In this case, if the program requests an ASCII locale, GHC's char8 encoding is used rather than the program failing. However, silently mangling data like char8 does when the programmer did not ask for it is poor behavior, for reasons described in D1059. This commit implements an ASCII encoding and uses it in the fallback case when iconv is unavailable and the user has requested ASCII. Test Plan: Added tests for the encodings defined in Latin1. Also, manually ran a statically-linked executable of that test in a chroot and the tests passed (up to the ones that call mkTextEncoding "LATIN1", since there is no fallback from iconv for that case yet). Reviewers: austin, hvr, hsyl20, bgamari Reviewed By: hsyl20, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1085 GHC Trac Issues: #7695, #10623 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 19:42:09 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 19:42:09 -0000 Subject: [GHC] #7695: Hang when locale-archive and gconv-modules are not there In-Reply-To: <042.96ea14c731f7f52fd1ea0cef77ce2267@haskell.org> References: <042.96ea14c731f7f52fd1ea0cef77ce2267@haskell.org> Message-ID: <057.6da87cc915df591b2135eb466449f301@haskell.org> #7695: Hang when locale-archive and gconv-modules are not there -------------------------------------+------------------------------------- Reporter: hpd | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.2 Component: None | Version: 7.8.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #8977, #10298 | Differential Revisions: Phab:D898 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"dbe6dac96543f426297a59d8d16c3f5afacf42d4/ghc" dbe6dac/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="dbe6dac96543f426297a59d8d16c3f5afacf42d4" When iconv is unavailable, use an ASCII encoding to encode ASCII D898 and D1059 implemented a fallback behavior to handle the case that the end user's iconv installation is broken (typically due to running inside a chroot in which the necessary locale files and/or gconv modules have not been installed). In this case, if the program requests an ASCII locale, GHC's char8 encoding is used rather than the program failing. However, silently mangling data like char8 does when the programmer did not ask for it is poor behavior, for reasons described in D1059. This commit implements an ASCII encoding and uses it in the fallback case when iconv is unavailable and the user has requested ASCII. Test Plan: Added tests for the encodings defined in Latin1. Also, manually ran a statically-linked executable of that test in a chroot and the tests passed (up to the ones that call mkTextEncoding "LATIN1", since there is no fallback from iconv for that case yet). Reviewers: austin, hvr, hsyl20, bgamari Reviewed By: hsyl20, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1085 GHC Trac Issues: #7695, #10623 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 20:07:39 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 20:07:39 -0000 Subject: [GHC] #9832: Get rid of PERL dependency of `ghc-split` In-Reply-To: <042.a80d180822707ef08b1350d4a542cee3@haskell.org> References: <042.a80d180822707ef08b1350d4a542cee3@haskell.org> Message-ID: <057.ac76f3d4cb59729b5d9278e38dc41504@haskell.org> #9832: Get rid of PERL dependency of `ghc-split` -------------------------------------+------------------------------------- Reporter: hvr | Owner: Phyx- Type: task | Status: new Priority: high | Milestone: 7.12.1 Component: Driver | Version: Resolution: | Keywords: perl Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Phyx-): I'm not quite sure the problem being solved here is either, but I don't think it's binary size. since the perl distribution (looking at GHC 7.10.1) comes down to a `perl.exe` and a `perl56.dll` which together with the perl `GHC-split` file comes to a smaller since than the Haskell `GHC- split`. My assumption has been that the problem being addressed is to lower the amount of "other" languages used by the compiler/tools. The actual implementation isn't that big, what ended up being big is the fact that I needed to use a perl regular expression library unless I rewrite it to using something else, like parsec maybe... Two things could be done: First I could instead of having the `pcre` source inlined I could depend on the availability of `libpcre` being available on the build platform. This would remove the 30,000 lines of C but introduce an extra dependency. Secondly I can strip the `pcre` Haskell bindings down to the bare essentials that I actually use. This would be a very small subset of the current code. But would also mean that if you want to extend this and need any features I didn't need before from the lib the code would have to be re-introduced. Also when doing this I found a few lines of dead code and functions that I could never get the compiler to generate code to enter. Which makes me wonder if those parts are still needed to begin with. But in general, I agree, this may be more trouble then it's worth. Especially if the original goal was to reduce binary size. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 20:16:03 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 20:16:03 -0000 Subject: [GHC] #10510: Testsuite driver does not run tests in parallel on Windows In-Reply-To: <045.f7051a2be634cd79e52b8850db4fc44f@haskell.org> References: <045.f7051a2be634cd79e52b8850db4fc44f@haskell.org> Message-ID: <060.1958e7c5355d58a9e2be6ab39fc9d3e9@haskell.org> #10510: Testsuite driver does not run tests in parallel on Windows -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Test Suite | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Phyx-): I have some time set aside this weekend to try to get to the bottom of this. Or at least get closer. The ordinals resolve to: {{{ 1816 717 000EDB02 strptime 208 CF 000EC4BE _ecvtbuf 130 81 000EBFB4 _aclsort }}} But not really sure why `strptime` would be calling `_aclsort` unless I'm missing something. We don't seem to be the only ones with this issue though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 20:32:14 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 20:32:14 -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.362fe0b24d885e1153bbc96c98c37fb2@haskell.org> #10623: Handling of ASCII encodings introduced in D898 breaks Unicode terminal detection -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: T8958a Blocked By: | Blocking: Related Tickets: #10298, #7695 | Differential Revisions: | Phab:D1059, Phab:D1085 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 20:35:56 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 20:35:56 -0000 Subject: [GHC] #10665: INLINE breaks rewrite rules when '-g' is used Message-ID: <045.95657d2fca941df9621daef19a7fe710@haskell.org> #10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The bug is found when building conduit-1.2.4.2 package with '-O2 -g' options. The distilled sample looks like that: {{{#!hs {-# LANGUAGE BangPatterns #-} module RewriteBug (bug) where bug :: () -> () bug () = bug () {-# NOINLINE bug #-} a2 :: () a2 = () {-# INLINE[1] a2 #-} {-# RULES "bug a2" [0] bug a2 = () #-} {- Crashes as: $ inplace/bin/ghc-stage2 -c -O1 -fforce-recomp RewriteBug.hs -g ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150721 for x86_64-unknown-linux): Tick in rule () -} }}} My theory of sequence of actions is the following: - rewrite rule gets read as-is by GHC (gentle phase) - a2 INLINE changes LHS of rewrite rule (phase 1) - when time comes to apply 'bug a2' rule GHC detects INLINE problem (phase 0) In real code it happened across multiple files. The bug is reproducible in both ghc-7.10.2-rc2 and today's HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 21 22:32:38 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 21 Jul 2015 22:32:38 -0000 Subject: [GHC] #10666: Distinguish between semantic module / identity module in TcGblEnv, ModIface and ModGuts Message-ID: <045.a63a148a701a6aba51ee3e839e6cd62c@haskell.org> #10666: Distinguish between semantic module / identity module in TcGblEnv, ModIface and ModGuts -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package | Version: 7.10.1 system | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- When we write a signature like {{{ package p where signature H where data T }}} and compile it to an interface file, there are two ways we might say what the `Module` of this interface is: 1. The **identity module** uniquely identifies an interface file, and is used for dependency analysis and tracking. In the example above, the identity module is `p(H -> HOLE:H):H`. 2. The **semantic module** tells us what the `Name`s of the entities defined in the module are supposed to be; e.g., it's used for generating new names when type-checking hs files or interfaces. In the example above, the semantic module is `hole:H`, since this signature exports one entity named `hole:H.T`. The semantic module can always be derived from the identity module. For normal Haskell modules, the semantic and identity module coincide. However, for signatures they differ: we may have many signatures for the same module; they all share their semantic module but have differing identity modules. By in large, when GHC manipulates `Module` directly it is interested in the identity module. However, when a `Module` is used with reference to a `Name` (primarily `nameIsLocalOrFrom`), we want to use the SEMANTIC module. (Another example: when we filter out the type environment before making a `ModIface`, need to filter against the semantic module.) I tried a few ways of factoring GHC's code so we'd be less likely to confuse these two `Module`s when typechecking signatures: the big problem is if you're adding a `getModule` call to `TcRn`, you're probably not going to think too hard whether or not you actually wanted the semantic module or the identity module. But if you pick the wrong thing that will break all sorts of things for signatures. Here are some things we could do: 1. My initial attempt was to change `tcg_mod`, `mg_module` and `mi_module` to record a new data type `TopModule` which recorded both the semantic and identity module, with `getModule` in `TcRn` continuing to return a semantic module, but `mi_module` returning an identity module. However, the resulting patch was pretty ugly and it's not altogether clear that `getModule` returning the semantic module is always correct. 2. My other idea is to say that these entries always are IDENTITY modules (this will result on fail fast behavior for signatures if you get it wrong), and then rewrite `nameIsLocalOrFrom`, `externaliseAndTidyId`, `initIfaceTcRn`, `newGlobalBinder` so that they always do the right thing (i.e. use the semantic module); thus, the only time you can get it wrong is if you're creating some new functionality that's not these functions that needs to use semantic modules. Pretty delicate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 01:13:43 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 01:13:43 -0000 Subject: [GHC] #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings In-Reply-To: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> References: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> Message-ID: <064.8853ae23c9d38c4cdbf085309d20e73b@haskell.org> #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings -------------------------------------+------------------------------------- Reporter: rpglover64 | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: partial- crash | sigs/should_compile/T10438 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rpglover64): For reference, this is still an issue in ghc-7.10.1.20150630 (i.e. 7.10.2-rc2). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 04:34:53 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 04:34:53 -0000 Subject: [GHC] #9218: Upgrade the version of MinGW shipped with GHC In-Reply-To: <047.dd7762c6a468e59baf096987bc6ae487@haskell.org> References: <047.dd7762c6a468e59baf096987bc6ae487@haskell.org> Message-ID: <062.7488f5f57522aaa2a024c8aed5125aad@haskell.org> #9218: Upgrade the version of MinGW shipped with GHC -------------------------------------+------------------------------------- Reporter: komadori | Owner: gintas Type: task | Status: patch Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 9014 | Blocking: 9215 Related Tickets: #3390 | Differential Revisions: Phab:D339 -------------------------------------+------------------------------------- Comment (by lukexi): Would be awesome to get this merged! This causes tons of noise on Windows. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 07:19:50 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 07:19:50 -0000 Subject: [GHC] #10666: Distinguish between semantic module / identity module in TcGblEnv, ModIface and ModGuts In-Reply-To: <045.a63a148a701a6aba51ee3e839e6cd62c@haskell.org> References: <045.a63a148a701a6aba51ee3e839e6cd62c@haskell.org> Message-ID: <060.4c182019b5f74b5bcb4b73cbd712db9a@haskell.org> #10666: Distinguish between semantic module / identity module in TcGblEnv, ModIface and ModGuts -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Can you give some examples (starting with the Backpack file I suppose) of when the behaviour of the two differs. In particular, I don't know what "dependency analysis and tracking" means. What shows up in interface files, for example? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 07:43:36 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 07:43:36 -0000 Subject: [GHC] #10660: .dyn_o isn't generated for .hsig files with -dynamic-too In-Reply-To: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> References: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> Message-ID: <060.028900bd3aea701545557b9968fbe217@haskell.org> #10660: .dyn_o isn't generated for .hsig files with -dynamic-too -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: bug | Status: patch Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1084 -------------------------------------+------------------------------------- Changes (by hvr): * keywords: => backpack * status: new => patch * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 08:56:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 08:56:08 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.d3e2387ef95d5e163670830ec6a56d89@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomasw): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 08:56:38 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 08:56:38 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.5354f193833f57c6572301d4d1fcc6bb@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomasw): This is fixed in HEAD by Phab:D613. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 09:10:19 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 09:10:19 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.27670402543194713547959bd42c2940@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Is it committed, or simply in Phab? Is there a regression test? If so can you update the "Test case" field? If not can you add one? Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 09:13:19 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 09:13:19 -0000 Subject: [GHC] #10667: '-g' option generates invalid assembly when '*/*' operator is used Message-ID: <045.7de7e3e8915f886ced608adea09f7f67@haskell.org> #10667: '-g' option generates invalid assembly when '*/*' operator is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Bug is observed when building cpphs-1.19 {{{#!hs module A where x */* y = 42 }}} {{{ $ ghc -fforce-recomp A -g [1 of 1] Compiling A ( A.hs, A.o ) /tmp/ghc23923_0/ghc_2.s: Assembler messages: /tmp/ghc23923_0/ghc_2.s:17:0: Error: bad expression /tmp/ghc23923_0/ghc_2.s:17:0: Warning: missing operand; zero assumed ... }}} The problem here is the following assembly snippet: {{{ .text .align 8 .loc 1 3 1 /* */* */ .quad 12884901911 .quad 0 .quad 15 }}} Would it be worthwile using ';' as a comment instead? Don't know if it's universally portable. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 09:21:06 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 09:21:06 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.9d8f08a24fcd39526e5a12be815cf945@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomasw): Replying to [comment:5 simonpj]: > Is it committed, or simply in Phab? Is there a regression test? If so can you update the "Test case" field? If not can you add one? Thanks [https://git.haskell.org/ghc.git/commit/058af6c90a0e8d122f2d1339b6b4fd0b5ec83d05 Yes]. I have a test for a wild card in a type instance, I'll add one for this too then. I'm actually thinking about adding support for wild cards in data/type instances. I would just replace them with fresh meta variables. This would also address #3699. I don't think named wild cards or extra-constraints wild cards make sense here. What do you think? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 09:33:36 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 09:33:36 -0000 Subject: [GHC] #9218: Upgrade the version of MinGW shipped with GHC In-Reply-To: <047.dd7762c6a468e59baf096987bc6ae487@haskell.org> References: <047.dd7762c6a468e59baf096987bc6ae487@haskell.org> Message-ID: <062.a1aba11db559a4b2c4c1bba0720b2a7b@haskell.org> #9218: Upgrade the version of MinGW shipped with GHC -------------------------------------+------------------------------------- Reporter: komadori | Owner: gintas Type: task | Status: patch Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 9014 | Blocking: 9215 Related Tickets: #3390 | Differential Revisions: Phab:D339 -------------------------------------+------------------------------------- Comment (by thomie): Status update. Nobody is working on this at the moment. GHC sees very little Windows volunteers in general. The unfinished patch in Phab:D339 does (too) many things: - use [http://mingw-w64.org MinGW-w64] instead of [http://www.mingw.org/ mingw] for 32-bit Windows also. - linker changes needed to go with that, mostly from awson's patch in comment:12 - change the provider of the [http://sourceforge.net/projects/mingw-w64/files/Toolchains%20targetting%20Win32/Personal%20Builds/ 32bit] and [http://sourceforge.net/projects/mingw-w64/files/Toolchains%20targetting%20Win64/Personal%20Builds/ 64bit] packages from rubenvb to mingw-builds. By default this results in much [https://phabricator.haskell.org/D339#25977 larger] downloads (2x for 64bit, 5x for 32bit), which means #9014 should be fixed first. - remove all Perl dependencies, which means it's waiting for #9832. - downloads mingw during `./configure` step, instead of via explicit `git clone ...ghc-tarballs.git`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 09:49:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 09:49:32 -0000 Subject: [GHC] #10665: INLINE breaks rewrite rules when '-g' is used In-Reply-To: <045.95657d2fca941df9621daef19a7fe710@haskell.org> References: <045.95657d2fca941df9621daef19a7fe710@haskell.org> Message-ID: <060.cb57161005fe943253d4899a9abac598@haskell.org> #10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Your diagnosis sounds dead right to me. It is very unreliable to have a rule where functions on the LHS can be inlined when the rule is active. Better to make sure that the rule is active only up to phase 2 (say), and the inlining of `a2` happens only after phase 2. Maybe this is really a bug in (the RULES of) conduit? Can you describe the actual RULE and inlining? Getting a panic is bad. Probably we should simply not inline in the LHS of a rule, regardless of INLINE pragmas. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 09:59:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 09:59:34 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.98a3b788b7a1d1080bcef5649537e04b@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): > I'm actually thinking about adding support for wild cards in data/type instances. I would just replace them with fresh meta variables. This would also address #3699. I don't think named wild cards or extra-constraints wild cards make sense here. What do you think? Yes, I agree. Do not use a ''meta'' variable. These are really ''skolems'', just like the named type variables in an ordinary declaration, just anonymous ones. Would need documentation about exactly where these skolem wildcards can appear. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 10:42:19 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 10:42:19 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.d97aff163cdd86c3dedc897498bf05d5@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomasw): Replying to [comment:7 simonpj]: > > I'm actually thinking about adding support for wild cards in data/type instances. I would just replace them with fresh meta variables. This would also address #3699. I don't think named wild cards or extra-constraints wild cards make sense here. What do you think? > > Yes, I agree. Do not use a ''meta'' variable. These are really ''skolems'', just like the named type variables in an ordinary declaration, just anonymous ones. Given the freshly generated `Name` of an anonymous wild card, which function should I use to create a skolem? `newSigTyVar :: Name -> Kind -> TcM TcTyVar` in TcMType using `newMetaKindVar :: TcM TcKind` as kind? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 10:58:59 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 10:58:59 -0000 Subject: [GHC] #9970: Export more types in GHC.RTS.Flags In-Reply-To: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> References: <050.a5b7a1426f78715d4c9bb9384727144d@haskell.org> Message-ID: <065.57e4726c2c15f15ece85298f87e7304f@haskell.org> #9970: Export more types in GHC.RTS.Flags -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: merge Priority: normal | Milestone: 7.10.3 Component: libraries/base | Version: 7.10.1-rc1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1030 -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:02:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:02:03 -0000 Subject: [GHC] #10493: Inaccessible code might be accessible with newtypes and Coercible In-Reply-To: <047.2c11d0767c97fbdfa43aeb457c1a28e7@haskell.org> References: <047.2c11d0767c97fbdfa43aeb457c1a28e7@haskell.org> Message-ID: <062.611f84b155c71bdf55f9a46c4f037046@haskell.org> #10493: Inaccessible code might be accessible with newtypes and Coercible -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10493 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * version: 7.11 => 7.10.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:05:18 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:05:18 -0000 Subject: [GHC] #10494: Representational equalities over AppTys are not hard failures In-Reply-To: <047.6c55cf81fc9e307934dd2710cdafc698@haskell.org> References: <047.6c55cf81fc9e307934dd2710cdafc698@haskell.org> Message-ID: <062.435904f7040262f1cae1844d0afeb73f@haskell.org> #10494: Representational equalities over AppTys are not hard failures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10494 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * version: 7.11 => * resolution: => fixed Comment: I am a bit confused; the cited example appears to compile for me with 7.8, 7.10.1, and 7.10.2. Perhaps this was introduced since 7.10 branched from master? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:07:27 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:07:27 -0000 Subject: [GHC] #10495: Poor error message for Coercible constraint unsatisfiability In-Reply-To: <047.88be9b06528fbf6e5c30196ecacf3fe5@haskell.org> References: <047.88be9b06528fbf6e5c30196ecacf3fe5@haskell.org> Message-ID: <062.41e6462620c52d602f68c6242ad7754c@haskell.org> #10495: Poor error message for Coercible constraint unsatisfiability -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T10495 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * version: 7.11 => 7.10.1 Comment: The reference to untouchable variables appeared in 7.10.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:10:31 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:10:31 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.0c243b1dfd9d5f6fedd843f72f437c14@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Follow the pattern in `TcHsType.tcHsTyVarBndr` (which in any case is probably the function you'll need to modify). It uses `mkTcTyVar` as far as I can see. Just do the same, but with a fresh `Name`. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:14:32 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:14:32 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.bc7c2fb069b325fb504f05b327077b58@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Changes (by bgamari): * milestone: 7.10.2 => 7.10.3 Comment: Kicking this off to 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:16:41 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:16:41 -0000 Subject: [GHC] #10621: Handle annotations in hsig/boot files In-Reply-To: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> References: <045.121a6e2af8a19b629ffb0f582f30666a@haskell.org> Message-ID: <060.ca760b0d37e87b417a650cb9ff299ed8@haskell.org> #10621: Handle annotations in hsig/boot files -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: feature request | Status: new Priority: normal | Milestone: Component: GHC API | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1091 -------------------------------------+------------------------------------- Changes (by spinda): * differential: => Phab:D1091 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 11:22:10 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 11:22:10 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.d520fe116f7b8512c1cdb46ff2f49b82@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Old description: > ghci -V > The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150612 > > ghci -package GLUT > GHCi, version 7.10.1.20150612: http://www.haskell.org/ghc/ :? for help > : can't load .so/.DLL for: > /Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 > -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib > (dlopen(/Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 > -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib, 5): Symbol not found: > _glutBitmap8By13 > Referenced from: > /Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 > -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib > Expected in: flat namespace > in > /Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 > -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib) > > This may be related to the fix for #10322 or the underlying problem > reported there. The GLUT people are aware of this. They believe it is > platform scpecific, a regression from 7.8.4 and probably a ghc issue. See > https://github.com/haskell-opengl/GLUT/issues/19 New description: {{{ $ ghci -V The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150612 $ ghci -package GLUT GHCi, version 7.10.1.20150612: http://www.haskell.org/ghc/ :? for help : can't load .so/.DLL for: /Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib (dlopen(/Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib, 5): Symbol not found: _glutBitmap8By13 Referenced from: /Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib Expected in: flat namespace in /Library/Haskell/ghc-7.10.1.20150612-x86_64/lib/GLUT-2.7.0.1/libHSGLUT-2.7.0.1 -4wlNyqnZsQF9mL67dfVCyA-ghc7.10.1.20150612.dylib) }}} This may be related to the fix for #10322 or the underlying problem reported there. The GLUT people are aware of this. They believe it is platform scpecific, a regression from 7.8.4 and probably a ghc issue. See https://github.com/haskell-opengl/GLUT/issues/19 -- Comment (by hvr): improve markup in ticket description for readability -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:00:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:00:14 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.945dbcc961ceda38e5b48975fcf288d5@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: Phab:D1092 -------------------------------------+------------------------------------- Changes (by thomasw): * status: closed => new * differential: => Phab:D1092 * resolution: fixed => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:00:33 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:00:33 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.286c339638b353315be3916f74f8c3f6@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: Phab:D1092 -------------------------------------+------------------------------------- Changes (by thomasw): * owner: => thomasw -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:22:41 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:22:41 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators Message-ID: <047.60a52fd2422f834202b3d782885a3356@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: | -------------------------------------+------------------------------------- {{{#!hs import Data.Type.Equality(Refl) }}} errors with {{{ error: In module ?Data.Type.Equality?: ?Refl? is a data constructor of ?:~:? To import it use ?import? Data.Type.Equality( :~:( Refl ) ) or ?import? Data.Type.Equality( :~:(..) ) }}} But the code there does not parse, one needs {{{#!hs import Data.Type.Equality((:~:)(Refl)) }}} instead (note the extra brackets!). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:35:19 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:35:19 -0000 Subject: [GHC] #9198: large performance regression in type checker speed in 7.8 In-Reply-To: <045.f5a457d59b89d5fb7ca7aaa1ff3c4984@haskell.org> References: <045.f5a457d59b89d5fb7ca7aaa1ff3c4984@haskell.org> Message-ID: <060.d0525d41add596c6d60f97de5f317301@haskell.org> #9198: large performance regression in type checker speed in 7.8 -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.8.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:35:52 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:35:52 -0000 Subject: [GHC] #3699: Wildcards in type functions In-Reply-To: <060.b01af1dc1c462193a392550aa45e1d6c@haskell.org> References: <060.b01af1dc1c462193a392550aa45e1d6c@haskell.org> Message-ID: <075.a640cbde03b216915c2bc874839512d8@haskell.org> #3699: Wildcards in type functions -------------------------------------+------------------------------------- Reporter: | Owner: msosn MartijnVanSteenbergen | Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: 6.10.4 checker) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1092 -------------------------------------+------------------------------------- Changes (by thomasw): * differential: => Phab:D1092 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:46:05 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:46:05 -0000 Subject: [GHC] #10669: Missing Generic instances for base types. Message-ID: <048.12bc38d5127d0e42b80d46a4c10d9acb@haskell.org> #10669: Missing Generic instances for base types. -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: | Version: 7.10.1 libraries/base | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- There is instance Generic Int in GHC.Generics, but no Generic Word. Also there is no Generic instances for Int8, Int16, Int32, Int64, Word8, Word16, Word32, Word64. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:46:15 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:46:15 -0000 Subject: [GHC] #3699: Wildcards in type functions In-Reply-To: <060.b01af1dc1c462193a392550aa45e1d6c@haskell.org> References: <060.b01af1dc1c462193a392550aa45e1d6c@haskell.org> Message-ID: <075.dac6d3d6de19d29337f10aa1799a3cbb@haskell.org> #3699: Wildcards in type functions -------------------------------------+------------------------------------- Reporter: | Owner: msosn MartijnVanSteenbergen | Type: feature request | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler (Type | Version: 6.10.4 checker) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1092 -------------------------------------+------------------------------------- Comment (by thomasw): Fixing #10586 led me to add support for wild cards in type/data family instance declarations, see Phab:D1092. @msosn: Sorry for stealing this. As I implemented partial type signatures in the first place, this was less than an hour's worth of work for me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 12:48:43 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 12:48:43 -0000 Subject: [GHC] #10586: GHC 7.10.1 panic due to wildcard in data family instance In-Reply-To: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> References: <051.1ad24f379aa873ec60f60cfdaf86ad2c@haskell.org> Message-ID: <066.a78f4f9c4e2967effef68e33608218e2@haskell.org> #10586: GHC 7.10.1 panic due to wildcard in data family instance -------------------------------------+------------------------------------- Reporter: WrenThornton | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #3699 | Differential Revisions: Phab:D1092 -------------------------------------+------------------------------------- Comment (by thomasw): See Phab:D1092 for a patch adding support for wild cards in type/data family instance declarations. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 13:00:21 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 13:00:21 -0000 Subject: [GHC] #10627: Regression: cabal install of numeric-prelude hangs In-Reply-To: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> References: <045.b2e2159c9432fe62a0670e01c485d997@haskell.org> Message-ID: <060.a8f6c443b32bc34147c0d9ffa1534abf@haskell.org> #10627: Regression: cabal install of numeric-prelude hangs -------------------------------------+------------------------------------- Reporter: George | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: crash | simplCore/should_compile/T10627 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Lemming): I can compile numeric-prelude with `ghc-7.10.1.20150715`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 13:44:49 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 13:44:49 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.5ff7b3dfd9e9abc18f6f38740149ed12@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by MtnViewMark): When building GLUT for HP, should we be adding the following to the cabal install step? Will this fix the issue for the pre-built libs that HP provides? {{{ --ghc-options="-optl-Wl,-framework,GLUT" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 14:04:18 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 14:04:18 -0000 Subject: [GHC] #10494: Representational equalities over AppTys are not hard failures In-Reply-To: <047.6c55cf81fc9e307934dd2710cdafc698@haskell.org> References: <047.6c55cf81fc9e307934dd2710cdafc698@haskell.org> Message-ID: <062.e502a1446c6465abc4bcbe00b64dda02@haskell.org> #10494: Representational equalities over AppTys are not hard failures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10494 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 7.10.3 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 14:30:42 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 14:30: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.2d91df6c354c17ac5387f0fcd87f4210@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by osa1): @rwbarton, sorry if I'm misunderstand things, but I think `DeriveAnyClass` isn't deriving `Functor` because of an implementation bug and not because how it's designed. I think we should reconsider design of `DeriveAnyClass` and make the documentation more clear about it. As usual, I'm willing to work on this :) FWIW, I have a patch that fixes(based on my understanding of `DervieAnyClass`) some specific cases but without specifying it better it's pointless. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 14:41:02 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 14:41:02 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators In-Reply-To: <047.60a52fd2422f834202b3d782885a3356@haskell.org> References: <047.60a52fd2422f834202b3d782885a3356@haskell.org> Message-ID: <062.b76d4b8dcbf4cb255339015c5215e853@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomasw): * owner: => thomasw -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 14:41:47 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 14:41:47 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators In-Reply-To: <047.60a52fd2422f834202b3d782885a3356@haskell.org> References: <047.60a52fd2422f834202b3d782885a3356@haskell.org> Message-ID: <062.e50069069703a112eb99d8ae2a0e4f1a@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomasw): I have found the cause, I'll upload a diff on Phabricator. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 14:59:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 14:59:34 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators In-Reply-To: <047.60a52fd2422f834202b3d782885a3356@haskell.org> References: <047.60a52fd2422f834202b3d782885a3356@haskell.org> Message-ID: <062.2693fff0626b7da9dfa9d60416c1ee55@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1093 -------------------------------------+------------------------------------- Changes (by thomasw): * differential: => Phab:D1093 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 15:01:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 15:01:14 -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.669d2dedd8ce05b3cfe70a76fd0e64d4@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by kosmikus): I think the confusion is understandable, because a large design space is being discussed here. The issue as reported is mainly about interaction between `GeneralizedNewtypeDeriving` and `DeriveAnyClass`. There are four options specified here: https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#InteractionwithGeneralizedNewtypeDeriving All four have disadvantages, and unfortunately the document does not say which of the four options actually has been implemented. It seems from the current behaviour of GHC like the implementation is along the lines of option 2 (and perhaps 3). However, even then we still have the fact that the error messages don't seem to properly reflect what is going on. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 15:09:12 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 15:09:12 -0000 Subject: [GHC] #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 Message-ID: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: Compile-time (amd64) | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The following code causes a panic when loaded into GHCi (more complicated code below makes GHC panic also) {{{#!hs {-# LANGUAGE GADTs , PolyKinds #-} module Bug where data TyConT (a::k) = TyConT String tyConTArr :: TyConT (->) tyConTArr = TyConT "(->)" data G2 c a where G2 :: TyConT a -> TyConT b -> G2 c (c a b) getT2 :: TyConT (c :: k2 -> k1 -> k) -> TyConT (a :: k) -> Maybe (G2 c a) getT2 (TyConT c) (TyConT a) = Nothing s tf = case getT2 tyConTArr tf of Just (G2 _ _) -> Nothing _ -> Nothing }}} `ghci Bug.hs` yields {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): ASSERT failed! file compiler/types/Type.hs line 1712 a_ame -> b_amf k_anj }}} And for GHC: {{{#!hs {-# LANGUAGE GADTs , PolyKinds , FlexibleInstances , TypeOperators , ScopedTypeVariables #-} module Bug2 where import Unsafe.Coerce data TyConT (a::k) = TyConT String eqTyConT :: TyConT a -> TyConT b -> Bool eqTyConT (TyConT a) (TyConT b) = a == b tyConTArr :: TyConT (->) tyConTArr = TyConT "(->)" data TypeRepT (a::k) where TRCon :: TyConT a -> TypeRepT a TRApp :: TypeRepT a -> TypeRepT b -> TypeRepT (a b) data GetAppT a where GA :: TypeRepT a -> TypeRepT b -> GetAppT (a b) getAppT :: TypeRepT a -> Maybe (GetAppT a) getAppT (TRApp a b) = Just $ GA a b getAppT _ = Nothing eqTT :: TypeRepT (a::k1) -> TypeRepT (b::k2) -> Bool eqTT (TRCon a) (TRCon b) = eqTyConT a b eqTT (TRApp c a) (TRApp d b) = eqTT c d && eqTT a b eqTT _ _ = False data G2 c a where G2 :: TypeRepT a -> TypeRepT b -> G2 c (c a b) getT2 :: TypeRepT (c :: k2 -> k1 -> k) -> TypeRepT (a :: k) -> Maybe (G2 c a) getT2 c t = do GA t' b <- getAppT t GA c' a <- getAppT t' if eqTT c c' then Just (unsafeCoerce $ G2 a b :: G2 c a) else Nothing tyRepTArr :: TypeRepT (->) tyRepTArr = TRCon tyConTArr s tf = case getT2 tyRepTArr tf of Just (G2 _ _) -> Nothing _ -> Nothing }}} `ghc Bug2.hs` yields {{{ [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): ASSERT failed! file compiler/types/Type.hs line 1712 a_amr -> b_ams k_a1c2 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This is a regression from 7.10.1 (fails at 1224bb55cac502fe04005345aad47a6bc5c4a297) `uname -a`: `Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux` using GCC 4.6.3 `gcc -v` output: {{{ Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} `ghc -v Bug2.hs`: {{{ Glasgow Haskell Compiler, Version 7.11.20150717, stage 2 booted by GHC version 7.10.1 Using binary package database: /5playpen/t-bepric/ghc- build/inplace/lib/package.conf.d/package.cache Using binary package database: /home/t-bepric/.ghc/x86_64-linux-7.11.20150717/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.2.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.11.20150717-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.2.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.11.20150717-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: *Bug2.hs Stable obj: [] Stable BCO: [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-22 15:01:01 UTC ms_mod = Bug2, ms_textual_imps = [import (implicit) Prelude, import Unsafe.Coerce] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file Bug2.hs Created temporary directory: /tmp/ghc33699_0 *** Checking old interface for Bug2: [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) *** Parser: *** Renamer/typechecker: *** Desugar: Result size of Desugar (before optimization) = {terms: 206, types: 667, coercions: 24} Result size of Desugar (after optimization) = {terms: 133, types: 421, coercions: 10} *** Simplifier: *** Deleting temp files: Deleting: /tmp/ghc33699_0/ghc_1.s Warning: deleting non-existent /tmp/ghc33699_0/ghc_1.s *** Deleting temp dirs: Deleting: /tmp/ghc33699_0 ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): ASSERT failed! file compiler/types/Type.hs line 1712 a_amr -> b_ams k_a1c2 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 15:18:45 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 15:18:45 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.761dd609f4049b91cd86fb270d94c00a@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by darchon): Replying to [comment:35 MtnViewMark]: > When building GLUT for HP, should we be adding the following to the cabal install step? Will this fix the issue for the pre-built libs that HP provides? > > {{{ > --ghc-options="-optl-Wl,-framework,GLUT" > }}} I think so yes. With those options, the GLUT Haskell library is properly linked against the GLUT framework lib. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 15:40:33 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 15:40:33 -0000 Subject: [GHC] #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 In-Reply-To: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> References: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> Message-ID: <062.0840c990e2cdf94f87efbb8eed0bb572@haskell.org> #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bjmprice: Old description: > The following code causes a panic when loaded into GHCi > (more complicated code below makes GHC panic also) > {{{#!hs > {-# LANGUAGE GADTs , PolyKinds #-} > > module Bug where > > data TyConT (a::k) = TyConT String > > tyConTArr :: TyConT (->) > tyConTArr = TyConT "(->)" > > data G2 c a where > G2 :: TyConT a -> TyConT b -> G2 c (c a b) > > getT2 :: TyConT (c :: k2 -> k1 -> k) -> TyConT (a :: k) -> Maybe (G2 c a) > getT2 (TyConT c) (TyConT a) = Nothing > > s tf = case getT2 tyConTArr tf > of Just (G2 _ _) -> Nothing > _ -> Nothing > }}} > `ghci Bug.hs` yields > {{{ > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.11.20150717 for x86_64-unknown-linux): > ASSERT failed! > file compiler/types/Type.hs line 1712 > a_ame -> b_amf > k_anj > }}} > > And for GHC: > {{{#!hs > {-# LANGUAGE GADTs , PolyKinds , FlexibleInstances , TypeOperators , > ScopedTypeVariables #-} > > module Bug2 where > > import Unsafe.Coerce > > data TyConT (a::k) = TyConT String > > eqTyConT :: TyConT a -> TyConT b -> Bool > eqTyConT (TyConT a) (TyConT b) = a == b > > > tyConTArr :: TyConT (->) > tyConTArr = TyConT "(->)" > > data TypeRepT (a::k) where > TRCon :: TyConT a -> TypeRepT a > TRApp :: TypeRepT a -> TypeRepT b -> TypeRepT (a b) > > data GetAppT a where > GA :: TypeRepT a -> TypeRepT b -> GetAppT (a b) > > getAppT :: TypeRepT a -> Maybe (GetAppT a) > getAppT (TRApp a b) = Just $ GA a b > getAppT _ = Nothing > > > eqTT :: TypeRepT (a::k1) -> TypeRepT (b::k2) -> Bool > eqTT (TRCon a) (TRCon b) = eqTyConT a b > eqTT (TRApp c a) (TRApp d b) = eqTT c d && eqTT a b > eqTT _ _ = False > > data G2 c a where > G2 :: TypeRepT a -> TypeRepT b -> G2 c (c a b) > > getT2 :: TypeRepT (c :: k2 -> k1 -> k) -> TypeRepT (a :: k) -> Maybe (G2 > c a) > getT2 c t = do GA t' b <- getAppT t > GA c' a <- getAppT t' > if eqTT c c' > then Just (unsafeCoerce $ G2 a b :: G2 c a) > else Nothing > > tyRepTArr :: TypeRepT (->) > tyRepTArr = TRCon tyConTArr > > s tf = case getT2 tyRepTArr tf > of Just (G2 _ _) -> Nothing > _ -> Nothing > }}} > `ghc Bug2.hs` yields > {{{ > [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.11.20150717 for x86_64-unknown-linux): > ASSERT failed! > file compiler/types/Type.hs line 1712 > a_amr -> b_ams > k_a1c2 > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} > > This is a regression from 7.10.1 (fails at > 1224bb55cac502fe04005345aad47a6bc5c4a297) > > `uname -a`: > `Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 > 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux` > > using GCC 4.6.3 > > `gcc -v` output: > {{{ > Using built-in specs. > COLLECT_GCC=gcc > COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper > Target: x86_64-linux-gnu > Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro > 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs > --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- > suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib > --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix > --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable- > nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug > --enable-libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin > --enable-objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic > --enable-checking=release --build=x86_64-linux-gnu --host=x86_64-linux- > gnu --target=x86_64-linux-gnu > Thread model: posix > gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) > }}} > > `ghc -v Bug2.hs`: > {{{ > Glasgow Haskell Compiler, Version 7.11.20150717, stage 2 booted by GHC > version 7.10.1 > Using binary package database: /5playpen/t-bepric/ghc- > build/inplace/lib/package.conf.d/package.cache > Using binary package database: > /home/t-bepric/.ghc/x86_64-linux-7.11.20150717/package.conf.d/package.cache > wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace > wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace > wired-in package base mapped to base-4.8.2.0-inplace > wired-in package rts mapped to builtin_rts > wired-in package template-haskell mapped to template- > haskell-2.10.0.0-inplace > wired-in package ghc mapped to ghc-7.11.20150717-inplace > wired-in package dph-seq not found. > wired-in package dph-par not found. > Hsc static flags: > wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace > wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace > wired-in package base mapped to base-4.8.2.0-inplace > wired-in package rts mapped to builtin_rts > wired-in package template-haskell mapped to template- > haskell-2.10.0.0-inplace > wired-in package ghc mapped to ghc-7.11.20150717-inplace > wired-in package dph-seq not found. > wired-in package dph-par not found. > *** Chasing dependencies: > Chasing modules from: *Bug2.hs > Stable obj: [] > Stable BCO: [] > Ready for upsweep > [NONREC > ModSummary { > ms_hs_date = 2015-07-22 15:01:01 UTC > ms_mod = Bug2, > ms_textual_imps = [import (implicit) Prelude, import > Unsafe.Coerce] > ms_srcimps = [] > }] > *** Deleting temp files: > Deleting: > compile: input file Bug2.hs > Created temporary directory: /tmp/ghc33699_0 > *** Checking old interface for Bug2: > [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) > *** Parser: > *** Renamer/typechecker: > *** Desugar: > Result size of Desugar (before optimization) > = {terms: 206, types: 667, coercions: 24} > Result size of Desugar (after optimization) > = {terms: 133, types: 421, coercions: 10} > *** Simplifier: > *** Deleting temp files: > Deleting: /tmp/ghc33699_0/ghc_1.s > Warning: deleting non-existent /tmp/ghc33699_0/ghc_1.s > *** Deleting temp dirs: > Deleting: /tmp/ghc33699_0 > ghc-stage2: panic! (the 'impossible' happened) > (GHC version 7.11.20150717 for x86_64-unknown-linux): > ASSERT failed! > file compiler/types/Type.hs line 1712 > a_amr -> b_ams > k_a1c2 > }}} New description: The following code causes a panic when loaded into GHCi (more complicated code below makes GHC panic also) {{{#!hs {-# LANGUAGE GADTs , PolyKinds #-} module Bug where data TyConT (a::k) = TyConT String tyConTArr :: TyConT (->) tyConTArr = TyConT "(->)" data G2 c a where G2 :: TyConT a -> TyConT b -> G2 c (c a b) getT2 :: TyConT (c :: k2 -> k1 -> k) -> TyConT (a :: k) -> Maybe (G2 c a) getT2 (TyConT c) (TyConT a) = Nothing s tf = case getT2 tyConTArr tf of Just (G2 _ _) -> Nothing _ -> Nothing }}} `ghci Bug.hs` yields {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): ASSERT failed! file compiler/types/Type.hs line 1712 a_ame -> b_amf k_anj }}} And for GHC: {{{#!hs {-# LANGUAGE GADTs , PolyKinds #-} module Bug2 where import Unsafe.Coerce data TyConT (a::k) = TyConT String eqTyConT :: TyConT a -> TyConT b -> Bool eqTyConT (TyConT a) (TyConT b) = a == b tyConTArr :: TyConT (->) tyConTArr = TyConT "(->)" data TypeRepT (a::k) where TRCon :: TyConT a -> TypeRepT a TRApp :: TypeRepT a -> TypeRepT b -> TypeRepT (a b) data GetAppT a where GA :: TypeRepT a -> TypeRepT b -> GetAppT (a b) getAppT :: TypeRepT a -> Maybe (GetAppT a) getAppT (TRApp a b) = Just $ GA a b getAppT _ = Nothing eqTT :: TypeRepT (a::k1) -> TypeRepT (b::k2) -> Bool eqTT (TRCon a) (TRCon b) = eqTyConT a b eqTT (TRApp c a) (TRApp d b) = eqTT c d && eqTT a b eqTT _ _ = False data G2 c a where G2 :: TypeRepT a -> TypeRepT b -> G2 c (c a b) getT2 :: TypeRepT (c :: k2 -> k1 -> k) -> TypeRepT (a :: k) -> Maybe (G2 c a) getT2 c t = do GA t' b <- getAppT t GA c' a <- getAppT t' if eqTT c c' then Just (unsafeCoerce $ G2 a b :: G2 c a) else Nothing tyRepTArr :: TypeRepT (->) tyRepTArr = TRCon tyConTArr s tf = case getT2 tyRepTArr tf of Just (G2 _ _) -> Nothing _ -> Nothing }}} `ghc Bug2.hs` yields {{{ [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): ASSERT failed! file compiler/types/Type.hs line 1712 a_amr -> b_ams k_a1c2 Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This is a regression from 7.10.1 (fails at 1224bb55cac502fe04005345aad47a6bc5c4a297) `uname -a`: `Linux cam-05-unx 3.5.0-54-generic #81~precise1-Ubuntu SMP Tue Jul 15 04:02:22 UTC 2014 x86_64 x86_64 x86_64 GNU/Linux` using GCC 4.6.3 `gcc -v` output: {{{ Using built-in specs. COLLECT_GCC=gcc COLLECT_LTO_WRAPPER=/usr/lib/gcc/x86_64-linux-gnu/4.6/lto-wrapper Target: x86_64-linux-gnu Configured with: ../src/configure -v --with-pkgversion='Ubuntu/Linaro 4.6.3-1ubuntu5' --with-bugurl=file:///usr/share/doc/gcc-4.6/README.Bugs --enable-languages=c,c++,fortran,objc,obj-c++ --prefix=/usr --program- suffix=-4.6 --enable-shared --enable-linker-build-id --with-system-zlib --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --with-gxx-include-dir=/usr/include/c++/4.6 --libdir=/usr/lib --enable-nls --with-sysroot=/ --enable-clocale=gnu --enable-libstdcxx-debug --enable- libstdcxx-time=yes --enable-gnu-unique-object --enable-plugin --enable- objc-gc --disable-werror --with-arch-32=i686 --with-tune=generic --enable- checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu Thread model: posix gcc version 4.6.3 (Ubuntu/Linaro 4.6.3-1ubuntu5) }}} `ghc -v Bug2.hs`: {{{ Glasgow Haskell Compiler, Version 7.11.20150717, stage 2 booted by GHC version 7.10.1 Using binary package database: /5playpen/t-bepric/ghc- build/inplace/lib/package.conf.d/package.cache Using binary package database: /home/t-bepric/.ghc/x86_64-linux-7.11.20150717/package.conf.d/package.cache wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.2.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.11.20150717-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.2.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.11.20150717-inplace wired-in package dph-seq not found. wired-in package dph-par not found. *** Chasing dependencies: Chasing modules from: *Bug2.hs Stable obj: [] Stable BCO: [] Ready for upsweep [NONREC ModSummary { ms_hs_date = 2015-07-22 15:01:01 UTC ms_mod = Bug2, ms_textual_imps = [import (implicit) Prelude, import Unsafe.Coerce] ms_srcimps = [] }] *** Deleting temp files: Deleting: compile: input file Bug2.hs Created temporary directory: /tmp/ghc33699_0 *** Checking old interface for Bug2: [1 of 1] Compiling Bug2 ( Bug2.hs, Bug2.o ) *** Parser: *** Renamer/typechecker: *** Desugar: Result size of Desugar (before optimization) = {terms: 206, types: 667, coercions: 24} Result size of Desugar (after optimization) = {terms: 133, types: 421, coercions: 10} *** Simplifier: *** Deleting temp files: Deleting: /tmp/ghc33699_0/ghc_1.s Warning: deleting non-existent /tmp/ghc33699_0/ghc_1.s *** Deleting temp dirs: Deleting: /tmp/ghc33699_0 ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150717 for x86_64-unknown-linux): ASSERT failed! file compiler/types/Type.hs line 1712 a_amr -> b_ams k_a1c2 }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 15:51:54 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 15:51:54 -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.bd60d517e0ec23c1985c6b12bcfcd7a7@haskell.org> #10512: Generic instances missing for Int32, Word64 etc. -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: ekmett Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * cc: vagarenko (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 15:52:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 15:52:03 -0000 Subject: [GHC] #10669: Missing Generic instances for base types. In-Reply-To: <048.12bc38d5127d0e42b80d46a4c10d9acb@haskell.org> References: <048.12bc38d5127d0e42b80d46a4c10d9acb@haskell.org> Message-ID: <063.d833352cd433db27093ec7cc317affd8@haskell.org> #10669: Missing Generic instances for base types. -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: libraries/base | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => duplicate Comment: Duplicate of #10512. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 16:08:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 16:08:01 -0000 Subject: [GHC] #10458: GHCi fails to load shared object (the 'impossible' happened) In-Reply-To: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> References: <046.4114d092404072b00fcfc0e155d0e19b@haskell.org> Message-ID: <061.65c07a7257a3e3f82927b833ba5bb939@haskell.org> #10458: GHCi fails to load shared object (the 'impossible' happened) ---------------------------------+----------------------------------------- Reporter: rleslie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: GHCi | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+----------------------------------------- Changes (by rwbarton): * milestone: 7.12.1 => 7.10.3 Comment: I guess it's too late for 7.10.2 but we should really fix this for 7.10.3. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 16:32:57 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 16:32:57 -0000 Subject: [GHC] #4945: Another SpecConstr infelicity In-Reply-To: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> References: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> Message-ID: <068.8de0f18a11f772cedc0d5a2849d8b720@haskell.org> #4945: Another SpecConstr infelicity -------------------------------------+------------------------------------- Reporter: batterseapower | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T4945 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"50b9a7a355d6fbcb539d4f5aa8313fc0536e8fc3/ghc" 50b9a7a3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="50b9a7a355d6fbcb539d4f5aa8313fc0536e8fc3" Revert "Trac #4945 is working again" This reverts commit 5d98b6828f65ce6eea45e93880928b7031955d38. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 16:34:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 16:34:34 -0000 Subject: [GHC] #4945: Another SpecConstr infelicity In-Reply-To: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> References: <053.dd99f570cc6450886c16aa213467aa21@haskell.org> Message-ID: <068.6bfce9706071f6f77fce8497913e9995@haskell.org> #4945: Another SpecConstr infelicity -------------------------------------+------------------------------------- Reporter: batterseapower | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_compile/T4945 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: fixed => Comment: Let's leave it open until it is fixed for good. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 16:43:22 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 16:43:22 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.5c37538da6e614170414ad915e4785f6@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by lelf): * cc: lelf (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 16:50:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 16:50:08 -0000 Subject: [GHC] #9706: New block-structured heap organization for 64-bit In-Reply-To: <045.a63dcd9ee3561b6e809272c4a2e2bc36@haskell.org> References: <045.a63dcd9ee3561b6e809272c4a2e2bc36@haskell.org> Message-ID: <060.d727f179679dcbfc5b9551026776c6e8@haskell.org> #9706: New block-structured heap organization for 64-bit -------------------------------------+------------------------------------- Reporter: ezyang | Owner: gcampax Type: task | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D524 -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"0d1a8d09f452977aadef7897aa12a8d41c7a4af0/ghc" 0d1a8d09/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="0d1a8d09f452977aadef7897aa12a8d41c7a4af0" Two step allocator for 64-bit systems Summary: The current OS memory allocator conflates the concepts of allocating address space and allocating memory, which makes the HEAP_ALLOCED() implementation excessively complicated (as the only thing it cares about is address space layout) and slow. Instead, what we want is to allocate a single insanely large contiguous block of address space (to make HEAP_ALLOCED() checks fast), and then commit subportions of that in 1MB blocks as we did before. This is currently behind a flag, USE_LARGE_ADDRESS_SPACE, that is only enabled for certain OSes. Test Plan: validate Reviewers: simonmar, ezyang, austin Subscribers: thomie, carter Differential Revision: https://phabricator.haskell.org/D524 GHC Trac Issues: #9706 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 16:54:03 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 16:54:03 -0000 Subject: [GHC] #9706: New block-structured heap organization for 64-bit In-Reply-To: <045.a63dcd9ee3561b6e809272c4a2e2bc36@haskell.org> References: <045.a63dcd9ee3561b6e809272c4a2e2bc36@haskell.org> Message-ID: <060.2dc949c7eae04f8b5c61547095b46f42@haskell.org> #9706: New block-structured heap organization for 64-bit -------------------------------------+------------------------------------- Reporter: ezyang | Owner: gcampax Type: task | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 7.8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D524 -------------------------------------+------------------------------------- Changes (by simonmar): * status: new => closed * resolution: => fixed Comment: Thanks to everyone who worked on this, particularly @ezyang for exploring the earlier solution and @gcampax for writing most of the patch I just committed. @ezyang, I suggest making a separate ticket for experiments with reorganising the block descriptors if you want to follow up on that. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 18:11:59 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 18:11:59 -0000 Subject: [GHC] #10622: Rename Backpack packages to units In-Reply-To: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> References: <045.e723515149f295a7a83a3d60032cca8e@haskell.org> Message-ID: <060.4f61531d9daad8ff51a9d70110e56a5e@haskell.org> #10622: Rename Backpack packages to units -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | 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 Revisions: Phab:D1057 -------------------------------------+------------------------------------- Old description: > After today's weekly Backpack call, we have come to the conclusion that > we have two different types of "packages" in the Backpack world: > > 1. Cabal packages, which have a single `.cabal` file and are a unit of > distribution which get uploaded to Hackage, and > > 2. Backpack packages, of which there may be multiple defined in a > Backpack file shipped with a Cabal package; and are the building blocks > for modular development in the small. > > It's really confusing to have both of these called packages: thus, we > propose to rename all occurrences of Backpack package to unit. A Cabal > ''package'' may contain MULTIPLE Backpack ''units'', and old-style Cabal > files will only define one unit. Every Cabal package has a distinguished > unit (with the same name as the package) that serves as the publically > visible unit. > > A Cabal package remains > * The unit of distribution > * The unit that Hackage handles > * The unit of versioning > * The unit of ownership (who maintains it etc) > > Here are some of the consequences: > > 1. The "installed package database" no longer maintains a one-to-one > mapping between Cabal packages and entries in the database. This > invariant is being dropped for two reasons: (1) With a Nix-style > database, a package `foo-0.1` may be installed many times with different > dependencies / source code, all of which live in the installed package > database. (2) With Backpack, a package containing a Backpack file may > install multiple units. To avoid having to rename *everything*, we'll > keep calling this the installed package database, but really it's more > like an installed *unit* database. > > 2. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather > than a Cabal package. (I think this actually makes the function of these > identifiers clearer.) We'll also distinguish Cabal-file level > `PackageName`s from Backpack-file `UnitName`s. Installed units are > identified by an `InstalledUnitId` instead of an `InstalledPackageId`. > > 3. The source-level syntax of Backpack files will use `unit` in place of > where `package` was used before. > > 4. For old-style packages, Cabal will continue to write and register a > single entry in the installed package database. For Backpack packages, > Cabal will register as many entries as is necessary to install a package. > The entry with the same `UnitName` as `PackageName` is publically visible > to other packages. If a Backpack file defines other packages, those > packages are registered with different `UnitName`s (giving them different > `InstalledPackageId`s) which are not publically visible. The non- > publically visible packages will have their description/URL/etc fields > blank, and have a pointer to the "real" package. > > 5. If when installing a unit, we discover that it is already present in > the database, we check if the ABI hashes are the same. If they are, we > simply skip installing the unit but otherwise proceed. If the ABI hashes > are not the same, we error: the units we are installing need to be > recompiled against the unit present in the database. New description: After today's weekly Backpack call, we have come to the conclusion that we have two different types of "packages" in the Backpack world: 1. Cabal packages, which have a single `.cabal` file and are a unit of distribution which get uploaded to Hackage, and 2. Backpack packages, of which there may be multiple defined in a Backpack file shipped with a Cabal package; and are the building blocks for modular development in the small. It's really confusing to have both of these called packages: thus, we propose to rename all occurrences of Backpack package to unit. A Cabal ''package'' may contain MULTIPLE Backpack ''units'', and old-style Cabal files will only define one unit. Every Cabal package has a distinguished unit (with the same name as the package) that serves as the publically visible unit. A Cabal package remains * The unit of distribution * The unit that Hackage handles * The unit of versioning * The unit of ownership (who maintains it etc) Here are some of the consequences: 1. The "installed package database" no longer maintains a one-to-one mapping between Cabal packages and entries in the database. This invariant is being dropped for two reasons: (1) With a Nix-style database, a package `foo-0.1` may be installed many times with different dependencies / source code, all of which live in the installed package database. (2) With Backpack, a package containing a Backpack file may install multiple units. To avoid having to rename *everything*, we'll keep calling this the installed package database, but really it's more like an installed *unit* database. 2. We rename `PackageKey` to `UnitKey`, as it identifies a unit rather than a Cabal package. (I think this actually makes the function of these identifiers clearer.) We'll also distinguish Cabal-file level `PackageName`s from Backpack-file `UnitName`s. Installed units are identified by an `InstalledUnitId` instead of an `InstalledPackageId`. 3. The source-level syntax of Backpack files will use `unit` in place of where `package` was used before. 4. For old-style packages, Cabal will continue to write and register a single entry in the installed package database. For Backpack packages, Cabal will register as many entries as is necessary to install a package. The entry with the same `UnitName` as `PackageName` is publically visible to other packages. If a Backpack file defines other packages, those packages are registered with different `UnitName`s (giving them different `InstalledPackageId`s) which are not publically visible. The non- publically visible packages will have their description/URL/etc fields blank, and have a pointer to the "real" package. 5. If when installing a unit, we discover that it is already present in the database, we check if the ABI hashes are the same. If they are, we simply skip installing the unit but otherwise proceed. If the ABI hashes are not the same, we error: the units we are installing need to be recompiled against the unit present in the database. 6. Dependency tracking should be fine-grained within a PACKAGE, and coarse-grained outside. So we need to let interface files track module dependencies for files which are not in the same unit, but are in the same package. -- Comment (by ezyang): Add a remark about how dependency tracking should change between units in the same package. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 19:29:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 19:29:40 -0000 Subject: [GHC] #10664: T8131 times out on master In-Reply-To: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> References: <046.cb11813953cf382c76feac6f7fc0b89d@haskell.org> Message-ID: <061.25aa3bdf713ca2d77bb9552dbae1b55d@haskell.org> #10664: T8131 times out on master -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Using `-dshow-passes` it appears to get `<>` when parsing the `.cmm` input file. I have no idea why. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 22 21:24:37 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 22 Jul 2015 21:24: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.d55496e2ec26608217702747825017b7@haskell.org> #10598: DeriveAnyClass and GND don't work well together -------------------------------------+------------------------------------- Reporter: osa1 | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by oerjan): Hm so here is my "ideal" made-up-on-the-spot system. It somewhat combines all of 2, 3 and 4 from https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/GenericDeriving#InteractionwithGeneralizedNewtypeDeriving. It is intended to be backwards-compatible, except for one added warning. * By 3, classes may be annotated (pragma?) to say they prefer GND or DAC deriving. Builtin-derived classes count as annotated for their own style of deriving. To actually derive a class in a module, any extension for the derivation style still needs to be enabled as well. * By 4, if `GeneralizedNewtypeDeriving` is enabled, the `newtype` keyword may be used to signify that an instance for a newtype should be GND derived, even if this is against the annotated behavior for the class. This might even include builtin-derived classes like `Show`. (Obviously not `Typeable`, though.) * Also by 4, if both `GeneralizedNewtypeDeriving` and `DeriveAnyClass` are enabled (or for least surprise, maybe even with just the latter), the `default` keyword may be used to signify that an instance for a newtype should ''not'' be GND-derived, even if this is the annotated behavior for the class. * By 2, if ''neither'' the newtype deriving nor the class is annotated, then the behavior depends on which of `GeneralizedNewtypeDeriving` and `DeriveAnyClass` is enabled. If ''both'' are enabled, then a ''warning'' should be given. (This prevents surprises when a user adds both extensions for unrelated instances.) Then it defaults to DAC as today. * Although the proper extensions need to be enabled for whichever annotations/derivation styles end up being used, the ''only'' case where simply changing the extensions enabled will change code from one legal style of derivation to another should be the one in the previous point. (And thus the warning.) As of now, I don't remember any classes with builtin-derivations that also are useful with `DeriveAnyClass`. So I think there isn't much need to be able to distinguish those two cases. Which also means that none of this matters to `data` declarations, only `newtype`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 03:15:00 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 03:15:00 -0000 Subject: [GHC] #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override Message-ID: <043.3dbf7fc0356f7f2fdf48023120606ded@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build | Version: 7.10.1 System | Keywords: | Operating System: Linux Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Building ghc 7.10.1 on RHEL 5.8. I need to override the old system linker which lacks features and performance. I get stage1 built but then it forgets the override. Configure: ./configure --prefix=/home/cavtools/opt/ghc-7.10.1 --with- ld=/home/cavtools/64/pkg/bin/gld --with-ar=/home/cavtools/64/pkg/bin/gar --with-ranlib=/home/cavtools/64/pkg/bin/granlib settings: [("GCC extra via C opts", " -fwrapv"), ("C compiler command", "/usr/bin/gcc"), ("C compiler flags", " -fno-stack-protector"), ("C compiler link flags", ""), ("Haskell CPP command","/usr/bin/gcc"), ("Haskell CPP flags","-E -undef -traditional "), ("ld command", "/home/cavtools/64/pkg/bin/gld"), ("ld flags", ""), ("ld supports compact unwind", "YES"), ("ld supports build-id", "YES"), ("ld supports filelist", "NO"), ("ld is GNU ld", "YES"), ("ar command", "/home/cavtools/64/pkg/bin/gar"), ("ar flags", "q"), ("ar supports at file", "YES"), ("touch command", "touch"), ("dllwrap command", "/bin/false"), ("windres command", "/bin/false"), ("libtool command", "libtool"), ("perl command", "/usr/bin/perl"), ("target os", "OSLinux"), ("target arch", "ArchX86_64"), ("target word size", "8"), ("target has GNU nonexec stack", "True"), ("target has .ident directive", "True"), ("target has subsections via symbols", "False"), ("Unregisterised", "NO"), ("LLVM llc command", "llc"), ("LLVM opt command", "opt") ] inplace/lib/settings: [("GCC extra via C opts", " -fwrapv"), ("C compiler command", "/usr/bin/gcc"), ("C compiler flags", " -fno-stack-protector"), ("C compiler link flags", ""), ("Haskell CPP command","/usr/bin/gcc"), ("Haskell CPP flags","-E -undef -traditional "), ("ld command", "/home/cavtools/64/pkg/bin/gld"), ("ld flags", ""), ("ld supports compact unwind", "YES"), ("ld supports build-id", "YES"), ("ld supports filelist", "NO"), ("ld is GNU ld", "YES"), ("ar command", "/home/cavtools/64/pkg/bin/gar"), ("ar flags", "q"), ("ar supports at file", "YES"), ("touch command", "touch"), ("dllwrap command", "/bin/false"), ("windres command", "/bin/false"), ("libtool command", "libtool"), ("perl command", "/usr/bin/perl"), ("target os", "OSLinux"), ("target arch", "ArchX86_64"), ("target word size", "8"), ("target has GNU nonexec stack", "True"), ("target has .ident directive", "True"), ("target has subsections via symbols", "False"), ("Unregisterised", "NO"), ("LLVM llc command", "llc"), ("LLVM opt command", "opt") ] Failure looks like: "inplace/bin/ghc-stage1" -hisuf p_hi -osuf p_o -hcsuf p_hc -static -prof -H32m -O -this-package-key ghcpr_8TmvWUcS1U1IKHT0levwg3 -hide-all- packages -i -ilibraries/ghc-prim/. -ilibraries/ghc-prim/dist-install/build -ilibraries/ghc-prim/dist-install/build/autogen -Ilibraries/ghc-prim/dist- install/build -Ilibraries/ghc-prim/dist-install/build/autogen -Ilibraries /ghc-prim/. -optP-include -optPlibraries/ghc-prim/dist- install/build/autogen/cabal_macros.h -package-key rts -this-package-key ghc-prim -XHaskell2010 -O2 -no-user-package-db -rtsopts -odir libraries/ghc-prim/dist-install/build -hidir libraries/ghc-prim/dist- install/build -stubdir libraries/ghc-prim/dist-install/build -split-objs -c libraries/ghc-prim/./GHC/IntWord64.hs -o libraries/ghc-prim/dist- install/build/GHC/IntWord64.p_o -dyno libraries/ghc-prim/dist- install/build/GHC/IntWord64.dyn_o /usr/bin/ld: unrecognized option '--build-id=none' /usr/bin/ld: use the --help option for usage information collect2: ld returned 1 exit status But why are you using /usr/bin/ld? I told you not to use /usr/bin/ld! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 03:36:45 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 03:36:45 -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.5f5fcd538afa9190fd9f50c69aaf1162@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): That command doesn't look like it should invoke a linker at all. Were you building in parallel (`make -j`)? Can you build serially to figure out which command failed for sure? Then, if you could rerun the failing command with `-v` and paste the output here, that'd be great. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 04:15:04 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 04:15:04 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking Message-ID: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Windows Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: #9297 #10563 Differential Revisions: | #8237 -------------------------------------+------------------------------------- When compiling an executable that uses Template Haskell against a library that contains C++ code, GHC crashes: {{{ [2 of 2] Compiling Main ( app\Main.hs, dist\build\main\main- tmp\Main.o ) ghc.exe: internal error: checkProddableBlock: invalid fixup in runtime linker: 0000000000360564 (GHC version 7.10.1 for x86_64_unknown_mingw32) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} I've boiled this down into a minimal reproduction of a library that includes a .cpp file, and an executable that depends on it. To test: {{{ git clone https://github.com/lukexi/cxx-link-fail-repro cabal run }}} The crash does not occur in the repro unless I use C++ exceptions in the library, and use Template Haskell in the executable, but in the project I boiled this down from (http://github.com/lukexi/bullet-mini) the problem occurs even with {{{cc-options: -fno-exceptions}}}. Some more details are at https://github.com/lukexi/cxx-link-fail-repro The platform is Windows 8.1 under MSYS2 (GHC is still using its inbuilt mingw). I've also tried 7.10.2-RC1 with the same result. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 04:24:54 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 04:24:54 -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.65c88e74de8abf731dae2602ad38ca5d@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by mfox): {{{ "inplace/bin/ghc-stage1" -this-package-key rts -shared -dynamic -dynload deploy -no-auto-link-packages -Lrts/dist/build -lffi -optl-Wl,-rpath -optl-Wl,'$ORIGIN' -optl-Wl,-zorigin `cat rts/dist/libs.depend` rts/dist/build/Adjustor.dyn_o rts/dist/build/Arena.dyn_o rts/dist/build/Capability.dyn_o rts/dist/build/CheckUnload.dyn_o rts/dist/build/ClosureFlags.dyn_o rts/dist/build/Disassembler.dyn_o rts/dist/build/FileLock.dyn_o rts/dist/build/Globals.dyn_o rts/dist/build/Hash.dyn_o rts/dist/build/Hpc.dyn_o rts/dist/build/HsFFI.dyn_o rts/dist/build/Inlines.dyn_o rts/dist/build/Interpreter.dyn_o rts/dist/build/LdvProfile.dyn_o rts/dist/build/Linker.dyn_o rts/dist/build/Messages.dyn_o rts/dist/build/OldARMAtomic.dyn_o rts/dist/build/Papi.dyn_o rts/dist/build/Printer.dyn_o rts/dist/build/ProfHeap.dyn_o rts/dist/build/Profiling.dyn_o rts/dist/build/Proftimer.dyn_o rts/dist/build/RaiseAsync.dyn_o rts/dist/build/RetainerProfile.dyn_o rts/dist/build/RetainerSet.dyn_o rts/dist/build/RtsAPI.dyn_o rts/dist/build/RtsDllMain.dyn_o rts/dist/build/RtsFlags.dyn_o rts/dist/build/RtsMain.dyn_o rts/dist/build/RtsMessages.dyn_o rts/dist/build/RtsStartup.dyn_o rts/dist/build/RtsUtils.dyn_o rts/dist/build/STM.dyn_o rts/dist/build/Schedule.dyn_o rts/dist/build/Sparks.dyn_o rts/dist/build/Stable.dyn_o rts/dist/build/StaticPtrTable.dyn_o rts/dist/build/Stats.dyn_o rts/dist/build/StgCRun.dyn_o rts/dist/build/StgPrimFloat.dyn_o rts/dist/build/Task.dyn_o rts/dist/build/ThreadLabels.dyn_o rts/dist/build/ThreadPaused.dyn_o rts/dist/build/Threads.dyn_o rts/dist/build/Ticky.dyn_o rts/dist/build/Timer.dyn_o rts/dist/build/Trace.dyn_o rts/dist/build/WSDeque.dyn_o rts/dist/build/Weak.dyn_o rts/dist/build/hooks/FlagDefaults.dyn_o rts/dist/build/hooks/MallocFail.dyn_o rts/dist/build/hooks/OnExit.dyn_o rts/dist/build/hooks/OutOfHeap.dyn_o rts/dist/build/hooks/StackOverflow.dyn_o rts/dist/build/sm/BlockAlloc.dyn_o rts/dist/build/sm/Compact.dyn_o rts/dist/build/sm/Evac.dyn_o rts/dist/build/sm/GC.dyn_o rts/dist/build/sm/GCAux.dyn_o rts/dist/build/sm/GCUtils.dyn_o rts/dist/build/sm/MBlock.dyn_o rts/dist/build/sm/MarkWeak.dyn_o rts/dist/build/sm/Sanity.dyn_o rts/dist/build/sm/Scav.dyn_o rts/dist/build/sm/Storage.dyn_o rts/dist/build/sm/Sweep.dyn_o rts/dist/build/eventlog/EventLog.dyn_o rts/dist/build/posix/GetEnv.dyn_o rts/dist/build/posix/GetTime.dyn_o rts/dist/build/posix/Itimer.dyn_o rts/dist/build/posix/OSMem.dyn_o rts/dist/build/posix/OSThreads.dyn_o rts/dist/build/posix/Select.dyn_o rts/dist/build/posix/Signals.dyn_o rts/dist/build/posix/TTY.dyn_o rts/dist/build/Apply.dyn_o rts/dist/build/Exception.dyn_o rts/dist/build/HeapStackCheck.dyn_o rts/dist/build/PrimOps.dyn_o rts/dist/build/StgMiscClosures.dyn_o rts/dist/build/StgStartup.dyn_o rts/dist/build/StgStdThunks.dyn_o rts/dist/build/Updates.dyn_o rts/dist/build/AutoApply.dyn_o -fPIC -dynamic -H32m -O -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 -fno-use-rpaths -optl- Wl,-zorigin -o rts/dist/build/libHSrts-ghc7.10.1.so -v Glasgow Haskell Compiler, Version 7.10.1, stage 1 booted by GHC version 7.10.1 Using binary package database: /home/cavtools/src/ghc-7.10.1/inplace/lib/package.conf.d/package.cache Using binary package database: /home/cavtools/.ghc/x86_64-linux-7.10.1/package.conf.d/package.cache package HTTP-4000.2.19-452bb564befa140f2d9875a431f06774 is unusable due to missing or recursive dependencies: array-0.5.1.0-e29cdbe82692341ebb7ce6e2798294f9 base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 bytestring-0.10.6.0-0909f8f31271f3d75749190bf2ee35db mtl-2.2.1-9986828fc95bc8459870303efaabd81e network-2.6.0.2-5b571cbc862842e6a0b3b4f8ff195156 network- uri-2.6.0.1-4b5177daf89becaf2de36ae93281687f old- time-1.1.0.3-c6c471a5ec61ff049468f265b077486d parsec-3.1.7-0adb5f9cdf6ae0c8268c412595b3159a package mtl-2.2.1-9986828fc95bc8459870303efaabd81e is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 transformers-0.4.2.0-c1a7bb855a176fe475d7b665301cd48f package network-2.6.0.2-5b571cbc862842e6a0b3b4f8ff195156 is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 bytestring-0.10.6.0-0909f8f31271f3d75749190bf2ee35db unix-2.7.1.0-91bacaa07e5044ef0f978252f01c4a06 package network-uri-2.6.0.1-4b5177daf89becaf2de36ae93281687f is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 parsec-3.1.7-0adb5f9cdf6ae0c8268c412595b3159a package old-locale-1.0.0.7-c52866273f79efea5d2d03d1e32baad2 is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 package old-time-1.1.0.3-c6c471a5ec61ff049468f265b077486d is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 old- locale-1.0.0.7-c52866273f79efea5d2d03d1e32baad2 package parsec-3.1.7-0adb5f9cdf6ae0c8268c412595b3159a is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 bytestring-0.10.6.0-0909f8f31271f3d75749190bf2ee35db mtl-2.2.1-9986828fc95bc8459870303efaabd81e text-1.2.0.3-9eeb5a52cd7997b3db44037e296ae2da package random-1.1-bf46233feed8bd64cb90bcd77d1c4b8c is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 time-1.5.0.1-e17a9220d438435579d2914e90774246 package stm-2.4.4-1ae235706b0ce6e6ef8d19cd83227592 is unusable due to missing or recursive dependencies: array-0.5.1.0-e29cdbe82692341ebb7ce6e2798294f9 base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 package text-1.2.0.3-9eeb5a52cd7997b3db44037e296ae2da is unusable due to missing or recursive dependencies: array-0.5.1.0-e29cdbe82692341ebb7ce6e2798294f9 base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 bytestring-0.10.6.0-0909f8f31271f3d75749190bf2ee35db deepseq-1.4.1.1-c1376f846fa170f2cc2cb2e57b203339 ghc- prim-0.4.0.0-7c945cc0c41d3b7b70f3edd125671166 integer- gmp-1.0.0.0-3c947e5fb6dca14804d9b2793c521b67 package zlib-0.5.4.2-7f8fa1baff7481f1dca70c1ad6ffca0e is unusable due to missing or recursive dependencies: base-4.8.0.0-6369eb7fa2a0ecb1401c3a53d41cfbb7 bytestring-0.10.6.0-0909f8f31271f3d75749190bf2ee35db wired-in package ghc-prim mapped to ghc-prim-0.4.0.0-inplace wired-in package integer-gmp mapped to integer-gmp-1.0.0.0-inplace wired-in package base mapped to base-4.8.0.0-inplace wired-in package rts mapped to builtin_rts wired-in package template-haskell mapped to template- haskell-2.10.0.0-inplace wired-in package ghc mapped to ghc-7.10.1-inplace wired-in package dph-seq not found. wired-in package dph-par not found. Hsc static flags: *** Linker: /usr/bin/gcc -fno-stack-protector -DTABLES_NEXT_TO_CODE '-Wl,--hash- size=31' -Wl,--reduce-memory-overheads -Wl,--no-as-needed -Wl,-rpath '-Wl,$ORIGIN' -Wl,-zorigin -Wl,-zorigin -o rts/dist/build/libHSrts- ghc7.10.1.so -shared -Wl,-h,libHSrts-ghc7.10.1.so rts/dist/build/Adjustor.dyn_o rts/dist/build/Arena.dyn_o rts/dist/build/Capability.dyn_o rts/dist/build/CheckUnload.dyn_o rts/dist/build/ClosureFlags.dyn_o rts/dist/build/Disassembler.dyn_o rts/dist/build/FileLock.dyn_o rts/dist/build/Globals.dyn_o rts/dist/build/Hash.dyn_o rts/dist/build/Hpc.dyn_o rts/dist/build/HsFFI.dyn_o rts/dist/build/Inlines.dyn_o rts/dist/build/Interpreter.dyn_o rts/dist/build/LdvProfile.dyn_o rts/dist/build/Linker.dyn_o rts/dist/build/Messages.dyn_o rts/dist/build/OldARMAtomic.dyn_o rts/dist/build/Papi.dyn_o rts/dist/build/Printer.dyn_o rts/dist/build/ProfHeap.dyn_o rts/dist/build/Profiling.dyn_o rts/dist/build/Proftimer.dyn_o rts/dist/build/RaiseAsync.dyn_o rts/dist/build/RetainerProfile.dyn_o rts/dist/build/RetainerSet.dyn_o rts/dist/build/RtsAPI.dyn_o rts/dist/build/RtsDllMain.dyn_o rts/dist/build/RtsFlags.dyn_o rts/dist/build/RtsMain.dyn_o rts/dist/build/RtsMessages.dyn_o rts/dist/build/RtsStartup.dyn_o rts/dist/build/RtsUtils.dyn_o rts/dist/build/STM.dyn_o rts/dist/build/Schedule.dyn_o rts/dist/build/Sparks.dyn_o rts/dist/build/Stable.dyn_o rts/dist/build/StaticPtrTable.dyn_o rts/dist/build/Stats.dyn_o rts/dist/build/StgCRun.dyn_o rts/dist/build/StgPrimFloat.dyn_o rts/dist/build/Task.dyn_o rts/dist/build/ThreadLabels.dyn_o rts/dist/build/ThreadPaused.dyn_o rts/dist/build/Threads.dyn_o rts/dist/build/Ticky.dyn_o rts/dist/build/Timer.dyn_o rts/dist/build/Trace.dyn_o rts/dist/build/WSDeque.dyn_o rts/dist/build/Weak.dyn_o rts/dist/build/hooks/FlagDefaults.dyn_o rts/dist/build/hooks/MallocFail.dyn_o rts/dist/build/hooks/OnExit.dyn_o rts/dist/build/hooks/OutOfHeap.dyn_o rts/dist/build/hooks/StackOverflow.dyn_o rts/dist/build/sm/BlockAlloc.dyn_o rts/dist/build/sm/Compact.dyn_o rts/dist/build/sm/Evac.dyn_o rts/dist/build/sm/GC.dyn_o rts/dist/build/sm/GCAux.dyn_o rts/dist/build/sm/GCUtils.dyn_o rts/dist/build/sm/MBlock.dyn_o rts/dist/build/sm/MarkWeak.dyn_o rts/dist/build/sm/Sanity.dyn_o rts/dist/build/sm/Scav.dyn_o rts/dist/build/sm/Storage.dyn_o rts/dist/build/sm/Sweep.dyn_o rts/dist/build/eventlog/EventLog.dyn_o rts/dist/build/posix/GetEnv.dyn_o rts/dist/build/posix/GetTime.dyn_o rts/dist/build/posix/Itimer.dyn_o rts/dist/build/posix/OSMem.dyn_o rts/dist/build/posix/OSThreads.dyn_o rts/dist/build/posix/Select.dyn_o rts/dist/build/posix/Signals.dyn_o rts/dist/build/posix/TTY.dyn_o rts/dist/build/Apply.dyn_o rts/dist/build/Exception.dyn_o rts/dist/build/HeapStackCheck.dyn_o rts/dist/build/PrimOps.dyn_o rts/dist/build/StgMiscClosures.dyn_o rts/dist/build/StgStartup.dyn_o rts/dist/build/StgStdThunks.dyn_o rts/dist/build/Updates.dyn_o rts/dist/build/AutoApply.dyn_o -lffi -lm -lrt -ldl -Lrts/dist/build -L/home/cavtools/src/ghc-7.10.1/rts/dist/build /usr/bin/ld: rts/dist/build/RtsStartup.dyn_o: relocation R_X86_64_PC32 against `exitStaticPtrTable' can not be used when making a shared object; recompile with -fPIC /usr/bin/ld: final link failed: Bad value collect2: ld returned 1 exit status *** Deleting temp files: Deleting: *** Deleting temp dirs: Deleting: }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 04:25:51 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 04:25:51 -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.999ee361f6348a8bcd0fc34f8d51eea4@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by mfox): As a workaround I try to get the message through to gcc: {{{ LD=/home/cavtools/64/pkg/bin/gld make -j8 LD=/home/cavtools/64/pkg/bin/gld }}} It doesn't help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 04:52:44 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 04:52:44 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking In-Reply-To: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> References: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> Message-ID: <060.ee99e6d09da2d43fe31608d95d6c94ca@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #9297 #10563 | Differential Revisions: #8237 #9907 | -------------------------------------+------------------------------------- Changes (by lukexi): * related: #9297 #10563 #8237 => #9297 #10563 #8237 #9907 Comment: I've tested on GHC 7.8.4 now and get this error instead: {{{ Loading package cxxylib-0.1.0.0 ... ghc.exe: Unknown PEi386 section name `.gcc_except_table' (while processing: C:\msys64\home\lukex_000\cxx-link- fail-repro\dist\build\HScxxylib-0.1.0.0.o) : ghc.exe: panic! (the 'impossible' happened) (GHC version 7.8.4 for x86_64-unknown-mingw32): loadObj "C:\\msys64\\home\\lukex_000\\cxx-link-fail- repro\\dist\\build\\HScxxylib-0.1.0.0.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} so it looks like this is related to #9907 and friends. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 04:57:20 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 04:57:20 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking In-Reply-To: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> References: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> Message-ID: <060.5d53e82e1e293d7c5f41332962aa69ec@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #9297 #10563 | Differential Revisions: #8237 #9907 | -------------------------------------+------------------------------------- Changes (by lukexi): * cc: thoughtpolice (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 05:03:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 05:03:27 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking In-Reply-To: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> References: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> Message-ID: <060.1f74ceebc3aab01a58365701306112f6@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #9297 #10563 | Differential Revisions: #8237 #9907 | -------------------------------------+------------------------------------- Comment (by lukexi): Results of 7.8.4 with {{{bullet-mini}}}, which is using {{{-fno- exceptions}}} to avoid linking {{{libgcc_s_sjlj-1.dll}}} {{{ Loading package bullet-mini-0.1.0.0 ... ghc.exe: Unknown PEi386 section name `.text$_ZN21btBroadphaseInterfaceD1Ev' (while processing: C:\msys64\home\lukex_000\Projects\bullet-mini\dist\build\HSbullet- mini-0.1.0.0.o) : ghc.exe: panic! (the 'impossible' happened) (GHC version 7.8.4 for x86_64-unknown-mingw32): loadObj "C:\\msys64\\home\\lukex_000\\Projects\\bullet- mini\\dist\\build\\HSbullet-mini-0.1.0.0.o": failed Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 06:17:04 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 06:17:04 -0000 Subject: [GHC] #10673: GHCi crashes when decoding with Aeson Message-ID: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> #10673: GHCi crashes when decoding with Aeson -----------------------------------------+------------------------------- Reporter: orion | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Keywords: | Operating System: FreeBSD Architecture: x86_64 (amd64) | Type of failure: GHCi crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -----------------------------------------+------------------------------- {{{ $ ghci GHCi, version 7.8.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Prelude> :set -XOverloadedStrings Prelude> let r = "{\"took\":1,\"timed_out\":false,\"_shards\":{\"total\":5,\"successful\":5,\"failed\":0},\"hits\":{\"total\":7,\"max_score\":1.0,\"hits\":[{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"2725954419\",\"_score\":1.0,\"fields\":{\"updated\":[\"20150722T053908+0000\"]}},{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"9580897143\",\"_score\":1.0,\"fields\":{\"updated\":[\"20150716T205624+0000\"]}},{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"3511215163\",\"_score\":1.0,\"fields\":{\"updated\":[\"20150701T024616+0000\"]}},{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"22006\",\"_score\":1.0,\"fields\":{\"updated\":[\"20150723T040619+0000\"]}},{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"4240142128\",\"_score\":1.0,\"fields\":{\"updated\":[\"20150713T222827+0000\"]}},{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"1258498\",\"_score\":1.0,\"fields\":{\"updated\":[\"20150722T134305+0000\"]}},{\"_index\":\"foo\",\"_type\":\"group\",\"_id\":\"1675836265\",\"_score\":1.0,\" fields\":{\"updated\":[\"20150720T222152+0000\"]}}]}}" Prelude> import Data.Aeson Prelude Data.Aeson> decode r :: Maybe Object Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package bytestring-0.10.4.0 ... linking ... done. Loading package containers-0.5.5.1 ... linking ... done. Loading package text-1.1.0.0 ... linking ... done. Loading package attoparsec-0.10.4.0 ... linking ... done. Loading package hashable-1.2.2.0 ... linking ... done. Loading package unordered-containers-0.2.4.0 ... linking ... done. Loading package primitive-0.5.2.1 ... linking ... done. Loading package vector-0.10.9.1 ... linking ... done. Loading package old-locale-1.0.0.6 ... linking ... done. Loading package time-1.4.2 ... linking ... done. Loading package dlist-0.7.1 ... linking ... done. Loading package transformers-0.3.0.0 ... linking ... done. Loading package mtl-2.1.3.1 ... linking ... done. Loading package scientific-0.3.3.0 ... linking ... done. Loading package syb-0.4.1 ... linking ... done. Loading package pretty-1.1.1.1 ... linking ... done. Loading package template-haskell ... linking ... done. Loading package aeson-0.7.0.6 ... linking ... done. Just fromList [("took",Number 1.0),("_shards",Object fromList [("successful",Number 5.0),("total",Number 5.0),("failed",Number 0.0)]),("timed_out",Bool False),("hits",Object fromList [("max_score",Number 1.0),("total",Number 7.0),("hits",Array (fromList [Object fromList [("_type",String "group"),("_score",Number 1.0),("_id",String "2725954419"),("_index",String "foo"),("fields",Object fromList [("updated",Array (fromList [String "20150722T053908+0000"]))])],Object fromList [("_type",String "group"),("_score",Number 1.0),("_id",String "9580897143"),("_index",String "foo"),("fields",Object fromList [("updated",Array (fromList [String "20150716T205624+0000"]))])],Object fromList [("_type",String "group"),("_score",Number 1.0),("_id",String "3511215163"),("_index",String "foo"),("fields",Object fromList [("updated",Array (fromList [String "20150701T024616+0000"]))])],Object fromList [("_type",String "group"),("_score",Number 1.0),("_id",String "22006"),("_index",String "foo"),("fields",Object fromList [("updated",Array (fromList [String "20150723T040619+0000"]))])],Object fromList [("_type",String "group"),("_score",Number 1.0),("_id",String "4240142128"),("_index",String "foo"),Segmentation fault (core dumped) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 07:32:04 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 07:32:04 -0000 Subject: [GHC] #10673: GHCi crashes when decoding with Aeson In-Reply-To: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> References: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> Message-ID: <059.ed2a0f073ea8aa9787d34a0030d01516@haskell.org> #10673: GHCi crashes when decoding with Aeson -------------------------------+----------------------------------------- Reporter: orion | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: wontfix | Keywords: Operating System: FreeBSD | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => wontfix Comment: Well, I actually tried to reproduce this using the exact versions of all those packages, but aeson-0.7.0.6 has a lower bound attoparsec >= 0.11.3.4, so I don't know how you got into this situation. If you can give steps to reproduce this crash on 7.10 and with a consistent set of packages, that would be extremely interesting (and unexpected). Otherwise, closing as wontfix since this is an old version of ghc and there seems to be something fishy about the set of packages you have installed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 07:33:33 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 07:33:33 -0000 Subject: [GHC] #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 In-Reply-To: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> References: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> Message-ID: <062.ebfcf95b5abae3e3f5616b39250951b8@haskell.org> #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"5c3fc921aeeeec392a89914783b2be9ea3dade27/ghc" 5c3fc921/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5c3fc921aeeeec392a89914783b2be9ea3dade27" Fix Trac #10670 In dataConCannotMatch we were using a GADT data con without properly instantiating the existential type variables. The fix is easy, and the code is tighter. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 07:36:18 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 07:36: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.534a1657763d341929e04e98d9a86b6e@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Yes, as you can see ghc invokes gcc for the link step. You will need to work out how to tell gcc to use your custom linker, and then create a wrapper around gcc that does so and specify that as the C compiler to configure. Or perhaps there is already such a C compiler in `/home/cavtools/64/pkg/bin/`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 07:49:26 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 07:49:26 -0000 Subject: [GHC] #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 In-Reply-To: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> References: <047.7fbebf8a6b9d106f3e82eb63d2178dbc@haskell.org> Message-ID: <062.5c38c7c09b70e35a30e795fbccf96d9b@haskell.org> #10670: panic! ASSERT failed compiler/types/Type.hs line 1712 -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: crash | polykinds/T10670,T10670a Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => polykinds/T10670,T10670a * status: new => closed * resolution: => fixed Comment: Great bug, thanks. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 10:18:00 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 10:18:00 -0000 Subject: [GHC] #10674: Expose OSThreadID and assorted functions from Haskell Message-ID: <047.35673a1245c9e2068498a881d95a8afe@haskell.org> #10674: Expose OSThreadID and assorted functions from Haskell -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Currently given two {{{ThreadId}}}s, there is no way to tell without FFI if they are running on the same OS thread. There is not even a way to ask what OS thread we are currently on: something like {{{myThreadId}}} except {{{myOsThreadId}}}. Currently to remedy this, the user has to effectively copy and paste parts of the internal rts files and use something like {{{.hsc}}} with CPP to get at this information. This is not really portable on the user side and requires nasty gutting. In the RTS the function we are interested in is at least {{{osThreadId}}}: at least with this function we can inspect current {{{OSThreadId}}} and communicate it out through an {{{MVar}}} or otherwise. So this is a feature request for an abstract type {{{OSThreadId}}} with instances of at least {{{Eq, Show}}} and a function {{{myOsThreadId :: IO OSThreadId}}}. Nice to have would be {{{osThreadId :: ThreadID -> IO OSThreadId}}} but not critical. If there is room for optimisation in GHC, functions like {{{sameOsThread :: ThreadId -> ThreadId -> IO Bool}}} would also be nice but again not critical. Not sure what to set in ticket meta-data so please change as appropriate. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 10:19:05 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 10:19:05 -0000 Subject: [GHC] #10674: Expose OSThreadID and assorted functions from Haskell In-Reply-To: <047.35673a1245c9e2068498a881d95a8afe@haskell.org> References: <047.35673a1245c9e2068498a881d95a8afe@haskell.org> Message-ID: <062.d020e4e16a9ceddbde1d67db3e590a06@haskell.org> #10674: Expose OSThreadID and assorted functions from Haskell -------------------------------------+------------------------------------- Reporter: Fuuzetsu | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by Fuuzetsu: Old description: > Currently given two {{{ThreadId}}}s, there is no way to tell without FFI > if they are running on the same OS thread. There is not even a way to ask > what OS thread we are currently on: something like {{{myThreadId}}} > except {{{myOsThreadId}}}. > > Currently to remedy this, the user has to effectively copy and paste > parts of the internal rts files and use something like {{{.hsc}}} with > CPP to get at this information. This is not really portable on the user > side and requires nasty gutting. > > In the RTS the function we are interested in is at least > {{{osThreadId}}}: at least with this function we can inspect current > {{{OSThreadId}}} and communicate it out through an {{{MVar}}} or > otherwise. > > So this is a feature request for an abstract type {{{OSThreadId}}} with > instances of at least {{{Eq, Show}}} and a function {{{myOsThreadId :: IO > OSThreadId}}}. > > Nice to have would be {{{osThreadId :: ThreadID -> IO OSThreadId}}} but > not critical. If there is room for optimisation in GHC, functions like > {{{sameOsThread :: ThreadId -> ThreadId -> IO Bool}}} would also be nice > but again not critical. > > Not sure what to set in ticket meta-data so please change as appropriate. New description: Currently given two {{{ThreadId}}}s, there is no way to tell without FFI if they are running on the same OS thread. There is not even a way to ask what OS thread we are currently on: something like {{{myThreadId}}} except {{{myOsThreadId}}}. Currently to remedy this, the user has to effectively copy and paste parts of the internal rts files and use something like {{{.hsc}}} with CPP to get at this information. This is not really portable on the user side and requires nasty gutting. In the RTS the function we are interested in is at least {{{osThreadId}}}: with this function we can inspect current {{{OSThreadId}}} and communicate it out through an {{{MVar}}} or otherwise. So this is a feature request for an abstract type {{{OSThreadId}}} with instances of at least {{{Eq, Show}}} and a function {{{myOsThreadId :: IO OSThreadId}}}. Nice to have would be {{{osThreadId :: ThreadID -> IO OSThreadId}}} but not critical. If there is room for optimisation in GHC, functions like {{{sameOsThread :: ThreadId -> ThreadId -> IO Bool}}} would also be nice but again not critical. Not sure what to set in ticket meta-data so please change as appropriate. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 12:54:52 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 12:54:52 -0000 Subject: [GHC] #10398: Support consecutive named Haddock comments In-Reply-To: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> References: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> Message-ID: <062.70a043c66923291e1e11401387f188b1@haskell.org> #10398: Support consecutive named Haddock comments -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: patch Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: | haddock/should_compile_flag_haddock/T10398 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1025 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d784bdeb62a6b11831c5235a97449ff2a86dcc52/ghc" d784bde/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d784bdeb62a6b11831c5235a97449ff2a86dcc52" Lexer: support consecutive references to Haddock chunks (#10398) Reviewers: austin, bgamari, Fuuzetsu Reviewed By: bgamari Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1025 GHC Trac Issues: #10398 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 12:54:52 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 12:54:52 -0000 Subject: [GHC] #10660: .dyn_o isn't generated for .hsig files with -dynamic-too In-Reply-To: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> References: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> Message-ID: <060.41bfacdc2252e228fa92f5c3192bb13d@haskell.org> #10660: .dyn_o isn't generated for .hsig files with -dynamic-too -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: bug | Status: patch Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1084 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"d2b4df157532adf014789ae9b2496f88369e43ea/ghc" d2b4df1/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d2b4df157532adf014789ae9b2496f88369e43ea" Generate .dyn_o files for .hsig files with -dynamic-too With -dynamic-too, .dyn_o files were not being generated for .hsig files. Normally, this is handled in the pipeline; however, the branch for .hsig files called compileEmptyStub directly instead of going through runPipeline. When compiling a Cabal package that included .hsig files, this triggered a linker error later on, as it expected a .dyn_o file to have been generated for each .hsig. The fix is to use runPipeline for .hsig files, just as with .hs files. Alternately, one could duplicate the logic for handling -dynamic-too in the .hsig branch, but simply calling runPipeline ends up being much cleaner. Test Plan: validate Reviewers: austin, ezyang, bgamari, thomie Reviewed By: ezyang, thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1084 GHC Trac Issues: #10660 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 12:54:52 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 12:54:52 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators In-Reply-To: <047.60a52fd2422f834202b3d782885a3356@haskell.org> References: <047.60a52fd2422f834202b3d782885a3356@haskell.org> Message-ID: <062.ac258ee953a87d643d71c87d1fc297df@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1093 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"b5c94262fa79f735334165c53667f113e07df5e1/ghc" b5c94262/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b5c94262fa79f735334165c53667f113e07df5e1" Parenthesise TypeOperator in import hints When a constructor was mistakenly imported directly instead of as a constructor of a data type, a hint will be shown on how to correctly import it. Just like the constructor, the data type should be surrounded in parentheses if it is an operator (TypeOperator in this case). Instead of: error: In module ?Data.Type.Equality?: ?Refl? is a data constructor of ?:~:? To import it use ?import? Data.Type.Equality( :~:( Refl ) ) or ?import? Data.Type.Equality( :~:(..) ) Print: error: In module ?Data.Type.Equality?: ?Refl? is a data constructor of ?(:~:)? To import it use ?import? Data.Type.Equality( (:~:)( Refl ) ) or ?import? Data.Type.Equality( (:~:)(..) ) Test Plan: pass new test Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1093 GHC Trac Issues: #10668 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 12:58:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 12:58:21 -0000 Subject: [GHC] #4012: Compilation results are not deterministic In-Reply-To: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> References: <043.9c3dc141e8901acb12e4d7c1e6038096@haskell.org> Message-ID: <058.ebf19a6e3204939a82a3b13a8ab691e9@haskell.org> #4012: Compilation results are not deterministic -------------------------------------+------------------------------------- Reporter: kili | Owner: niteria Type: bug | Status: patch Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 6.12.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1073 -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"7ec07e4027826ad92cf651798cc4b5b9eea34a18/ghc" 7ec07e40/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7ec07e4027826ad92cf651798cc4b5b9eea34a18" Slight refactoring to the fix for #4012 Add CoreSyn.chooseOrphanAnchor, and use it }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 12:59:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 12:59:38 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators In-Reply-To: <047.60a52fd2422f834202b3d782885a3356@haskell.org> References: <047.60a52fd2422f834202b3d782885a3356@haskell.org> Message-ID: <062.796d8d54d6c4c79ed7701186399ff634@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: thomasw Type: bug | Status: new Priority: normal | Milestone: 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: T10668 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1093 -------------------------------------+------------------------------------- Changes (by thomasw): * testcase: => T10668 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 13:37:08 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 13:37:08 -0000 Subject: [GHC] #10668: Missing brackets in import hint with TypeOperators In-Reply-To: <047.60a52fd2422f834202b3d782885a3356@haskell.org> References: <047.60a52fd2422f834202b3d782885a3356@haskell.org> Message-ID: <062.6ec53b028e577c03e2f7da0a565a46a3@haskell.org> #10668: Missing brackets in import hint with TypeOperators -------------------------------------+------------------------------------- Reporter: bjmprice | Owner: thomasw Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 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: T10668 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1093 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 13:37:45 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 13:37:45 -0000 Subject: [GHC] #10660: .dyn_o isn't generated for .hsig files with -dynamic-too In-Reply-To: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> References: <045.56b69c19eb1cb2d0ece6f18980e16b58@haskell.org> Message-ID: <060.812286af19f40189da476622946c8184@haskell.org> #10660: .dyn_o isn't generated for .hsig files with -dynamic-too -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1084 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 13:38:09 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 13:38:09 -0000 Subject: [GHC] #10398: Support consecutive named Haddock comments In-Reply-To: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> References: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> Message-ID: <062.6564344406f24705844b1fd6380d9664@haskell.org> #10398: Support consecutive named Haddock comments -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: | haddock/should_compile_flag_haddock/T10398 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1025 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 14:03:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 14:03:27 -0000 Subject: [GHC] #4929: Support all top-level declarations in GHCi In-Reply-To: <047.ad1f6cca8cd5513a02f6e27fd2ce6cd5@haskell.org> References: <047.ad1f6cca8cd5513a02f6e27fd2ce6cd5@haskell.org> Message-ID: <062.b60a0f61ae6898c787c241d1fb5e645a@haskell.org> #4929: Support all top-level declarations in GHCi -------------------------------------+--------------------------------- Reporter: simonmar | Owner: simonmar Type: task | Status: closed Priority: high | Milestone: 7.4.1 Component: GHCi | Version: 7.0.1 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:"e809ef57d841695f76ab9b2758f7aeb774d6b223/ghc" e809ef5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e809ef57d841695f76ab9b2758f7aeb774d6b223" ghci: fixity declarations for infix data constructors (#10018) Declaring a custom fixity for an infix data constructor should work: Prelude> data Infix a b = a :@: b; infixl 4 :@: This is a followup to #2947, which handled fixity declarations in ghci statements (e.g. let add = (+); infixl 6 `add`). Support for declarations (data, type, newtype, class, instance, deriving, and foreign) was added to GHCi in #4929. Reviewers: simonpj, austin, thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1028 GHC Trac Issues: #10018 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 14:03:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 14:03:27 -0000 Subject: [GHC] #10018: Cannot define custom fixity for infix data constructors in GHCi In-Reply-To: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> References: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> Message-ID: <065.14a11c6f2673fcce830a4bd56d1a0893@haskell.org> #10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | ghci/scripts/T10018 Blocked By: | Blocking: Related Tickets: #9830, #2947, | Differential Revisions: Phab:D1028 #4929 | -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"e809ef57d841695f76ab9b2758f7aeb774d6b223/ghc" e809ef5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e809ef57d841695f76ab9b2758f7aeb774d6b223" ghci: fixity declarations for infix data constructors (#10018) Declaring a custom fixity for an infix data constructor should work: Prelude> data Infix a b = a :@: b; infixl 4 :@: This is a followup to #2947, which handled fixity declarations in ghci statements (e.g. let add = (+); infixl 6 `add`). Support for declarations (data, type, newtype, class, instance, deriving, and foreign) was added to GHCi in #4929. Reviewers: simonpj, austin, thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1028 GHC Trac Issues: #10018 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 14:03:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 14:03:27 -0000 Subject: [GHC] #2947: infix precedence of backtick functions defined in ghci is not reported by :info In-Reply-To: <048.ac55607c7d8b9643c6c08e90e9bdf49b@haskell.org> References: <048.ac55607c7d8b9643c6c08e90e9bdf49b@haskell.org> Message-ID: <063.eb2f87da04f26127979fc2f13d7b961a@haskell.org> #2947: infix precedence of backtick functions defined in ghci is not reported by :info -------------------------------------+--------------------------------- Reporter: EyalLotem | Owner: pcapriotti Type: bug | Status: closed Priority: lowest | Milestone: 7.6.1 Component: GHCi | Version: 6.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | -------------------------------------+--------------------------------- Comment (by Ben Gamari ): In [changeset:"e809ef57d841695f76ab9b2758f7aeb774d6b223/ghc" e809ef5/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e809ef57d841695f76ab9b2758f7aeb774d6b223" ghci: fixity declarations for infix data constructors (#10018) Declaring a custom fixity for an infix data constructor should work: Prelude> data Infix a b = a :@: b; infixl 4 :@: This is a followup to #2947, which handled fixity declarations in ghci statements (e.g. let add = (+); infixl 6 `add`). Support for declarations (data, type, newtype, class, instance, deriving, and foreign) was added to GHCi in #4929. Reviewers: simonpj, austin, thomie Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1028 GHC Trac Issues: #10018 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 14:03:53 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 14:03:53 -0000 Subject: [GHC] #10018: Cannot define custom fixity for infix data constructors in GHCi In-Reply-To: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> References: <050.b73ae7970094272181854c9a26f7e4d3@haskell.org> Message-ID: <065.c9271a777596c4ce34a0e5c09eda6fdc@haskell.org> #10018: Cannot define custom fixity for infix data constructors in GHCi -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: GHCi | Version: 7.10.1-rc2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | ghci/scripts/T10018 Blocked By: | Blocking: Related Tickets: #9830, #2947, | Differential Revisions: Phab:D1028 #4929 | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 14:11:20 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 14:11:20 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.8cfc937fca15b9dc9d64c36bfb9fab36@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by MtnViewMark): I've added code to HP to build GLUT this way on OS X, and it works. Next release will have it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 14:59:28 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 14:59:28 -0000 Subject: [GHC] #10673: GHCi crashes when decoding with Aeson In-Reply-To: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> References: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> Message-ID: <059.eb7f35227a6450a23ed21a8ff0f6c351@haskell.org> #10673: GHCi crashes when decoding with Aeson -------------------------------+----------------------------------------- Reporter: orion | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: wontfix | Keywords: Operating System: FreeBSD | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by orion): The library version issue seems to be related to FreeBSD's package management: http://www.freebsd.org/cgi/ports.cgi?query=aeson&stype=all -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 16:29:06 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 16:29:06 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly Message-ID: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Consider {{{ {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, ScopedTypeVariables #-} class C a b | a -> b where op :: a -> b instance C [x] [x] instance {-# OVERLAPS #-} C x y => C [x] [Maybe y] f x = op [x] }}} Should these two instance declarations be accepted? They are simply ''inconsistent'' in the sense of Definition 6 of the [http://research.microsoft.com/en-us/um/people/simonpj/papers/fd- chr/jfp06.pdf FDs through CHRs paper]. Sadly GHC does not currently reject these as inconsistent. As a result it'll use ''both'' instance for improvement. In the definition of `f` for example we get {{{ C [alpha] beta }}} where `x:alpha` and the result type of `f` is `beta`. By using both instances for improvement we get {{{ C [Maybe gamma] [Maybe gamma] }}} Is that what we want? The two instances don't ''contradict'' each other, but neither do they agree as all published work on FDs says they should! Examples in the testsuite that exploit this loophole are {{{ ghci/scripts ghci047 polykinds T9106 typecheck/should_compile FD4 typecheck/should_compile T7875 }}} I'm not sure what the right thing here is. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 16:35:58 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 16:35:58 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.bf16e987a5ab24b2ebcddc74b81b37cd@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by simonpj: Old description: > Consider > {{{ > {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, > FlexibleInstances, UndecidableInstances, > ScopedTypeVariables #-} > > class C a b | a -> b where > op :: a -> b > > instance C [x] [x] > instance {-# OVERLAPS #-} C x y => C [x] [Maybe y] > > f x = op [x] > }}} > Should these two instance declarations be accepted? They are simply > ''inconsistent'' in the sense of Definition 6 of the > [http://research.microsoft.com/en-us/um/people/simonpj/papers/fd- > chr/jfp06.pdf FDs through CHRs paper]. > > Sadly GHC does not currently reject these as inconsistent. As a result > it'll use ''both'' instance for improvement. In the definition of `f` > for example we get > {{{ > C [alpha] beta > }}} > where `x:alpha` and the result type of `f` is `beta`. By using both > instances for improvement we get > {{{ > C [Maybe gamma] [Maybe gamma] > }}} > Is that what we want? The two instances don't ''contradict'' each other, > but neither do they agree as all published work on FDs says they should! > > Examples in the testsuite that exploit this loophole are > {{{ > ghci/scripts ghci047 > polykinds T9106 > typecheck/should_compile FD4 > typecheck/should_compile T7875 > }}} > I'm not sure what the right thing here is. New description: Consider {{{ {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances, ScopedTypeVariables #-} class C x a b | a -> b where op :: x -> a -> b instance C Bool [x] [x] instance C Char x y => C Char [x] [Maybe y] f x = op True [x] }}} Should these two instance declarations be accepted? The two instances don't ''contradict'' each other, but neither do they agree as all published work on FDs says they should! They are ''inconsistent'' in the sense of Definition 6 of the [http://research.microsoft.com/en-us/um/people/simonpj/papers/fd- chr/jfp06.pdf FDs through CHRs paper]. Sadly GHC does not currently reject these as inconsistent. As a result it'll use ''both'' instance for improvement. In the definition of `f` for example we get {{{ C Bool [alpha] beta }}} where `x:alpha` and the result type of `f` is `beta`. By using both instances for improvement we get {{{ C Bool [Maybe gamma] [Maybe gamma] }}} That can be solved, so we get {{{ f :: Maybe x -> [Maybe x] }}} But where did that `Maybe` come from? It's really nothing to do with it. Examples in the testsuite that exploit this loophole are {{{ ghci/scripts ghci047 polykinds T9106 typecheck/should_compile FD4 typecheck/should_compile T7875 }}} I'm not sure what the right thing here is. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 16:36:37 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 16:36:37 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.6728bb4b5057c203857c31cf085e4886@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: diatchki, dimitris, goldfire (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 16:53:59 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 16:53:59 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.9ba28e457ef28d60c4516332b5500519@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jstolarek): * cc: jstolarek (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 19:00:35 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 19:00:35 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# Message-ID: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: Runtime (amd64) | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Consider the module {{{ {-# LANGUAGE MagicHash #-} module Min where import GHC.Exts fgood :: Int# -> Int# -> Int fgood x# y# = case isTrue# (x# <# y#) of False -> I# y# True -> I# x# fbad :: Int# -> Int# -> Int fbad x# y# = case x# <# y# of 0# -> I# y# _ -> I# x# }}} The code for `fgood` looks fine: {{{ 0000000000000130 : 130: 49 83 c4 10 add $0x10,%r12 134: 4d 3b a5 58 03 00 00 cmp 0x358(%r13),%r12 13b: 77 1a ja 157 13d: 49 39 f6 cmp %rsi,%r14 140: 7c 29 jl 16b 142: 49 c7 44 24 f8 00 00 movq $0x0,-0x8(%r12) 149: 00 00 147: R_X86_64_32S ghczmprim_GHCziTypes_Izh_con_info 14b: 49 89 34 24 mov %rsi,(%r12) 14f: 49 8d 5c 24 f9 lea -0x7(%r12),%rbx 154: ff 65 00 jmpq *0x0(%rbp) 157: 49 c7 85 88 03 00 00 movq $0x10,0x388(%r13) 15e: 10 00 00 00 162: bb 00 00 00 00 mov $0x0,%ebx 163: R_X86_64_32 Min_fgood_closure 167: 41 ff 65 f8 jmpq *-0x8(%r13) 16b: 49 c7 44 24 f8 00 00 movq $0x0,-0x8(%r12) 172: 00 00 170: R_X86_64_32S ghczmprim_GHCziTypes_Izh_con_info 174: 4d 89 34 24 mov %r14,(%r12) 178: 49 8d 5c 24 f9 lea -0x7(%r12),%rbx 17d: ff 65 00 jmpq *0x0(%rbp) }}} But the code for `fbad` has several problems: {{{ 0000000000000018 : 18: 48 8d 45 f0 lea -0x10(%rbp),%rax 1c: 4c 39 f8 cmp %r15,%rax 1f: 72 3a jb 5b 21: 48 89 f0 mov %rsi,%rax 24: 4c 89 f3 mov %r14,%rbx 27: 49 39 f6 cmp %rsi,%r14 2a: 0f 9c c1 setl %cl 2d: 0f b6 c9 movzbl %cl,%ecx 30: 48 85 c9 test %rcx,%rcx 33: 75 51 jne 86 35: 49 83 c4 10 add $0x10,%r12 39: 4d 3b a5 58 03 00 00 cmp 0x358(%r13),%r12 40: 0f 87 aa 00 00 00 ja f0 46: 49 c7 44 24 f8 00 00 movq $0x0,-0x8(%r12) 4d: 00 00 4b: R_X86_64_32S ghczmprim_GHCziTypes_Izh_con_info 4f: 49 89 04 24 mov %rax,(%r12) 53: 49 8d 5c 24 f9 lea -0x7(%r12),%rbx 58: ff 65 00 jmpq *0x0(%rbp) 5b: bb 00 00 00 00 mov $0x0,%ebx 5c: R_X86_64_32 Min_fbad_closure 60: 41 ff 65 f8 jmpq *-0x8(%r13) ... ; c1Sm_info is the other case with its own heap check and GC entry code ; c1Su_info is another GC entry ; in total, another 160 bytes of code }}} For some reason, the heap checks were moved into the alternatives, which was not a good decision in this case. But the silly thing here is the `cmp/setl/movzbl/test/jne` sequence in `Min_fbad_info`, which should be replaced by a `cmp/jl` as in `Min_fgood_info`. Same behavior in 7.8 and HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 19:29:48 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 19:29:48 -0000 Subject: [GHC] #10677: slightly silly assembly for testing whether a Word# is 0## Message-ID: <047.666ef36ac1cc91ac56611c092c7fbb22@haskell.org> #10677: slightly silly assembly for testing whether a Word# is 0## -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: x86_64 | Type of failure: Runtime (amd64) | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- {{{ {-# LANGUAGE MagicHash #-} module Zero where import GHC.Exts f :: Word# -> Word# f 0## = 1## f x## = x## }}} in HEAD produces {{{ 0000000000000018 : 18: 49 83 fe 01 cmp $0x1,%r14 1c: 72 06 jb 24 1e: 4c 89 f3 mov %r14,%rbx 21: ff 65 00 jmpq *0x0(%rbp) 24: bb 01 00 00 00 mov $0x1,%ebx 29: ff 65 00 jmpq *0x0(%rbp) }}} Well, `cmp $0x1,%r14/jb` isn't wrong. But it's a byte longer than `test %r14,%r14/je`, so the latter should be preferred. GHC 7.10 produced the `test/je` version, so I'm guessing this is a side effect of nomeata's work on #10137. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 20:38:36 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 20:38:36 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.540d1e0659486432b7b138d96d5f2cef@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1056 -------------------------------------+------------------------------------- Comment (by Edward Z. Yang ): In [changeset:"f9687caf337d409e4735d5bb4cf73a7dc629a58c/ghc" f9687caf/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f9687caf337d409e4735d5bb4cf73a7dc629a58c" Library names, with Cabal submodule update A library name is a package name, package version, and hash of the version names of all textual dependencies (i.e. packages which were included.) A library name is a coarse approximation of installed package IDs, which are suitable for inclusion in package keys (you don't want to put an IPID in a package key, since it means the key will change any time the source changes.) - We define ShPackageKey, which is the semantic object which is hashed into a PackageKey. You can use 'newPackageKey' to hash a ShPackageKey to a PackageKey - Given a PackageKey, we can lookup its ShPackageKey with 'lookupPackageKey'. The way we can do this is by consulting the 'pkgKeyCache', which records a reverse mapping from every hash to the ShPackageKey. This means that if you load in PackageKeys from external sources (e.g. interface files), you also need to load in a mapping of PackageKeys to their ShPackageKeys so we can populate the cache. - We define a 'LibraryName' which encapsulates the full depenency resolution that Cabal may have selected; this is opaque to GHC but can be used to distinguish different versions of a package. - Definite packages don't have an interesting PackageKey, so we rely on Cabal to pass them to us. - We can pretty-print package keys while displaying the instantiation, but it's not wired up to anything (e.g. the Outputable instance of PackageKey). Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1056 GHC Trac Issues: #10566 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 20:39:11 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 20:39:11 -0000 Subject: [GHC] #10566: Move "package key" generation to GHC In-Reply-To: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> References: <045.ddebeff3d0e9a54644e59a805a0d4635@haskell.org> Message-ID: <060.35827888bb5c73926b653a5c49dcf392@haskell.org> #10566: Move "package key" generation to GHC -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Package system | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1056 -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 20:59:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 20:59:38 -0000 Subject: [GHC] #10665: INLINE breaks rewrite rules when '-g' is used In-Reply-To: <045.95657d2fca941df9621daef19a7fe710@haskell.org> References: <045.95657d2fca941df9621daef19a7fe710@haskell.org> Message-ID: <060.ca20c6beda27cfda33bc4bc607142b3c@haskell.org> #10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): (side note: I'm not an author of those packages, just a mere distribution packager :)) conduit is a big package, i'll try to prepare self-contained bundle to ease analysis of existing RULES in there. Meanwhile I've found smaller package that fails in similar way: unification-fd-0.10.0.1. The plus is that everything happens in a single module '''Data.Functor.Fixedpoint'''. The failure is: {{{ $ ghc -hide-all-packages -package=base -O2 -c -g Fixedpoint.hs ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): Tick in rule eps_aPv @ (Fix f_aPy) (unFix @ f_aPy x_a2gY) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug (Or with -dsuppress-uniques:) Tick in rule eps @ (Fix f) (unFix @ f x) }}} Would it be easy to add actual rule name to that crash to ease analysis of what exactly went wrong? (Or maybe there already is a trace knob for it?) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 21:00:24 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 21:00:24 -0000 Subject: [GHC] #10665: INLINE breaks rewrite rules when '-g' is used In-Reply-To: <045.95657d2fca941df9621daef19a7fe710@haskell.org> References: <045.95657d2fca941df9621daef19a7fe710@haskell.org> Message-ID: <060.39d6bfdd5ff881ef056a203fb173b2c9@haskell.org> #10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by slyfox): * Attachment "Fixedpoint.hs" added. taken as-is from unification-fd-0.10.0.1/src/Data/Functor/Fixedpoint.hs -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 21:36:25 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 21:36:25 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.0db61c94b3d22182acb8190d3c3932e8@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 22:21:53 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 22:21:53 -0000 Subject: [GHC] #10665: INLINE breaks rewrite rules when '-g' is used In-Reply-To: <045.95657d2fca941df9621daef19a7fe710@haskell.org> References: <045.95657d2fca941df9621daef19a7fe710@haskell.org> Message-ID: <060.39e18d39bcb7e1741bfd63d2774f45da@haskell.org> #10665: INLINE breaks rewrite rules when '-g' is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): And here goes conduit sample: http://code.haskell.org/~slyfox/when-rules- tick-in-conduit-T10665.tar.gz (3MB of haskell code). Tarball contains original hackage packages with 2-3 language pragmas added. It does not require external depends and can be built with inplace/bin /ghc-stage2. Fails thusly on 7.10.2: {{{ $ ./trigger-a-bug.bash [97 of 99] Compiling Data.Conduit.Extra.ZipConduitSpec ( conduit-1.2.4.3/test/Data/Conduit/Extra/ZipConduitSpec.hs, conduit-1.2.4.3/test/Data/Conduit/Extra/ZipConduitSpec.o ) ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): Tick in rule unstream @ a21_a4C66 @ Void @ m_a4C64 @ b_a4C65 (ConduitWithStream @ a21_a4C66 @ Void @ m_a4C64 @ b_a4C65 (let { $dApplicative_a4BDD :: Applicative (ConduitM a21_a4C66 Void m_a4C64) [LclId, Str=DmdType] $dApplicative_a4BDD = $fApplicativeConduitM @ a21_a4C66 @ Void @ m_a4C64 ($fFunctorConduitM @ a21_a4C66 @ Void @ m_a4C64) } in ... }}} To follow by source code: {{{#!hs --| rewrite rule is triggered by '$$' operator at conduit-1.2.4.3/test/Data/Conduit/Extra/ZipConduitSpec.hs: res <- src $$ conduit =$ sink --| '''conduit-1.2.4.3/Data/Conduit/List.hs''' refines rewrite rule as: {-# RULES "conduit: $$ fold" forall src f b. src $$ fold f b = connectFold src f b #-} --| '''fold''' is defined at conduit-1.2.4.3/Data/Conduit/List.hs: fold, foldC :: Monad m => (b -> a -> b) -> b -> Consumer a m b foldC f = loop where loop !accum = await >>= maybe (return accum) (loop . f accum) {-# INLINE foldC #-} STREAMING(fold, foldC, foldS, f accum) --| STREAMING is a macro in conduit-1.2.4.3/fusion-macros.h that inlines 'fold' lately: #define STREAMING(name, nameC, nameS, vars) ;\ name = nameC ;\ {-# INLINE [0] name #-} ;\ {-# RULES "unstream name" forall vars. \ name vars = unstream (streamConduit (nameC vars) (nameS vars)) \ #-} }}} Here delaying inline does not help as rewrite rule becomes broken when compliling one module (where it's defined) and used in another. That's the reson why original reproducer so carefully setups phases. To be able to compile it under windows you might need to change {{{ -D'UNIX=1' \ }}} to {{{ -D'WINDOWS=1' \ }}} in '''trigger-a-bug.bash''' script. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 23 23:58:31 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 23 Jul 2015 23:58:31 -0000 Subject: [GHC] #10678: integer-gmp's runS seems unnecessarily expensive Message-ID: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> #10678: integer-gmp's runS seems unnecessarily expensive -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- integer-gmp uses an unsafePerformIO-like operation to work with mutable BigNats (unsafePerformIO and even the IO type are not yet available, since integer-gmp is a dependency of base): {{{ type S s a = State# s -> (# State# s, a #) -- NB: equivalent of GHC.IO.unsafeDupablePerformIO, see notes there runS :: S RealWorld a -> a runS m = lazy (case m realWorld# of (# _, r #) -> r) {-# NOINLINE runS #-} }}} It's tempting to think of such an operation as "free" like an unsafeCoerce, but it is actually somewhat expensive. Consider `plusBigNat` for instance. (Most BigNat operations have a similar structure.) {{{ plusBigNat :: BigNat -> BigNat -> BigNat plusBigNat x y | isTrue# (eqBigNatWord# x 0##) = y | isTrue# (eqBigNatWord# y 0##) = x | isTrue# (nx# >=# ny#) = go x nx# y ny# | True = go y ny# x nx# where go (BN# a#) na# (BN# b#) nb# = runS $ do mbn@(MBN# mba#) <- newBigNat# na# (W# c#) <- liftIO (c_mpn_add mba# a# na# b# nb#) case c# of 0## -> unsafeFreezeBigNat# mbn _ -> unsafeSnocFreezeBigNat# mbn c# nx# = sizeofBigNat# x ny# = sizeofBigNat# y }}} The assembly for `go` begins {{{ 00000000000001d0 : 1d0: 49 83 c4 28 add $0x28,%r12 1d4: 4d 3b a5 58 03 00 00 cmp 0x358(%r13),%r12 1db: 77 26 ja 203 1dd: 49 c7 44 24 e0 00 00 movq $0x0,-0x20(%r12) 1e4: 00 00 1e2: R_X86_64_32S .text+0x38 1e6: 4d 89 74 24 e8 mov %r14,-0x18(%r12) 1eb: 49 89 7c 24 f0 mov %rdi,-0x10(%r12) 1f0: 49 89 74 24 f8 mov %rsi,-0x8(%r12) 1f5: 4d 89 04 24 mov %r8,(%r12) 1f9: 4d 8d 74 24 e1 lea -0x1f(%r12),%r14 1fe: e9 00 00 00 00 jmpq 203 1ff: R_X86_64_PC32 integerzmgmp_GHCziIntegerziType_runS_info-0x4 203: ... ; heap overflow }}} This allocates a 5-word closure (containing `a#`, `na#`, `b#`, `nb#`) whose code is at `.text+0x38` and passes it to `runS`, which does some `stg_ap`-y things to call back into the closure, which reads its free variables back from the heap and finally does all the real work. Altogether it's around two dozen instructions compared to if we could call directly from `go` to the argument of `runS`. The old integer-gmp somehow avoided this particular overhead by instead using the implicit "unsafePerformIO" of a foreign import prim which performed both the allocation and the addition. Is this overhead a necessary consequence of doing the work in multiple steps in Haskell? I understand that we cannot allow everything to be inlined and, for example, the `newBigNat#` to be shared between a `plusBigNat` and `minusBigNat` with the same arguments. But once `runS` has done its job of keeping the `newBigNat#/c_mpn_add/unsafeFreeze*` together, it would be nice to eliminate it completely in the backend when compiling `go`, or any inlined version of `go`. I'm not sure whether this should be fixed in the code generator or in integer-gmp itself. I'm also aware that this is a tricky subject but haven't really done my homework on the related tickets, so I might be missing something important! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 01:18:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 01:18:02 -0000 Subject: [GHC] #10679: Generalize hi-boot/hi for signatures, to manage intermediate merged interfaces Message-ID: <045.12de5382940d37915572908b5eadd02a@haskell.org> #10679: Generalize hi-boot/hi for signatures, to manage intermediate merged interfaces -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package | Version: 7.11 system | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- == The problem == In some situations, we need to output multiple interface files for what is morally the same module name. === Example 1: Merging external and home signatures === {{{ unit a-sig where signature A unit p where include a-sig signature A }}} Compiling `p/A.hsig` produces an interface file which contains just the definitions declared in `p`. However, someone including `p` should see the merge of the interface of `p/A.hsig` AND `a-sig/A.hsig` (which was included.) === Example 2: Merging two home signatures === {{{ unit p where signature A signature B where import A ... signature A where import B ... }}} What should we do if a signature is specified multiple times in the same unit? The compilation of each produces a distinct interface, and the public interface we want to expose is the merge of the two. (And by the way, what's the source file name of `A`, if we are not using the inline syntax?) === Example 3: Merging a signature and a module === {{{ unit p where signature A module B where import A ... module A where import B ... }}} `A` and `B` are mutually recursive, and we want to use a signature file to break the gap. The signature produces an interface file, only to be overwritten when we actually define the module proper. But wait! We have a solution for this example already: the first interface file for `A` is not saved to `A.hi`, but `A.hi-boot`... == The proposal == I want to take the `A.hi-boot` versus `A.hi` distinction and generalize it: we should be able to name intermediate interface files A.1.hi, A.2.hi, ... and finally A.hi (which is publically visible outside the unit.) This naming convention applies to Haskell files too. === User-visible consequences === Every signature file is numbered, and every import of a signature file refers to a specific number. This number is unique among all other modules in a unit which share the same name. For backwards compatibility, some number/file name extensions are treated specially: 1. `.hs` files compile to `.hi` (implicitly numbered 0) 2. `.hs-boot` files compile to `.hi-boot` (implicitly numbered 1) 3. `.hsig` files compile to `.hi-boot` (implicitly numbered 1) 4. `.n.hsig` files compile to `.n.hi-boot` (numbered n, where n is greater than 1) **Flex point:** We could give `.hsig` files their own file extension for interface files; just would require some more work to distinguish between `hs-boot` and `hsig` as well as record the numbering. To import, the `{-# SOURCE n #-}` pragma can be used (with `{-# SOURCE #-}` being equivalent `{-# SOURCE 1 #-}`.) Inline Backpack files can omit numbering, since we can figure it out based on the ordering of declarations (numbering in REVERSE order of occurrence). Example 2 can be numbered as follows: {{{ signature {-# SOURCE 2 #-} A signature {-# SOURCE 1 #-} B where import {-# SOURCE 2 #-} A ... signature {-# SOURCE 1 #-} A where import {-# SOURCE 1 #-} B ... }}} === Internal consequences === In many places in the code today, we record a boolean indicating if we depended on the boot interface `hi-boot` or the normal interface `hi`. We now replace this marker with an integer which records the numbering. The primary affected components are dependency recording in interfaces, interface loading code in GHC, and the implementation of `--make`. === Interaction with signature merging === Unlike `hs-boot` files, `hsig` files can be included from external units, in which case the semantics are that all signatures in scope are merged together. The key rule is that we **generate an hi file for each partial merge**; this means that whenever we want to typecheck a module, there is exactly one interface file per module we import. Consider this example: {{{ unit a-sig where signature A unit a-sig2 where signature A unit p where include a-sig module B include a-sig2 module C signature A module D }}} When compiling this, we generate four interface files for `A`: {{{ unit p where include a-sig -- Produces A.3.hi-boot (a-sig) module B -- uses A.3.hi-boot include a-sig2 -- Produces A.2.hi-boot (a-sig + a-sig2) module C -- uses A.2.hi-boot signature A -- Produces A.hi-boot (everything) module D -- uses A.hi-boot -- At the end, A.hi-boot copied to A.hi to be publically visible }}} == Can we do anything simpler? == There are a few barriers to doing something simpler: 1. We can avoid generating extra interface files if we instead merge them on-the-fly when we use them. However, this forces later instances of GHC to do repeated work remerging interface files, so it seems desirable from a performance perspective to merge before writing. Another scheme is that we could merge on use for signatures in the home package, and then write out a unified file at the very end, trading off performance for less written interface files. 2. The Backpack language is defined in a way that allows modules, signatures and includes to be ordered in a semantically meaningful way. For example: {{{ unit q where signature M signature A where f :: Int -> Int ... unit p where signature A where data T module M where import A -- should get T but not f ... include q -- fill in M module S where import A -- should get T and f }}} This means that even within a unit, the interface of a signature file may differ. We could rule this out, but we would have to work out how to explain this limitation to users. (For example, we could solve the example above by saying that units which define modules do not bring their signatures into scope for a package which imports them; but this is a pretty ad hoc rule! And you still have to deal with repeated signatures, or a signature importing a module importing a signature. There are a lot of cases.) 3. This problem cannot be avoided at all if you are truly doing recursive modules, since you need the intermediate interface file to do compilation at all prior to getting the real implementation. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 02:00:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 02:00:05 -0000 Subject: [GHC] #10663: ghci ignores stuff after an import command and a semicolon In-Reply-To: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> References: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> Message-ID: <062.92c5818cbbb5700cf63353ea15ce6980@haskell.org> #10663: ghci ignores stuff after an import command and a semicolon -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) Comment: I'm trying to understand expected syntax here. It seems like I can only put expressions after the first semicolon, other GHCi commands don't work: {{{ ?:6> import Data.List; x; x + y ?:7> import Data.List; import Data.Char : parse error in import declaration ?:8> let x = 10 ?:9> x; x; x :9:2: parse error on input ?;? ?:10> let y = 10; y :10:14: parse error (possibly incorrect indentation or mismatched brackets) ?:11> import Data.Char; x ?:12> }}} Also, I can't see anything related with semicolons in user manual "Using GHCi" section(https://downloads.haskell.org/~ghc/latest/docs/html/users_guide /interactive-evaluation.html) so it seems to me like this semicolon behavior is not intended and just a side effect of the used parser. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 02:02:03 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 02:02:03 -0000 Subject: [GHC] #10663: ghci ignores stuff after an import command and a semicolon In-Reply-To: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> References: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> Message-ID: <062.01d77b0266bcf37228a0235ce6977c03@haskell.org> #10663: ghci ignores stuff after an import command and a semicolon -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Right, I think the expected behavior here (at least given the current behavior of ghci with respect to semicolons generally) is for `import Data.List; x` to be a syntax error of some kind. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 02:34:57 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 02:34:57 -0000 Subject: [GHC] #10678: integer-gmp's runS seems unnecessarily expensive In-Reply-To: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> References: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> Message-ID: <062.b7bf0447ad8b9c90ec1108014419c49a@haskell.org> #10678: integer-gmp's runS seems unnecessarily expensive -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I note that bytestring and text have the same issue (using `unsafeDupablePerformIO` and `runSTRep` respectively in the role of `runS`) so this may be a known problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 02:53:54 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 02:53:54 -0000 Subject: [GHC] #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings In-Reply-To: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> References: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> Message-ID: <064.9f06e0411fdded97204a66f140c6a913@haskell.org> #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings -------------------------------------+------------------------------------- Reporter: rpglover64 | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: partial- crash | sigs/should_compile/T10438 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rpglover64): If my `git bisect` was correct, the patch that fixes the problem is https://git.haskell.org/ghc.git/commitdiff/28299d6 "Always generalise a partial type signature". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 03:04:59 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 03:04:59 -0000 Subject: [GHC] #3549: unlit does not follow H98 spec In-Reply-To: <045.eacb9764be0b8b701a8c620148ff0200@haskell.org> References: <045.eacb9764be0b8b701a8c620148ff0200@haskell.org> Message-ID: <060.c61059740b9621116a358e8c458b64d5@haskell.org> #3549: unlit does not follow H98 spec -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: bug | Status: new Priority: normal | Milestone: ? Component: Compiler | Version: 6.10.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by lenish): I recently ran into this bug when trying to learn Haskell. I always indent my LaTeX blocks to improve readability, but that doesn't work properly with unlit. The readline function handles prefixed whitespace properly. It's when we get to checking for `\end{code}` after `\begin{code}` that things break. The file I'm working with: {{{ \documentclass[12pt]{article} \begin{document} \maketitle \section{Type Declaration} \begin{code} data Thingy = Thing \end{code} \end{document} }}} Unfortunately, from the original report, it sounds as though the specification requires these lines to not be indented? Being new to Haskell & GHC I've no idea how to go about changing things like that or if such a change is possible. My general impression is that the 'correct' way to do this would be to parse the file, locate `\begin{code}` and `\end{code}` sections that TeX would treat as such (not in comments, etc), and then strip out everything but those blocks. That it does not work this way currently makes this feature way less enticing to me, as I won't be able to create maintainable and readable LaTeX files without proper indentation. If there were a desire for this to be reimplemented in Haskell with proper (or a reasonable approximation of proper) TeX parsing then I wouldn't mind trying to figure out how to do that as part of my learning how to program in Haskell project. Again, not sure what the situation is with the specification or even if such a patch would be accepted? I have a relatively simple, hacky patch which prevents leading whitespace from causing `\end{code}` to fail to match. I also modified the PSEUDOCODE section, as it seems to have the same issue. There may be issues with this patch in the event someone had a 1000 character line, but that seems... excessive. {{{#!diff diff --git a/utils/unlit/unlit.c b/utils/unlit/unlit.c index a367a0a..dff43bc 100644 --- a/utils/unlit/unlit.c +++ b/utils/unlit/unlit.c @@ -273,7 +273,15 @@ void unlit(char *file, FILE *istream, FILE *ostream) exit(1); } linesread++; - if (strncmp(lineb,ENDCODE,LENENDCODE) == 0) { + + size_t offset = 0; + for(offset = 0; offset < sizeof lineb; ++offset) { + if (!isWhitespace(lineb[offset])) { + break; + } + } + + if (strncmp(&lineb[offset],ENDCODE,LENENDCODE) == 0) { myputc('\n', ostream); break; } @@ -289,9 +297,17 @@ void unlit(char *file, FILE *istream, FILE *ostream) complain(file, linesread, MISSINGENDPSEUDOCODE); exit(1); } + + size_t offset = 0; + for(offset = 0; offset < sizeof lineb; ++offset) { + if (!isWhitespace(lineb[offset])) { + break; + } + } + linesread++; myputc('\n', ostream); - if (strncmp(lineb,ENDPSEUDOCODE,LENENDPSEUDOCODE) == 0) { + if (strncmp(&lineb[offset],ENDPSEUDOCODE,LENENDPSEUDOCODE) == 0) { break; } } }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 03:11:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 03:11:39 -0000 Subject: [GHC] #10677: slightly silly assembly for testing whether a Word# is 0## In-Reply-To: <047.666ef36ac1cc91ac56611c092c7fbb22@haskell.org> References: <047.666ef36ac1cc91ac56611c092c7fbb22@haskell.org> Message-ID: <062.bb1147594bc8bccdbadf527f12ad367a@haskell.org> #10677: slightly silly assembly for testing whether a Word# is 0## -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 (CodeGen) | Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * keywords: => newcomer Comment: This is probably pretty easy to fix as a special case in the Cmm switch->branches code. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 03:42:59 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 03:42:59 -0000 Subject: [GHC] #10673: GHCi crashes when decoding with Aeson In-Reply-To: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> References: <044.df9d52797d9f846d1b0250579748cef7@haskell.org> Message-ID: <059.d9373c8a697667740d9d13b4e306ce18@haskell.org> #10673: GHCi crashes when decoding with Aeson -------------------------------+----------------------------------------- Reporter: orion | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: GHCi | Version: 7.8.3 Resolution: wontfix | Keywords: Operating System: FreeBSD | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by rwbarton): I see. There are two patches to aeson there, one to relax the version bound on attoparsec and one to add whatever functionality is missing in the old version. I tried building all these versions together with these patches applied (on a Linux machine) and they built successfully and unsurprisingly did not segfault when I tried your example. I didn't check whether any other packages among these had patches in ports. I wonder if the segfault would go away if you just rebuilt all the libraries... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 03:52:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 03:52:47 -0000 Subject: [GHC] #10680: Make Backpack order-independent (again) Message-ID: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> #10680: Make Backpack order-independent (again) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package | Version: 7.11 system | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- When we moved to the new `bkp` file format, we also went back to the a format which is order-dependent: that is to say, the order in which you put the declarations matters. So if you write: {{{ unit p where module A where import B module B where ... }}} this fails to type-check, GHC complaining that `B` is not in scope. I did this, in part because it's what the Backpack paper described, and because it was "simpler" to implement. I think we should move back to an order-independent scheme, for the following reasons: 1. Haskell users are used to not needing pay particularly close attention to the ordering of their modules, and forcing people to linearize their module descriptions would be spectacularly disruptive with large amounts of modules. So un-ordered modules are "more natural. 2. Order-independence imposes some constraints on how expressive programs are (with order-dependent Backpack, you can do some pretty tricky things by ordering things certain ways); this could simplify some aspects of compiler implementation and make Backpack easier to explain. 3. A particular case of (2): it seems a lot simpler UX-wise to let a user assume that if you import a module `M` in a unit, it doesn't matter where you import it: you always get the same set of identifiers brought into scope. Thus, the incremental results of signatures should not be visible, c.f. #10679 The main idea is that only the surface-syntax is un-ordered: the internal representation of units is a DAG which we work out in an elaboration phase, not altogether unsimilar from what `GhcMake` computes. Here are the details: **The intermediate representation.** We translate into an intermediate representation which consists of a directed graph between modules, signatures and includes. Edges in the graph indicate a "depends on" relation: 1. `include p` depends on `include q` if, for some module name `H`, `p` requires `H` and `q` provides `H`. 2. A module/signature `M` depends on `include p` if `M` imports a module provided or required by `p`. 3. A module/signature `M` depends on a module/signature `S` if `M` imports `S`. 4. An `include p` depends on a module `M` if `p` requires a module named `M`. (This rule is included for completeness; we are going to disallow it shortly.) We impose one restriction: a signature cannot depend on a home module. See below for how to eliminate this restriction. Rule (2) is worth remarking upon: if a module imports a signature, it depends-on every `include` which requires that signature, as well as the relevant home signature. This could easily result in a cycle; see (2) for how to break these cycles. The consequence of this, however, is that we can factor the graph to introduce the node for the "merge of signatures", which depends on each signature and include which requires it; we can use this opportunity to build and write out the merged interface file for the unit. **Elaboration.** Take a Backpack file, construct this graph, and topsort it into a DAG of SCCs. SCCs with a single node are compileable as before. SCCs with multiple nodes will have to be managed with some mutual recursion mechanism; see refinements for more thoughts on this. **Refinements:** 1. **Can a signature depend on a (home) module?** Imports of this kind require a retypecheck loop. Consider this situation: {{{ unit p where signature H where data T module M where import H data S = S T unit q where include p module Q where import M signature H where import Q data T = T S }}} Here, signature H in q depends on Q. When we typecheck `Q`, we bring `M.S` into the type environment with a `TyThing` that describes the constructor as accepting an abstract type `T`. However, when we subsequently typecheck the local signature `H`, we must refine all `TyThing`s of `T` with the true description (e.g. constructor information). So you'll need to retypecheck `Q` (and `M`) in order to make sure the `TyThing` is correct. 2. **Can an include depend on a (home) module?** If the module has no (transitive) dependency on signatures, this is fine. However, it's easy to have a circular dependency. Consider: {{{ unit p where signature A signature B module M unit q where include p module B where import A ... }}} `B` depends on `p` for `p/A.hsig`; however, `p` depends on `B` because this module is filling a requirement. Fortunately, we can untangle this knot without any mutual recursion nonsense (and the attendant efficiency loss): `A` is just an export list, we can compute it from the abstractly type-checked version of `p` without instantiating `B`. 3. **Can we deal with include-include dependency cycles?** Yes! Just use the Backpack paper's strategy for creating a recursive unit key and compile the two packages `hs-boot` style. But I'm not planning on implementing this yet. 4. **Can we deal with signature-signature dependency cycles?** Ordered Backpack would have supported this: {{{ unit a-sig where signature A where data T unit ab-sig where include a-sig signature B where import A data S = S T signature A where import B data T = T S }}} In our model, `ab-sig` has a cycle. However, I believe any such cycle can be broken by creating sufficiently many units: {{{ unit a-sig where signature B where data T signature A where data S = S T unit b-sig where signature A where data S signature B where data T = T S unit ab-sig where include a-sig include b-sig }}} In principle, GHC could automatically break import cycles by replacing an import with an import of a reduced signature that simply has abstract type definitions. (I'm not sure this is possible for all language features.) This technique would also work for normal modules, assuming that every function is explicitly annotated with a type. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 04:15:23 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 04:15:23 -0000 Subject: [GHC] #9256: Support automatic derivation of an hs-boot file from an hs file In-Reply-To: <045.8b36d4401d2cf222c4ddb4c787a0a219@haskell.org> References: <045.8b36d4401d2cf222c4ddb4c787a0a219@haskell.org> Message-ID: <060.e96b5d211400f39079515371f06f1b46@haskell.org> #9256: Support automatic derivation of an hs-boot file from an hs file -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: invalid | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => closed * resolution: => invalid Comment: I'm going to terminate this proposal: the crux of the issue is that you really do want the imports of the new hs-boot file to be computed automatically. I think I have a way to deal with this, but it really is a different proposal. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 04:48:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 04:48:06 -0000 Subject: [GHC] #10681: Teach GHC to interpret all hs files as two types of hs-boot files (abstract types only/full types + values) Message-ID: <045.0dac7803547af5ada3f670c588d36854@haskell.org> #10681: Teach GHC to interpret all hs files as two types of hs-boot files (abstract types only/full types + values) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This is a new proposal for solving #1409. The big addition here is that we create **two** hs-boot files for each hs file: one that is a full hs-boot file to be imported by hs files to break loops, and a second which only includes abstract types for hs-boot files to import. C.f. #10679 **Discussion.** Here is a slightly goofy `hs-boot` file I've excerpted from GHC: {{{ module Packages where import {-# SOURCE #-} Module (PackageKey) import {-# SOURCE #-} DynFlags (DynFlags) packageKeyPackageIdString :: DynFlags -> PackageKey -> Maybe String }}} The `hs-boot` file must itself import `hs-boot` files, because this boot file is used by `Module` and `DynFlags`; without `{-# SOURCE #-}`, the boot file itself will participate in a cycle! But notice that there is something very interesting: a boot file is ONLY ever interested in importing other modules to get types. Never to import constructors or functions! We can use this observation to give us a mechanical transformation of an `hs` file to an `hs-boot` file, ASSUMING we can define a "second level" of `hs-boot` file to record our abstract types. **Example.** In this example, we have chosen to break the loop from `A`s import to `B`. {{{ module A where import {-# SOURCE #-} B data A = A B f :: A -> Bool f (A (B (A b))) = g b f _ = True module B where import A data B = B A g :: B -> Bool g (B (A (B b))) = f b g _ = False }}} The first-level `hs-boot`s are: {{{ module A where -- not actually used import {-# SOURCE 2 #-} B data A = A B f :: A -> Bool module B where import {-# SOURCE 2 #-} A data B = B A g :: B -> Bool }}} The second-level `hs-boot`s are: {{{ module A where data A module B where -- not actually used data B }}} **Commentary.** Here are some remarks: 1. Because we have to lift the transitive dependencies of anything we `{-# SOURCE #-}` import, it doesn't make sense to have a pragma which explicitly says what to put in the `hs-boot` file; instead, we just put in everything that we *can* handle in an `hs-boot` file (so exclude anything with missing type signatures, type families, etc.) Ideally, these automatic hs-boot files are generated lazily, but they should be reused as necessary. 2. This facility actually makes `{-# SOURCE #-}` a lot more attractive for increasing separate compilation: you can mark an import `{-# SOURCE #-}` to ensure that if its implementation changes, you don't have to recompile this module / you can build the module in parallel with that module. The downside is that when the imported file is modified, we have to regenerate the `hs-boot` stub before we conclude that the types have not changed (as opposed to with separate `hs-boot` files, where a modification to `hs` would not bump the timestamp on `hs-boot`. 3. This seems to definitely suggest that you should never need more than two levels of hs-boot nesting, or perhaps three with kinding. (But maybe someone has a fancy type system feature for which this is not true!) Maybe this applies to signature files too. 4. We can't force the first level of `hs-boot` files to be abstract types, for two reasons: (1) a source file importing the hs-boot file may really need the selector/constructor, and (2) the `hs-boot` files will reflect any cycles from the source files, that's no good! Rolling out to the second level breaks the cycle because abstract types never need any imports. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 04:48:28 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 04:48:28 -0000 Subject: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything) In-Reply-To: <051.8a467503f7e6e3ea87602b7d1c1e067f@haskell.org> References: <051.8a467503f7e6e3ea87602b7d1c1e067f@haskell.org> Message-ID: <066.37377def21bc0ece02c2bd057a37af69@haskell.org> #1409: Allow recursively dependent modules transparently (without .hs-boot or anything) -------------------------------------+------------------------------------- Reporter: Isaac Dupree | Owner: Type: feature request | Status: new Priority: normal | Milestone: ? Component: Compiler | Version: 6.10.2 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9256 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Hi guys, I have another proposal for how to fix this: #10681 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 04:50:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 04:50:20 -0000 Subject: [GHC] #10681: Teach GHC to interpret all hs files as two levels of hs-boot files (abstract types only/full types + values) (was: Teach GHC to interpret all hs files as two types 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.869102e99017c855402d67d9a4c99263@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 04:52:52 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 04:52:52 -0000 Subject: [GHC] #10679: Generalize hi-boot/hi for signatures, to manage intermediate merged interfaces In-Reply-To: <045.12de5382940d37915572908b5eadd02a@haskell.org> References: <045.12de5382940d37915572908b5eadd02a@haskell.org> Message-ID: <060.8e99007ea822c13ee423ced6d5240f4f@haskell.org> #10679: Generalize hi-boot/hi for signatures, to manage intermediate merged interfaces -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: closed Priority: normal | Milestone: Component: Package system | Version: 7.11 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * status: new => closed * resolution: => invalid Comment: I've decided that this proposal as a whole is a bad idea. But there are some good ideas which I've recorded separately at #10681 and #10680. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 05:12:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 05:12:02 -0000 Subject: [GHC] #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) Message-ID: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: aarch64 | Type of failure: Building GHC | failed Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Some time in the last week, GHC Git HEAD started to fail to build with: {{{ dll-split: out of memory (requested 1099512676352 bytes) compiler/ghc.mk:655: recipe for target 'compiler/stage2/dll-split.stamp' failed }}} Obviously, attempting to allocate a terrabyte is not going to work. Will try to git bisect. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 05:15:30 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 05:15:30 -0000 Subject: [GHC] #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) In-Reply-To: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> References: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> Message-ID: <059.30e83548601316708905129ffc948d67@haskell.org> #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) ----------------------------------------+---------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: aarch64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ----------------------------------------+---------------------------------- Comment (by erikd): The value `1099512676352` on hex is `0x10000100000`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 05:22:52 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 05:22:52 -0000 Subject: [GHC] #9706: New block-structured heap organization for 64-bit In-Reply-To: <045.a63dcd9ee3561b6e809272c4a2e2bc36@haskell.org> References: <045.a63dcd9ee3561b6e809272c4a2e2bc36@haskell.org> Message-ID: <060.e50c210d808d36465e5b92ddb5787af3@haskell.org> #9706: New block-structured heap organization for 64-bit -------------------------------------+------------------------------------- Reporter: ezyang | Owner: gcampax Type: task | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 7.8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D524 -------------------------------------+------------------------------------- Changes (by rwbarton): * differential: D524 => Phab:D524 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 05:26:48 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 05:26:48 -0000 Subject: [GHC] #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) In-Reply-To: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> References: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> Message-ID: <059.6047888408c76173da97587030e9ca83@haskell.org> #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) ----------------------------------------+---------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: aarch64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ----------------------------------------+---------------------------------- Comment (by rwbarton): Oh, it's probably Phab:D524 (#9706) then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 07:15:41 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 07:15:41 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking In-Reply-To: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> References: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> Message-ID: <060.c60d06ab44322bc7f8dc7c8ac442d99b@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #9297 #10563 | Differential Revisions: #8237 #9907 | -------------------------------------+------------------------------------- Comment (by lukexi): I'm able to get by the crash by commenting out the first call to {{{checkProddableBlock}}} in {{{ocResolve_PEi386}}} https://github.com/ghc/ghc/blob/master/rts/Linker.c#L4696. I'm not sure how to translate that into a proper fix yet ??does that give anyone familiar with the linker any clues? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 07:58:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 07:58:35 -0000 Subject: [GHC] #3549: unlit does not follow H98 spec In-Reply-To: <045.eacb9764be0b8b701a8c620148ff0200@haskell.org> References: <045.eacb9764be0b8b701a8c620148ff0200@haskell.org> Message-ID: <060.34c6394c3affaebf58da7e4bbfe37f23@haskell.org> #3549: unlit does not follow H98 spec -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: bug | Status: patch Priority: normal | Milestone: ? Component: Compiler | Version: 6.10.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 08:09:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 08:09:39 -0000 Subject: [GHC] #10663: ghci ignores stuff after an import command and a semicolon In-Reply-To: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> References: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> Message-ID: <062.2de45511b25e89ae635c373e8460d9c7@haskell.org> #10663: ghci ignores stuff after an import command and a semicolon -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Fwiw, you can use the semicolon to set fixities: {{{ > let add = (+); infixl 6 `add` }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 09:16:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 09:16:58 -0000 Subject: [GHC] #10678: integer-gmp's runS seems unnecessarily expensive In-Reply-To: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> References: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> Message-ID: <062.783fd405ca1d88da57584c28a7cc6948@haskell.org> #10678: integer-gmp's runS seems unnecessarily expensive -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Reid, indeed it is known: #5916. (If you find any other tickets about this, please add them.) I think the best approach would be as in comment:16 of ticket:5916#comment:16 * '''Inline `runS` very late, in `CorePrep`''' Some thoughts about this. * We'd want a single, magical function which has this behaviour. Things like `unsafeDupablePerformIO` should call `runS`. * Now I think about it, I wonder if the magical function should instead be this: {{{ runRW# :: (State# s -> (# State s, a)) -> (# State s, a #) {-# NOINLINE runRW# #-} runRW# f = f realWorld# }}} That is, all `runRW#` does is to apply its argument to a fresh state token. Now we can define your `runS` thus: {{{ runS f = case ruNRW# f of (# _, r #) -> r }}} I think we can inline `runS` freely, which is good because it means that more code is exposed to the optimiser (in particular that `case`). * Moreover, if we do this, I think we now don't need `lazy`. Because `runRW#`'s strictness signature won't be strict in the `r` part; see `Note [unsafeDupablePerformIO has a lazy RHS]` in `GHC.IO`. * If `CorePrep` saw `runRW# (f a b)` it can generate `f a b realWorld#`. But if it sees `runRW# (\s.e)`, it should generate `e[realWorld#/s]`. That is, it should do the beta-reduction on the fly. That's slightly annoying because `CorePrep` doesn't currently carry around a substitution. But I suppose that you could literally call `substExpr`; this doesn't happen much. * Alternatively maybe this could be done in the code generator, effectively treating `runRW` as a primop. That would be a good plan, except that by the time we get to STG the program is in ANF, so instead of `runRW# (f a b)` we'd have {{{ let g = f a b in ruNRW# g }}} and before we see the `runRW#` we'll have generated code to allocate a closure for `g`. So we'd need to allow STG syntax (for specified primops) to have expressions, not just atoms, as the arguments to the primop. This might actually be a Jolly Good Thing. At the moment `catch# (\s -> e1) (\x s -> e2)` allocates two closures before it gets to the `catch#`, which is pretty stupid since the first thing we do after pushing the exception-catch frame is to execute `e1`. I think changes like this would make modest but significant improvements to many programs. If you'd like to dig into it, I'd gladly help. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 09:50:40 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 09:50:40 -0000 Subject: [GHC] #5916: runST isn't free In-Reply-To: <044.d958bab6cdf04501b440e190747a91b9@haskell.org> References: <044.d958bab6cdf04501b440e190747a91b9@haskell.org> Message-ID: <059.17a946d51e3fff2d422d4d3e96cd8355@haskell.org> #5916: runST isn't free -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): See also #10678 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 10:00:21 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 10:00:21 -0000 Subject: [GHC] #10683: Haare schneller wachsen lassen mit Hair Vox Message-ID: <051.287e485be985ad8cd2f81a51ab7f423b@haskell.org> #10683: Haare schneller wachsen lassen mit Hair Vox -------------------------------------+------------------------------------- Reporter: | Owner: schulzwinter | Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Hair Vox ? Hair growth und Anti-Hairloss Spray Durch Hair Vox gibt es endlich das Produkt, welches den Haarausfall ein Ende setzt und neuen Haarwuchs in Gang setzt. Durch die raffinierte Kombination von Anti-Haarausfall-Tabletten plus einem aktivierenden Spray wird erm?glicht, innerhalb von nur 4 Monaten zu dichtem sowie sch?nerem Haar zu gelangen, ohne dabei Haartransplantationen machen zulassen. Die Produktkombination ist dadurch der simpelste und sicherste Weg, die Probleme mit dem Haarwuchs in den Griff zu bekommen. Der Gebrauch von [http://www.beauty-health-produkte.com/hair-vox-selbsttest/ Hair Vox] schont auf diesem Weg auch den Geldbeutel. Das Mittel beinhaltet nur Natur-basierte Inhaltsstoffe, dessen Erfolge klinisch bewiesen ist. Eine Zusammenstellung der Wirksubstanzen bringen optimalen Haarwuchs. Hair Vox Erfahrungen Falls man ausreichend im WWW nachschaut, sind haufenweise ?beraus positiven Berichten ?ber die Produkte zu finden, die alle einen wiedererlangten Haarwuchs beschreiben. Die [http://www.beauty-health- produkte.com/ Hair Vox Erfahrungen] zeigen, dass augenscheinlich innerhalb von nur ein paar Monaten das Haar zur G?nze nachw?chst und ?berhauptkeine kahlen Stellen mehr zu sehen sind. Das Resultat ist ?beraus ansehnlich. Dazu hilft das Produkt M?nnern und Frauen gleicherma?en. Die Verbraucher sind sehr froh, dass dieses Produkt so effektiv aber trotzdem sanft wirkt. W?hrend des Anwendens berichten viele ?ber ein Hautkribbeln, dass den beginnenden Haarwuchs bezeichnet. Ab da a kann der Anwender buchst?blich beim Wachsen der Haare zugucken. Hair Vox Wirkung und Hair Vox Inhaltsstoffe Das Erfolgsgeheimnis hinter dem Produkt ist ein Eiwei?-Komplex, welcher von Fischen aus der Tiefsee stammt. Solche Tierarten sind wahre K?nstler des rasanten Zellwachstums und haben die F?higkeit alle Teile ihres K?rpers flink zu reparieren. Dieses einzigartige Merkmal wurde nun auf den Menschen ?bertragen. Haarausfall und kahle Stellen sind ein Zeichen von sterbenden Follikeln, die zuvor f?r das Bilden von Haaren zust?ndig sind. Durch die Tiefsee-Eiwei?e werden unsere Haarfollikel wieder belebt und k?nnen dann neue Haare wachsenlassen. Daneben sind noch andere Stoffe wie z.B. Aminos?uren und Vitamin-B-Komplexe. Das Zusammenwirken dieser Stoffe regt das Haarwachstum au?erordentlich an und verleiht den Menschen sch?nes Haar. Hair Vox Test Unser eigener Hair Vox Test konnte die extremen Ergebnisse sogar best?tigen. Es wurde bewiesen, dass innerhalb des beschriebenen Zeitfensters alle Haare sichtbar wachsen und nicht eine von den kahlen Stellen ?brig bleiben. Unser Tester war wahnsinnig ?berzeugt von der wundervollen Wirkung des Haarwuchsmittels und ist heute stolzer Besitzer einer ?ppigen Frisur. Ein weiterer und lobenswerter Bonuspunkt f?r das Produkt ist, dass mit Hair Vox Nebenwirkungen komplett ausbleiben. Damit ist dieses Haarwuchsprodukt gesund anwendbar. Unsere Testperson hat Hair Vox ?ber 2 Wochen genommen und ist bereits kaum wiedererkennbar. Man kann meinen, die Person h?tte eine Transplantation machen lassen, doch war es blo? ein g?nstiges Haarwuchsmittel, das die Haare spriessen l?sst. Hair Vox kaufen Zu der Frage, wie man am billigsten Hair Vox kaufen kann, gibt es nur eine Antwort: direkt bei dem Hersteller. Dort ist das Haarwuchsprodukt am billigsten und ab und zu findet man dort sogar einen Hair Vox Rabatt. Der Produkthersteller ist sehr vertrauensw?rdig und kommt den K?ufern sehr entgegen. Sein Versprechen, durch das Mittel den Haarwuchs um ?ber 61,2 Prozent zu optimieren, wird eingehalten und erweist sich als wahrheitsgem??e Angabe. Sollte die Behandlung widererwarten keinen Erfolg bringen, kommt der Verk?ufer dem Kunden mit der Hair Vox Geld-zur?ck- Garantie entgegen, durch welche bei Unzufriedenheit mit Hair Vox der komplette Kaufpreis zur?ck gegeben werden kann. Wurde Hair Vox erfolgreich bestellt, dauert es nur 2 bis 5 Tage, bis es geliefert wird. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 10:14:43 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 10:14:43 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.db311110a2c4c819d0c3b99001064d24@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: jstolarek (added) Comment: CC jstolarek as the author of [wiki:PrimBool]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 11:30:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 11:30:56 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.64485a8841a76d03bc357fbbbbfca438@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"d53d80890f2762b78071f5d53c88dc9e6c0ca72e/ghc" d53d8089/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="d53d80890f2762b78071f5d53c88dc9e6c0ca72e" Refactoring around FunDeps This refactoring was triggered by Trac #10675. We were using 'improveClsFD' (previously called 'checkClsFD') for both * Improvement: improving a constraint against top-level instances * Consistency: checking when two top-level instances are consistent Using the same code for both seemed attractive at the time, but it's just too complicated. So I've split it: * Improvement: improveClsFD * Consistency: checkFunDeps Much clearer now! }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 13:09:13 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 13:09:13 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.be9a3da2e8480d07213baede7efed775@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): I think you are essentially seeing #8326. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 13:30:56 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 13:30:56 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text (was: compile time performance regression on big literal) In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.4975570a75b327d353098cf4a72453b5@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => high * version: => 7.10.2-rc2 * milestone: => 7.10.3 Comment: I can reproduce this with the test below. Compiling with `7.10.2` takes more than 10x longer than with `7.10.1`. {{{ {-# LANGUAGE OverloadedStrings #-} module T10528 where import Data.Text (Text) strings :: [Text] strings = [ "abstime", "aclitem", "bit", "bool", "box", "bpchar", "bytea", "char", "cid", "cidr", "circle", "date", "float4", "float8", "gtsvector", "inet", "interval", "json", "jsonb", "line", "lseg", "macaddr", "money", "name", "numeric", "oid", "oidvector", "path", "pg_lsn", "pg_node_tree", "point", "polygon", "refcursor", "regclass", "regconfig", "regdictionary", "regoper", "regoperator", "regproc", "regprocedure", "regtype", "reltime", "smgr", "text", "tid", "time", "timestamp", "timestamptz", "timetz", "tinterval", "tsquery", "tsvector", "txid_snapshot", "unknown", "uuid", "varbit", "varchar", "xid", "bit", "bool", "box", "bpchar", "bytea", "char", "cid", "cidr", "circle", "date", "float4", "float8", "gtsvector", "inet", "int2", "int2vector", "int4", "int8", "interval", "json", "jsonb", "line", "lseg", "macaddr", "money", "name", "numeric", "oid", "oidvector", "path", "pg_lsn", "pg_node_tree", "point", "polygon", "refcursor", "regclass", "regconfig", "regdictionary", "regoper", "regoperator", "regproc", "regprocedure", "regtype", "reltime", "smgr", "text", "tid", "time", "timestamp", "timestamptz", "timetz", "tinterval", "tsquery", "tsvector", "txid_snapshot", "unknown", "uuid", "varbit", "varchar", "xid", "xml" ] }}} {{{ $ cabal install text $ ghc-7.10.1 T10528.hs -c -fforce-recomp -Rghc-timing -O < $ ghc-7.10.2 T10528.hs -c -fforce-recomp -Rghc-timing -O <> }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 14:27:46 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 14:27:46 -0000 Subject: [GHC] #10680: Make Backpack order-independent (again) In-Reply-To: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> References: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> Message-ID: <060.f960b0713e811e3052da1028219795d0@haskell.org> #10680: Make Backpack order-independent (again) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package system | 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 Revisions: -------------------------------------+------------------------------------- Changes (by skilpat): * cc: skilpat (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 14:28:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 14:28:02 -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.c726342fb1a5771075f30e84df0a1c88@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by skilpat): * cc: skilpat (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 14:33:50 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 14:33:50 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.2169ca06ec7716e8dcd7c4a43bcce147@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, I had somehow missed this one. Let me have a look. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 14:34:11 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 14:34:11 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.1dd20eba885a84dfdd52a44f740d4c52@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * owner: => bgamari -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 15:53:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 15:53:44 -0000 Subject: [GHC] #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings In-Reply-To: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> References: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> Message-ID: <064.2d8e219e3f962d48b02a76ef085a002f@haskell.org> #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings -------------------------------------+------------------------------------- Reporter: rpglover64 | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: partial- crash | sigs/should_compile/T10438 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rpglover64): It seems like cherry picking said patch onto the ghc-7.10 branch fixes the bug (running tests locally now to make sure it doesn't break anything else), but I don't know what the correct workflow is in this case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:09:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:09:20 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.de5abeeb770410b3ecb984e26bb50767@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): The program gets substantially larger after the first simplifier pass in 7.10.2: while in 7.10.1 it always stays around 1000 terms or less, in 7.10.2 it grows to 40000 terms at its peak. The issue is reproducible on the `master` branch as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:23:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:23:36 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.6ba7ddc2a2254ca9d07a91abe6470e98@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): It appears that inlining is occurring where there previously was none. For instance, each top-level bindings under 7.10.1 produces (in `-ddump- simpl`), {{{#!hs T10528.strings181 :: Text [GblId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 50 0}] T10528.strings181 = text-1.2.1.1:Data.Text.Show.unpackCString# "abstime"# }}} Whereas in 7.10.2 we get this, {{{#!hs T10528.strings_dt62 :: [Char] [GblId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 50 0}] T10528.strings_dt62 = unpackCString# "abstime"# Rec { -- RHS size: {terms: 220, types: 125, coercions: 9} T10528.strings476 [InlPrag=[0], Occ=LoopBreaker] :: forall s1_a3V7. Data.Text.Array.MArray s1_a3V7 -> Int -> [Char] -> Int# -> State# s1_a3V7 -> (# State# s1_a3V7, Text #) [GblId, Arity=5, Str=DmdType ] T10528.strings476 = ... end Rec } -- RHS size: {terms: 2, types: 0, coercions: 0} T10528.strings121 :: Int [GblId, Caf=NoCafRefs, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] T10528.strings121 = I# 4# -- RHS size: {terms: 14, types: 15, coercions: 0} T10528.strings475 :: forall s1_a3V7. State# s1_a3V7 -> (# State# s1_a3V7, Text #) [GblId, Arity=1, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [0] 83 0}] T10528.strings475 = \ (@ s1_a3V7) (s2_a3V8 [OS=OneShot] :: State# s1_a3V7) -> case newByteArray# @ s1_a3V7 8# s2_a3V8 of _ [Occ=Dead] { (# ipv_a3Vu, ipv1_a3Vv #) -> T10528.strings476 @ s1_a3V7 (Data.Text.Array.MArray @ s1_a3V7 ipv1_a3Vv) T10528.strings121 T10528.strings_dt62 0# ipv_a3Vu } -- RHS size: {terms: 2, types: 1, coercions: 0} T10528.strings474 :: Text [GblId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 20 0}] T10528.strings474 = runSTRep @ Text T10528.strings475 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:26:13 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:26:13 -0000 Subject: [GHC] #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings In-Reply-To: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> References: <049.41b7d0833f2869d11544c1b4baf6f0c5@haskell.org> Message-ID: <064.af687ad4da2bcbf494a6787a32a4cad6@haskell.org> #10438: GHC 7.10.1 panic due to PartialTypeSignatures, TypeFamilies, and local bindings -------------------------------------+------------------------------------- Reporter: rpglover64 | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Compile-time | Test Case: partial- crash | sigs/should_compile/T10438 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: I'll change status to merge, so that if we do 7.10.3 it'll get in. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:31:09 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:31:09 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.3e8ec341c1bbb683748e4e9099653b20@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): In both 7.10.1 and 7.10.2 the following simplifications occur (in chronological order), * First 7.10.1 and 7.10.2 both inline `Data.Text.$fIsStringText` and `Data.String.fromString` (something like once for each binding) * In the next simplifier run they both inline `GHC.Base.build` and `GHC.Base.pack` (again, something like once per binding) * In the next simplifier iteration 7.10.1 does no inlining. 7.10.2, however, keeps going, inlining `Data.Text.Internal.Fusion.unstream`, `Data.Text.Internal.Fusion.Common.map`, `Data.Text.Internal.Fusion.Common.streamList`, `Data.Text.Internal.safe`, and `Data.Text.Internal.Fusion.Types.$WYield` (again, proportional to the number of bindings). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:47:25 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:47:25 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.3f680141affa6745c8c58c255d5ed656@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Right, so after your second bullet (end of phase 1) we have something reasonable (this is for a list with two strings in it): {{{ -- RHS size: {terms: 6, types: 1, coercions: 0} a_s3zW :: Text [LclId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 120 0}] a_s3zW = Data.Text.Internal.Fusion.unstream (Data.Text.Internal.Fusion.Common.map Data.Text.Internal.safe (Data.Text.Internal.Fusion.Common.streamList @ Char (unpackCString# "abstime"#))) -- RHS size: {terms: 6, types: 1, coercions: 0} a_s3zY :: Text [LclId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 120 0}] a_s3zY = Data.Text.Internal.Fusion.unstream (Data.Text.Internal.Fusion.Common.map Data.Text.Internal.safe (Data.Text.Internal.Fusion.Common.streamList @ Char (unpackCString# "aclitem"#))) -- RHS size: {terms: 3, types: 2, coercions: 0} a_s3zX :: [Text] [LclId, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}] a_s3zX = : @ Text a_s3zY ([] @ Text) -- RHS size: {terms: 3, types: 1, coercions: 0} strings :: [Text] [LclIdX, Str=DmdType, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}] strings = : @ Text a_s3zW a_s3zX }}} The `unstream/map/safe/streamList` is the result of inlining `Data.Text.pack`. I suppose it's ok to have that much for every literal string. But then in the next pass (phase 0) we inline `unstream`, which is pretty big; and `Data.Text.Internal.Fusion.Common.map` and `Data.Text.Internal.safe` and `Data.Text.Internal.Fusion.Common.streamList`. All of these are inlined because of an INLINE pragma. So we are inlining boat-loads of code, under explicit user guidance, but for no purpose. I say this is the fault of the `text` library, not of GHC! What do you ''want'' to happen for literal strings? I don't know what has changed. Has `text` changed? I think the same thing should happen with any version of GHC though I have not tried. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:55:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:55:36 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.6bfc43e568e4816e4bf3f6d19afc3f62@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): There is supposed to be a "Rule fired: TEXT literal" but I see it only with 7.10.1, not my 7.10.1.20150719. Both using text-1.2.1.1. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 16:58:54 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 16:58:54 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.1df762ed3be49e10b4bd4d7983d824d6@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Yep, I just came to this realization myself. The rule in question is here, https://github.com/bos/text/blob/master/Data/Text/Show.hs -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:05:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:05:20 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.112b5ddc6b167fb034f76aa74270dc09@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): In the simplifier pass right before the two compilers diverse the code looks something like, {{{ (c_d32a (Data.Text.pack (GHC.Base.build @ GHC.Types.Char (\ (@ b) -> GHC.CString.unpackFoldrCString# @ b "bpchar"#))) (c_d32a (Data.Text.pack (GHC.Base.build @ GHC.Types.Char (\ (@ b) -> GHC.CString.unpackFoldrCString# @ b "bytea"#))) }}} Into this `GHC.Base.build` is inlined, {{{ Considering inlining: build arg infos [ValueArg] interesting continuation RuleArgCtxt some_benefit True is exp: True is work-free: True guidance ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=False) ANSWER = YES Inlining done: GHC.Base.build Inlined fn: \ (@ a) (g [Occ=Once!] :: forall b. (a -> b -> b) -> b -> b) -> g @ [a] (GHC.Types.: @ a) (GHC.Types.[] @ a) }}} and then `pack`, {{{ Considering inlining: pack arg infos [NonTrivArg] interesting continuation BoringCtxt some_benefit True is exp: True is work-free: True guidance ALWAYS_IF(arity=0,unsat_ok=False,boring_ok=False) ANSWER = YES Inlining done: Data.Text.pack Inlined fn: \ (x [Occ=Once] :: GHC.Base.String) -> Data.Text.Internal.Fusion.unstream (Data.Text.Internal.Fusion.Common.map Data.Text.Internal.safe (Data.Text.Internal.Fusion.Common.streamList @ GHC.Types.Char x)) }}} which I believe is then supposed to cause this rule to fire, {{{ {-# RULES "TEXT literal" forall a. unstream (S.map safe (S.streamList (GHC.unpackCString# a))) = unpackCString# a #-} }}} Yet this appears not to happen in 7.10.2. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:11:46 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:11:46 -0000 Subject: [GHC] #1498: Optimisation: eliminate unnecessary heap check in recursive function In-Reply-To: <047.d854a286f40f24efedada1697ad637ee@haskell.org> References: <047.d854a286f40f24efedada1697ad637ee@haskell.org> Message-ID: <062.02165b8674c0e65d8c5993f110ca0567@haskell.org> #1498: Optimisation: eliminate unnecessary heap check in recursive function -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 6.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: 4258 | Blocking: Related Tickets: 8326 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * cc: rwbarton (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:14:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:14:02 -0000 Subject: [GHC] #8326: Place heap checks common in case alternatives before the case In-Reply-To: <048.ea9ba5e4eb4f979285dd8d72b9c4bf7b@haskell.org> References: <048.ea9ba5e4eb4f979285dd8d72b9c4bf7b@haskell.org> Message-ID: <063.2314ae4b1cf4eeaa30124e56ecb6d6d1@haskell.org> #8326: Place heap checks common in case alternatives before the case -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 8317 Related Tickets: #1498 | Differential Revisions: Phab:D343 -------------------------------------+------------------------------------- Changes (by rwbarton): * cc: rwbarton (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:42:40 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:42:40 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.1483fe62c9c71d59e00d3dfa681557e3@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Yes, I think so. But there is a problem besides the fact that the heap check is duplicated. Referring to the Cmm listing in #8326, something seems to think that `_sEV` (the 0#-or-1# result of the primop) is live in the alternatives, even to the point of passing it through the GC, when really it will never be used after the branch. I think that's the reason that later passes are unable to avoid this ugly `cmp/setCC/movzbl/test/jne` sequence. Otherwise the definition of `_sEV` would be inlined at its only use site, the branch, and the code generator would then generate a nice `cmp/jCC` sequence. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:44:30 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:44:30 -0000 Subject: [GHC] #8326: Place heap checks common in case alternatives before the case In-Reply-To: <048.ea9ba5e4eb4f979285dd8d72b9c4bf7b@haskell.org> References: <048.ea9ba5e4eb4f979285dd8d72b9c4bf7b@haskell.org> Message-ID: <063.63d8166b0cca90860f7779ac05fe1bc1@haskell.org> #8326: Place heap checks common in case alternatives before the case -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 8317 Related Tickets: #1498 | Differential Revisions: Phab:D343 -------------------------------------+------------------------------------- Comment (by rwbarton): Even if it was right to do the heap checks in the alternatives there's another problem with this Cmm: `_sEV` is being kept live longer than it should be. See #10676. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:44:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:44:47 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.ff73906694e01f3ab0aec313e9d210c2@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8326 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * related: => #8326 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 17:50:53 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 17:50:53 -0000 Subject: [GHC] #10464: ghc 7.8.4 on arm In-Reply-To: <051.d5878ed901f03828231ecea66d3e9618@haskell.org> References: <051.d5878ed901f03828231ecea66d3e9618@haskell.org> Message-ID: <066.4456c1dde5ec2aebf5a2643ed29ebd15@haskell.org> #10464: ghc 7.8.4 on arm ---------------------------------+-------------------------------- Reporter: andrewufrank | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+-------------------------------- Changes (by thomie): * cc: nomeata (added) * failure: Compile-time performance bug => None/Unknown * component: Compiler => Build System Comment: From reading this [http://stackoverflow.com/questions/15247569/warning- cannot-scan-executable-section-for-cortex-a8-erratum-because-it-has-no question] on stackoverflow, I think GHC should be built with the option `STRIP_CMD = :` for your platform. The `debian/rules` file in http://http.debian.net/debian/pool/main/g/ghc/ghc_7.8.4-9.debian.tar.xz contains: {{{ ifneq (,$(findstring nostrip,$(DEB_BUILD_OPTIONS))) # echo "GhcStage1HcOpts += -DDEBUG" >> mk/build.mk # echo "GhcStage2HcOpts += -DDEBUG" >> mk/build.mk echo "SRC_HC_OPTS += -H32m -O0" >> mk/build.mk echo "GhcHcOpts += -Rghc-timing -DDEBUG" >> mk/build.mk # echo "GhcLibHcOpts += -O -dcore-lint -keep-hc-files " >> mk/build.mk echo "SplitObjs = NO" >> mk/build.mk echo "STRIP = :" >> mk/build.mk endif }}} Notice `STRIP` on the last line. That should at least be `STRIP_CMD`, ever since the following commit: commit 0481fe092fd9e274096fff1fd9885fd68805202a {{{ Author: Ian Lynagh <> Date: Wed Jun 16 16:11:08 2010 +0000 Rename some variables from FOO to FOO_CMD This fixes a problem with commands like gzip, where if $GZIP is exported in the environment, then when make runs a command it'll put the Makefile variable's value in the environment. But gzip treats $GZIP as arguments for itself, so when we run gzip it thinks we're giving it "gzip" as an argument. }}} Please open a bug with Debian, linking back to this question. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 18:01:49 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 18:01:49 -0000 Subject: [GHC] #9229: Compiler memory use regression In-Reply-To: <047.2dfbe078c69c15d5f9a03a8fcfb51c79@haskell.org> References: <047.2dfbe078c69c15d5f9a03a8fcfb51c79@haskell.org> Message-ID: <062.b80c184aeedfe18609f8c2146a80bf67@haskell.org> #9229: Compiler memory use regression -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: worksforme | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8852, #8980, | Differential Revisions: #8941, 8960, #7898, #7068, #7944, | #5550, #8836 | -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme Comment: Please reopen if this is still a problem. You can get ghc-7.8.4 for 32-bit windows here: https://www.haskell.org/ghc/download_ghc_7_8_4#windows -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 19:09:16 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 19:09:16 -0000 Subject: [GHC] #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) In-Reply-To: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> References: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> Message-ID: <059.2acc90562895c0f307bd40a5c801d9e0@haskell.org> #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) ----------------------------------------+---------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: aarch64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ----------------------------------------+---------------------------------- Comment (by erikd): Confirmed. Commit 96f9b79fbf05fbb84 broke it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 19:32:52 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 19:32:52 -0000 Subject: [GHC] #10464: ghc 7.8.4 on arm In-Reply-To: <051.d5878ed901f03828231ecea66d3e9618@haskell.org> References: <051.d5878ed901f03828231ecea66d3e9618@haskell.org> Message-ID: <066.bf701eceaa38136ff96ea7e63fe7d7ea@haskell.org> #10464: ghc 7.8.4 on arm ---------------------------------+-------------------------------- Reporter: andrewufrank | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: arm Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ---------------------------------+-------------------------------- Comment (by nomeata): Thanks. Note that the code from `debian/rules` above is only executed when `nostrip` is enabled, which is not the default. And by default, neither `STRIP` nor `STRIP_CMD` is touched. So I wonder if there is not something that the upstream build system needs to do different. But then, the Debian build script later runs `dh_strip`, which is basically run for every package, and which removes debugging symbols, which should be safe. Other places online indicate that this might be a linker bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 20:00:13 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 20:00:13 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.66a427f25189f91b0bd321fa3d5ec70a@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 Resolution: | Keywords: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by facundo.dominguez): After staring a while to the code in {{{GHC.Event}}}, I got this program which seems to reproduce the problem. I'm using {{{network-2.6.2.1}}}, though I don't think the particular version makes a difference. {{{ -- t.hs -- -- The output should look like -- -- > $ ghc --make -threaded t.hs -- > $ ./t -- > threadWaitWrite: terminated -- > threadWaitRead: thread blocked indefinitely in an MVar operation -- > threadWaitRead: terminated -- > main thread terminated -- main thread terminated import Control.Concurrent import Control.Exception import Control.Monad import System.IO import System.Mem import Network.Socket main :: IO () main = do (s0, s1) <- socketPair AF_UNIX Stream defaultProtocol let fd = fdSocket s0 forkIO $ do catch (threadWaitRead (fromIntegral fd)) $ \e -> putStrLn $ "threadWaitRead: " ++ show (e :: SomeException) putStrLn "threadWaitRead: terminated" forkIO $ do threadDelay 500000 catch (threadWaitWrite (fromIntegral fd)) $ \e -> putStrLn $ "threadWaitWrite: " ++ show (e :: SomeException) putStrLn "threadWaitWrite: terminated" threadDelay 1000000 send s1 "hello" putStrLn "main thread terminated" }}} {{{GHC.Event.Manager}}} has a suspicious [https://github.com/ghc/ghc/blob/ghc-7.10.1-release/libraries/base/GHC/Event/Manager.hs#L459 line]. It removes all callbacks from the table, but I can't see where the unmatched callbacks are added back. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 20:17:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 20:17:33 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.f480fed178ba010728109346999ecf7f@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 Resolution: | Keywords: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by facundo.dominguez): ... and it seems to have been fixed in #10317. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 20:36:50 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 20:36:50 -0000 Subject: [GHC] #10684: Error cascade when unrelated class derivation fails Message-ID: <045.c629d6ca48d10e5b203720966d06c869@haskell.org> #10684: Error cascade when unrelated class derivation fails -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.11 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Pretty minor bug, but I thought I'd point it out: {{{ module A where import Data.Typeable data A = A deriving (Show, Typeable) data B = B A deriving (Show) }}} I get two errors when I expect one: {{{ A.hs:3:28: Can't make a derived instance of `Typeable A': You need -XDeriveDataTypeable to derive an instance for this class In the data declaration for `A' A.hs:4:24: No instance for (Show A) arising from the 'deriving' clause of a data type declaration Possible fix: add an instance declaration for (Show A) or use a standalone 'deriving instance' declaration, so you can specify the instance context yourself When deriving the instance for (Show B) }}} The failed Typeable derivation also causes the Show derivation to fail, which causes an error later in the file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 22:51:55 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 22:51:55 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.f3ac537de772795c4a4dac61620bf119@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8326, #8327 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => duplicate * related: #8326 => #8326, #8327 Comment: Oh, I just found #8327. Will close this one as a duplicate then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 23:26:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 23:26:12 -0000 Subject: [GHC] #9370: unfolding info as seen when building a module depends on flags in a previously-compiled module In-Reply-To: <045.e2e9bbeb8a2151371c0306e4a7b88a0a@haskell.org> References: <045.e2e9bbeb8a2151371c0306e4a7b88a0a@haskell.org> Message-ID: <060.b31e77bad572e460f6a159b8e9b1ed79@haskell.org> #9370: unfolding info as seen when building a module depends on flags in a previously-compiled module -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8635 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * related: => #8635 Comment: This is pretty much the same issue as #8635. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 23:26:22 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 23:26:22 -0000 Subject: [GHC] #8635: GHC optimisation flag ignored when importing a local module with derived type classes In-Reply-To: <051.b56cbb747db73c4a6033f73a503b3d1a@haskell.org> References: <051.b56cbb747db73c4a6033f73a503b3d1a@haskell.org> Message-ID: <066.cbe6e59e7805fe2d0bd0778d5f53f2a1@haskell.org> #8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9370 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * related: => #9370 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 00:05:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 00:05:15 -0000 Subject: [GHC] #8199: Get rid of HEAP_ALLOCED In-Reply-To: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> References: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> Message-ID: <060.3ab74622167faeebade65957ade6d101@haskell.org> #8199: Get rid of HEAP_ALLOCED -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 5435 | Blocking: Related Tickets: | Differential Revisions: D207 -------------------------------------+------------------------------------- Comment (by rwbarton): Is this ticket now obsolete since #9706 is done? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 00:06:55 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 00:06:55 -0000 Subject: [GHC] #10685: ghci segfaults on Travis Message-ID: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> #10685: ghci segfaults on Travis -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: GHCi | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHCi crash Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Some 100 ghci tests are failing on Travis. I bisected it down to b949c96b4960168a3b399fe14485b24a2167b982 "Eliminate zero_static_objects_list()", Phab:D1076. Not that the Travis build sets `DYNAMIC_GHC_PROGRAMS = NO` and 'GhcLibWays = v`. Complete log: https://s3.amazonaws.com/archive.travis-ci.org/jobs/72543456/log.txt -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 00:32:08 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 00:32:08 -0000 Subject: [GHC] #8199: Get rid of HEAP_ALLOCED In-Reply-To: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> References: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> Message-ID: <060.0443b0651a85b04399e1c86b40e5cc1e@haskell.org> #8199: Get rid of HEAP_ALLOCED -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 5435 | Blocking: Related Tickets: | Differential Revisions: D207 -------------------------------------+------------------------------------- Comment (by ezyang): Not quite, because the #9706 technique doesn't work for Windows. But it seems unlikely we'll want to deploy this big patch just to make Windows work. So... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 00:46:35 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 00:46:35 -0000 Subject: [GHC] #8604: Some stack/vmem limits (ulimit) combinations causing GHC to fail In-Reply-To: <045.3fd2dc262c9d5efa9cc8ba9b4a4654dd@haskell.org> References: <045.3fd2dc262c9d5efa9cc8ba9b4a4654dd@haskell.org> Message-ID: <060.905258175c54ce2dcbbd51ad0c447560@haskell.org> #8604: Some stack/vmem limits (ulimit) combinations causing GHC to fail -------------------------------------+------------------------------------- Reporter: clavin | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Documentation | Version: 7.6.3 Resolution: | Keywords: Operating System: Other | Architecture: x86_64 Type of failure: Documentation | (amd64) bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I'm wary of trying to document the underlying behavior of the operating system in the user's guide, especially when that behavior is likely to vary between different operating systems. It seems that the behavior of ghc (or any program built with the threaded runtime) is no different than any other program that starts multiple OS threads. Granted it might not be obvious to the user that ghc itself starts multiple threads, but then they will never know where to look in the documentation to learn this. But I guess we could at least clarify in the documentation for some or all of the `-K/-k*` options that they refer to the Haskell stack, not the C stack. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 04:16:31 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 04:16:31 -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.d35cf1eabf6568e81b8c7b106552f1cf@haskell.org> #10333: hs-boot modification doesn't induce recompilation -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): I've diagnosed why this is occurring. `GhcMake` does some fancy business to determine if an object is stable. Essentially, object stability is a timestamped based check which tries to let `GhcMake` avoid recompiling source files which didn't change at all. However, stability is computed on a **per module name** basis, preferentially checking to see if `hs` files have been updated. This means that if you modify an `hs-boot` file but not the `hs` file, GHC will still consider it "stable" because the stability check was done on `hs`; and will proceed to tell the one-shot compiler that the file was not modified. I'm not sure what the correct solution to this problem is. > You might also notice something else a bit funny, which is that X.hs gets compiled, even though it's not directly in the import chain of Y. I think this might be intentional but I'm not sure. This is because there is explicit logic in `GhcMake` to make this be the case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 07:16:20 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 07:16:20 -0000 Subject: [GHC] #8327: Cmm sinking does not eliminate dead code in loops In-Reply-To: <048.db1f76a3cb62b60bb69e968bf8de2551@haskell.org> References: <048.db1f76a3cb62b60bb69e968bf8de2551@haskell.org> Message-ID: <063.1fecdb88e6b86ea553af15ea5ffff10f@haskell.org> #8327: Cmm sinking does not eliminate dead code in loops -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #10676 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by jstolarek): * related: => #10676 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 08:38:45 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 08:38:45 -0000 Subject: [GHC] #10313: ApiAnnotations : strings in warnings do not return SourceText In-Reply-To: <044.808d3812fac81928344a0fd1bb2faa89@haskell.org> References: <044.808d3812fac81928344a0fd1bb2faa89@haskell.org> Message-ID: <059.40527efbac791b8e744de8c55df29e46@haskell.org> #10313: ApiAnnotations : strings in warnings do not return SourceText -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: | ApiAnnotations Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D907 -------------------------------------+------------------------------------- Comment (by Sergei Trofimovich ): In [changeset:"b04bed0a391335e70b3c3bdbdccbaa0781697cce/ghc" b04bed0a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b04bed0a391335e70b3c3bdbdccbaa0781697cce" renamer: fix module-level deprecation message Noticed today that deprecation warnings are slightly broken in -HEAD: mtl-2.2.1/Control/Monad/Error/Class.hs:46:1: warning: Module ?Control.Monad.Trans.Error? is deprecated: ([", U, s, e, , C, o, n, t, r, o, l, ., M, o, n, a, d, ., T, r, a, n, s, ., E, x, c, e, p, t, , i, n, s, t, e, a, d, "], Use Control.Monad.Trans.Except instead) Commit e6191d1cc37e98785af8b309100ea840084fa3ba slightly changed WarningTxt declaration: -data WarningTxt = WarningTxt (Located SourceText) [Located FastString] - | DeprecatedTxt (Located SourceText) [Located FastString] +data WarningTxt = WarningTxt (Located SourceText) + [Located (SourceText,FastString)] + | DeprecatedTxt (Located SourceText) + [Located (SourceText,FastString)] But 'moduleWarn' function was not updated to do the stripping. Signed-off-by: Sergei Trofimovich Reviewers: austin, bgamari, hvr, goldfire, rwbarton, alanz Reviewed By: rwbarton, alanz Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1096 GHC Trac Issues: #10313 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 11:25:46 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 11:25:46 -0000 Subject: [GHC] #10686: Process stops responding to sigINT Message-ID: <045.4331532de44ba06680224cb60774d4c5@haskell.org> #10686: Process stops responding to sigINT -------------------------------------+------------------------------------- Reporter: hamish | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Every now and then the leksah-server process has required a kill -9 it to get rid of it. Now Leksah is using the threaded RTS it seems to be happening in Leksah too. It is worse in Leksah because child processes inherit the behaviour and do not terminate when sent Leksah sends them sigINT (which Leksah does very frequently). Once the problem arrises it continues until the Leksah is restarted. Both leksah-server and Leksah start child processes using the process package. I think process package and the GHC GC both call blockUserSignals and it only has one place to store savedSignals. My guess is that two calls go into blockUserSignals from different threads before unblockUserSignals is called on either. The result is that when unblockUserSignals is called it does nothing (because savedSignals was overwritten). Perhaps savedSignals could use some kind of thread local storage? Also docs seem to indicate sigprocmask should not be used at all in multithreaded processes. Perhaps the GHC RTS should use pthread_sigprocmask instead? If the calling process delegates Ctrl+C the problem might be largely hidden. The sigINT signal is enabled again in the child fork and the parent will get an exception if the child is terminated with a sigINT. However I believe the parent is still left in a state where it will no longer respond to sigINT if the child process terminates normally (assuming two calls in a row were made to blockUserSignals at some point). The work around for now in Leksah is to reenable sigINT before each createProcess call. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 16:51:43 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 16:51:43 -0000 Subject: [GHC] #10667: '-g' option generates invalid assembly when '*/*' operator is used In-Reply-To: <045.7de7e3e8915f886ced608adea09f7f67@haskell.org> References: <045.7de7e3e8915f886ced608adea09f7f67@haskell.org> Message-ID: <060.429090292600a9674594cb084587f0a3@haskell.org> #10667: '-g' option generates invalid assembly when '*/*' operator is used -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by scpmw): Well spotted - should have seen that one coming. Here's what the GNU assembler documentation says: The line comment character is target specific, and some targets multiple comment characters. Some targets also have line comment characters that only work if they are the first character on a line. Some targets use a sequence of two characters to introduce a line comment. Some targets can also change their line comment characters depending upon command line options that have been used. According to the same documentation, the line comment character for x86 is apparently `#`, while it's `@` for ARM. So possible, but a bit messy. I think the better course of action here would be to just "escape" the name - or maybe just drop the comment in the first place if the name looks problematic. It's not really that useful anyway. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 17:07:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 17:07:36 -0000 Subject: [GHC] #10506: SourceNotes are not applied to all identifiers In-Reply-To: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> References: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> Message-ID: <064.f2db3380bddc7b3073ac24b2fd144e6a@haskell.org> #10506: SourceNotes are not applied to all identifiers -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by scpmw): * Attachment "tick-vars.patch" added. Proposed patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 17:12:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 17:12:36 -0000 Subject: [GHC] #10506: SourceNotes are not applied to all identifiers In-Reply-To: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> References: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> Message-ID: <064.548491de8437813b3b441d77a39a03bc@haskell.org> #10506: SourceNotes are not applied to all identifiers -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by scpmw): Patch attached, but not too happy with it. Making it a dump patch is probably the least offensive option - at least it shows the right intent. Yet it is awkward both in terms of overriding the "tick never" as well as in terms of actually changing the Haskell syntax tree based on a dump flag. Does this at least help you, gridaphobe? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 18:05:24 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 18:05:24 -0000 Subject: [GHC] #10687: Clang 3.6 fails with -g due to .file directive order Message-ID: <044.67379f3a8d9d1920a99529a73d2b00f0@haskell.org> #10687: Clang 3.6 fails with -g due to .file directive order -------------------------------------+------------------------------------- Reporter: scpmw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- On Mac Os X, compiling with `-g` will sometimes fail with an error like follows: {{{ /var/folders/yt/bmbchswn57nbmz1l67btd6p00000gn/T/ghc27418_0/ghc_1.s:6573:7: error: error: unassigned file number in '.loc' directive .loc 7 106 17 /* cast */ ^ }}} Which refers to the following code: {{{ [...] .file 7 "libraries/base/Data/Typeable.hs" .file 6 "libraries/ghc-prim/GHC/Classes.hs" [...] .loc 7 106 17 /* cast */ }}} So the file number is clearly assigned, we are just not assigning them "in order". This is okay for most compilers, but Clang 3.6 seems to disagree. The attached patch changes the code so `.file` directives are always generated in order. Could try to produce a testcase if required - it would be rather easy to check that `.file` directives appear in order in a given assembly file. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 18:07:32 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 18:07:32 -0000 Subject: [GHC] #10687: Clang 3.6 fails with -g due to .file directive order In-Reply-To: <044.67379f3a8d9d1920a99529a73d2b00f0@haskell.org> References: <044.67379f3a8d9d1920a99529a73d2b00f0@haskell.org> Message-ID: <059.b019f0afaf6ed71f08ef35dac6cfb15d@haskell.org> #10687: Clang 3.6 fails with -g due to .file directive order -------------------------------------+------------------------------------- Reporter: scpmw | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by scpmw): * Attachment "file-order-clang-fix.patch" added. Proposed patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 18:39:08 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 18:39:08 -0000 Subject: [GHC] #10687: Clang 3.6 fails with -g due to .file directive order In-Reply-To: <044.67379f3a8d9d1920a99529a73d2b00f0@haskell.org> References: <044.67379f3a8d9d1920a99529a73d2b00f0@haskell.org> Message-ID: <059.beb547a84bbe5dcf97106cbc57feccfe@haskell.org> #10687: Clang 3.6 fails with -g due to .file directive order -------------------------------------+------------------------------------- Reporter: scpmw | Owner: Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => patch -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 19:43:07 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 19:43:07 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code Message-ID: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The program enters an infinite loop (100% cpu, not stopping) because it fails to recognize the stopping condition of a takeWhile. If we make the list finite, it takes all the elements while it should stop before. I don't know how to simplify the code since if I change it a little (e.g. by replacing the name of an object by its definition), sometimes it works well, sometimes not. When I enter the code in ghci, it works well but not when compiled. I don't know if I should explain what the code was for initially, tell me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 19:48:54 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 19:48:54 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.9ad6abc0b729b2c061721c79054d6a19@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Is it possible to upload a (presumably large) program which reproduces the problem? Even some code snippets would help; what's the stopping condition of `takeWhile`? Can you reproduce with `-O0`? Can you try with 7.10.2 or even the latest master version of GHC? Some description of what the code does would also be useful. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:10:18 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:10:18 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.4f6fdfb42b4a2008a4caca0f7565b66a@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * priority: normal => lowest Old description: > The program enters an infinite loop (100% cpu, not stopping) because it > fails to recognize the stopping condition of a takeWhile. If we make the > list finite, it takes all the elements while it should stop before. > > I don't know how to simplify the code since if I change it a little (e.g. > by replacing the name of an object by its definition), sometimes it works > well, sometimes not. > > When I enter the code in ghci, it works well but not when compiled. > > I don't know if I should explain what the code was for initially, tell > me. New description: The program enters an infinite loop (100% cpu, not stopping) because it fails to recognize the stopping condition of a `takeWhile`. If we make the list finite, it takes all the elements while it should stop before. I don't know how to simplify the code since if I change it a little (e.g. by replacing the name of an object by its definition), sometimes it works well, sometimes not. When I enter the code in ghci, it works well but not when compiled. I don't know if I should explain what the code was for initially, tell me. edit : Actually, I realized that this is not a bug. This is due to the lack of type signatures in my program. I thought that was a bug because sometimes the program used `Int`s, sometimes `Integer`s, and just expanding a definition can change this (see the code in attachment). I apologize for opening a ticket for that (I thought `Integer`s were used since it is the case in ghci). -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:10:33 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:10:33 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.6a84ed8f952edbc6fb009ec15b531f2d@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:11:04 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:11:04 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.692a441de95feb76526f57accc6499e1@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by Ideophage: Old description: > The program enters an infinite loop (100% cpu, not stopping) because it > fails to recognize the stopping condition of a `takeWhile`. If we make > the list finite, it takes all the elements while it should stop before. > > I don't know how to simplify the code since if I change it a little (e.g. > by replacing the name of an object by its definition), sometimes it works > well, sometimes not. > > When I enter the code in ghci, it works well but not when compiled. > > I don't know if I should explain what the code was for initially, tell > me. > > edit : > Actually, I realized that this is not a bug. This is due to the lack of > type signatures in my program. I thought that was a bug because sometimes > the program used `Int`s, sometimes `Integer`s, and just expanding a > definition can change this (see the code in attachment). I apologize for > opening a ticket for that (I thought `Integer`s were used since it is the > case in ghci). New description: edit : Actually, I realized that this is not a bug. This is due to the lack of type signatures in my program. I thought that was a bug because sometimes the program used `Int`s, sometimes `Integer`s, and just expanding a definition can change this (see the code in attachment). I apologize for opening a ticket for that (I thought `Integer`s were used since it is the case in ghci). Below my original message. The program enters an infinite loop (100% cpu, not stopping) because it fails to recognize the stopping condition of a `takeWhile`. If we make the list finite, it takes all the elements while it should stop before. I don't know how to simplify the code since if I change it a little (e.g. by replacing the name of an object by its definition), sometimes it works well, sometimes not. When I enter the code in ghci, it works well but not when compiled. I don't know if I should explain what the code was for initially, tell me. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:13:26 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:13:26 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.6a84ed8f952edbc6fb009ec15b531f2d@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:13:26 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:13:26 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.ae57865d25b5e9389ab6c74d8b3509f4@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:14:38 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:14:38 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.522945aa53312074b1e3c8e935247012@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.2.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:14:53 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:14:53 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.63067d638609f89ff76733da68d28469@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:14:53 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:14:53 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.ae57865d25b5e9389ab6c74d8b3509f4@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:17:01 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:17:01 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' Message-ID: <045.743fe21fa784fce71ea539681c963bac@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- First observed on singletons-1.1.2.1 package ghc-7.10.2. I've tried to distill it down to a single file. The file manages to crash both GHC and GHCi. GHCi: {{{ $ inplace/bin/ghc-stage2 -hide-all-packages -package=base --interactive List.hs GHCi, version 7.11.20150723: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling List ( List.hs, interpreted ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150723 for x86_64-unknown-linux): floatExpr tick break<2>() Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} GHC: {{{ $ inplace/bin/ghc-stage2 -hide-all-packages -package=base --make List.hs -dsuppress-all -dsuppress-uniques [1 of 1] Compiling List ( List.hs, List.o ) ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20150723 for x86_64-unknown-linux): Template variable unbound in rewrite rule m [a_afdP, x, m, ipv, ipv, sc, sc, sc, sg] [a_afdP, x, m, ipv, ipv, sc, sc, sc, sg] [TYPE a_afdP, TYPE x, TYPE Let1627448493XsSym4 x m ipv ipv, sc, (SCons @~ ... sc sc) `cast` ...] [TYPE a_afdP, TYPE x, TYPE Let1627448493XsSym4 x ipv ipv ipv, sc, (SCons @~ ... ipv ipv) `cast` ...] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} The "minimal" single-file sample is attached. If you need original selfcontained reproducer (79 modules, template haskell code) this is the version i've started with: http://code.haskell.org/~slyfox/unbound-template-var.tar.gz Adjusting path to GHC in '''./trigger-a-bug.bash''' should be enough. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:18:05 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:18:05 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.1aa859802bf9884b6a8922ea9be60db2@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by slyfox): * Attachment "List.hs" added. a tiny part of singletons-1.1.2.1/src/Data/Singletons/Prelude/List.hs required to trigger a bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:22:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:22:28 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.1d44b5e3d32cf6e9327d353b1234379b@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ideophage): Replying to [comment:1 ezyang]: > Is it possible to upload a (presumably large) program which reproduces the problem? Even some code snippets would help; what's the stopping condition of `takeWhile`? Can you reproduce with `-O0`? Can you try with 7.10.2 or even the latest master version of GHC? Some description of what the code does would also be useful. Thanks for your reply. I checked the box for adding an attachment and I thought my ticket was not opened. I added the code. This is reproducible with `-O0`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:28:38 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:28:38 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.63067d638609f89ff76733da68d28469@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:28:38 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:28:38 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.a448f3084617eeac37326c30ac731bff@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:29:14 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:29:14 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.65087dce6a28718f10bf3c8e4718f0e3@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.2.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:29:14 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:29:14 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.522945aa53312074b1e3c8e935247012@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: new Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Ideophage): * Attachment "bug1.2.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:38:30 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:38:30 -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.35afdfd441adbe21bbcd467674849fb1@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: erikd (added) Comment: I think the problem is that although `--with-ld` adds "ld command" to the settings file, it isn't used anywhere. {{{ $ git grep "ld command" compiler/ settings.in settings.in: ("ld command", "@SettingsLdCommand@"), }}} In the function `initSysTools` in `compiler/main/SysTools.hs`, the C compiler is always used as the linker: {{{ ... ; gcc_prog <- getSetting "C compiler command" ; gcc_args_str <- getSetting "C compiler flags" ... -- Other things being equal, as and ld are simply gcc ; let as_prog = gcc_prog as_args = gcc_args ld_prog = gcc_prog ld_args = gcc_args ... }}} cc erikd, since he added the `--with-ld` option in Phab:D828 (the FIND_LD macro in aclocal.m4). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:38:30 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:38:30 -0000 Subject: [GHC] #10506: SourceNotes are not applied to all identifiers In-Reply-To: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> References: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> Message-ID: <064.a43c1f00f27b00979a40a81a4745d05e@haskell.org> #10506: SourceNotes are not applied to all identifiers -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Thanks scpmw, this looks promising. I'll build LiquidHaskell against your patch and make sure we get the extra Ticks we need. For our purposes, hiding this behind a flag is fine, but calling it a dump flag seems a bit off to me. As your comment says, the flag is modifying the generated Core, wouldn't a name like `-ftick-everything` make more sense? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:48:03 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:48:03 -0000 Subject: [GHC] #10690: Save merged signatures to disk Message-ID: <045.25a62546e19528fda1b12c19e43ea653@haskell.org> #10690: Save merged signatures to disk -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: backpack | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The Backpack model of development encourages users to mix signatures together. For example: {{{ unit p where signature H where x :: Int unit q where signature H where y :: Int unit r where include p include q module A where import H(x,y) }}} When `A` imports `H`, it should see both `x` and `y` (i.e. a merged version of the two signatures.) There are two possible ways to implement this: 1. The old strategy: When `A` imports `H`, it somehow "sees" both the interface for H from `p`, and the interface from `q`, and it merges them together on-the-fly. 2. The new strategy: Before compiling `A`, we merge the interfaces together, and use that merged interface as what A imports and gets its export from. Strategy (2) has a few advantages: in separate compilation, it avoids the need to repeatedly merge interfaces together, and it also simplifies GHC in that we don't have to manage on the fly signature merging. Now the challenge: GHC currently assumes that every build product is associated with a source file: however, merged interface files don't have this property. Both `--make` and one-shot `-c` compilation infrastructure is organized around this property. Here's is the proposal for how to slot this in: 1. Eliminate `HscSource` distinction between `HsBootFile` and `HsigFile`: the file is always called `A.hs-boot`. Instead, the type checker simply behaves differently depending on whether or not we know what the underlying implementation of `A` is (passed in using the `-sig-of` flag. If we know the underlying implementation is `containers:Data.Map`, we compile the hs-boot file "signature-style", if we don't, we assume it's `this-package:A` and compile it "boot-style" (Conceivably for cross-unit mutual recursion this will need to be more sophisticated, but this will do for now.) By the way, this means that all signature files now compile to A.hi-boot. 2. We introduce a new `HscSource` type, `HsBootMerge`, representing an `hi` (and stub `o`) file that will be generated by a signature merge. Intuitively, this operation will merge together A.hi-boot as well as any signatures which were brought into scope by a `-package` flag. Unlike `HsSrcFile` and `HsBootFile`, `ModSummary`s that are `HsBootMerge` don't have a source file. 3. When compiling `--make`, for all "signature-style" hs-boot files in the module graph, we generate an `HsBootMerge` summary to serve as the `NotBoot` node of that module name. This means if you `import A`, you're actually importing the `HsBootMerge` that produces `A.hi`. 4. When compiling one-shot, we have a new command for generating the `HsBootMerge`: `ghc --merge-requirements A`. This will go and look for an A.hi-boot as well as any external signatures and merge them together. Note that we can't use the existing compilation pipeline `-c` to generate merged hs-boot files, since these presuppose that there is some input source file, which there is none in this case. 5. When generating a Makefile dependency graph, an entry for an `HsBootMerge` looks like this: {{{ A.o : A.hi-boot A.o : /path/to/ghc/foo-0.1/A.hi # if -include-pkg-deps is added }}} That is to say, an `HsBootMerge` looks like a normal source file that imports each signature it's merging together, but doesn't have a source file associated with it. One downside with this representation is that it makes Makefile rules a little more complicated: how do you build `A.o`? Not with `ghc -c A.hs`, but with `ghc --merge-requirements A`. I'm not sure what the best way of solving this is. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 20:51:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 20:51:28 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.1af8cd40a38c492107b1ce2523702447@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => invalid Comment: > edit : Actually, I realized that this is not a bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 21:09:33 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 21:09:33 -0000 Subject: [GHC] #10546: conc034 is failing with a Core Lint error In-Reply-To: <047.9168d37927d1a0edb26045a19a955209@haskell.org> References: <047.9168d37927d1a0edb26045a19a955209@haskell.org> Message-ID: <062.79d2f4f8e32bfedf7e4f786e91c22941@haskell.org> #10546: conc034 is failing with a Core Lint error -------------------------------------+------------------------------------- Reporter: simonmar | Owner: simonpj Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | concurrent/should_run/conc034.hs Blocked By: | Blocking: Related Tickets: #10659 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #10659 * milestone: => 7.12.1 Comment: Fixed in #10659. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 21:23:10 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 21:23:10 -0000 Subject: [GHC] #10378: min/max for Double/Float instances are incorrect In-Reply-To: <045.4765ac29584fe513da96250006286137@haskell.org> References: <045.4765ac29584fe513da96250006286137@haskell.org> Message-ID: <060.305608c6bda80f79c9e4a583dcf4dca1@haskell.org> #10378: min/max for Double/Float instances are incorrect -------------------------------------+------------------------------------- Reporter: lerkok | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * priority: high => normal Comment: Please start a discussion about this on libraries@ or glasgow-haskell- users at . -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 21:32:43 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 21:32:43 -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.e7d879704ea78cb368fef65520e314e8@haskell.org> #9630: compile-time performance regression (probably due to Generics) -------------------------------------+------------------------------------- Reporter: hvr | Owner: simonpj Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9583, #10293 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Replying to [comment:13 goldfire]: > One thing I see in the (first set of) numbers above is that `lintAnnots` takes up a lot of time! Please be aware of #10007: "Fix misattribution of Cost Centre profiles to lintAnnots". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 21:39:58 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 21:39:58 -0000 Subject: [GHC] #9267: Lack of type information in GHC error messages when the liberage coverage condition is unsatisfied In-Reply-To: <046.5fa88da4adf3eafbdc66687875e23aec@haskell.org> References: <046.5fa88da4adf3eafbdc66687875e23aec@haskell.org> Message-ID: <061.f576adef6e9a00dfb1eae8521955b75c@haskell.org> #9267: Lack of type information in GHC error messages when the liberage coverage condition is unsatisfied -------------------------------------+------------------------------------- Reporter: danilo2 | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #8634 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * priority: high => normal * related: => #8634 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 22:04:20 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 22:04:20 -0000 Subject: [GHC] #5129: "evaluate" optimized away In-Reply-To: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> References: <043.215a28fb6b8d99f7d854d81f8accbd88@haskell.org> Message-ID: <058.389c575b0461477a9a1fe696b8b56575@haskell.org> #5129: "evaluate" optimized away -------------------------------------+------------------------------------- Reporter: dons | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: fixed | Keywords: seq, | evaluate Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D615 -------------------------------------+------------------------------------- Changes (by thomie): * differential: => Phab:D615 Comment: In commit de9a836cd920722a4c28dcb464ff2c8d5905acb9: {{{ Author: Roman Cheplyaka <> Date: Mon Feb 9 13:44:03 2015 -0600 Clarify the documentation for 'evaluate' Summary: See: https://www.haskell.org/pipermail/ghc-devs/2015-January/007900.html https://ghc.haskell.org/trac/ghc/ticket/5129#comment:17 Reviewers: hvr, Mikolaj, austin Reviewed By: Mikolaj, austin Subscribers: ezyang, nomeata, thomie Differential Revision: https://phabricator.haskell.org/D615 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sat Jul 25 23:50:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sat, 25 Jul 2015 23:50:15 -0000 Subject: [GHC] #9125: int-to-float conversion broken on ARM In-Reply-To: <046.674440465a685280d146765ea38d0bfb@haskell.org> References: <046.674440465a685280d146765ea38d0bfb@haskell.org> Message-ID: <061.920224be722d77f2d71c1ae5b0032f58@haskell.org> #9125: int-to-float conversion broken on ARM -------------------------------------+------------------------------------- Reporter: Ansible | Owner: Type: bug | Status: infoneeded Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Incorrect result | Test Case: at runtime | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): With #10074, ./configure checks for llvm-3.6 to be installed, with which this problem does not occur, according to comment:43. Replying to [comment:25 rwbarton]: > Well that's good to know, at least! I still think our TBAA information is wrong for this code, though. Is that the reason this ticket is still open? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 00:54:01 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 00:54:01 -0000 Subject: [GHC] #9125: int-to-float conversion broken on ARM In-Reply-To: <046.674440465a685280d146765ea38d0bfb@haskell.org> References: <046.674440465a685280d146765ea38d0bfb@haskell.org> Message-ID: <061.33a3039f436dee6b46d7d5f1ff248a69@haskell.org> #9125: int-to-float conversion broken on ARM -------------------------------------+------------------------------------- Reporter: Ansible | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 (CodeGen) | Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: arm Type of failure: Incorrect result | Test Case: at runtime | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * status: infoneeded => closed * resolution: => invalid Comment: The TBAA issue is tracked at #9504, so we can close this one as "bug in LLVM 3.0". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 01:01:25 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 01:01:25 -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.67e7183f30c15572c70bf057d4b4f461@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by erikd): Replying to [comment:5 thomie]: > In the function `initSysTools` in `compiler/main/SysTools.hs`, the C compiler is always used as the linker: I can't remember where, but I did find that the linker is called directly somewhere or somehow. Possibly when cross-compiling? I really should have documented this when I found it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 01:12:19 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 01:12:19 -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.423cedda02d4a99d5106c45753dc2d42@haskell.org> #10671: inplace/bin/ghc-stage1 doesn't respect --with-ld override -------------------------------------+------------------------------------- Reporter: mfox | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build System | Version: 7.10.1 Resolution: | Keywords: Operating System: Linux | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): It's used by cabal sometimes, I think it's when linking a static Haskell library. That is, cabal parses the output of `ghc --info` to determine what linker it should invoke. I don't know whether ghc ever directly invokes the linker itself. (The fact that ghc uses gcc and not ld for the link step is a bit confusing, and I'm not sure whether it is documented anywhere. For example it means that `-optl` needs to take gcc options, which are not always the same as ld options. The description of `-optl` in the man page is just "pass option to the linker".) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 01:53:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 01:53:15 -0000 Subject: [GHC] #9861: ghc readme provides out of date git clone directions In-Reply-To: <045.ee10b522121d648c9ddb8fa0d461111b@haskell.org> References: <045.ee10b522121d648c9ddb8fa0d461111b@haskell.org> Message-ID: <060.1eeb4ac7f8d0adfb40e021428c2f0da9@haskell.org> #9861: ghc readme provides out of date git clone directions -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | 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 Revisions: phab:D555 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:11:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:11:36 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.3acb8e87daeab7be50c97a15c0fda9f3@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Simon says: > I'm not sure what the right thing here is. I say that we should reject these programs. They're bogus! This might make some affected people complain, but the situation seems similar to what happened between 7.6 and 7.8 where the FD check was tightened (most recently). Some people's programs stopped working, but it was all for a good reason. The examples all look like an attempt to encode instance chains. GHC has hitherto failed to notice the overlap, but it's been there all along. Happily, each of these examples could straightforwardly (if verbosely and unpleasantly) be refactored to use closed type families. Or, if we ever get around to finishing the work for #8634, folks who want the old behavior can just call their functional dependency to be dysfunctional (which it really is) and get on with it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:22:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:22:15 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.85f98d94cf302e58a6504516ca486acb@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): See also #9210, where a potential fix broke the same four test cases. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:28:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:28:36 -0000 Subject: [GHC] #10494: Representational equalities over AppTys are not hard failures In-Reply-To: <047.6c55cf81fc9e307934dd2710cdafc698@haskell.org> References: <047.6c55cf81fc9e307934dd2710cdafc698@haskell.org> Message-ID: <062.3766f43fa6b363e7cb1b21993c5737bf@haskell.org> #10494: Representational equalities over AppTys are not hard failures -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10494 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:3 bgamari]: > I am a bit confused; the cited example appears to compile for me with 7.8, 7.10.1, and 7.10.2. Perhaps this was introduced since 7.10 branched from master? Quite possible. I guess I didn't test in 7.10. And, in any case, you've simply decided that it's not convenient to merge the change. :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:34:18 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:34:18 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.b13bb2298cb2de3e36e784bc362bdef4@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8326, #8327 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Reid Barton ): In [changeset:"7e70c063ad88052ca5f2586eb07e5d1571956acd/ghc" 7e70c063/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7e70c063ad88052ca5f2586eb07e5d1571956acd" Use isTrue# around primitive comparisons in integer-gmp Summary: The form case na# ==# nb# of 0# -> ... _ -> ... sometimes generates convoluted assembly, see #10676. timesInt2Integer was the most spectacular offender, especially as it is a rather cheap function overall (no calls to gmp). I checked a few instances and some of the old generated assembly was fine already, but I changed them all for consistency. The new form is also more consistent with use of these primops in general. Test Plan: validate Reviewers: hvr, bgamari, goldfire, austin Reviewed By: hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1094 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:47:00 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:47:00 -0000 Subject: [GHC] #9982: cross building integer-gmp is running target program on build host In-Reply-To: <046.8a1ffc42fb5fbbea8ac62e5a7db86511@haskell.org> References: <046.8a1ffc42fb5fbbea8ac62e5a7db86511@haskell.org> Message-ID: <061.71df7df5c9ff3bfd4b2a3f341ee84cae@haskell.org> #9982: cross building integer-gmp is running target program on build host -------------------------------------+------------------------------------- Reporter: newsham | Owner: Type: bug | Status: new Priority: low | Milestone: 7.12.1 Component: Build System | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * priority: normal => low * milestone: => 7.12.1 Comment: Since the new integer-gmp is the default in 7.10 and the old integer-gmp is currently gone in HEAD, I'm marking this ticket as low priority and also setting a milestone so that it will be garbage collected. To the 7.12 branch maintainer, if the 7.10 branch becomes defunct, close this ticket 'wontfix', else please remilestone appropriately. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:50:34 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:50:34 -0000 Subject: [GHC] #5916: runST isn't free In-Reply-To: <044.d958bab6cdf04501b440e190747a91b9@haskell.org> References: <044.d958bab6cdf04501b440e190747a91b9@haskell.org> Message-ID: <059.bb5896f0a1ec8533ae279e961a14658e@haskell.org> #5916: runST isn't free -------------------------------------+------------------------------------- Reporter: tibbe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Runtime | Test Case: performance bug | simplCore/should_run/runST Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * testcase: => simplCore/should_run/runST -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:53:24 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:53:24 -0000 Subject: [GHC] #8326: Place heap checks common in case alternatives before the case In-Reply-To: <048.ea9ba5e4eb4f979285dd8d72b9c4bf7b@haskell.org> References: <048.ea9ba5e4eb4f979285dd8d72b9c4bf7b@haskell.org> Message-ID: <063.436561e6c0e9ce9a7089006590632bf4@haskell.org> #8326: Place heap checks common in case alternatives before the case -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: 8317 Related Tickets: #1498 | Differential Revisions: Phab:D343 -------------------------------------+------------------------------------- Changes (by rwbarton): * failure: None/Unknown => Runtime performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 03:56:49 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 03:56:49 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy Message-ID: <047.5a091b0736d5db136f703c98736ac583@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This came up in #ghc the other day. {{{ rwbarton at morphism:~$ ghci-7.10.1 GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Prelude> undefined * 0 0 }}} For consistency not just with Int, but also other integer-* implementations, this should be undefined. Also affected is for example `andInteger`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 06:56:43 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 06:56:43 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy In-Reply-To: <047.5a091b0736d5db136f703c98736ac583@haskell.org> References: <047.5a091b0736d5db136f703c98736ac583@haskell.org> Message-ID: <062.eaa9017d2cbaad49cba7b46bc326791b@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Bummer... I put quite some effort to model the `Integer` type to allow for such case-analysis for being able to avoid allocations and FFI calls in case of operations with absorbing elements... :-/ I wonder if and how `nofib` will regress if e.g. `0` doesn't shortcut anymore... However, I'd rather expect this to be fixed in the `Num` instance rather than crippling `integer-gmp` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 07:04:21 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 07:04:21 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy In-Reply-To: <047.5a091b0736d5db136f703c98736ac583@haskell.org> References: <047.5a091b0736d5db136f703c98736ac583@haskell.org> Message-ID: <062.2bc1a9a54bb3f1a5a7bc98e5f152de7c@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Replying to [comment:1 hvr]: > Bummer... I put quite some effort to model the `Integer` type to allow for such case-analysis for being able to avoid allocations and FFI calls in case of operations with absorbing elements... :-/ > > I wonder if and how `nofib` will regress if e.g. `0` doesn't shortcut anymore... You can still save the work of doing a multiplication in GMP, you just have to force evaluation of the other argument when you do so. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 07:57:45 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 07:57:45 -0000 Subject: [GHC] #10678: integer-gmp's runS seems unnecessarily expensive In-Reply-To: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> References: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> Message-ID: <062.8875e1703fdfd9cd490a97c8e1f04eff@haskell.org> #10678: integer-gmp's runS seems unnecessarily expensive -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I am working on a patch that adds such a `runRW#` function with special treatment in CorePrep, since it seems easy and most of the work could be reused for the special primop approach anyways. No benchmarks yet but it does produce the expected Cmm without the floating-out problems of `inlinePerformIO` in my simple test, and it passes validate (which might not greatly stress this case, but the new `runRW#` is being used from integer-gmp and I guess also from bytestring via `unsafeDupablePerformIO`). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 09:22:37 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 09:22:37 -0000 Subject: [GHC] #9982: cross building integer-gmp is running target program on build host In-Reply-To: <046.8a1ffc42fb5fbbea8ac62e5a7db86511@haskell.org> References: <046.8a1ffc42fb5fbbea8ac62e5a7db86511@haskell.org> Message-ID: <061.193db24792340ce07e3e02d9d90a2ef8@haskell.org> #9982: cross building integer-gmp is running target program on build host -------------------------------------+------------------------------------- Reporter: newsham | Owner: Type: bug | Status: new Priority: low | Milestone: 7.12.1 Component: Build System | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): Using autoconf for 7.8 is also straightforward changeset:52f554582339d14c28a3cc91385f9cb0343f6779 (I used that to build ia64 ghc+integer-gmp on amd64) but requires not too old version of autoconf, IIRC MacOS users were not happy and it was reverted changeset:916be615048cc844498319f4a21cc62bec162cd8 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 09:32:53 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 09:32:53 -0000 Subject: [GHC] #7325: threadDelay mistreats minBound and maxBound in some configurations In-Reply-To: <048.f6376e5e233d59dcc7fd251637dbe84b@haskell.org> References: <048.f6376e5e233d59dcc7fd251637dbe84b@haskell.org> Message-ID: <063.c5e0866391dcfa4f198eb8f12176e10d@haskell.org> #7325: threadDelay mistreats minBound and maxBound in some configurations -------------------------------------+------------------------------------- Reporter: joeyadams | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Runtime System | Version: 7.6.1 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: Incorrect result | Test Case: at runtime | base/tests/T8089 Blocked By: | Blocking: Related Tickets: #9722 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => base/tests/T8089 * os: Unknown/Multiple => Windows Comment: The issue around `threadDelay maxBound` on OS X is I think fixed. At least, #8089 added a test for it, which is supposedly passing on OS X. That makes this a Windows only problem now. Unexpected failures: . T8089 [bad exit code] (normal,hpc,optasm) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 10:20:36 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 10:20:36 -0000 Subject: [GHC] #5001: makeCorePair: arity missing In-Reply-To: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> References: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> Message-ID: <060.a1b52b977dc12e70352028f5f4b69de5@haskell.org> #5001: makeCorePair: arity missing -------------------------------------+------------------------------------- Reporter: maeder | Owner: Type: bug | Status: new Priority: high | Milestone: 7.4.1 Component: Compiler | Version: 7.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | deSugar/should_compile/T5001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Here is a test to reproduce the problem from comment:21. {{{#!haskell {-# LANGUAGE DefaultSignatures #-} module T5001b where class GEnum a where genum :: [a] default genum :: [a] genum = undefined instance GEnum Int where {-# INLINE genum #-} }}} {{{ $ ghc-7.10.2 T5001b.hs [1 of 1] Compiling T5001b ( T5001b.hs, T5001b.o ) makeCorePair: arity missing $cgenum_am5 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 12:23:39 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 12:23:39 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.4089b981710aaf87c447655cbf07c10d@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Thanks to the wonders of `git bisect run` I was able to determine the first bad commit (on the `ghc-7.10` branch) to be 8af219adb914b292d0f8c737fe0a1e3f7fb19cf3, "Fix a huge space leak in the mighty Simplifier". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 13:21:28 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 13:21:28 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking In-Reply-To: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> References: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> Message-ID: <060.95f175185b356d744884169cff86630b@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #9297 #10563 | Differential Revisions: #8237 #9907 | -------------------------------------+------------------------------------- Changes (by lukexi): * milestone: => 7.10.3 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 13:30:15 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 13:30:15 -0000 Subject: [GHC] #10672: checkProddableBlock crash during Template Haskell linking In-Reply-To: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> References: <045.04cee7c60b130b0ccc29791ed61c4f5f@haskell.org> Message-ID: <060.2243f5f7a21b3e0c312427284b41f804@haskell.org> #10672: checkProddableBlock crash during Template Haskell linking -------------------------------------+------------------------------------- Reporter: lukexi | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Windows | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: #9297 #10563 | Differential Revisions: #8237 #9907 | -------------------------------------+------------------------------------- Changes (by lukexi): * cc: igloo (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 17:29:19 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 17:29:19 -0000 Subject: [GHC] #10692: Replace (SourceText, FastString) with WithSourceText data type Message-ID: <044.c56d65db37c6df403dcc678377793b55@haskell.org> #10692: Replace (SourceText,FastString) with WithSourceText data type -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Phab:D907 introduced `SourceText` for a number of data types, by replacing `FastString` with `(SourceText,FastString)`. Since this has an `Outputable` instance, no warnings are generated when `ppr` is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the `(SourceText,FastString)` tuples with a new data type {{{#!hs data WithSourceText = WithSourceText SourceText FastString }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 19:33:27 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 19:33:27 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.4795d2c8cf6cef048eb974f00d373a65@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by George): It's great that Mark has a fix but I'm still not clear on this issue. Are there bugs to be fixed in ghc and/or cabal or was the problem that GLUT was not being built properly? If the former can somebody describe the bugs or are we still investigating this issue? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Sun Jul 26 21:58:39 2015 From: ghc-devs at haskell.org (GHC) Date: Sun, 26 Jul 2015 21:58:39 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy In-Reply-To: <047.5a091b0736d5db136f703c98736ac583@haskell.org> References: <047.5a091b0736d5db136f703c98736ac583@haskell.org> Message-ID: <062.0bef7399176467427ff8a5226f7f8d25@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Replying to [comment:2 rwbarton]: > You can still save the work of doing a multiplication in GMP, you just have to force evaluation of the other argument when you do so. I'm not sure I understand that; a multiplication with 0 would have made no sense to dispatched a call into GMP anyway, that's not the cost I'm worried about. It's rather forcing of the other argument that may trigger all sorts of potentially costly evaluations and GMP-calls only to ultimately absorb it into a `0`-result... -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 00:41:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 00:41:52 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy In-Reply-To: <047.5a091b0736d5db136f703c98736ac583@haskell.org> References: <047.5a091b0736d5db136f703c98736ac583@haskell.org> Message-ID: <062.cf84b77981dd49ed2d17fdafce202f8a@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): On the other hand - Making `(*)` strict means the strictness analyser can prevent some cases of thunk build-up when the accumulated expression is going to be multiplied by a variable. Most of the time the value that is in the lazy argument position of `(*)` really will be needed, and much of the rest of the time (when the integers involved are small) computing it will be cheaper than building the thunks anyways. It's quite possible that there will be speed-ups in nofib from a strict `(*)` as well as slow-downs. - There are two different ways to make a `(*)` that is lazy when one argument is zero (it can't be lazy on both sides), and the one currently chosen in integer-gmp is not documented, nor is it consistent between different operations (`undefined * 0 = 0`, but `0 .&. undefined = 0`). - It's easy and cheap to turn any of the three versions (strict in both arguments, lazy in first argument, lazy in second argument) into any other, so I don't think there is much value in providing more than one. None is strictly superior or inferior to the others in terms of performance, and the version that is strict in both arguments is clearly the least surprising choice for several reasons. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 00:58:43 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 00:58:43 -0000 Subject: [GHC] #10506: SourceNotes are not applied to all identifiers In-Reply-To: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> References: <049.4498c09b08bd56b963d5dfbd770a867b@haskell.org> Message-ID: <064.f6bdd68f3225dde33d35feb4468cd4a8@haskell.org> #10506: SourceNotes are not applied to all identifiers -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by gridaphobe): Hrm, this patch doesn't produce the output I would expect. Consider {{{ module Bar where bar = 1 + 2 }}} {{{ $ ghc -ddump-tick-vars -ddump-ticked -g bar.hs [1 of 1] Compiling Bar ( bar.hs, bar.o ) AbsBinds [] [] {Exports: [bar <= bar_amB <>] Exported types: bar :: Integer [LclId, Str=DmdType] Binds: -- ticks = [src] bar_amB = src (+) src 1 src 2} }}} The tick on the `(+)` spans the whole application, which is not precise enough for us. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 06:46:36 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 06:46:36 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.fe08cd9f8707ddaa944a1e441a2c4ae6@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8326, #8327 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Wait! I believe that you are saying that {{{ case na# ==# nb# of 0# -> e1 _ -> e2 }}} generates much worse code than {{{ case isTrue# (na# ==# nb#) of False -> e1 True -> e2 }}} even though the former appears more primitive. This is all very odd and either deserves to be fixed, or at least documented somewhere prominent! Where would be a good place to document it? Perhaps with the primops for `(==)#`, `(>=)#`, etc? Or with `isTrue#`? And we need a ticket to say "let's fix this". Speaking of which do you know why it behaves so badly? Just changing the code is leaving land-mines for future generations :-). Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 06:48:21 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 06:48:21 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy In-Reply-To: <047.5a091b0736d5db136f703c98736ac583@haskell.org> References: <047.5a091b0736d5db136f703c98736ac583@haskell.org> Message-ID: <062.0adf66ec36a51bb4b0614874511475bc@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by hvr): Fair enough... (but I'd still want a `nofib` delta to see if this has any noteworthy impact...) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 06:55:27 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 06:55:27 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.5c5afdaece575cd62bf78e0ac40e74ac@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8326, #8327, | Differential Revisions: #9661 | -------------------------------------+------------------------------------- Changes (by jstolarek): * related: #8326, #8327 => #8326, #8327, #9661 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 06:55:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 06:55:48 -0000 Subject: [GHC] #10676: silly assembly for comparing the result of comparisons that return Int# against 0# In-Reply-To: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> References: <047.c9f81303ccca01d21593f2a37d62e3ce@haskell.org> Message-ID: <062.8595b136ba5f29f969bd8329ba719ce9@haskell.org> #10676: silly assembly for comparing the result of comparisons that return Int# against 0# -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8326, #8327, | Differential Revisions: #9661 | -------------------------------------+------------------------------------- Comment (by jstolarek): #9661 might be related here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 07:25:03 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 07:25:03 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.13bf434333a19ad51c2fee5c23da8d02@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Interesting. Now that you understand what went wrong, you could write a note explaining the trap you fell into, and share it with others. It is, after all, rather surprising when you are told "omit a type signature and you get an infinite loop". Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 07:37:57 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 07:37:57 -0000 Subject: [GHC] #10675: GHC does not check the functional dependency consistency condition correctly In-Reply-To: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> References: <046.c63a3d5abf02d779fbe6a1e8e4a5d19e@haskell.org> Message-ID: <061.7f6f1387b9f961f5e836c51ffcb6fb0e@haskell.org> #10675: GHC does not check the functional dependency consistency condition correctly -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes, good link! I agree with Richard: we just just make these programs illegal. #9210 is a particularly egregious case of what can go wrong otherwise. I would like Iavor's opinion before doing this. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 07:46:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 07:46:52 -0000 Subject: [GHC] #10691: certain operations in new integer-gmp are too lazy In-Reply-To: <047.5a091b0736d5db136f703c98736ac583@haskell.org> References: <047.5a091b0736d5db136f703c98736ac583@haskell.org> Message-ID: <062.008e02c1820e2b8373655920672c61af@haskell.org> #10691: certain operations in new integer-gmp are too lazy -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: libraries | Version: 7.10.1 (other) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I agree with Reid's points in comment:4 Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 07:47:48 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 07:47:48 -0000 Subject: [GHC] #10678: integer-gmp's runS seems unnecessarily expensive In-Reply-To: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> References: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> Message-ID: <062.6d20e045eba1708e425a82d625a44301@haskell.org> #10678: integer-gmp's runS seems unnecessarily expensive -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Great! Thank you. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 07:54:32 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 07:54:32 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.31687be44dfc1168d5ce8fa97b4322e2@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by darchon): For me, the ''two'' bugs seem pretty clear: - GHC bug: When linking a dynamic ''library'', GHC does not pass the {{{-framework}}} flags to the system linker. - Cabal bug: The {{{-framework}}} flags that should be passed to GHC somehow get lost. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 08:18:49 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 08:18:49 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.cbc29a41ade3c5ac16ff9afc801f5146@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by bgamari): darchon, aren't these both symptoms of the same Cabal bug? Namely that `-framework` isn't passed to GHC. It would be great if someone could track down why this is the case. While I don't believe ?https://github.com/haskell/cabal/issues/2689 is terribly related to the current issue, it would be great if someone could have a look at (or, even better, test) https://github.com/haskell/cabal/pull/2739, which fixes #2689. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 08:47:23 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 08:47:23 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.304c9ce6f1748bee2d4d621397abefb5@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by darchon): Replying to [comment:40 bgamari]: > darchon, aren't these both symptoms of the same Cabal bug? Namely that `-framework` isn't passed to GHC. It would be great if someone could track down why this is the case. I would find that hard to believe... because, as seen in comment:21 and comment:27, passing the {{{--ghc-options="-framework GLUT"}}} options to Cabal still doesn't make GHC pass the {{{-framework}}} flag to the system linker. I would find it extremely hard to believe that Cabal: 1. Parses the content of {{{--ghc-options}}} and 2. then actively deletes/filters the {{{-framework}}} part. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 09:27:54 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 09:27:54 -0000 Subject: [GHC] #10001: GHC crash trying to build a project within Nix-shell In-Reply-To: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> References: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> Message-ID: <062.4cc83198d26bbd0d0ad3dc8bd9fd6280@haskell.org> #10001: GHC crash trying to build a project within Nix-shell -------------------------------------+------------------------------------- Reporter: wolftune | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: 9825 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by johnleuner): I managed to work around this problem by creating a temporary directory in my working directory. From my nix shell: export TMPDIR=$(pwd)/temp cabal install -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 09:32:50 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 09:32:50 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.6c52d3b7575a99dae6683f7e6431baa9@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Comment (by bgamari): Replying to [comment:41 darchon]: > Replying to [comment:40 bgamari]: > > darchon, aren't these both symptoms of the same Cabal bug? Namely that `-framework` isn't passed to GHC. It would be great if someone could track down why this is the case. > > I would find that hard to believe... because, as seen in comment:21 and comment:27, passing the {{{--ghc-options="-framework GLUT"}}} options to Cabal still doesn't make GHC pass the {{{-framework}}} flag to the system linker. Ahh, I had forgotten about this result. Yes, this does sound suspicious. Thanks! I believe the relevant portion of GHC is [https://ghc.haskell.org/trac/ghc/browser/ghc/compiler/main/DriverPipeline.hs#L1748 DriverPipeline.linkBinary]. The framework logic there looks correct but it would be nice if someone with access to OS X could add some traces so we could figure out where things are going awry. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 11:25:49 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 11:25:49 -0000 Subject: [GHC] #10001: GHC crash trying to build a project within Nix-shell In-Reply-To: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> References: <047.a911662f59d5386fa0d95515f4c6d044@haskell.org> Message-ID: <062.f099311c3978f70344bc05b47623e04c@haskell.org> #10001: GHC crash trying to build a project within Nix-shell -------------------------------------+------------------------------------- Reporter: wolftune | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: 9825 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by spl): * cc: sean.leather@? (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 11:49:05 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 11:49:05 -0000 Subject: [GHC] #8347: Add a Strict LANGUAGE pragma In-Reply-To: <044.d01bb368b2606104539d1aa05530b018@haskell.org> References: <044.d01bb368b2606104539d1aa05530b018@haskell.org> Message-ID: <059.6f669b12a876c45a6b60279dbbc7dfd0@haskell.org> #8347: Add a Strict LANGUAGE pragma -------------------------------------+------------------------------------- Reporter: tibbe | Owner: tibbe Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1033 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"f842ad6c751c14ec331ca1709538c2f3e9a30ae7/ghc" f842ad6/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="f842ad6c751c14ec331ca1709538c2f3e9a30ae7" Implementation of StrictData language extension This implements the `StrictData` language extension, which lets the programmer default to strict data fields in datatype declarations on a per-module basis. Specification and motivation can be found at https://ghc.haskell.org/trac/ghc/wiki/StrictPragma This includes a tricky parser change due to conflicts regarding `~` in the type level syntax: all ~'s are parsed as strictness annotations (see `strict_mark` in Parser.y) and then turned into equality constraints at the appropriate places using `RdrHsSyn.splitTilde`. Updates haddock submodule. Test Plan: Validate through Harbormaster. Reviewers: goldfire, austin, hvr, simonpj, tibbe, bgamari Reviewed By: simonpj, tibbe, bgamari Subscribers: lelf, simonpj, alanz, goldfire, thomie, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D1033 GHC Trac Issues: #8347 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 11:49:05 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 11:49:05 -0000 Subject: [GHC] #10522: Add UInfixT, like UInfixE or UInfixP but for types In-Reply-To: <045.117758279834e73fff10891f1400af9d@haskell.org> References: <045.117758279834e73fff10891f1400af9d@haskell.org> Message-ID: <060.76340a8b02d021ca6491ddfd450638d4@haskell.org> #10522: Add UInfixT, like UInfixE or UInfixP but for types -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1088 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"217827393dcacd0ef696c4f9f6136e21b3be63a8/ghc" 2178273/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="217827393dcacd0ef696c4f9f6136e21b3be63a8" Add UInfixT to TH types (fixes #10522) UInfixT is like UInfixE or UInfixP but for types. Template Haskell splices can use it to punt fixity handling to GHC when constructing types. UInfixT is converted in compiler/hsSyn/Convert to a right-biased tree of HsOpTy, which is already rearranged in compiler/rename/RnTypes to match operator fixities. This patch consists of (1) adding UInfixT to the AST, (2) implementing the conversion and updating relevant comments, (3) updating pretty-printing and library support, and (4) adding tests. Test Plan: validate Reviewers: austin, goldfire, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1088 GHC Trac Issues: #10522 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 11:54:35 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 11:54:35 -0000 Subject: [GHC] #8199: Get rid of HEAP_ALLOCED In-Reply-To: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> References: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> Message-ID: <060.3d6c035f3d76abb37277d5d646bb3b63@haskell.org> #8199: Get rid of HEAP_ALLOCED -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 5435 | Blocking: Related Tickets: | Differential Revisions: D207 -------------------------------------+------------------------------------- Comment (by simonmar): I wonder whether we might try an alternative strategy on Windows: a bitmap covering the whole 48-bit address space (units of 1MB) is only 32MB, and most of it won't be touched in the common case. The remaining question is whether checking this bitmap can be made as cheap as the current cache. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 12:00:41 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 12:00:41 -0000 Subject: [GHC] #10522: Add UInfixT, like UInfixE or UInfixP but for types In-Reply-To: <045.117758279834e73fff10891f1400af9d@haskell.org> References: <045.117758279834e73fff10891f1400af9d@haskell.org> Message-ID: <060.f47b53fdff9fe24ab50df241a0cb5f93@haskell.org> #10522: Add UInfixT, like UInfixE or UInfixP but for types -------------------------------------+------------------------------------- Reporter: spinda | Owner: spinda Type: feature request | Status: closed Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1088 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 12:01:42 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 12:01:42 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.fd29e9891d6f38e806f0e779c05a3c0b@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Aha! RULE `TEXT literal` is terribly fragile: * In `GHC.Base` we have {{{ {-# RULES "unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a) "unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a }}} * `build` inlines in phase 1 So, transformation goes like this: {{{ Start with fromString (unpackCString# "blah"#) ---> (simplify: gentle phase) fire rule "unpack" fromString (build (unpackFoldrCString# "blah"#)) ---> (simplify: phase2) inline fromString Data.Text.pack (build (unpackFoldrCString# "blah"#)) ---> (simplify: phase1) inline pack, build, fire rule "unpack-list" unstream (map safe (streamList (unpackCString# "blah"#))) }}} Now you'd think that rule "TEXT literal" would now fire. But its LHS too has been rewritten by RULE "unpack" to {{{ "TEXT literal" [ALWAYS] forall a :: Addr# unstream (map safe (streamList @ Char (build @ Char (\ @ b -> unpackFoldrCString# @ b a)))) = unpackCString# a }}} You can see this by doing `ghc --show-iface Data/Text/Show.hi`, incidentally. Why did that happen? Arguably it's a bug: we should not rewrite the LHS of a rule with other rules, any more than we should inline functions on the LHS of a rule. But it betrays a potential flaw in the rule setup. Consider a source- program expression `(unnstream (map safe (streamList (unpackCString# "foo"))))`. Since there is a rule for `unpackCString#`, there is no guarantee that rule `TEXT literal` will fire before rule `unpack`. In this case we know that the `unpackCString#` call will eventually be rewritten back into `unpackCString#`. But it would be better to express that directly by saying {{{ {-# RULES [2] "TEXT literal" forall a. unstream (S.map safe (S.streamList (GHC.unpackCString# a))) = unpackCString# a #-} }}} Now the two rules do not compete, and all will be good. So there are several things to say here * GHC probably should do no inlining and no rule rewriting on LHS of rules. I'll fix that. * GHC already warns when an inlining competes with a rule; but it should also warn if a rule competes with a rule. I'll fix that too. * To eliminate the warning, rule "TEXT literal" should be fixed as above. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 13:31:40 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 13:31:40 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.e5ef7a006aa31fcdc13162aa7baf973f@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Ahh, I should have thought to check the interface file! That being said, I never would have expected the rewrite of the LHS. I'll open a pull request against `text` fixing the rule. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 13:47:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 13:47:55 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.391db6fab5b1651a2c31e7b232afb328@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"bc4b64ca5b99bff6b3d5051b57cb2bc52bd4c841/ghc" bc4b64ca/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="bc4b64ca5b99bff6b3d5051b57cb2bc52bd4c841" Do not inline or apply rules on LHS of rules This is the right thing to do anyway, and fixes Trac #10528 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 13:47:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 13:47:55 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.ea47292a7768a986b135eb4084c9a923@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4/ghc" 2d88a531/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4" Improve warnings for rules that might not fire Two main things here * Previously we only warned about the "head" function of the rule, but actually the warning applies to any free variable on the LHS. * We now warn not only when one of these free vars can inline, but also if it has an active RULE (c.f. Trac #10528) See Note [Rules and inlining/other rules] in Desugar This actually shows up quite a few warnings in the libraries, notably in Control.Arrow, where it correctly points out that rules like "compose/arr" forall f g . (arr f) . (arr g) = arr (f . g) might never fire, because the rule for 'arr' (dictionary selection) might fire first. I'm not really sure what to do here; there is some discussion in Trac #10595. A minor change is adding BasicTypes.pprRuleName to pretty-print RuleName. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 13:47:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 13:47:55 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.1db8505d9a4b7b7867f52ee4bdf62203@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.11 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4/ghc" 2d88a531/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4" Improve warnings for rules that might not fire Two main things here * Previously we only warned about the "head" function of the rule, but actually the warning applies to any free variable on the LHS. * We now warn not only when one of these free vars can inline, but also if it has an active RULE (c.f. Trac #10528) See Note [Rules and inlining/other rules] in Desugar This actually shows up quite a few warnings in the libraries, notably in Control.Arrow, where it correctly points out that rules like "compose/arr" forall f g . (arr f) . (arr g) = arr (f . g) might never fire, because the rule for 'arr' (dictionary selection) might fire first. I'm not really sure what to do here; there is some discussion in Trac #10595. A minor change is adding BasicTypes.pprRuleName to pretty-print RuleName. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 13:50:10 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 13:50:10 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.209314b40eb2dbdc3321a11b843d6929@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): The commit in comment:15 fixes this regression, regardless of the change to the "TEXT literal" rule I'll leave this open because * We might want to merge to 7.10.3 * There's still an open question about rules for class methods (see comment:16) Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 14:40:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 14:40:53 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.2f6aa8fb10b13b723ebf7ce96aa79907@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: scpmw Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Comment (by simonpj): Try the effect of changing (in `SimplCore`): {{{ ; guts' <- lintAnnots (ppr pass) (doCorePass pass) guts }}} to {{{ ; guts' <- lintAnnots (ppr pass) (\p -> doCorePass pass p) guts }}} Simon M speculates that this might work around the problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 14:47:12 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 14:47:12 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.4047d117a564c5fce502959d1db210e8@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * priority: normal => high * milestone: => 7.10.2 Comment: Bumping priority, as these sorts of bugs regularly get reported to me. But there's an easy workaround, so this certainly shouldn't be "highest". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 14:58:50 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 14:58:50 -0000 Subject: [GHC] #10685: ghci segfaults on Travis In-Reply-To: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> References: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> Message-ID: <060.70ffd1b88bded30c3c9cd0f61ad785b2@haskell.org> #10685: ghci segfaults on Travis -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonmar): * owner: => simonmar Comment: I reverted the patch, I'll look into this and the reported perf regression in `fannkuch-redux` https://phabricator.haskell.org/rGHCb949c96b4960 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 14:59:56 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 14:59:56 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.9c0dad7ddd15e5f3a6fec7108e59f676@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: scpmw Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Comment (by scpmw): Unfortunately, I am pretty sure I tested that - and it doesn't work. The easiest workaround is updating all `doCorePass` equations as follows: {{{ doCorePass pass@(CoreDoSimplify {}) guts = {-# SCC "Simplify" #-} simplifyPgm pass guts }}} Which avoids this problem by not putting the SCC on a function-type value. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:02:42 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:02:42 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.9eee53a868442acf806c28405971fd5e@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: closed => merge * milestone: 7.12.1 => 7.10.2 Comment: This '''does''' happen in the tip of the 7.10 branch. But you need a DEBUG build to know that. Please merge the commit above. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:12:17 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:12:17 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.e5a84d97c4f41238fa64604e206cccac@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: highest | Milestone: 7.10.2 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Then that test should include the setup function `unless(compiler_debugged(), skip)`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:31:02 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:31:02 -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.b8c227fc549f88b747e7929867a19043@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): ezyang says: > This seems to definitely suggest that you should never need more than two levels of hs-boot nesting, or perhaps three with kinding. (But maybe someone has a fancy type system feature for which this is not true!) I believe I have such a fancy type system feature. My solution to #7961 (that is, my very long-running "nokinds" [https://github.com/goldfirere/ghc/ branch], due to be merged Any Season Now [at least it's better than Any Year Now]) merges types with kinds, allowing an arbitrary number of "levels". In other words, I think a pathological case can (if I understand your proposal here correctly) require an arbitrary number of hs-boot levels. For example: {{{ data A data B :: A -> * data C :: B a -> * data D :: C b -> * data E :: D c -> * }}} This compiles fine on my branch, but I believe would cause problems with this proposal. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:42:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:42:53 -0000 Subject: [GHC] #7647: UNPACK polymorphic fields In-Reply-To: <045.8091f80cf766b683cf12520609e77aee@haskell.org> References: <045.8091f80cf766b683cf12520609e77aee@haskell.org> Message-ID: <060.447a7f2d8224ad54eb4ad159c88e5ecb@haskell.org> #7647: UNPACK polymorphic fields -------------------------------------+------------------------------------- Reporter: liyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #3990 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: MikeIzbicki (added) * related: 3990 => #3990 Comment: See this [https://izbicki.me/blog/fast-nearest-neighbor-queries-in- haskell.html blog post] for a request for "polymorphic unpacking", in the section "Lesson 1: Polymorphic code in GHC is slower than it needs to be." The blog post also refers to a [https://www.reddit.com/r/haskell/comments/29onpf/why_does_ghc_always_box_polymorphic_fields_in/ reddit discussion] on the subject. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:43:54 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:43:54 -0000 Subject: [GHC] #7647: UNPACK polymorphic fields In-Reply-To: <045.8091f80cf766b683cf12520609e77aee@haskell.org> References: <045.8091f80cf766b683cf12520609e77aee@haskell.org> Message-ID: <060.983a0bf782319d031b93afad0856ce0b@haskell.org> #7647: UNPACK polymorphic fields -------------------------------------+------------------------------------- Reporter: liyang | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #3990 #9655 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * related: #3990 => #3990 #9655 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:56:52 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:56:52 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.750bb3d72c33f1c156f3b22b1c79d852@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: scpmw Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Comment (by bgamari): scpmw, I've tested Simon's suggestion on `master` and it appears to work for me. Costs are correctly attributed to cost-centers beneath `lintAnnots`. I'll be merging this to `master`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 15:57:39 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 15:57:39 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.854a656efdf43ad866aff1a74c5564dd@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): See this [https://izbicki.me/blog/fast-nearest-neighbor-queries-in- haskell.html blog post] for a use case for this feature, towards the end of "Lesson 4: Haskell?s standard libraries were not designed for fast numeric computing." -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:02:57 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:02:57 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.d915dbd23399dc587b7619d7ee44adb8@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: scpmw Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Comment (by scpmw): Interesting. I checked, and the code I used to reproduce the problem was exactly what simonpj suggested, but with an extra SCC on the `doCorePass` call. That way, I could catch exactly the "leaking" costs. Maybe that annotation also changed the compiler behaviour sufficiently to stop this from working. Anyway, all the better. Maybe we should close this ticket then, and continue the discussion of the larger issue in #5654? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:13:34 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:13:34 -0000 Subject: [GHC] #10685: ghci segfaults on Travis In-Reply-To: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> References: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> Message-ID: <060.a6dcf6e1d383d182c0facaef8a0c868c@haskell.org> #10685: ghci segfaults on Travis -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonmar Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: GHCi | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): thomie, are you sure this was reproducible with 09d05050346c1be7bac20ba3f40861e05217368b? There was indeed a bug affecting ghci in the initial `zero_static_objects_list` patch but I fixed it in that commit. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:29:08 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:29:08 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.d50addc1a1b74c343925b91e18240fd7@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Ideophage): Replying to [comment:6 simonpj]: > Interesting. Now that you understand what went wrong, you could write a note explaining the trap you fell into, and share it with others. It is, after all, rather surprising when you are told "omit a type signature and you get an infinite loop". > > Simon I don't know if it's always the case, but according to my tests, the type inferrence algorithm specialize the types without class constraints (however, if we enter `:t (unlines . map show)` in GHCi, the polymorphic type is inferred). For instance, the following code either prints "1" or generates an error depending on whether we comment out or not the definition of `print_b` (which is not used)?: {{{#!hs a = (2^64) `div` (2^64) -- 64 or 32 b = length [] show' = show print_a = print $ show' a -- print_b = print $ show' b main = print_a }}} This is because if we apply `show'` to `b`, then the inferred type of `show'` becomes `Int ? String` (I expected it to be the same as `show`) and because we also apply it to `a`, the inferred type of `a` becomes `Int`. The ??types implication graph?? of the code I first gave was more complex, but there is nothing more than this involved. I thought it was a bug because I assumed GHC's Haskell was referentially transparent even without explicit types annotations (so that expanding a definition, adding a definition, etc. was not supposed to make a program do something else), but I don't know what is feasible. The infinite loop is due to the fact that the termination rely on arithmetic properties of `Integer`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:37:30 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:37:30 -0000 Subject: [GHC] #10688: Incorrect program produced, different result with equivalent code In-Reply-To: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> References: <048.ed29a6a3bb22cb9764399752d229ffca@haskell.org> Message-ID: <063.5730d6e63189715bc82746f2b9309412@haskell.org> #10688: Incorrect program produced, different result with equivalent code -------------------------------------+------------------------------------- Reporter: Ideophage | Owner: Type: bug | Status: closed Priority: lowest | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Right, it's not a bug, but it is a confusing consequence of the monomorphism restriction together with defaulting and type inference. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:49:35 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:49:35 -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.10f412404aaeeb19b138505dbbbc74f9@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by ezyang): Thanks Richard. Do you have any examples which would require "infinitely" many levels? Your example requires an arbitrary number of levels, but it's always finite. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:55:41 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:55:41 -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.1f9dfbdc6529d9299b77278b11a215ae@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): I don't, at the moment. But I conjecture they're possible. The "infinite" case would correspond to programs that aren't writable in Agda/Coq/Idris due to their universe hierarchy. I hear tell of programmers running into this limitation occasionally, but I don't know if the cases are pathological or not. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:56:53 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:56:53 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.b9dfbb7b65225660a5599483ad2b8b67@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.2 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Confirmed reproducible on the 7.10 tip, and in a recent HEAD. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 16:59:55 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 16:59:55 -0000 Subject: [GHC] #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter In-Reply-To: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> References: <050.3a603b13f2e5db743d4a3b6e8b6ae555@haskell.org> Message-ID: <065.8ff9b34c24f0618a00297101fdf91a72@haskell.org> #10620: Primitive chars and strings aren't handled by Template Haskell's quasiquoter -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: th/T10620 Blocked By: | Blocking: Related Tickets: #4168, #5218, | Differential Revisions: Phab:D1054 #5877, | -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => fixed Comment: This seems all set. Correct me if I'm wrong. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 17:26:35 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 17:26:35 -0000 Subject: [GHC] #10007: Fix misattribution of Cost Centre profiles to lintAnnots In-Reply-To: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> References: <052.018bee922f3a1f3c0286b790702cf38d@haskell.org> Message-ID: <067.2d3871df95d7009d472e346bb20dddb1@haskell.org> #10007: Fix misattribution of Cost Centre profiles to lintAnnots -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: scpmw Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Profiling | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #9961 | Differential Revisions: Phab:D616 | Phab:D636 -------------------------------------+------------------------------------- Comment (by bgamari): Hmm, actually it seems that `master` is now doing the right thing even without my patch. I am quite confused. I'll return to this after the release. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 17:38:44 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 17:38:44 -0000 Subject: [GHC] #10693: Profile ghc -j with an eye for performance issues Message-ID: <046.6fd3f063432c26f27d6b1f5e1971e2d7@haskell.org> #10693: Profile ghc -j with an eye for performance issues -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- `ghc -j` doesn't seem to scale as well as it could. Reports claim that even packages with embarasssingly parallel module structures (e.g. `highlighting-kate`) only scale out to three or so processors. Profiling a parallel build would be a useful first step to finding out why. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 17:42:36 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 17:42:36 -0000 Subject: [GHC] #10693: Profile ghc -j with an eye for performance issues In-Reply-To: <046.6fd3f063432c26f27d6b1f5e1971e2d7@haskell.org> References: <046.6fd3f063432c26f27d6b1f5e1971e2d7@haskell.org> Message-ID: <061.246e4ca2db4b82bb9b478592d4d0ceff@haskell.org> #10693: Profile ghc -j with an eye for performance issues -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9221 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #9221 Comment: Oops, looks like #9221 already reported this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 17:44:18 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 17:44:18 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.64d7ea8faca39750090cbf383a57d7a9@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): For future readers, `highlighting-kate` would likely be an excellent package to benchmark with as it has a large number of largely independent modules. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 17:59:18 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 17:59:18 -0000 Subject: [GHC] #8199: Get rid of HEAP_ALLOCED In-Reply-To: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> References: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> Message-ID: <060.02c0ce9ed82f16fbde2ef1b2e237e984@haskell.org> #8199: Get rid of HEAP_ALLOCED -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 5435 | Blocking: Related Tickets: | Differential Revisions: D207 -------------------------------------+------------------------------------- Comment (by ezyang): Reproducing some comments from the Phabricator diff for posterity. #9706 didn't work on Windows because Windows counted page table memory as part of committed memory. Go has the same problem: {{{ // Number of bits in page to span calculations (4k pages). // On Windows 64-bit we limit the arena to 32GB or 35 bits. // Windows counts memory used by page table into committed memory // of the process, so we can't reserve too much memory. // See https://golang.org/issue/5402 and https://golang.org/issue/5236. // On other 64-bit platforms, we limit the arena to 512GB, or 39 bits. // On 32-bit, we don't bother limiting anything, so we use the full 32-bit address. // On Darwin/arm64, we cannot reserve more than ~5GB of virtual memory, // but as most devices have less than 4GB of physical memory anyway, we // try to be conservative here, and only ask for a 2GB heap. }}} The links are good reading: https://golang.org/issue/5402 and https://golang.org/issue/5236 (scroll down). Note that there is a little bit about Go relying on overcommitting causing problems for people on systems that don't overcommit; this is not relevant to us since we're not actually committing memory and relying on the OS to lazily initialize it if they don't actually use it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 18:02:26 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 18:02:26 -0000 Subject: [GHC] #8199: Get rid of HEAP_ALLOCED In-Reply-To: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> References: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> Message-ID: <060.c52c6171c07df8039844bd95b703c571@haskell.org> #8199: Get rid of HEAP_ALLOCED -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 5435 | Blocking: Related Tickets: | Differential Revisions: D207 -------------------------------------+------------------------------------- Comment (by ezyang): Simon, are you thinking doing some sort of lazy committing for the 32MB bitmap, so that most of it doesn't need to backed with real memory? I guess I don't see any reason this shouldn't work. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 18:14:04 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 18:14:04 -0000 Subject: [GHC] #10680: Make Backpack order-independent (again) In-Reply-To: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> References: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> Message-ID: <060.8039dd152e228e3720b173bf9276f9bf@haskell.org> #10680: Make Backpack order-independent (again) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package system | 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 Revisions: -------------------------------------+------------------------------------- Description changed by ezyang: Old description: > When we moved to the new `bkp` file format, we also went back to the a > format which is order-dependent: that is to say, the order in which you > put the declarations matters. So if you write: > > {{{ > unit p where > module A where > import B > module B where > ... > }}} > > this fails to type-check, GHC complaining that `B` is not in scope. I > did this, in part because it's what the Backpack paper described, and > because it was "simpler" to implement. > > I think we should move back to an order-independent scheme, for the > following reasons: > > 1. Haskell users are used to not needing pay particularly close attention > to the ordering of their modules, and forcing people to linearize their > module descriptions would be spectacularly disruptive with large amounts > of modules. So un-ordered modules are "more natural. > > 2. Order-independence imposes some constraints on how expressive programs > are (with order-dependent Backpack, you can do some pretty tricky things > by ordering things certain ways); this could simplify some aspects of > compiler implementation and make Backpack easier to explain. > > 3. A particular case of (2): it seems a lot simpler UX-wise to let a user > assume that if you import a module `M` in a unit, it doesn't matter where > you import it: you always get the same set of identifiers brought into > scope. Thus, the incremental results of signatures should not be visible, > c.f. #10679 > > The main idea is that only the surface-syntax is un-ordered: the internal > representation of units is a DAG which we work out in an elaboration > phase, not altogether unsimilar from what `GhcMake` computes. > > Here are the details: > > **The intermediate representation.** We translate into an intermediate > representation which consists of a directed graph between modules, > signatures and includes. Edges in the graph indicate a "depends on" > relation: > > 1. `include p` depends on `include q` if, for some module name `H`, `p` > requires `H` and `q` provides `H`. > 2. A module/signature `M` depends on `include p` if `M` imports a module > provided or required by `p`. > 3. A module/signature `M` depends on a module/signature `S` if `M` > imports `S`. > 4. An `include p` depends on a module `M` if `p` requires a module named > `M`. (This rule is included for completeness; we are going to disallow it > shortly.) > > We impose one restriction: a signature cannot depend on a home module. > See below for how to eliminate this restriction. > > Rule (2) is worth remarking upon: if a module imports a signature, it > depends-on every `include` which requires that signature, as well as the > relevant home signature. This could easily result in a cycle; see (2) > for how to break these cycles. The consequence of this, however, is that > we can factor the graph to introduce the node for the "merge of > signatures", which depends on each signature and include which requires > it; we can use this opportunity to build and write out the merged > interface file for the unit. > > **Elaboration.** Take a Backpack file, construct this graph, and topsort > it into a DAG of SCCs. SCCs with a single node are compileable as before. > SCCs with multiple nodes will have to be managed with some mutual > recursion mechanism; see refinements for more thoughts on this. > > **Refinements:** > > 1. **Can a signature depend on a (home) module?** Imports of this kind > require a retypecheck loop. Consider this situation: > {{{ > unit p where > signature H where > data T > module M where > import H > data S = S T > unit q where > include p > module Q where > import M > signature H where > import Q > data T = T S > }}} > Here, signature H in q depends on Q. When we typecheck `Q`, we bring > `M.S` into the type environment with a `TyThing` that describes the > constructor as accepting an abstract type `T`. However, when we > subsequently typecheck the local signature `H`, we must refine all > `TyThing`s of `T` with the true description (e.g. constructor > information). So you'll need to retypecheck `Q` (and `M`) in order to > make sure the `TyThing` is correct. > > 2. **Can an include depend on a (home) module?** If the module has no > (transitive) dependency on signatures, this is fine. However, it's easy > to have a circular dependency. Consider: > {{{ > unit p where > signature A > signature B > module M > unit q where > include p > module B where > import A > ... > }}} > `B` depends on `p` for `p/A.hsig`; however, `p` depends on `B` because > this module is filling a requirement. Fortunately, we can untangle this > knot without any mutual recursion nonsense (and the attendant efficiency > loss): `A` is just an export list, we can compute it from the abstractly > type-checked version of `p` without instantiating `B`. > > 3. **Can we deal with include-include dependency cycles?** Yes! Just use > the Backpack paper's strategy for creating a recursive unit key and > compile the two packages `hs-boot` style. But I'm not planning on > implementing this yet. > > 4. **Can we deal with signature-signature dependency cycles?** Ordered > Backpack would have supported this: > {{{ > unit a-sig where > signature A where > data T > unit ab-sig where > include a-sig > signature B where > import A > data S = S T > signature A where > import B > data T = T S > }}} > In our model, `ab-sig` has a cycle. However, I believe any such cycle > can be broken by creating sufficiently many units: > {{{ > unit a-sig where > signature B where > data T > signature A where > data S = S T > unit b-sig where > signature A where > data S > signature B where > data T = T S > unit ab-sig where > include a-sig > include b-sig > }}} > In principle, GHC could automatically break import cycles by replacing > an import with an import of a reduced signature that simply has abstract > type definitions. (I'm not sure this is possible for all language > features.) This technique would also work for normal modules, assuming > that every function is explicitly annotated with a type. New description: When we moved to the new `bkp` file format, we also went back to the a format which is order-dependent: that is to say, the order in which you put the declarations matters. So if you write: {{{ unit p where module A where import B module B where ... }}} this fails to type-check, GHC complaining that `B` is not in scope. I did this, in part because it's what the Backpack paper described, and because it was "simpler" to implement. I think we should move back to an order-independent scheme, for the following reasons: 1. Haskell users are used to not needing pay particularly close attention to the ordering of their modules, and forcing people to linearize their module descriptions would be spectacularly disruptive with large amounts of modules. So un-ordered modules are "more natural for a traditional Haskell user. 2. Order-independence imposes some constraints on how expressive programs are (with order-dependent Backpack, you can do some pretty tricky things by ordering things certain ways); this could simplify some aspects of compiler implementation and make Backpack easier to explain. 3. A particular case of (2): it seems a lot simpler UX-wise to let a user assume that if you import a module `M` in a unit, it doesn't matter where you import it: you always get the same set of identifiers brought into scope. Thus, the incremental results of signatures should not be visible, c.f. #10679 The main idea is that only the surface-syntax is un-ordered: the internal representation of units is a DAG which we work out in an elaboration phase, not altogether unsimilar from what `GhcMake` computes. An important auxiliary idea is that `import A` where `A` is backed by some signatures depends on EVERY signature in scope. Here are the details: **The intermediate representation.** We translate into an intermediate representation which consists of a directed graph between modules, signatures and includes. Edges in the graph indicate a "depends on" relation: 1. `include p` depends on `include q` if, for some module name `H`, `p` requires `H` and `q` provides `H`. 2. A module/signature `M` depends on `include p` if `M` imports a module provided or required by `p`. 3. A module/signature `M` depends on a module/signature `S` if `M` imports `S`. 4. An `include p` depends on a module `M` if `p` requires a module named `M`. We impose one restriction: a signature cannot depend on a home module. (But see below for how to eliminate this restriction.) Rule (2) is worth remarking upon: if a module imports a signature, it depends-on every `include` which requires that signature, as well as the relevant home signature. This could easily result in a cycle; see refinement 2 for how to break these cycles. The consequence of this, however, is that we can factor the graph to introduce the node for the "merge of signatures", which depends on each signature and include which requires it; we can use this opportunity to build and write out the merged interface file for the unit which is desirable from an efficiency perspective. **Elaboration.** Take a Backpack file, construct this graph, and topsort it into a DAG of SCCs. SCCs with a single node are compileable as before. SCCs with multiple nodes will have to be managed with some mutual recursion mechanism; see refinements for more thoughts on this. **Refinements:** 1. **Can a signature depend on a (home) module?** Imports of this kind require a retypecheck loop. Consider this situation: {{{ unit p where signature H where data T module M where import H data S = S T unit q where include p module Q where import M signature H where import Q data T = T S }}} Here, signature H in q depends on Q. When we typecheck `Q`, we bring `M.S` into the type environment with a `TyThing` that describes the constructor as accepting an abstract type `T`. However, when we subsequently typecheck the local signature `H`, we must refine all `TyThing`s of `T` with the true description (e.g. constructor information). So you'll need to retypecheck `Q` (and `M`) in order to make sure the `TyThing` is correct. 2. **Can an include depend on a (home) module?** If the module has no (transitive) dependency on signatures, this is fine. However, it's easy to have a circular dependency. Consider: {{{ unit p where signature A -- imports nothing signature B -- imports nothing module M unit q where include p module B where import A ... }}} `B` depends on `p` for `p/A.hsig`; however, `p` depends on `B` because this module is filling a requirement. However, if we were to include the internal graph of `p` into `q`, the resulting graph would not have an cycles; so this is one possibility of how to untangle this situation. However, if there's still a cycle (e.g. `A` imports `B`), then you will need at least a retypecheck loop, and maybe `hs-boot` style compilation. We're not going to implement this for now. 3. **Can we deal with include-include dependency cycles?** Yes! Just use the Backpack paper's strategy for creating a recursive unit key and compile the two packages `hs-boot` style. But I'm not planning on implementing this yet. 4. **Can we deal with signature-signature dependency cycles?** Ordered Backpack would have supported this: {{{ unit a-sig where signature A where data T unit ab-sig where include a-sig signature B where import A data S = S T signature A where import B data T = T S }}} In our model, `ab-sig` has a cycle. However, I believe any such cycle can be broken by creating sufficiently many units: {{{ unit a-sig where signature B where data T signature A where data S = S T unit b-sig where signature A where data S signature B where data T = T S unit ab-sig where include a-sig include b-sig }}} In principle, GHC could automatically break import cycles by replacing an import with an import of a reduced signature that simply has abstract type definitions. See #10681. (I'm not sure this is possible for all language features.) This technique would also work for normal modules, assuming that every function is explicitly annotated with a type. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 20:12:09 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 20:12:09 -0000 Subject: [GHC] #9646: Simplifer non-determinism leading to 8 fold difference in run time performance In-Reply-To: <044.91d1be288ff53f5ea138a0b071967333@haskell.org> References: <044.91d1be288ff53f5ea138a0b071967333@haskell.org> Message-ID: <059.9efc0a9f218e97e66a23a93c5f2947a0@haskell.org> #9646: Simplifer non-determinism leading to 8 fold difference in run time performance -------------------------------------+------------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: fixed => Comment: Replying to [comment:14 jstolarek]: > It would be great if we could have a test for this so we're sure this does not regress again. I looked at the repo and the code to reproduce this is pretty big. I wonder if it could be reduced further to include it in the testsuite. Good idea. Reopening. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 20:29:41 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 20:29:41 -0000 Subject: [GHC] #4019: deriving Ord can produce incorrect and inefficient instances In-Reply-To: <041.298973948e102a278f8085229cb5ae01@haskell.org> References: <041.298973948e102a278f8085229cb5ae01@haskell.org> Message-ID: <056.a285a991f9dbe2165da5863270ed1814@haskell.org> #4019: deriving Ord can produce incorrect and inefficient instances -------------------------------------+------------------------------------- Reporter: rl | Owner: Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 6.13 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 Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: Let's skip that regression test on a bug that was fixed 5 years ago. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 20:52:19 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 20:52:19 -0000 Subject: [GHC] #10695: Trac errors when creating a ticket with a Blocking: field (was: test ticket, please ignore) In-Reply-To: <047.1d8ee7f1c6b0f872cccb3fd261b4239d@haskell.org> References: <047.1d8ee7f1c6b0f872cccb3fd261b4239d@haskell.org> Message-ID: <062.64470834deab9598159ea47f57579a42@haskell.org> #10695: Trac errors when creating a ticket with a Blocking: field -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: hvr Type: bug | Status: new Priority: normal | Milestone: Component: Trac & Git | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: 10694 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by rwbarton: Old description: > I got an error message when filing ticket #10694, though the ticket was > in fact created. The error was: > > {{{ > Trac detected an internal error: > AttributeError: 'NoneType' object has no attribute 'split' > }}} > > Possibly it had something to do with the fact that I filled in the > Blocking: field? New description: I got an error message when filing ticket #10694, though the ticket was in fact created. The error was: {{{ Trac detected an internal error: AttributeError: 'NoneType' object has no attribute 'split' }}} Possibly it had something to do with the fact that I filled in the Blocking: field? Update: I think so, since I did the same on this ticket to test and Trac errored again. If Trac is just erroring on all ticket creation I assume it will be fixed quickly :) Specifically, I entered the value `#10678` when filing #10694. Maybe I wasn't supposed to include the `#`. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 20:54:58 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 20:54:58 -0000 Subject: [GHC] #10694: CPR analysis too optimistic when returning a component of a product In-Reply-To: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> References: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> Message-ID: <062.ed3bfd2e0cbe8244c9c073d8a5bbdce7@haskell.org> #10694: CPR analysis too optimistic when returning a component of a product -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | 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: 10678 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Something funny happened while filing this ticket (see #10695) and I did not receive an email about it, so here is a content-free comment to make sure the ticket gets seen. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 20:59:19 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 20:59:19 -0000 Subject: [GHC] #10678: integer-gmp's runS seems unnecessarily expensive In-Reply-To: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> References: <047.1e3027d49179affc6473e88cc8dec51a@haskell.org> Message-ID: <062.613f43c290cf0bf70b8e483bf28b44e5@haskell.org> #10678: integer-gmp's runS seems unnecessarily expensive -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Results are mildly promising so far but I ran into an unexpected snag related to CPR analysis that is undoing some of the gains. See #10694. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 21:28:46 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 21:28:46 -0000 Subject: [GHC] #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) In-Reply-To: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> References: <044.b28ef9f55aa85f3be9d617cd7c0f70a5@haskell.org> Message-ID: <059.13d12d5f1d4935a530a8a1933a32fa74@haskell.org> #10682: AArch64: dll-split: out of memory (requested 1099512676352 bytes) ----------------------------------------+---------------------------------- Reporter: erikd | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: aarch64 Type of failure: Building GHC failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: ----------------------------------------+---------------------------------- Comment (by erikd): If I hack `configure.ac` and disable `USE_LARGE_ADDRESS_SPACE` GHC builds fine. Need to figure out why Arm64 doesn't support this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 23:21:12 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 23:21:12 -0000 Subject: [GHC] #8538: confusing specialization CORE warning, also can't mark type class instances INLINEABLE unless class defn is marked INLINEABLE In-Reply-To: <045.0346f50016bea4aa3ebc93806a21256a@haskell.org> References: <045.0346f50016bea4aa3ebc93806a21256a@haskell.org> Message-ID: <060.6ef1a1e01c0e61641c5dd6ee30c76933@haskell.org> #8538: confusing specialization CORE warning, also can't mark type class instances INLINEABLE unless class defn is marked INLINEABLE -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8848 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #8848 Comment: Fixed in #8848. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 23:26:42 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 23:26:42 -0000 Subject: [GHC] #10696: -fcpr-off doesn't disable CPR completely Message-ID: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> #10696: -fcpr-off doesn't disable CPR completely -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- `Demand.cprProdDmdType` produces nontrivial information even when `-fcpr- off` is specified. I think it's unintentional. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Mon Jul 27 23:33:46 2015 From: ghc-devs at haskell.org (GHC) Date: Mon, 27 Jul 2015 23:33:46 -0000 Subject: [GHC] #10696: -fcpr-off doesn't disable CPR completely In-Reply-To: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> References: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> Message-ID: <062.764479f2bf0c301c85859a69baef7d78@haskell.org> #10696: -fcpr-off doesn't disable CPR completely -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | 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 Revisions: Phab:D1104 -------------------------------------+------------------------------------- Changes (by rwbarton): * differential: => Phab:D1104 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 00:32:27 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 00:32:27 -0000 Subject: [GHC] #10694: CPR analysis too optimistic when returning a component of a product In-Reply-To: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> References: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> Message-ID: <062.c409aaeaff1e1bfe7e1eee8e7f410059@haskell.org> #10694: CPR analysis too optimistic when returning a component of a product -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | 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: 10678 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): To demonstrate the problem, if I build with `-funfolding-use-threshold=1` to induce w/w to run, I get this core (with `-dsuppress-all`): {{{ -- RHS size: {terms: 11, types: 9, coercions: 0} $wm $wm = \ w_sDP w1_sDQ -> case pm w_sDP w1_sDQ of _ { (pr_as8, mr_as9) -> case mr_as9 of _ { I# ww1_sDT -> ww1_sDT } } -- RHS size: {terms: 9, types: 3, coercions: 0} m m = \ w_sDP w1_sDQ -> case $wm w_sDP w1_sDQ of ww_sDT { __DEFAULT -> I# ww_sDT } }}} This can only lose, never gain, compared to not generating a worker/wrapper pair. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 03:49:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 03:49:59 -0000 Subject: [GHC] #10697: Change template-haskell API to allow NOUNPACK, lazy annotations Message-ID: <050.a6bdd5be72187642ef8374a6f8b97464@haskell.org> #10697: Change template-haskell API to allow NOUNPACK, lazy annotations -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Type: feature | Status: new request | Priority: normal | Milestone: Component: Template | Version: 7.10.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #8347 Differential Revisions: | -------------------------------------+------------------------------------- Currently, the {{{template-haskell}}} API is lagging behind what is possible with GHC's strictness annotations in data types, especially since the advent of {{{StrictData}}}. Currently, {{{template-haskell}}} has {{{Strict}}}: {{{#!hs data Strict = IsStrict | NotStrict | Unpacked }}} But it appears that there are actually nine different combinations of packedness and strictness annotations: {{{#!hs data A = A Int -- No unpackedness, no strictness data A = A !Int -- No unpackedness, strict data A = A ~Int -- No unpackedness, lazy data A = A {-# NOUNPACK #-} A Int -- NOUNPACK, no strictness data A = A {-# NOUNPACK #-} A !Int -- NOUNPACK, strict data A = A {-# NOUNPACK #-} A ~Int -- NOUNPACK, lazy data A = A {-# UNPACK #-} A Int -- UNPACK, no strictness data A = A {-# UNPACK #-} A !Int -- UNPACK, strict data A = A {-# UNPACK #-} A ~Int -- UNPACK, lazy }}} It seems like the most consistent thing to do would be change {{{Strict}}} and add {{{Unpack}}} to the {{{template-haskell}}} API: {{{#!hs data Strict = IsStrict | NotStrict | IsLazy data Unpack = Unpack | NoUnpack | NotUnpacked type UnpackStrictType = (Unpack, Strict, Type) type VarUnpackStrictType = (Name, Unpack, Strict, Type) }}} And so on. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 07:59:34 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 07:59:34 -0000 Subject: [GHC] #7567: invalidateModSummaryCache throws exception if ms_hs_date is 0 In-Reply-To: <044.528a24a412eb29535dc4aa70b74720f6@haskell.org> References: <044.528a24a412eb29535dc4aa70b74720f6@haskell.org> Message-ID: <059.fb6fdd673ebe53749701337107092d59@haskell.org> #7567: invalidateModSummaryCache throws exception if ms_hs_date is 0 -------------------------------------+------------------------------------- Reporter: edsko | Owner: | thoughtpolice Type: bug | Status: closed Priority: high | Milestone: Component: Compiler | Version: 7.6.1 Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme * milestone: 7.12.1 => Comment: This issue should be fixed with the switch to the `time` package. In commit 08894f96407635781a233145435a78f144accab0: {{{ Author: Ian Lynagh <> Date: Sat Jan 14 17:07:10 2012 +0000 Switch to using the time package, rather than old-time }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 08:03:09 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 08:03:09 -0000 Subject: [GHC] #7919: Heap corruption (segfault) from large 'let' expression In-Reply-To: <045.3707d678a38441ef54b667e63e238d84@haskell.org> References: <045.3707d678a38441ef54b667e63e238d84@haskell.org> Message-ID: <060.214c84d9142f5fd26ee16dfe64f0d286@haskell.org> #7919: Heap corruption (segfault) from large 'let' expression -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Runtime System | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => new -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 08:33:32 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 08:33:32 -0000 Subject: [GHC] #10593: compilation failure on OpenBSD In-Reply-To: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> References: <046.c4d96acf4b7cc58678e486f88d73d0d6@haskell.org> Message-ID: <061.7bce3e3d5d89a3a37e6dd0f535d905d5@haskell.org> #10593: compilation failure on OpenBSD -------------------------------------+------------------------------------- Reporter: kgardas | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Runtime System | Version: 7.11 Resolution: fixed | Keywords: Operating System: OpenBSD | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:1023 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed * milestone: 7.10.3 => 7.12.1 Comment: Fixed in bbf607865323f7d8dbd37dbfa2ae705fafb22417: {{{ Author: Karel Gardas <> Date: Wed Jul 1 00:02:52 2015 +0200 disable check for .init_array section on OpenBSD Summary: The patch disables check for .init_array section on OpenBSD. It is provided in OpenBSD ports tree and was done by Matthias Kilian. Reviewers: austin Subscribers: thomie, bgamari Differential Revision: https://phabricator.haskell.org/D1023 }}} Please set milestone back to 7.10.3 and status=merge if this needs to go to the 7.10 branch as well. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 08:33:44 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 08:33:44 -0000 Subject: [GHC] #5666: Can't use writeFile to write unicode characters. In-Reply-To: <043.6e0e4a95f997e7dc06fe8203bd67272e@haskell.org> References: <043.6e0e4a95f997e7dc06fe8203bd67272e@haskell.org> Message-ID: <058.556f286028503914c950f1e4ab359d88@haskell.org> #5666: Can't use writeFile to write unicode characters. -------------------------------------+------------------------------------- Reporter: tsou | Owner: ekmett Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Core Libraries | Version: 7.4.2 Resolution: worksforme | Keywords: unicode | writeFile Operating System: OpenBSD | Architecture: x86_64 | (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #8118 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme Comment: > Can anyone on OpenBSD confirm this is still a problem with GHC 7.8.3? No response. Closing again. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 08:37:48 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 08:37:48 -0000 Subject: [GHC] #5666: Can't use writeFile to write unicode characters. In-Reply-To: <043.6e0e4a95f997e7dc06fe8203bd67272e@haskell.org> References: <043.6e0e4a95f997e7dc06fe8203bd67272e@haskell.org> Message-ID: <058.75d878d97bb9dfd262d7ac5f65096f22@haskell.org> #5666: Can't use writeFile to write unicode characters. -------------------------------------+------------------------------------- Reporter: tsou | Owner: ekmett Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 7.4.2 Resolution: worksforme | Keywords: unicode | writeFile Operating System: OpenBSD | Architecture: x86_64 | (amd64) Type of failure: Runtime crash | Test Case: Blocked By: | Blocking: Related Tickets: #8118 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: core-libraries-committee@? (removed) * milestone: 7.12.1 => Comment: Please comment in #8118 if this is still a problem. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 09:18:33 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 09:18:33 -0000 Subject: [GHC] #8767: Add rules involving `coerce` to the libraries In-Reply-To: <046.3c0b9cf8af710082a3b44b8616f52521@haskell.org> References: <046.3c0b9cf8af710082a3b44b8616f52521@haskell.org> Message-ID: <061.01d28de5dd6e51c9e113a28fbe282534@haskell.org> #8767: Add rules involving `coerce` to the libraries -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ekmett Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Core Libraries | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | tests/simplCore/should_run/T2110.hs Blocked By: 8718 | Blocking: Related Tickets: #2110 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): `Data.Map` already has rules for `map`, this [pull request](https://github.com/haskell/containers/pull/163) adds them for `mapKeysMonotonic`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 11:06:02 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 11:06:02 -0000 Subject: =?utf-8?b?W0dIQ10gIzEwNjk4OiBGb3JhbGwnZCB2YXJpYWJsZSDigJgkcmNv?= =?utf-8?q?box=E2=80=99_is_not_bound_in_RULE_lhs?= Message-ID: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> #10698: Forall'd variable ?$rcobox? is not bound in RULE lhs -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I tried to add this rule to the code of `Data.Map`: {{{ {-# RULES "mapKeysMonotonic/coerce" mapKeysMonotonic coerce = coerce #-} }}} but it would not go through: {{{#!hs libraries/containers/Data/Map/Base.hs:1800:1: warning: Forall'd variable ?$rcobox? is not bound in RULE lhs Orig bndrs: [k2, a, $rcobox] Orig lhs: let { cobox_ab8H :: Coercible k2 k2 [LclId, Str=DmdType] cobox_ab8H = MkCoercible @ * @ k2 @ k2 @~ (_R :: k2 ~R# k2) } in mapKeysMonotonic @ k2 @ k2 @ a (coerce @ k2 @ k2 cobox_ab8H) optimised lhs: mapKeysMonotonic @ k2 @ k2 @ a (\ (tpl_B2 :: k2) -> case cobox_ab8H of _ [Occ=Dead] { MkCoercible tpl_B3 -> tpl_B2 }) }}} The same syntax works for mapping the second parameter, i.e. {{{ {-# RULES "map/coerce" map coerce = coerce #-} }}} (this still `Data.Map`?s `map`). This blocks https://github.com/haskell/containers/pull/163 I?ll see if I can produce a stand-alone testcase. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 11:22:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 11:22:25 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMDY5ODogRm9yYWxsJ2QgdmFyaWFibGUg4oCY?= =?utf-8?q?=24rcobox=E2=80=99_is_not_bound_in_RULE_lhs?= In-Reply-To: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> References: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> Message-ID: <061.1778183ab540143fb609e8d8413ea4a6@haskell.org> #10698: Forall'd variable ?$rcobox? is not bound in RULE lhs -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Hmm, guess I was misguided here. Of course, `Map`?s first argument is set by the user to have role Nominal. For some reason I assumed that, as long as the constructors are in scope, I can still coerce it. But that?s not the way we went. So the whole rule is unfortunately not possible. Anyways, ghc-7.8 has a proper error message, instead of a weird warning: {{{ T10698.hs:19:53: Could not coerce from ?Map k1 a? to ?Map k2 a? because the first type argument of ?Map? has role Nominal, but the arguments ?k1? and ?k2? differ arising from a use of ?coerce? from the context (Coercible k1 k2) bound by the RULE "mapKeysMonotonic/coerce" at T10698.hs:19:1-58 In the expression: coerce When checking the transformation rule "mapKeysMonotonic/coerce" }}} so the bug is about the regression of the error message. Will commit a test case right away. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 11:22:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 11:22:59 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMDY5ODogRm9yYWxsJ2QgdmFyaWFibGUg4oCY?= =?utf-8?q?=24rcobox=E2=80=99_is_not_bound_in_RULE_lhs?= In-Reply-To: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> References: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> Message-ID: <061.420cbb1ac4d4f826f48d1b4fee00523b@haskell.org> #10698: Forall'd variable ?$rcobox? is not bound in RULE lhs -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by Joachim Breitner ): In [changeset:"e343c0a7fbaca4285a89008e5e23d35a50603763/ghc" e343c0a7/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e343c0a7fbaca4285a89008e5e23d35a50603763" Test case for #10698 the expected error message is from an older version of GHC; I don?t know the exact error message that we should get here until the bug is fixed... }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 13:54:17 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 13:54:17 -0000 Subject: =?utf-8?b?UmU6IFtHSENdICMxMDY5ODogRm9yYWxsJ2QgdmFyaWFibGUg4oCY?= =?utf-8?q?=24rcobox=E2=80=99_is_not_bound_in_RULE_lhs?= In-Reply-To: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> References: <046.295b861af72c5c92d6ac10d326dc72f0@haskell.org> Message-ID: <061.99e2f919955d2c990684093a08ae4e4b@haskell.org> #10698: Forall'd variable ?$rcobox? is not bound in RULE lhs -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: bug | 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 Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): It can be triggered already with {{{ {-# RULES "coerce/id" coerce = id #-} }}} so my hypothesis is that the desugar creates something like {{{ Orig bndrs: [b, $rcobox] Orig lhs: let { cobox_acD :: Coercible b b [LclId, Str=DmdType] cobox_acD = MkCoercible @ * @ b @ b @~ $rcobox } in coerce @ b @ b cobox_acD }}} but since `$rcobox :: b ~_R b`, the coercion simplifier simplifies this to {{{ Orig bndrs: [b, $rcobox] Orig lhs: let { cobox_acD :: Coercible b b [LclId, Str=DmdType] cobox_acD = MkCoercible @ * @ b @ b @~ _R } in coerce @ b @ b cobox_acD }}} and the ?Forall'd variable ?`$rcobox`?? is is no longer used. One possibly sensible fix would be to remove forall?ed variables that are also not mentioned on the right hand side (I would assume that to be the case here, although I did not check), and do that before the warning is triggered. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 14:24:34 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 14:24:34 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.8a3e12f6ec15e1aa6d4deb4f288f87bf@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | 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 Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: invalid => Comment: HEAD now shows the following warning for the example from the description: {{{ Test.hs:4:11: warning: Rule "d exp" may never fire because rule "Class op exp" for ?exp? might fire first Probable fix: add phase [n] or [~n] to the competing rule }}} That "Probable fix" is not probable at all, because "Class op exp" is a built-in rule. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 14:44:32 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 14:44:32 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.a3f23c0990f739b0285649df5152d290@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | 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 Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes; I don't know what the right design is here, so currently I'm doing nothing. See also #10528. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 15:04:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 15:04:25 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.0c221e32eb7c1920ff196ae92f7714dc@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 15:44:29 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 15:44:29 -0000 Subject: [GHC] #10227: Type checker cannot deduce type In-Reply-To: <047.38bc9ed8d3484bd4c9bcb2480f8e1743@haskell.org> References: <047.38bc9ed8d3484bd4c9bcb2480f8e1743@haskell.org> Message-ID: <062.75fbbb9a286a219667576baca8f820bf@haskell.org> #10227: Type checker cannot deduce type -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by nfrisby): * cc: nfrisby (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 16:28:54 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 16:28:54 -0000 Subject: [GHC] #10699: Regression: panic with custom rewrite rules on primops Message-ID: <045.5b271be3c8bb670898d870a1cce120d7@haskell.org> #10699: Regression: panic with custom rewrite rules on primops -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #10555 Differential Revisions: | -------------------------------------+------------------------------------- The following program results in a panic with ghc-7.10.2 (and also HEAD with the patches for #10528 and #10595 applied), but not with ghc-7.10.1. {{{#!haskell {-# LANGUAGE MagicHash #-} module T10555b where import GHC.Prim {-# RULES "double commute left *" forall x1 x2 x3. (*##) x1 ((*##) x2 x3) = (*##) ((*##) x2 x3) x1 #-} {-# RULES "double **4" forall x . x **## 4.0## = let xx = x *## x in xx *## xx #-} }}} {{{ $ ghc-7.10.2 -fforce-recomp -O T10555b.hs ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): Simplifier ticks exhausted When trying RuleFired double commute left * 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: 4004 }}} I find this suprising, because there isn't anything to rewrite yet, is there? These are the prerequisites to trigger the bug: * both rules are needed * the function (`*##`) should be a primop If I replace the function (`*##`) by `f` below, I don't get a panic, but I do get the following warning: {{{ RULE left-hand side too complicated to desugar Optimised lhs: case f x2 x3 of wild_00 { __DEFAULT -> f x1 wild_00 } Orig lhs: case f x2 x3 of wild_00 { __DEFAULT -> f x1 wild_00 } }}} {{{#!haskell {-# NOINLINE f #-} f :: Double# -> Double# -> Double# f = undefined }}} Note that the first rewrite rule (`"double commute left *"`) is buggy by itself, since it will loop on `times4` (with any compiler version): {{{#!haskell times4 :: Double -> Double times4 (D# x) = D# ((x *## x) *## (x *## x)) }}} So I'm not quite sure if there is a actually a bug in GHC here, but I don't understand what's going on either. These examples are extracted from the [https://hackage.haskell.org/package /fast-math fast-math] package. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 16:45:32 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 16:45:32 -0000 Subject: [GHC] #1595: duplicate "not in scope" error when giving multiple vars type-signatures at once In-Reply-To: <051.0e4de7c150cd454ea10fcaac09018c82@haskell.org> References: <051.0e4de7c150cd454ea10fcaac09018c82@haskell.org> Message-ID: <066.2ac05969795a99138dc49ee695ee0d1a@haskell.org> #1595: duplicate "not in scope" error when giving multiple vars type-signatures at once -------------------------------------+------------------------------------- Reporter: Isaac Dupree | Owner: michalt Type: bug | Status: closed Priority: normal | Milestone: 7.2.1 Component: Compiler | Version: 6.6.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | rename/should_fail/T1595 Blocked By: | Blocking: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"a1dd7dd6ea276832aef0caaf805f0ab9f4e16262/ghc" a1dd7dd/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a1dd7dd6ea276832aef0caaf805f0ab9f4e16262" Fallout from more assiduous RULE warnings GHC now warns if rules compete, so that it's not predicatable which will work and which will not. E.g. {-# RULES f (g x) = ... g True = ... #-} If we had (f (g True)) it's not clear which rule would fire. This showed up fraility in the libraries. * Suppress warnigns in Control.Arrow, Control.Category for class methods. At the moment we simply don't have a good way to write a RULE with a class method in the LHS. See Trac #1595. Arrow and Category attempt to do so; I have silenced the complaints with -fno-warn-inline-rule-shadowing, but it's not a great solution. * Adjust the NOINLINE pragma on 'GHC.Base.map' to account for the map/coerce rule * Adjust the rewrite rules in Enum, especially for the "literal 1" case. See Note [Enum Integer rules for literal 1]. * Suppress warnings for 'bytestring' e.g. libraries/bytestring/Data/ByteString.hs:895:1: warning: Rule "ByteString specialise break (x==)" may never fire because rule "Class op ==" for ?==? might fire first Probable fix: add phase [n] or [~n] to the competing rule }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 17:29:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 17:29:24 -0000 Subject: [GHC] #10555: RULE left-hand side too complicated to desugar In-Reply-To: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> References: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> Message-ID: <061.a60fcb12ea36fb4a49a9bdc394506f85@haskell.org> #10555: RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: yongqli | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: #10699 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #10699 Comment: Thank you for the report. I analysed the problem in #10699. I also opened a [https://github.com/liyang/fast-math/pull/4 pull request] to fast-math that will make the package compile with ghc-7.10.2 (and HEAD). Maybe you could comment there if it works for you. Otherwise, please comment in #10699. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 18:10:30 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 18:10:30 -0000 Subject: [GHC] #10700: include/stg/Prim.h isn't C++ compatible Message-ID: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> #10700: include/stg/Prim.h isn't C++ compatible -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Build | Version: 7.10.1 System | Keywords: FFI | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- StgWord hs_cmpxchg8(volatile StgWord8 *x, StgWord old, StgWord new); and a few other declarations in Prim.h causes problems as they use ''new'' as a variable name. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 18:50:40 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 18:50:40 -0000 Subject: [GHC] #10700: include/stg/Prim.h isn't C++ compatible In-Reply-To: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> References: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> Message-ID: <060.4d1126d83d8c037377bcce01ae624932@haskell.org> #10700: include/stg/Prim.h isn't C++ compatible -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.1 Resolution: | Keywords: FFI, | newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: FFI => FFI, newcomers * component: Build System => Compiler (FFI) Comment: Maybe you want to write a patch yourself? See the [wiki:Newcomers] info and [wiki:WorkingConventions/FixingBugs]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 19:15:34 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 19:15:34 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules Message-ID: <045.34230300350f9fc926fd4336a412b885@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: TH | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | crash Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- In cross compilation builds, the current TH situation is a bit of a showstopper. However, much TH code is 'safe' to cross-compile. Before the TH situation is solved, it would be great if GHC could automate as much of the work-around process as possible. -dth-dec-file is a big step on the way to create a non-TH version of the source. However, there are some problems with the generated code. One is that qualified names from hidden modules are used. A instance declaration for Aeson.ToJSON is outputted as follows: {{{#!hs instance Data.Aeson.Types.Class.ToJSON InputDropboxFiles where }}} Ideally, GHC would be able to combine the splice output with the original file, replacing all $() with the corresponding splice, and even generate correct imports. I personally think this would be a great solution to the TH problem. Most cross-compilation projects could just generate the non-TH version with the host GHC, and the few that depends on architecture specific variables can be edited before cross-compiled -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 19:24:28 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 19:24:28 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.269c3002f1a94cfbb4a69864dd44381f@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: TH Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Fabian: I think I read you have a list of issues to report, hence I'm mentioning the following; For all bug reports, please attach or copy-paste a small program (as small as possible is best) that demonstrates the bug you found, including the instructions to compile and run it. This saves us time constructing it ourselves, and we can put it in the testsuite later. See [wiki:ReportABug#Fulldescription:whatinformationtoprovideinthebodyofyourbugreport]. Thanks! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 19:32:16 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 19:32:16 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions Message-ID: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #10701 Differential Revisions: | -------------------------------------+------------------------------------- {{{#!hs instance Data.Aeson.ToJSON InputDropboxFiles where Data.Aeson.toJSON x@(InputDropboxFiles {}) = Data.Aeson.object (Data.Maybe.catMaybes [Just ((Data.Aeson..=) "root" (inputDropboxFilesRoot x)), Just ((Data.Aeson..=) "path" (inputDropboxFilesPath x)), fmap ((Data.Aeson..=) "rev") (inputDropboxFilesRev x), Just ((Data.Aeson..=) "access_token" (inputDropboxFilesAccess_token x))]) }}} Data.Aeson.toJSON should be toJSON at line 2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 20:02:06 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 20:02:06 -0000 Subject: [GHC] #10700: include/stg/Prim.h isn't C++ compatible In-Reply-To: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> References: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> Message-ID: <060.ffa7c7d67f3799b2d9e089dcf613b297@haskell.org> #10700: include/stg/Prim.h isn't C++ compatible -------------------------------------+------------------------------------- Reporter: Fabian | Owner: rasen Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.1 Resolution: | Keywords: FFI, | newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rasen): * owner: => rasen -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 20:12:28 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 20:12:28 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.935f37579cdffa3636616c88e45cb55b@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * keywords: TH => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 20:12:39 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 20:12:39 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas Message-ID: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #10701 Differential Revisions: | -------------------------------------+------------------------------------- {{{#!hs instance Data.TH.Object.Object InputDropboxFiles String Language.JavaScript.Interpret.Primitive where toObject x@(InputDropboxFiles {}) = fromList (Data.Maybe.catMaybes [Just (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "root" (inputDropboxFilesRoot x)), Just (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "path" (inputDropboxFilesPath x)), fmap (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "rev") (inputDropboxFilesRev x), Just (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "access_token" (inputDropboxFilesAccess_token x))]) }}} {{{#!hs (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr)) "root" (inputDropboxFilesRoot x) }}} should be {{{#!hs ((\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr))) "root" (inputDropboxFilesRoot x) }}} ie. the lambda needs parentheses around it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 20:16:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 20:16:25 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.0ecd8c7e936f3ad7695c6038f24ae906@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Old description: > {{{#!hs > instance Data.TH.Object.Object InputDropboxFiles String > Language.JavaScript.Interpret.Primitive where > toObject x@(InputDropboxFiles {}) > = fromList > (Data.Maybe.catMaybes > [Just > (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert > v_axsr) > "root" (inputDropboxFilesRoot x)), > Just > (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert > v_axsr) > "path" (inputDropboxFilesPath x)), > fmap > (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert > v_axsr) "rev") > (inputDropboxFilesRev x), > Just > (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert > v_axsr) > "access_token" (inputDropboxFilesAccess_token x))]) > }}} > > {{{#!hs > (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr)) > "root" (inputDropboxFilesRoot x) > }}} > > should be > > {{{#!hs > ((\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr))) > "root" (inputDropboxFilesRoot x) > }}} > > ie. the lambda needs parentheses around it. New description: {{{#!hs instance Data.TH.Object.Object InputDropboxFiles String Language.JavaScript.Interpret.Primitive where toObject x@(InputDropboxFiles {}) = fromList (Data.Maybe.catMaybes [Just (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "root" (inputDropboxFilesRoot x)), Just (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "path" (inputDropboxFilesPath x)), fmap (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "rev") (inputDropboxFilesRev x), Just (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "access_token" (inputDropboxFilesAccess_token x))]) }}} {{{#!hs (\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr) "root" (inputDropboxFilesRoot x)) }}} should be {{{#!hs ((\ k_axsq v_axsr -> (k_axsq, Data.TH.Convert.convert v_axsr)) "root" (inputDropboxFilesRoot x)) }}} ie. the lambda needs parentheses around it. -- Comment (by rwbarton): Edited to what I think you meant. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 20:28:04 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 20:28:04 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.f3b8fdc7b8ec9a7d5974a9bc7d790e9c@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): Replying to [comment:1 rwbarton]: > Edited to what I think you meant. Yes thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 20:30:24 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 20:30:24 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.fc8fc29260c9551fc8435e410d5dc8fb@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): Replying to [comment:1 thomie]: > Fabian: I think I read you have a list of issues to report, hence I'm mentioning the following; > > For all bug reports, please attach or copy-paste a small program (as small as possible is best) that demonstrates the bug you found, including the instructions to compile and run it. This saves us time constructing it ourselves, and we can put it in the testsuite later. See [wiki:ReportABug#Fulldescription:whatinformationtoprovideinthebodyofyourbugreport]. Thanks! > I'll put together a test case tomorrow and add it to the ticket -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:05:31 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:05:31 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell Message-ID: <050.da392650782a8199b770d3d93e898cab@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: | Owner: RyanGlScott | Type: feature | Status: new request | Priority: normal | Milestone: Component: Template | Version: 7.10.1 Haskell | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Currently, Template Haskell allows you to reify the fixity of regular functions, typeclass functions, and data constructors: {{{ ?> import Language.Haskell.TH ?> $(reify '($) >>= stringE . show) "VarI GHC.Base.$ (ForallT [KindedTV a_822083586 StarT,KindedTV b_822083587 (ConT GHC.Prim.OpenKind)] [] (AppT (AppT ArrowT (AppT (AppT ArrowT (VarT a_822083586)) (VarT b_822083587))) (AppT (AppT ArrowT (VarT a_822083586)) (VarT b_822083587)))) Nothing (Fixity 0 InfixR)" ?> $(reify '(+) >>= stringE . show) "ClassOpI GHC.Num.+ (ForallT [KindedTV a_1627404054 StarT] [AppT (ConT GHC.Num.Num) (VarT a_1627404054)] (AppT (AppT ArrowT (VarT a_1627404054)) (AppT (AppT ArrowT (VarT a_1627404054)) (VarT a_1627404054)))) GHC.Num.Num (Fixity 6 InfixL)" ?> $(reify '(:%) >>= stringE . show) "DataConI GHC.Real.:% (ForallT [KindedTV a_1627412324 StarT] [] (AppT (AppT ArrowT (VarT a_1627412324)) (AppT (AppT ArrowT (VarT a_1627412324)) (AppT (ConT GHC.Real.Ratio) (VarT a_1627412324))))) GHC.Real.Ratio (Fixity 9 InfixL)" }}} However, you can't do the same for infix typeclasses, type constructors, or type families: {{{ ?> :set -XTypeOperators -XTypeFamilies -XMultiParamTypeClasses ?> class a :=> b; infixr 5 :=> ?> $(reify ''(:=>) >>= stringE . show) "ClassI (ClassD [] Ghci5.:=> [KindedTV a_1627424666 StarT,KindedTV b_1627424667 StarT] [] []) []" ?> type a :+: b = Either a b; infixr 5 :+: ?> $(reify ''(:+:) >>= stringE . show) "TyConI (TySynD Ghci7.:+: [KindedTV a_1627426783 StarT,KindedTV b_1627426784 StarT] (AppT (AppT (ConT Data.Either.Either) (VarT a_1627426783)) (VarT b_1627426784)))" ?> $(reify ''(:*:) >>= stringE . show) "FamilyI (FamilyD TypeFam Ghci9.:*: [KindedTV a_1627426938 StarT,KindedTV b_1627426939 StarT] (Just StarT)) []" }}} We should add a {{{Fixity}}} field to {{{ClassI}}}, {{{TyConI}}}, and {{{FamilyI}}} to make them consistent with the other {{{Info}}} constructors that allow for infix things. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:27:49 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:27:49 -0000 Subject: [GHC] #10663: ghci ignores stuff after an import command and a semicolon In-Reply-To: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> References: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> Message-ID: <062.2adf6e68e069908512845d235e29a050@haskell.org> #10663: ghci ignores stuff after an import command and a semicolon -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): That is a single `let`-command, `let { add = (+); infixl 6 `add` }`. You can write `do x; y` too, same logic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:30:10 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:30:10 -0000 Subject: [GHC] #10663: ghci ignores stuff after an import command and a semicolon In-Reply-To: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> References: <047.73a74704a50af0b4eacdd79f94136aad@haskell.org> Message-ID: <062.00e412d85128078ac2985a8615c32f36@haskell.org> #10663: ghci ignores stuff after an import command and a semicolon -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): `type` (and presumably `data` and `class` and so on, everything which isn't real do-block syntax) has the same behavior as `import`, see #10704 for a real-life example. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:31:39 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:31:39 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.7d47d7d23abbde15047d8178b32ba6b7@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Note that those `; infixr 5 :+:` parts are ignored by ghci. {{{ rwbarton at morphism:~/ghc$ ghci-7.10.1 -XTypeOperators GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Prelude> type a :+: b = Either a b; infixr 5 :+: Prelude> :kind! () :+: () :+: () () :+: () :+: () :: * = (() :+: ()) :+: () }}} See #10663. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:38:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:38:59 -0000 Subject: [GHC] #10555: RULE left-hand side too complicated to desugar In-Reply-To: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> References: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> Message-ID: <061.c799655118262fcda41b7b668d625882@haskell.org> #10555: RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: yongqli | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc1 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: #10699 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I did look at the "lhs too complicated to desugar" issue. There's a good reason for it, and I'm not sure what to do. The issue is this. Most numeric primops are pure and can't fail, so they can be subject to aggressive code motion. Division, unlike most numeric primops, can fail. So GHC restricts its code motion by `case`-binding it. In particular something like {{{ a /## (b /## c) }}} doesn't obey the "let/app invariant" (see `CoreSyn.hs`) and gets turned into {{{ case b /## c of r -> a /## r }}} But the LHS of a rule is supposed to look like `f e1 .. en`. Maybe the let/app invariant is too strong -- after all, we only support imprecise exceptions for things like divide-by-zero. But if you say {{{ if x >## 3## then y /## x else ... }}} you jolly well don't expect the `(y /## x)` to be executed until after testing `x >## 3`, so we need to restrict code motion. Not clear what to do here. Avoid division primops on the LHS of a rule! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:39:59 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:39:59 -0000 Subject: [GHC] #10555: RULE left-hand side too complicated to desugar In-Reply-To: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> References: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> Message-ID: <061.3eea598a81d3f5a349e03a038e0e4e99@haskell.org> #10555: RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: yongqli | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: #10699 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * resolution: duplicate => Comment: PS: this is not the same issue as #10699. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:41:28 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:41:28 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.95bb5c69b5be11b3cb6724d4f26ee27a@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by RyanGlScott): Sorry, I forgot to mention that I was using the HEAD version of GHCi, in which it does work (after fixing #10018): {{{ $ inplace/bin/ghc-stage2 --interactive -XTypeOperators -XTypeFamilies -XMultiParamTypeClasses GHCi, version 7.11.20150727: http://www.haskell.org/ghc/ :? for help ?> class a :=> b; infixr 5 :=> ?> :i :=> class (:=>) a b -- Defined at :1:1 infixr 5 :=> ?> type a :+: b = Either a b; infixr 5 :+: ?> :i :+: type (:+:) a b = Either a b -- Defined at :3:1 infixr 5 :+: ?> type family a :*: b; infixr 5 :*: ?> :i :*: type family (:*:) a b :: * -- Defined at :5:1 infixr 5 :*: }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:44:17 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:44:17 -0000 Subject: [GHC] #10699: Regression: panic with custom rewrite rules on primops In-Reply-To: <045.5b271be3c8bb670898d870a1cce120d7@haskell.org> References: <045.5b271be3c8bb670898d870a1cce120d7@haskell.org> Message-ID: <060.23b3b5b1620c6d8813d1808ccf47f13b@haskell.org> #10699: Regression: panic with custom rewrite rules on primops -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.2-rc2 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #10555 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * resolution: => invalid Comment: As you point out, rule "double commute left" will rewrite {{{ (a *## b) *## (c *## d) ---> (c *## d) *## (a *## b) }}} and the rewrites will go on forever. And that is just what is happening here; it happens in the RHS of rules "double **4". GHE feels free to use rules A,B,C to rewrite the RHS of another rule D. After all, if rule D fires, the RHS would immediately be rewritten by A,B,C, so we may as well do it in advance. So I claim this is a bug in rule "double commute left" and not in HGC. Yell you if you disagree. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 21:51:26 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 21:51:26 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.002e969a3f5982e4932f8b846b14d37c@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): So to simplify, the use case is something like {{{ data IntArrayTree = IntArrayTree { value :: {-# UNPACK #-} !Int, children :: {-# UNPACK #-} !(Array Int IntArrayTree) } }}} and arguably the underlying problem that would be nice to fix is that there are two levels of indirection (`IntArrayTree` -> `Array#` -> `IntArrayTree`) per level of the tree. Of note is that the `IntArrayTree` values themselves are actually of constant size. But we can't store them efficiently in any sort of array because they contain a mix of pointer and non-pointer fields. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 22:00:29 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 22:00:29 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.867d8146eeeb50ccf7a0fb6b301b9413@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | 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 Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): In [changeset:"a1dd7dd6ea276832aef0caaf805f0ab9f4e16262/ghc" a1dd7dd/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a1dd7dd6ea276832aef0caaf805f0ab9f4e16262" Fallout from more assiduous RULE warnings GHC now warns if rules compete, so that it's not predicatable which will work and which will not. E.g. {-# RULES f (g x) = ... g True = ... #-} If we had (f (g True)) it's not clear which rule would fire. This showed up fraility in the libraries. * Suppress warnigns in Control.Arrow, Control.Category for class methods. At the moment we simply don't have a good way to write a RULE with a class method in the LHS. See Trac #1595. Arrow and Category attempt to do so; I have silenced the complaints with -fno-warn-inline-rule-shadowing, but it's not a great solution. * Adjust the NOINLINE pragma on 'GHC.Base.map' to account for the map/coerce rule * Adjust the rewrite rules in Enum, especially for the "literal 1" case. See Note [Enum Integer rules for literal 1]. * Suppress warnings for 'bytestring' e.g. libraries/bytestring/Data/ByteString.hs:895:1: warning: Rule "ByteString specialise break (x==)" may never fire because rule "Class op ==" for ?==? might fire first Probable fix: add phase [n] or [~n] to the competing rule }}} The commit message should have said #10595! Typo. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 22:01:25 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 22:01:25 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. Message-ID: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build | Version: 7.11 System | Keywords: | Operating System: Windows Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #9218 Differential Revisions: | -------------------------------------+------------------------------------- Currently checking out the source on windows requires two git checkouts. One for the GHC sources and one for the GHC-tarballs. This patch will make configure issue an error if compiling under windows and the GHC-tarballs folder is missing. On failure the user is told which command they need to run to get the tarballs or if they want configure to handle it for them configure provide the `--enable-tarballs-autodownload` flag. This is one part of the bigger #9218 patch which is being flit up to get it through. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 22:02:32 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 22:02:32 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.d94cdeb3b5799068a5c0a17d05a6d4c2@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: patch Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Changes (by Phyx-): * status: new => patch * differential: => Phab:D1108 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 22:17:20 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 22:17:20 -0000 Subject: [GHC] #9218: Upgrade the version of MinGW shipped with GHC In-Reply-To: <047.dd7762c6a468e59baf096987bc6ae487@haskell.org> References: <047.dd7762c6a468e59baf096987bc6ae487@haskell.org> Message-ID: <062.7517598a60b271cbdf0cf5b243d96c43@haskell.org> #9218: Upgrade the version of MinGW shipped with GHC -------------------------------------+------------------------------------- Reporter: komadori | Owner: gintas Type: task | Status: patch Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.8.2 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 9014 | Blocking: 9215 Related Tickets: #3390 #10705 | Differential Revisions: Phab:D339 -------------------------------------+------------------------------------- Changes (by Phyx-): * related: #3390 => #3390 #10705 Comment: I've started splitting this up to get it in: >> ?downloads mingw during ./configure step, instead of via explicit git clone ...ghc-tarballs.git. > This is now done in #10705 [[BR]] >> ?change the provider of the ?32bit and ?64bit packages from rubenvb to mingw-builds. By default this results in much ?larger downloads (2x for 64bit, 5x for 32bit), which means #9014 should be fixed first. > Any particular reason why this was done? Was there anything missing from the rubenvb builds? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Tue Jul 28 22:33:16 2015 From: ghc-devs at haskell.org (GHC) Date: Tue, 28 Jul 2015 22:33:16 -0000 Subject: [GHC] #10700: include/stg/Prim.h isn't C++ compatible In-Reply-To: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> References: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> Message-ID: <060.d4005e033d21c3183b1ad0a141020b5d@haskell.org> #10700: include/stg/Prim.h isn't C++ compatible -------------------------------------+------------------------------------- Reporter: Fabian | Owner: rasen Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.1 Resolution: | Keywords: FFI, | newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1107 -------------------------------------+------------------------------------- Changes (by rasen): * status: new => patch * differential: => Phab:D1107 Comment: The build fails (https://phabricator.haskell.org/harbormaster/build/5215/), but the failure isn't related to the change. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 01:42:25 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 01:42:25 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.8c3241d15bbe577951443bc397801d11@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => newcomer Comment: Straightforward improvement for anyone who wants to do it. Happy to advise. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 01:52:10 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 01:52:10 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.cbe3d5f729b2e8b8c7248872b5bac850@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * owner: => RyanGlScott -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 02:58:43 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 02:58:43 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.ed09edabfbf4812effbe6b50e156d9ee@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Changes (by RyanGlScott): * differential: => Phab:D1109 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 06:10:21 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 06:10:21 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.ecd87c3a149874148bc62b44f7711fea@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: highest | Milestone: 7.10.3 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * milestone: 7.10.2 => 7.10.3 Comment: (milestone:7.10.2 is effectively closed) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 06:16:05 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 06:16:05 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.8f1cafaad541fe7e1b2563f852081ecd@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * milestone: 7.10.2 => 7.10.3 Comment: (milestone:7.10.2 is effectively closed; we're way past the RC-phase, we have all binary dists built and tested, the Git commit has been signed, ...) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 06:19:18 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 06:19:18 -0000 Subject: [GHC] #10398: Support consecutive named Haddock comments In-Reply-To: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> References: <047.7740b80be062ec1bb48c700ce8a4b3f6@haskell.org> Message-ID: <062.e0a51a0e59215b1793050d147be4dc08@haskell.org> #10398: Support consecutive named Haddock comments -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: | haddock/should_compile_flag_haddock/T10398 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1025 -------------------------------------+------------------------------------- Changes (by hvr): * milestone: 7.10.3 => 7.12.1 Comment: This was never merged to 7.10, so I assume the milestone was wrong -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 07:46:08 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 07:46:08 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.2bfae9e555b286f948c9d26d04713e26@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I'm on this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 09:12:36 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 09:12:36 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.92b389dfc941fd7ca9b5036b44fe6d2b@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 09:14:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 09:14:01 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.8d14a701eead2000c24e0ccf75d579f6@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 09:14:35 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 09:14:35 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.856cb9dd4a6bafb5d6b9e4abf8bc3c3e@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 11:06:30 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 11:06:30 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.44d8a41d71a4646fe2f394b145cca9df@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by tibbe): Getting rid of the kind of array indirection rwbarton mentioned would greatly help unordered-containers. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 12:27:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 12:27:01 -0000 Subject: [GHC] #10706: Make -fcpr-off a dynamic flag Message-ID: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> #10706: Make -fcpr-off a dynamic flag -------------------------------------+------------------------------------- Reporter: darchon | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- I've run into a situation where I wanted to turn off CPR analysis for a single module in my project, but could not do that because {{{-fcpr-off}}} is a static flag. I will supply a patch that makes {{{-fcpr-off}}} a dynamic flag. From what I understand, this would also bring us one step closer to the desired goal of getting rid of static flags entirely. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 12:34:19 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 12:34:19 -0000 Subject: [GHC] #10706: Make -fcpr-off a dynamic flag In-Reply-To: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> References: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> Message-ID: <061.e9f80e4ff7ffd333150b5cc3b7105723@haskell.org> #10706: Make -fcpr-off a dynamic flag -------------------------------------+------------------------------------- Reporter: darchon | Owner: darchon Type: feature request | 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 Revisions: Phab:D1110 -------------------------------------+------------------------------------- Changes (by darchon): * owner: => darchon * differential: => Phab:D1110 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:12:30 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:12:30 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.76d75417ba2125b4e846c22814d85f41@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge Comment: `text-1.2.1.2` includes phase control specifications on the literal rewrite rules which should prevent the rule competition described by simonpj in comment:13. I'll mark this as status `merge` in case we end up doing a 7.10.3 release. This should now be fixed in `master`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:30:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:30:01 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses Message-ID: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Other Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #10701 Differential Revisions: | -------------------------------------+------------------------------------- instance Data.Aeson.Types.Class.ToJSON Language.Haskell.TH.Syntax.Name where Data.Aeson.Types.Class.toJSON x = \ k_a94l v_a94m -> case k_a94l of { GHC.Base.Just "" -> GHC.Err.undefined GHC.Base.Nothing -> GHC.Err.undefined } (GHC.Base.Just "test") "test2" -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:31:05 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:31:05 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.8f87920566835376fe711552a56fe0ff@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:32:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:32:14 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.2428191b100c819d8a9f771c9389dbde@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Description changed by Fabian: Old description: > instance Data.Aeson.Types.Class.ToJSON Language.Haskell.TH.Syntax.Name > where > Data.Aeson.Types.Class.toJSON x > = \ k_a94l v_a94m > -> case k_a94l of { > GHC.Base.Just "" -> GHC.Err.undefined > GHC.Base.Nothing -> GHC.Err.undefined } > (GHC.Base.Just "test") "test2" New description: {{{#!hs instance Data.Aeson.Types.Class.ToJSON Language.Haskell.TH.Syntax.Name where Data.Aeson.Types.Class.toJSON x = \ k_a94l v_a94m -> case k_a94l of { GHC.Base.Just "" -> GHC.Err.undefined GHC.Base.Nothing -> GHC.Err.undefined } (GHC.Base.Just "test") "test2" }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:45:55 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:45:55 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.482edf5ee455d3580299c17d3394ad77@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Comment (by goldfire): Now that this is done (see Phab:D1109 -- many thanks!), it looks like it could all be refactored a little more cleanly. What about {{{ module TH.Syntax where ... class ... => Quasi q where ... qReifyFixity :: Name -> q Fixity reifyFixity :: Name -> Q Fixity }}} and then remove all of the `Fixity` fields in `Info`? This should not be a hard change to deal with downstream, and it would declutter things somewhat. It's true that `TyVarI` doesn't have fixities (although they should, morally, except that Haskell provides no way of giving a fixity specification to a type variable), but `PrimTyConI` ''can'' have a fixity: `(->)` has hard-wired fixity `infixr 0`. I'm not wedded to this change, but I do think it's an improvement. Speak up if you have a strong opinion! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:55:06 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:55:06 -0000 Subject: [GHC] #10706: Make -fcpr-off a dynamic flag In-Reply-To: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> References: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> Message-ID: <061.188acd53d37b6d9ea30a87c002bc7ec6@haskell.org> #10706: Make -fcpr-off a dynamic flag -------------------------------------+------------------------------------- Reporter: darchon | Owner: darchon Type: feature request | 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 Revisions: Phab:D1110 -------------------------------------+------------------------------------- Comment (by simonpj): OK. It was originally intended for GHC hackers only. If there is ever a case you want to turn it off for a module I'd like to know why. Still I have no quarrel with making it dynamic -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 14:58:20 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 14:58:20 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.2c8e4cddccd0a2fa6e9fd6265d1da920@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Comment (by simonpj): That would be fine with me. (comment:6, that is) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:01:09 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:01:09 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.08b58c827bfe3504f17d7b18dfcf01a1@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:01:42 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:01:42 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.c94afe5486f951358873aee383c3ed90@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:01:48 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:01:48 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.4f2dedf4b93f7489fbc50ab63d290c3b@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Comment (by RyanGlScott): You're right, a {{{Quasi}}}-based approach would be way cleaner. I'll update Phab:D1109 to incorporate that. I have one more question about fixities of {{{PrimTyConI}}}, though. It makes sense that {{{(->)}}} has a fixity, now that I actually think about it, but what about prefix types like {{{Char#}}}? Would these always have be {{{infixl 9}}}? If so, should calling {{{qReifyFixity}}} on a {{{TyVarI}}} also yield {{{Fixity 9 InfixL}}}? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:02:35 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:02:35 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.7fe547a0d07d655a2a40f7b0f4f174a4@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * component: Compiler => Template Haskell * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:02:55 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:02:55 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.7e3711e569a0ace5e7b8dc61f15c80cd@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:03:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:03:13 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.0bbd30fc58f5709f33a3e09b3fe785b4@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:06:43 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:06:43 -0000 Subject: [GHC] #10708: Rejection of constant functions defined using conditional pattern matching Message-ID: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> #10708: Rejection of constant functions defined using conditional pattern matching -------------------------------------+------------------------------------- Reporter: | Owner: HubertGaravel | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: x86 | Type of failure: GHC rejects | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Hi, The Haskell program below is rejected, although it is correct. GHC gives the following error message: {{{ HASKELL/tricky.hs:12:1: Multiple declarations of `Main.d3' Declared at: HASKELL/tricky.hs:10:1 HASKELL/tricky.hs:11:1 HASKELL/tricky.hs:12:1 }}} I agree that the definition of d3 is tricky and useless, but it seems to be valid. This example was exctracted from Haskell code automatically produced by an in-house code generator. {{{#!hs data Nat = D0 | Succ Nat deriving (Show, Eq, Ord) d1 :: Nat d2 :: Nat d3 :: Nat d1 = (Succ D0) d2 | D0 == D0 = D0 d3 | D0 /= D0 = D0 d3 | (Succ D0) == D0 = D0 d3 | (Succ D0) /= D0 = (Succ D0) main = do print d1 print d2 print d3 }}} Best regards Hubert -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:07:00 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:07:00 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.bc8bd6064f9e2fd4f55aec20497da7d8@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Comment (by goldfire): Yes, something without a declared fixity defaults to `infixl 9`. But my guess is that the existing fixity-lookup scheme already handles this case. You'll probably have to deal with `(->)` specially (use `BasicTypes.funTyFixity`), but I think that will be the only special case. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:07:20 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:07:20 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.b1d4b56dac859ca149d9c588526ee414@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * keywords: => newcomer * component: Compiler => Template Haskell * milestone: => 7.12.1 Comment: Thanks for the report. No great care has been made to ensure that pretty- printed Template Haskell can be parsed, but this has been requested before. Straightforward to fix -- all the code is in `Language.Haskell.TH.Ppr`. Anyone care to submit a patch? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:08:56 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:08:56 -0000 Subject: [GHC] #10685: ghci segfaults on Travis In-Reply-To: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> References: <045.634562fcd04e702f240c372e7a4dcdff@haskell.org> Message-ID: <060.d0ce087416677a350ff130cf891579ec@haskell.org> #10685: ghci segfaults on Travis -------------------------------------+------------------------------------- Reporter: thomie | Owner: simonmar Type: bug | Status: closed Priority: high | Milestone: 7.12.1 Component: GHCi | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Closing as the erring change has been backed out and reintroduced in fixed form (in D1106). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:09:57 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:09:57 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.8fe6f7edeb0656452afe863866faaf94@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Comment (by RyanGlScott): > You'll probably have to deal with (->) specially (use BasicTypes.funTyFixity), but I think that will be the only special case. I was wondering if that was the case, since running {{{:i (->)}}} in GHCi doesn't tell what its fixity is. For that matter, {{{:i (~)}}} doesn't work in GHCi either... I should probably open a separate ticket for this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:21:16 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:21:16 -0000 Subject: [GHC] #10595: BuiltinRules override other rules in some cases. In-Reply-To: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> References: <046.a760bb9e6a838774f7b3904ff7776893@haskell.org> Message-ID: <061.73879597cd189d7e4bcf7e1bb0dc32ce@haskell.org> #10595: BuiltinRules override other rules in some cases. -------------------------------------+------------------------------------- Reporter: gjsimms | Owner: Type: bug | Status: new Priority: high | 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 Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:21:53 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:21:53 -0000 Subject: [GHC] #10706: Make -fcpr-off a dynamic flag In-Reply-To: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> References: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> Message-ID: <061.be32512d7b268dd1f12e6e5a7f6d4850@haskell.org> #10706: Make -fcpr-off a dynamic flag -------------------------------------+------------------------------------- Reporter: darchon | Owner: darchon Type: feature request | 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 Revisions: Phab:D1110 -------------------------------------+------------------------------------- Comment (by darchon): I have to confess that my use-case is very unconventional, perhaps even contrived: I work on a compiler that translates Haskell to circuits (www.clash- lang.org), and I use Streams to model sequential circuits: {{{ data Stream a = a :- Stream a }}} Given this model of a sequential circuit, appending an element to a stream: {{{ memory i s = i :- s }}} has a clear circuit semantics, it translates to a memory/latch. However, decomposing a stream: {{{ case s of i :- s' -> ... }}} would basically translate to "looking into the future", which cannot be transformed into a circuit. I have taken great care that, under normal conditions, a case statement with a {{{Signal a}}} as a scrutinee never occurs. For one by not exporting the constructor of the {{{Steam}}} data type. However, due to the CPR analysis I sometimes end up with a worker/wrapper that looks something like this: {{{ case memory i s of a :- bs -> g (#a,bs#) g (#a,bs#) = a :- bs }}} which gives me the troublesome case-decomposition on the {{{Stream}}} data type. Now, as to why I want {{{-fcpr-off}}} to be a dynamic flag: All my functions that manipulate the {{{Stream}}} type exist in a single module. If these functions get no CPR annotations, I noticed that the above troublesome worker/wrapper is never created elsewhere. The CPR annotations do not bother me in any of my other modules, and I do not want to turn off strictness analysis completely in the module where I define my {{{Stream}}}-manipulating functions. Hence I would like to have a {{{-fcpr-off}}} dynamic flag, so I can turn off CPR annotations just for that single module. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:22:37 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:22:37 -0000 Subject: [GHC] #10708: Rejection of constant functions defined using conditional pattern matching In-Reply-To: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> References: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> Message-ID: <067.92add427139dd9752e1d84d1b0df0194@haskell.org> #10708: Rejection of constant functions defined using conditional pattern matching -------------------------------------+------------------------------------- Reporter: HubertGaravel | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * status: new => closed * resolution: => invalid Comment: I believe you mean the code to say this: {{{ data Nat = D0 | Succ Nat deriving (Show, Eq, Ord) d1 :: Nat d2 :: Nat d3 :: Nat d1 = (Succ D0) d2 | D0 == D0 = D0 d3 | D0 /= D0 = D0 | (Succ D0) == D0 = D0 | (Succ D0) /= D0 = (Succ D0) main = do print d1 print d2 print d3 }}} The name of a defined symbol is not repeated in the different branches. Thanks for reporting, however! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:24:07 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:24:07 -0000 Subject: [GHC] #10706: Make -fcpr-off a dynamic flag In-Reply-To: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> References: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> Message-ID: <061.3951e9076c6126897958384cce8c9234@haskell.org> #10706: Make -fcpr-off a dynamic flag -------------------------------------+------------------------------------- Reporter: darchon | Owner: darchon Type: feature request | 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 Revisions: Phab:D1110 -------------------------------------+------------------------------------- Comment (by simonpj): But how can you tell that the troublesome `case` appears? Ah -- perhaps the missing piece is that you are using GHC as a library and consuming the optimised Core code that it produces? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:25:35 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:25:35 -0000 Subject: [GHC] #8199: Get rid of HEAP_ALLOCED In-Reply-To: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> References: <045.61ceff1405fed9aab9c8f0fda5e9d453@haskell.org> Message-ID: <060.7931fbdca14c545cf4bc45f5ca9aa06d@haskell.org> #8199: Get rid of HEAP_ALLOCED -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: 5435 | Blocking: Related Tickets: | Differential Revisions: D207 -------------------------------------+------------------------------------- Comment (by simonmar): I believe lazy committing should be the default if you just allocate a chunk of memory with `VirtualAlloc`. The pages will be lazily faulted in as necessary, so the pages we never touch won't consume any memory. We just need to use the convention that a zero bit means "not heap". -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:26:26 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:26:26 -0000 Subject: [GHC] #10706: Make -fcpr-off a dynamic flag In-Reply-To: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> References: <046.93a9ca311aa12689c8b9087cc77d185d@haskell.org> Message-ID: <061.3bd202fb0cdb9ac2139c68fd50826131@haskell.org> #10706: Make -fcpr-off a dynamic flag -------------------------------------+------------------------------------- Reporter: darchon | Owner: darchon Type: feature request | 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 Revisions: Phab:D1110 -------------------------------------+------------------------------------- Comment (by darchon): Ah, yes, I forgot to mention that. Indeed I use GHC as a library, I turn on/off specific optimisations: [https://github.com/clash-lang/clash- compiler/blob/master/clash-ghc/src-ghc/CLaSH/GHC/LoadModules.hs#L179] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:26:45 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:26:45 -0000 Subject: [GHC] #10704: Can't lookup fixities of infix types in Template Haskell In-Reply-To: <050.da392650782a8199b770d3d93e898cab@haskell.org> References: <050.da392650782a8199b770d3d93e898cab@haskell.org> Message-ID: <065.23eab765a1fbcc085037dea647d79c44@haskell.org> #10704: Can't lookup fixities of infix types in Template Haskell -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: | RyanGlScott Type: feature request | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1109 -------------------------------------+------------------------------------- Comment (by goldfire): I think that last point -- about `:i (~)` -- will be fixed once #10056 is done. If you're looking for a next GHC project, #10056 might be a great next step, once we can figure out the design! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:27:14 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:27:14 -0000 Subject: [GHC] #10056: Inconsistent precedence of ~ In-Reply-To: <047.6a12b15cc084aa108be95f499dfa0014@haskell.org> References: <047.6a12b15cc084aa108be95f499dfa0014@haskell.org> Message-ID: <062.0c47057fadd773338060171c274645a8@haskell.org> #10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10059 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): See also comment:10:ticket:10704, which points out that `:i (~)` fails. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:28:56 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:28:56 -0000 Subject: [GHC] #10708: Rejection of constant functions defined using conditional pattern matching In-Reply-To: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> References: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> Message-ID: <067.c5f0a29380618dfbe14cc8b1451bb84c@haskell.org> #10708: Rejection of constant functions defined using conditional pattern matching -------------------------------------+------------------------------------- Reporter: HubertGaravel | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): well of course you ''can'' define `d3` like that. But the question posed by the ticket is: is it valid Haskell to write `d3` as in the description. Looking at the [https://www.haskell.org/onlinereport/haskell2010/haskellch4.html language spec] section 4.4.3, it seems that a 'funlhs' must have at least one argument. So this must be a 'pat' lhs, which can only have one set of guarded rhss. So yes, I think it's invalid. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:30:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:30:13 -0000 Subject: [GHC] #10056: Inconsistent precedence of ~ In-Reply-To: <047.6a12b15cc084aa108be95f499dfa0014@haskell.org> References: <047.6a12b15cc084aa108be95f499dfa0014@haskell.org> Message-ID: <062.24c0e4f147be6a9fe8834df7a6fe5e7f@haskell.org> #10056: Inconsistent precedence of ~ -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.4 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #10059 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 15:30:34 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 15:30:34 -0000 Subject: [GHC] #10059: :i doesn't work for ~ In-Reply-To: <045.e4d34da19e8a219c9836208516141cc9@haskell.org> References: <045.e4d34da19e8a219c9836208516141cc9@haskell.org> Message-ID: <060.334eb4f23e465109249ff49f01c536f8@haskell.org> #10059: :i doesn't work for ~ -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10056 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 16:27:02 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 16:27:02 -0000 Subject: [GHC] #10696: -fcpr-off doesn't disable CPR completely In-Reply-To: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> References: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> Message-ID: <062.eeff6164bc2cd1740eba3c1aedd2336e@haskell.org> #10696: -fcpr-off doesn't disable CPR completely -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | 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 Revisions: Phab:D1104 -------------------------------------+------------------------------------- Comment (by Reid Barton ): In [changeset:"2dbb01a63a7ba7dc534c22815e80ab45c2f0ba69/ghc" 2dbb01a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="2dbb01a63a7ba7dc534c22815e80ab45c2f0ba69" Add a missing check for -fcpr-off Test Plan: validate Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1104 GHC Trac Issues: #10696 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 17:09:41 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 17:09:41 -0000 Subject: [GHC] #10708: Rejection of constant functions defined using conditional pattern matching In-Reply-To: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> References: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> Message-ID: <067.8c79f89d624e22e52a779dedf61b5b1e@haskell.org> #10708: Rejection of constant functions defined using conditional pattern matching -------------------------------------+------------------------------------- Reporter: HubertGaravel | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by HubertGaravel): Thanks for your prompt answers. Yet, assuming that the definition of d3 is invalid because a funlhs must have at least one argument, why is the definition of d2 accepted in the example given? Like d3, d2 is defined by a conditional rule and is not followed by an argument. I assume that GHC processes lines fromp top to bottom and that if it complains about the definition of d3, it means that it finds the definition of d1 and d2 valid. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 17:45:13 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 17:45:13 -0000 Subject: [GHC] #10652: Better cache performance in Array# In-Reply-To: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> References: <050.29d287c6c00bdf49b58de908b0c4a371@haskell.org> Message-ID: <065.40933a9bb53987e51e0214aafbc777b9@haskell.org> #10652: Better cache performance in Array# -------------------------------------+------------------------------------- Reporter: MikeIzbicki | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): One idea I had was to create a new family of array types along with boxed and unboxed arrays, called unpacked arrays. (Note this is the opposite of UnpackingArrays.) The idea is that whenever `T` is a type that can be unpacked with the `{-# UNPACK #-}` pragma, we can form values of type `UnpackedArray# T`. The heap representation of such a value is of the form {{{ UnpackedArray#_info T_con_info n a1 b1 c1 a2 b2 c2 ... an bn cn }}} representing an array containing the values {{{ T_con_info a1 b1 c1 T_con_info a2 b2 c2 ... T_con_info an bn cn }}} (Since `T` can be unpacked, it has just one constructor.) Compared to an `Array#` this costs one extra word `T_con_info`. It might be possible to save this word with a new type of info table layout, then the heap representation of `Array# a` would be identical (modulo info pointer value) to that of `UnpackedArray# (Box a)` where `data Box a = Box a`. The GC can use `T_con_info` to understand the layout of the rest of the heap object, while mutator operations like indexing would use operations from a magically-generated `Unpack` type class. This last part might be tricky. Then `IntArrayTree` could hold an `UnpackedArray# IntArrayTree` to avoid one of the layers of indirection. It won't apply to tibbe's unordered- containers though, since `IntMap` has multiple constructors. (I guess it could be used inside `Collision !Hash !(A.Array (Leaf k v))`, but that's rather pointless.) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 17:45:53 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 17:45:53 -0000 Subject: [GHC] #10708: Rejection of constant functions defined using conditional pattern matching In-Reply-To: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> References: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> Message-ID: <067.61968a6faf9970ec4b79116634b34c97@haskell.org> #10708: Rejection of constant functions defined using conditional pattern matching -------------------------------------+------------------------------------- Reporter: HubertGaravel | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Something defined without an argument ''can'' have a pattern guard on it. It's just that, if there are multiple patterns, the thing being defined must not be repeated before each guard. So any of the lines defining `d3` are valid -- they're just not valid in concert. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 17:51:45 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 17:51:45 -0000 Subject: [GHC] #9968: DeriveAnyClass fails on multi-parameter type classes In-Reply-To: <047.651a00b270696920750ca655201f4d2f@haskell.org> References: <047.651a00b270696920750ca655201f4d2f@haskell.org> Message-ID: <062.3e551603ba25e2bdaa8c1ee600bb3f59@haskell.org> #9968: DeriveAnyClass fails on multi-parameter type classes -------------------------------------+------------------------------------- Reporter: goldfire | Owner: dreixel Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9821 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by osa1): I managed to get a panic out of this: (this is with GHC 7.10.2) {{{ ? trac9968 cat Bug.hs {-# LANGUAGE DeriveAnyClass, MultiParamTypeClasses, FunctionalDependencies #-} module Bug where class C a b where showFirst :: (a, b) -> String showSecond :: (a, b) -> String data X deriving (C Bool) main :: IO () main = putStrLn "ok" ? trac9968 runhaskell Bug.hs Var/Type length mismatch: [b_alK] [] Var/Type length mismatch: [b_alK] [] Var/Type length mismatch: [b_alK] [] Var/Type length mismatch: [b_alK] [] ghc: panic! (the 'impossible' happened) (GHC version 7.10.2 for x86_64-unknown-linux): funResultTy forall b_alK. C X b_alK => (X, b_alK) -> String Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} A question about how `deriving` syntax supposed to work: Let's say we have {{{ class C a b data X }}} as in the example above. We can do `deriving (C Bool)`, which implements an instance for `C Bool X` but if I want to derive `C X Bool`, is there a way to do that? Currently if I try to do `deriving (C X Bool)` or `deriving (C Bool X)` I'm getting this error: {{{ ? trac9968 runhaskell Bug.hs Bug.hs:10:13: Expected kind ?k0 -> GHC.Prim.Constraint?, but ?C Bool X? has kind ?GHC.Prim.Constraint? In the data declaration for ?X? }}} Which is clear enough but I'm wondering if there are any workarounds to make `deriving (C X Bool)` work. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 17:52:01 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 17:52:01 -0000 Subject: [GHC] #9968: DeriveAnyClass fails on multi-parameter type classes In-Reply-To: <047.651a00b270696920750ca655201f4d2f@haskell.org> References: <047.651a00b270696920750ca655201f4d2f@haskell.org> Message-ID: <062.16023ec6d12b745079ce901a668b6e25@haskell.org> #9968: DeriveAnyClass fails on multi-parameter type classes -------------------------------------+------------------------------------- Reporter: goldfire | Owner: dreixel Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9821 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by osa1): * cc: osa1 (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 17:58:41 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 17:58:41 -0000 Subject: [GHC] #9968: DeriveAnyClass fails on multi-parameter type classes In-Reply-To: <047.651a00b270696920750ca655201f4d2f@haskell.org> References: <047.651a00b270696920750ca655201f4d2f@haskell.org> Message-ID: <062.699822bc505df98dca2723304a4a7a49@haskell.org> #9968: DeriveAnyClass fails on multi-parameter type classes -------------------------------------+------------------------------------- Reporter: goldfire | Owner: dreixel Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1-rc1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9821 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I think it's best to keep the simple rule: `data X = ... deriving (..., c, ...)` means to derive `c X` (here `c` is an application of a class constructor to zero or more types). After all if you want something else like `C X Bool` then you can express that with a standalone deriving declaration `deriving instance C X Bool`. Or in this case just write an empty instance, it's shorter :) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 20:20:16 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 20:20:16 -0000 Subject: [GHC] #10709: Using ($) allows sneaky impredicativity on its left Message-ID: <047.69b727f09e59d3453594f8d03a6e522d@haskell.org> #10709: Using ($) allows sneaky impredicativity on its left -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Observe the following shady interaction with GHCi: {{{ GHCi, version 7.10.1: http://www.haskell.org/ghc/ :? for help Prelude> import GHC.IO Prelude GHC.IO> import Control.Monad Prelude GHC.IO Control.Monad> :t mask mask :: forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b Prelude GHC.IO Control.Monad> :t replicateM 2 . mask :1:16: Couldn't match type ?a? with ?(forall a2. IO a2 -> IO a2) -> IO a1? ?a? is a rigid type variable bound by the inferred type of it :: a -> IO [a1] at Top level Expected type: a -> IO a1 Actual type: ((forall a. IO a -> IO a) -> IO a1) -> IO a1 In the second argument of ?(.)?, namely ?mask? In the expression: replicateM 2 . mask Prelude GHC.IO Control.Monad> :t (replicateM 2 . mask) undefined :1:17: Cannot instantiate unification variable ?a0? with a type involving foralls: (forall a1. IO a1 -> IO a1) -> IO a Perhaps you want ImpredicativeTypes In the second argument of ?(.)?, namely ?mask? In the expression: replicateM 2 . mask Prelude GHC.IO Control.Monad> :t (replicateM 2 . mask) $ undefined (replicateM 2 . mask) $ undefined :: forall a. IO [a] }}} Due to the way that GHC processes `($)`, it allows this form of impredicativity on the LHS of `($)`. This case is inspired by https://github.com/ghc/nofib/blob/master/smp/threads006/Main.hs which contains the line {{{ tids <- replicateM nthreads . mask $ \_ -> forkIO $ return () }}} I think that line should be rejected. The problem stems from the treatment of `OpenKind` as described in `Note [OpenTypeKind accepts foralls]` in TcMType. Unrelated work changes this behavior by rejecting the nofib program. The point of this ticket is to provoke discussion about what is right and what is wrong here, not to request a fix. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 20:36:40 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 20:36:40 -0000 Subject: [GHC] Batch modify: Message-ID: <20150729203640.829C33A2FF@ghc.haskell.org> Batch modification to by hvr: milestone to 7.10.3 Comment: Ticket retargeted after milestone closed -- Tickets URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Wed Jul 29 21:19:47 2015 From: ghc-devs at haskell.org (GHC) Date: Wed, 29 Jul 2015 21:19:47 -0000 Subject: [GHC] #10709: Using ($) allows sneaky impredicativity on its left In-Reply-To: <047.69b727f09e59d3453594f8d03a6e522d@haskell.org> References: <047.69b727f09e59d3453594f8d03a6e522d@haskell.org> Message-ID: <062.6a22e660e9987de9a714a1cd6499fe2f@haskell.org> #10709: Using ($) allows sneaky impredicativity on its left -------------------------------------+------------------------------------- Reporter: goldfire | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.10.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): From IRC discussion, something weird is happening that is not specific to `$`. All these type check: {{{ (replicateM 2 . mask) (\_ -> return ()) (replicateM 2 . mask) (\x -> undefined x) (replicateM 2 . mask) (id (\_ -> undefined)) }}} but these do not: {{{ (replicateM 2 . mask) (const undefined) (replicateM 2 . mask) ((\x -> undefined x) :: a -> b) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 00:28:49 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 00:28:49 -0000 Subject: [GHC] #10629: threadWaitRead throws BlockedIndefinitelyOnMVar In-Reply-To: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> References: <056.586b1ca3b16a53fa41134bf8c734bfb2@haskell.org> Message-ID: <071.967e394379ac8adedf6570bfa4c631be@haskell.org> #10629: threadWaitRead throws BlockedIndefinitelyOnMVar -------------------------------------+------------------------------------- Reporter: | Owner: simonmar facundo.dominguez | Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 7.10.1 Resolution: worksforme | Keywords: | concurrency sockets Operating System: Linux | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: #10317 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => worksforme * related: => #10317 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 07:19:38 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 07:19:38 -0000 Subject: [GHC] #10690: Save merged signatures to disk In-Reply-To: <045.25a62546e19528fda1b12c19e43ea653@haskell.org> References: <045.25a62546e19528fda1b12c19e43ea653@haskell.org> Message-ID: <060.fc5a46407b2db978d318146ef4a96c52@haskell.org> #10690: Save merged signatures to disk -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1098 -------------------------------------+------------------------------------- Changes (by ezyang): * differential: => Phab:D1098 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 07:33:15 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 07:33:15 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.05111cc0d9de79fe4470991e35d69bbd@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by jakewheat): I tried with text-1.2.1.2: with ghc 7.10.1: {{{ real 1m20.054s user 2m3.324s sys 0m51.684s }}} with ghc 7.10.2: {{{ real 10m32.169s user 13m39.756s sys 4m18.856s }}} It is still slow - is this expected? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 08:18:44 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 08:18:44 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.66d436ab8f9b360cde9a735464985529@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): That is most certainly not expected, contrary to my previous measurements, and very concerning. I will need to investigate. Thanks for mentioning this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 08:40:26 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 08:40:26 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.f6cac6553badc2e7f485521d1917099d@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by jakewheat): I wasn't able to see the speed up with the reduced test case code above either: ghc 7.10.2, text 1.2.1.1 {{{ time ghc Test.hs -c -fforce-recomp -Rghc-timing -O -package-db .cabal- sandbox/x86_64-linux-ghc-7.10.2-packages.conf.d/ <> real 0m2.958s user 0m2.908s sys 0m0.048s }}} ghc 7.10.2, text 1.2.1.2 {{{ time ghc Test.hs -c -fforce-recomp -Rghc-timing -O -package-db .cabal- sandbox/x86_64-linux-ghc-7.10.2-packages.conf.d/ <> real 0m2.954s user 0m2.892s sys 0m0.060s }}} ghc 7.10.1, text 1.2.1.2 {{{ time ghc Test.hs -c -fforce-recomp -Rghc-timing -O -package-db .cabal- sandbox/x86_64-linux-ghc-7.10.1-packages.conf.d/ <> real 0m0.289s user 0m0.280s sys 0m0.004s }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 09:08:00 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 09:08:00 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.52379878f6051a358517828aad13b2ba@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * owner: bgamari => * status: merge => new Comment: Unfortunately for reasons I don't yet understand, my testcase was not reliably reproducing the issue, which led me to believe that the phase control annotations resolved the issue. Sadly, it seems that this is not the case. Simon, I am a bit concerned that the phase control annotations aren't actually sufficient to resolve this issue. The problem being that the rules are being rewritten during the compilation of the module which defines them (`Data.Text.Show`); consequently the rules making it in to the interface file are still being rewritten to, {{{ "TEXT literal" [2] forall a :: Addr# unstream (map safe (streamList @ Char (build @ Char (\ @ b -> unpackFoldrCString# @ b a)))) = unpackCString# a }}} Perhaps I misunderstood: did you not expect this issue to be fixed via phase control? It seems that the only solution here is to fix the underlying issue: ensure that the LHS is not rewritten by merging the fix from comment:15. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 09:31:22 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 09:31:22 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.0207465fd47c445049412175a7172402@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Arg, it appears that my validation script was running against the wrong GHC tree when I went to validate the `text` change, hence the incorrect conclusion that it resolved the issue. A very unfortunate mistake. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 09:57:50 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 09:57:50 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.6918a6801b564f7d3617be58b8b55f69@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.3 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Cheery-picked in 3e1366e34e578fec9cbb2d34ccf0be380fbb2235 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 09:58:34 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 09:58:34 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.a08aea6b18eb6b272afcbf7d7636d9c4@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): When rewriting in a rule (or unfolding), GHC sets the phase to the activation phase of the rule (or unfolding); in this case [2]. Now, from comment:13, it was clear that I believed that rule `unpack` was switched off before (the new) `TEXT literal` was switched on. But I was wrong: `unpack` is active anytime before phase 1, and hence is active in phase 2; so the two still compete. I should have said {{{ {-# RULES [1] "TEXT literal" forall a. unstream (S.map safe (S.streamList (GHC.unpackCString# a))) = unpackCString# a #-} }}} Now `TEXT literal` won't be active until phase 1, by which time `unpack` is switched off. Try that. How annoying. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:02:07 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:02:07 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.a32f2003299d66970a4a0be41f47f8bc@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"4e8d74d2362fbb025614ddeedfa3a9202bb6f2bb/ghc" 4e8d74d/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4e8d74d2362fbb025614ddeedfa3a9202bb6f2bb" Deal with phantom type variables in rules See Note [Unbound template type variables] in Rules.hs This fixes Trac #10689. The problem was a rule LHS that mentioned a type variable in a phantom argument to a type synonym. Then matching the LHS didn't bind the type variable, and the rule matcher complained. This patch fixes the problem, as described by the Note. I also went back to not-cloning the template varaibles during rule matching. I'm convinced that it's not necessary now (if it ever was), and cloning makes the fix for #10689 much more fiddly. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:02:07 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:02:07 -0000 Subject: [GHC] #10694: CPR analysis too optimistic when returning a component of a product In-Reply-To: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> References: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> Message-ID: <062.83ef6ff7198f2d3f56a9de38eb191ed5@haskell.org> #10694: CPR analysis too optimistic when returning a component of a product -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | 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: 10678 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"499b926be70b06e2e97b234cdb39cac94dd249e0/ghc" 499b926/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="499b926be70b06e2e97b234cdb39cac94dd249e0" Fix Trac #10694: CPR analysis In this commit commit 0696fc6d4de28cb589f6c751b8491911a5baf774 Author: Simon Peyton Jones Date: Fri Jun 26 11:40:01 2015 +0100 I made an error in the is_var_scrut tests in extendEnvForProdAlt. This patch fixes it, thereby fixing Trac #10694. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:04:14 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:04:14 -0000 Subject: [GHC] #10694: CPR analysis too optimistic when returning a component of a product In-Reply-To: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> References: <047.b36bc2d7ae7b4264cf324d7e80722ffc@haskell.org> Message-ID: <062.5e374ee4f19f91c99f8f66aa816bf9a4@haskell.org> #10694: CPR analysis too optimistic when returning a component of a product -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | stranal/should_compile/T10694 Blocked By: | Blocking: 10678 Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => stranal/should_compile/T10694 * resolution: => fixed Comment: I think I've fixed this. Thanks for identifying it so clearly. I hope this unblocks your `runST` work. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:07:08 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:07:08 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.9d9897ed38d8a8d82501a0f9b22bea5a@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): > > When rewriting in a rule (or unfolding), GHC sets the phase to the activation phase of the rule (or unfolding);" > what does "the phase" refer to? The simplifier has an ambient phase. We just set the ambient phase before rewriting in unfoldings and rewrite rules. See `Note [Simplifying inside stable unfoldings]` in `SimplUtils` -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:08:36 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:08:36 -0000 Subject: [GHC] #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' In-Reply-To: <045.743fe21fa784fce71ea539681c963bac@haskell.org> References: <045.743fe21fa784fce71ea539681c963bac@haskell.org> Message-ID: <060.43707f67c062dca16ca0c107d3047d6d@haskell.org> #10689: compiling singletons-1.1.2.1 as -O1 -fspec-constr fails as 'Template variable unbound in rewrite rule' -------------------------------------+------------------------------------- Reporter: slyfox | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | simplCore/should_compile/T10689, | T10689a Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => simplCore/should_compile/T10689, T10689a * status: new => merge Comment: Fixed. We could merge to 7.10.3 I guess, so I'll set it to 'merge'. It's not an entirely trivial fix, so I'm a bit inclined not to, though. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:30:35 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:30:35 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.deb1de701de1f28a046bc3fa6d3ac10c@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): I see, while rewriting inside a rule or unfolding the simplifier is essentially pretending it is in the phase specified by the activation phase of the thing being rewritten. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 10:48:01 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 10:48:01 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.84ea8f2bb5dad79983f4b9efc266ac85@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 11:04:30 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 11:04:30 -0000 Subject: [GHC] #10710: More self-explanatory pragmas for inlining phase control Message-ID: <046.f56ee656c180387739bfbd9da62ea521@haskell.org> #10710: More self-explanatory pragmas for inlining phase control -------------------------------------+------------------------------------- Reporter: nomeata | Owner: Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Parser) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Eventually implement [[Proposal/SelfExplinatoryInlinePragmas]]. And while at it: Extend the docs where they say ?You shouldn't ever need to do this, unless you're very cautious about code size.? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 11:49:09 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 11:49:09 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.379eff04315151e18489887ff5952b72@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: fixed | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: This should now actually be resolved with `text` 1.2.1.3. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 11:50:48 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 11:50:48 -0000 Subject: [GHC] #10708: Rejection of constant functions defined using conditional pattern matching In-Reply-To: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> References: <052.6642c2a30fffd04ac1211d679c9e5063@haskell.org> Message-ID: <067.c10a57603c27fad2b5fc163677fd245a@haskell.org> #10708: Rejection of constant functions defined using conditional pattern matching -------------------------------------+------------------------------------- Reporter: HubertGaravel | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: invalid | Keywords: Operating System: Linux | Architecture: x86 Type of failure: GHC rejects | Test Case: valid program | Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by HubertGaravel): Thanks for the insight. If I try to reformulate, the definition of d3 is allowed by the syntax but forbidden by the static semantics. Perhaps the static semantics rule is too rigid and could be relaxed to make Haskell more regular. The example below shows that regularity is broken for arity 0 (empty pattern list). But I can live with this bizarre exception and will modify my Haskell generator to handle this corner case. Thanks again! Hubert {{{#!hs -- valid for arity 2 f2 x y | x == 0 = x f2 x y | x /= 0 = x + 1 -- valid for arity 1 f1 x | x == 0 = x f1 x | x /= 0 = x + 1 -- invalid for arity 0 f0 | 0 == 0 = 0 f0 | 0 /= 0 = 1 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 12:16:13 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 12:16:13 -0000 Subject: [GHC] #5218: Add unpackCStringLen# to create Strings from string literals In-Reply-To: <044.69091f2248f564745af8f69c26fefc28@haskell.org> References: <044.69091f2248f564745af8f69c26fefc28@haskell.org> Message-ID: <059.f97fbb3460c9d900c875e6c82e8b60e7@haskell.org> #5218: Add unpackCStringLen# to create Strings from string literals -------------------------------------+------------------------------------- Reporter: tibbe | Owner: | thoughtpolice Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5877 #10064 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): nomeata, I'm not sure I see how your problem would be treated by the proposal 2 described in comment:3. Perhaps I am missing something or are you thinking of another approach entirely? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 12:35:06 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 12:35:06 -0000 Subject: [GHC] #5218: Add unpackCStringLen# to create Strings from string literals In-Reply-To: <044.69091f2248f564745af8f69c26fefc28@haskell.org> References: <044.69091f2248f564745af8f69c26fefc28@haskell.org> Message-ID: <059.3f3d753522c2b245b4832cef5ab9d3a2@haskell.org> #5218: Add unpackCStringLen# to create Strings from string literals -------------------------------------+------------------------------------- Reporter: tibbe | Owner: | thoughtpolice Type: feature request | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.0.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5877 #10064 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Well, any way to include a literal bytestring would help in avoiding the runtime cost. If the setup is only for `Text.ByteString`, there might be some dark coercing magic required to make that a vector while still pointing at the same `Addr#`, but it should work. I currently have a template-haskell based solution in [my repository](https://github.com/entropia/tip-toi- reveng/blob/master/src/BakedVector.hs) which allows me to write [this code](https://github.com/entropia/tip-toi- reveng/blob/master/src/KnownCodes.hs), which works fine for me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 12:42:54 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 12:42:54 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm Message-ID: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Compile-time Unknown/Multiple | performance bug Test Case: ghcirun004 | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Phab:D924 has proposed that we redefine `mapM_`, currently, {{{ mapM_ = foldr ((>>) . f) (return ()) }}} as, {{{ mapM_ = foldr ((*>) . f) (return ()) = traverse_ }}} as part of the AMP proposal. However, this appears to have severe effects on the performance characteristics of the `Assembler` monad defined in `ByteCodeAsm`. In particular, the `mapM_` use in `ByteCodeAsm.assembleBCO` blows up severely, increasing the runtime of the `ghcirun004` testcase from 4 seconds to over 5 minutes. Intriguingly, defining `(*>) = (>>)` in `Assembler`'s `Applicative` instance (as done in Phab:D1097) restores reasonable runtime. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 12:46:15 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 12:46:15 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.2fb473e8271fb076cf0719ce894ba8df@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): [https://gist.github.com/bgamari/9623997162a3399859a9 Here] is a minimal testcase demonstrating the difference. The efficient definition of `mapM_` (using `(>>)`) produces this Core, {{{#!hs mapA_3 :: Assembler () mapA_3 = Main.Pure () doTestM_go :: [Assembler Integer] -> Assembler () doTestM_go = \ ds_a1XT -> case ds_a1XT of _ { [] -> mapA_3; : y_a1XY ys_a1XZ -> let { k_a1VW k_a1VW = doTestM_go ys_a1XZ } in $c>>= y_a1XY (\ _ -> k_a1VW) } doTestM :: Assembler () doTestM = doTestM_go test }}} Whereas the slower `Applicative`-based definition produces, {{{#!hs mapA_3 :: Assembler () mapA_3 = Main.Pure () mapA_2 :: Assembler (() -> ()) mapA_2 = Main.Pure id lvl4_r3JE :: Integer -> Assembler (() -> ()) lvl4_r3JE = \ _ -> Main.mapA_2 doTestA_go :: [Assembler Integer] -> Assembler () doTestA_go = \ ds_a1XT -> case ds_a1XT of _ { [] -> mapA_3; : y_a1XY ys_a1XZ -> let { m2_a1W7 m2_a1W7 = doTestA_go ys_a1XZ } in $c>>= ($c>>= y_a1XY lvl4_r3JE) (\ x1_a1W8 -> $c>>= m2_a1W7 (\ x2_a1W9 -> Pure (x1_a1W8 x2_a1W9))) } doTestA :: Assembler () doTestA = doTestA_go test }}} Note the three `(>>=)` uses in the applicative version, compared to the single invocation in the monadic version. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 13:00:13 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 13:00:13 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.38547676cb550bac8bcf527a9f73a908@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Indeed, one can go from the slow code to the efficient, by just applying all three of the monad laws in the right order :-) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 13:56:10 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 13:56:10 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.7bdb2393dcabd94d022838bb6018dfd8@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): BTW, here are the relevant definitions that add up to three `>>=` for one `*>`: {{{#!hs a1 *> a2 = (id <$ a1) <*> a2 (<$) = fmap . const fmap = liftM liftM f m1 = do { x1 <- m1; return (f x1) } -- here is one (<*>) = ap ap m1 m2 = do { x1 <- m1; x2 <- m2; return (x1 x2) } -- here are two }}} It seems that performance-worrying code should simply ''not'' implement `Functor` and `Applicative` via the `Monad`-derived methods. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 14:05:51 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 14:05:51 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.a13fbee4f22e2a4c7d6a8b669ef4aa83@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Of course, one might expect the compiler to derive the good implementation from the bad. It would be valid, assuming the monad laws hold (which we generally do not do): {{{#!hs a1 *> a2 == (id <$ a1) <*> a2 -- inline *> == fmap (const id) a1 <*> a2 -- inline <$ == liftM (const id) a1 <*> a2 -- inline fmap == (a1 >>= (\x1 -> return (const id x1))) <*> a2 -- liftM == (a1 >>= (\_ -> return id)) <*> a2 -- inline const == (a1 >>= (\_ -> return id)) >>= (\x2 -> a2 >>= (\x3 -> return (x2 x3))) -- inline <*> and ap == a1 >>= (\_ -> return id >>= (\x2 -> a2 >>= (\x3 -> return (x2 x3)))) -- assoc monad law == a1 >>= (\_ -> a2 >>= (\x3 -> return (id x3))) -- first monad law == a1 >>= (\_ -> a2 >>= return) -- inline id, eta-contract == a1 >>= (\_ -> a2) -- second monad law }}} Maybe a bit out of reach for our current simplification infrastructure, where for example the methods `>>=` and `return` will quickly be replaced by their concrete implementations -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 14:34:39 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 14:34:39 -0000 Subject: [GHC] #5001: makeCorePair: arity missing In-Reply-To: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> References: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> Message-ID: <060.b2628700b525fa4f723108f99832abea@haskell.org> #5001: makeCorePair: arity missing -------------------------------------+------------------------------------- Reporter: maeder | Owner: Type: bug | Status: new Priority: high | Milestone: 7.4.1 Component: Compiler | Version: 7.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | deSugar/should_compile/T5001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Simon Peyton Jones ): In [changeset:"72d23c3e0244b1163d7806e40128ad51cc959f7f/ghc" 72d23c3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="72d23c3e0244b1163d7806e40128ad51cc959f7f" Better treatment of signatures in cls/inst The provoking cause for this patch is Trac #5001, comment:23. There was an INLINE pragma in an instance decl, that shouldn't be there. But there was no complaint, just a mysterious WARN later. I ended up having to do some real refactoring but the result is, I think, simpler and more robust. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:04:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:04:40 -0000 Subject: [GHC] #9516: unsafeUnmask unmasks even inside uninterruptibleMask In-Reply-To: <044.1d01b7c46053b095d721dbccbd1f2dd3@haskell.org> References: <044.1d01b7c46053b095d721dbccbd1f2dd3@haskell.org> Message-ID: <059.5101657d764a9217434df7c4c3e2746f@haskell.org> #9516: unsafeUnmask unmasks even inside uninterruptibleMask -------------------------------------+------------------------------------- Reporter: edsko | Owner: simonmar Type: bug | Status: new Priority: normal | Milestone: Component: Runtime System | 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: | Differential Revisions: Phab:D181 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"5a8a8a64e793d2efbe9ea7d445cc8efe75d11f80/ghc" 5a8a8a64/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="5a8a8a64e793d2efbe9ea7d445cc8efe75d11f80" Don't allowInterrupt inside uninterruptibleMask This fixes #9516. Differential Revision: https://phabricator.haskell.org/D181 Authored-by: Edsko de Vries }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:04:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:04:40 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.f103f8d6d70a36039e0f9c524e247561@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: patch Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"9f7cdfee3e9f9ca6fbfa27d3b2dc2d86ac4ee226/ghc" 9f7cdfee/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="9f7cdfee3e9f9ca6fbfa27d3b2dc2d86ac4ee226" Make configure error out on missing ghc-tarballs on Windows Currently checking out the source on windows requires two git checkouts. One for the GHC sources and one for the GHC-tarballs. This patch will make configure issue an error if compiling under windows and the GHC-tarballs folder is missing. On failure the user is told which command they need to run to get the tarballs or if they want configure to handle it for them configure provide the `--enable-tarballs-autodownload` flag. Test Plan: 1. make sure ghc-tarballs folder is not present 2. run ./configure which should fail giving an error that tarballs is missing and how to get it 3. run ./configure --enable-tarballs-autodownload and the tarballs should be downloaded and configure finishes 4. rerun the command in 3, no new download should be done. 5. run configure without --enable-tarballs-autodownload, configure should finish correctly. Reviewers: bgamari, austin, thomie Reviewed By: thomie Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1108 GHC Trac Issues: #10705 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:04:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:04:40 -0000 Subject: [GHC] #10700: include/stg/Prim.h isn't C++ compatible In-Reply-To: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> References: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> Message-ID: <060.31d792e146d843b287a566251e7b8b6a@haskell.org> #10700: include/stg/Prim.h isn't C++ compatible -------------------------------------+------------------------------------- Reporter: Fabian | Owner: rasen Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.1 Resolution: | Keywords: FFI, | newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1107 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"e7c331af4674dd072a9f1d67feb586679b365b98/ghc" e7c331af/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="e7c331af4674dd072a9f1d67feb586679b365b98" Make headers C++ compatible (fixes #10700) Some headers used `new` as parameter name, which is reserved word in C++. This patch changes these names to `new_`. Test Plan: validate Reviewers: austin, ezyang, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1107 GHC Trac Issues: #10700 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:04:40 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:04:40 -0000 Subject: [GHC] #9600: Bad error message: Applicative is not a derivable class In-Reply-To: <042.64352bf7acca582cb0ead8359109244c@haskell.org> References: <042.64352bf7acca582cb0ead8359109244c@haskell.org> Message-ID: <057.9dfd64b0df39c13f8232f82106c04a01@haskell.org> #9600: Bad error message: Applicative is not a derivable class -------------------------------------+------------------------------------- Reporter: nh2 | Owner: | JohnWiegley Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D216 -------------------------------------+------------------------------------- Comment (by Ben Gamari ): In [changeset:"4f80ec0ee438800d95673a4898e69371957fed09/ghc" 4f80ec0e/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="4f80ec0ee438800d95673a4898e69371957fed09" Improve error message for newtypes and deriving clauses Summary: Change the error message generated when a deriving clause related to a newtype fails to always suggested trying GeneralizedNewtypeDeriving, even in situations where it may not work. Fixes #9600. Test Plan: testsuite/deriving/should_fail/9600.hs Reviewers: austin, bgamari, simonpj Rebased-by: bgamari Reviewed By: simonpj Subscribers: bgamari, hvr, simonmar, carter Differential Revision: https://phabricator.haskell.org/D216 GHC Trac Issues: #9600 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:10:22 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:10:22 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.41d009664eec6c69cee354172628924c@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Phyx- Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:10:34 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:10:34 -0000 Subject: [GHC] #9516: unsafeUnmask unmasks even inside uninterruptibleMask In-Reply-To: <044.1d01b7c46053b095d721dbccbd1f2dd3@haskell.org> References: <044.1d01b7c46053b095d721dbccbd1f2dd3@haskell.org> Message-ID: <059.9348ecdc37a5452e3effae85c1da2e28@haskell.org> #9516: unsafeUnmask unmasks even inside uninterruptibleMask -------------------------------------+------------------------------------- Reporter: edsko | Owner: simonmar Type: bug | Status: closed Priority: normal | Milestone: Component: Runtime System | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D181 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:10:43 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:10:43 -0000 Subject: [GHC] #10700: include/stg/Prim.h isn't C++ compatible In-Reply-To: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> References: <045.8e82f2e96f7b839c9a73a7c13e4442bc@haskell.org> Message-ID: <060.25e80319ff9a1b7ad4bd51cc4eeb11bd@haskell.org> #10700: include/stg/Prim.h isn't C++ compatible -------------------------------------+------------------------------------- Reporter: Fabian | Owner: rasen Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (FFI) | Version: 7.10.1 Resolution: fixed | Keywords: FFI, | newcomers Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1107 -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 15:10:51 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 15:10:51 -0000 Subject: [GHC] #9600: Bad error message: Applicative is not a derivable class In-Reply-To: <042.64352bf7acca582cb0ead8359109244c@haskell.org> References: <042.64352bf7acca582cb0ead8359109244c@haskell.org> Message-ID: <057.37025043f8c732ff59425d5be8d2ca4f@haskell.org> #9600: Bad error message: Applicative is not a derivable class -------------------------------------+------------------------------------- Reporter: nh2 | Owner: | JohnWiegley Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D216 -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 16:47:56 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 16:47:56 -0000 Subject: [GHC] #5001: makeCorePair: arity missing In-Reply-To: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> References: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> Message-ID: <060.a1055e849a200a760f5649ae1a572e5c@haskell.org> #5001: makeCorePair: arity missing -------------------------------------+------------------------------------- Reporter: maeder | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.4.1 Component: Compiler | Version: 7.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | deSugar/should_compile/T5001, | rename/should_fail/T5001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: deSugar/should_compile/T5001 => deSugar/should_compile/T5001, rename/should_fail/T5001 * resolution: => fixed Comment: OK, I've fixed this. `mono-traversable` is in error, and GHC properly reports it now: on line 514 of `MonoTraversable.hs` we have {{{ {-# INLINE ofoldMap #-} }}} but there is no corresponding method binding in that instance declaration. So that needs fixing in `mono-traversable`. Meanwhile I'll close the ticket. Thanks for the nice small test case. It's pretty harmless so no need to merge to 7.10. I added another test in `rename/should_fail/T5001`, not realising that we already have `deSugar/should_compile/T5001`. But that's fine, they don't conflict and test different things. Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 17:00:23 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 17:00:23 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.856322ed016fd4a4eaebd3f4d3d188df@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I have to say that I still don't understand exactly why {{{ a1 *> a2 == (a1 >>= (\_ -> return id)) >>= (\x2 -> a2 >>= (\x3 -> return (x2 x3))) }}} is more than a constant (say 10 times) slower than `a1 >> a2` for this `Assembler` monad. Experimentally bgamari's test program does ~n^2^ allocations and takes ~n^3^ total time in the Applicative version, while the Monad version runs in linear allocations and time. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 17:38:22 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 17:38:22 -0000 Subject: [GHC] #9772: Building documentation alone is broken In-Reply-To: <048.184975ea5e9493595c61ee0ae101aa72@haskell.org> References: <048.184975ea5e9493595c61ee0ae101aa72@haskell.org> Message-ID: <063.84b23ec97fcceb8afa755a037695420a@haskell.org> #9772: Building documentation alone is broken -------------------------------------+------------------------------------- Reporter: jstolarek | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.9 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => invalid Comment: Replying to [ticket:9772 jstolarek]: > At the moment it seems that the only way to build documentation is to actually build all of GHC, which is nonsense. Not nonsense at all. * To build the user's guide, the tool `utils/mkUserGuidePart` is needed, which relies on the ghc library. * To build the haddock docs, haddock (!) is needed, which also relies on the ghc library. Moreover, haddock itself needs to build a module before a can generate documentation for it (I don't know the details). From `rules/haddock.mk`: {{{ # --no-tmp-comp-dir above is important: it saves a few minutes in a # validate. This flag lets Haddock use the pre-compiled object files # for the package rather than rebuilding the modules of the package in # a temporary directory. Haddock needs to build the package when it # uses the Template Haskell or Annotations extensions, for example. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:10:27 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:10:27 -0000 Subject: [GHC] #10696: -fcpr-off doesn't disable CPR completely In-Reply-To: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> References: <047.f4fc0fb9a55bc4890094badcc2ea5c5d@haskell.org> Message-ID: <062.b3041c3a7e9acfe18b682f4b1d523f17@haskell.org> #10696: -fcpr-off doesn't disable CPR completely -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.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 Revisions: Phab:D1104 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:14:49 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:14:49 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.fa652100f1cf5d73ea780445b00cf55c@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: GregWeber (added) Comment: Fabian: if you change your test to not depend on any external libraries, that would be great. The problem is we can't put it in the testsuite ''as is''. cc GregWeber, who implemented this feature recently. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:17:06 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:17:06 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly In-Reply-To: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> References: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> Message-ID: <065.67bdc1f5fa148e6b643c5e6da0ee714e@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: dnusbaum Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1114 -------------------------------------+------------------------------------- Changes (by rodlogic): * status: new => patch * differential: => D1114 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:18:06 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:18:06 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly In-Reply-To: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> References: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> Message-ID: <065.2148140bda002c717587c8fb8314e36e@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: dnusbaum Type: bug | Status: patch Priority: normal | Milestone: Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: D1114 -------------------------------------+------------------------------------- Comment (by rodlogic): Sorry @dnusbaum, I had my nose around this issue, which was a problem pretty printing the HsSyn AST and not TH AST. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:18:14 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:18:14 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.1ad2c358148deba3d98c007016409d9b@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: GregWeber (added) Comment: Fabian: did you add the right test here (filename makes it appear it is for a different ticket)? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:18:35 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:18:35 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.5d2194152ec5826d36953cef0c2fc4f7@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: GregWeber (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:34:39 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:34:39 -0000 Subject: [GHC] #10555: RULE left-hand side too complicated to desugar In-Reply-To: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> References: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> Message-ID: <061.b83ea239311d97a04df5491eee83aaa8@haskell.org> #10555: RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: yongqli | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: #10699 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * version: 7.10.2-rc1 => 7.0.4 Old description: > GHC version 7.10.1.20150612 breaks the `fast-math` package, which > compiled fine on GHC 7.10.1.20150519. To reproduce, run `cabal install > fast-math`. > > {{{ > > Numeric/FastMath/Approximation.hs:60:1: Warning: > RULE left-hand side too complicated to desugar > Optimised lhs: case /## y2 x of wild_00 { __DEFAULT -> > (case /## y1 x of wild_X2 { __DEFAULT -> +## wild_X2 > }) wild_00 > } > Orig lhs: case /## y2 x of wild_00 { __DEFAULT -> > (case /## y1 x of wild_00 { __DEFAULT -> +## wild_00 }) > wild_00 > } > > Numeric/FastMath/Approximation.hs:63:1: Warning: > RULE left-hand side too complicated to desugar > Optimised lhs: case /## y2 x of wild_00 { __DEFAULT -> > (case /## y1 x of wild_X2 { __DEFAULT -> -## wild_X2 > }) wild_00 > } > Orig lhs: case /## y2 x of wild_00 { __DEFAULT -> > (case /## y1 x of wild_00 { __DEFAULT -> -## wild_00 }) > wild_00 > } > > Numeric/FastMath/Approximation.hs:103:1: Warning: > RULE left-hand side too complicated to desugar > Optimised lhs: case divideFloat# y2 x of wild_00 { __DEFAULT -> > (case divideFloat# y1 x of wild_X2 { __DEFAULT -> > minusFloat# wild_X2 > }) > wild_00 > } > Orig lhs: case divideFloat# y2 x of wild_00 { __DEFAULT -> > (case divideFloat# y1 x of wild_00 { __DEFAULT -> > minusFloat# wild_00 > }) > wild_00 > } > ghc: panic! (the 'impossible' happened) > (GHC version 7.10.1.20150612 for x86_64-unknown-linux): > Simplifier ticks exhausted > When trying RuleFired float commute left * > 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: 4004 > > Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug > }}} New description: GHC reports the following warnings for the `fast-math` package. To reproduce, run `cabal install fast-math==1.0 --with-ghc=ghc-7.10.1` (ghc-7.10.2 panics on this package, see #10699). {{{ Numeric/FastMath/Approximation.hs:60:1: Warning: RULE left-hand side too complicated to desugar Optimised lhs: case /## y2 x of wild_00 { __DEFAULT -> (case /## y1 x of wild_X2 { __DEFAULT -> +## wild_X2 }) wild_00 } Orig lhs: case /## y2 x of wild_00 { __DEFAULT -> (case /## y1 x of wild_00 { __DEFAULT -> +## wild_00 }) wild_00 } Numeric/FastMath/Approximation.hs:63:1: Warning: RULE left-hand side too complicated to desugar Optimised lhs: case /## y2 x of wild_00 { __DEFAULT -> (case /## y1 x of wild_X2 { __DEFAULT -> -## wild_X2 }) wild_00 } Orig lhs: case /## y2 x of wild_00 { __DEFAULT -> (case /## y1 x of wild_00 { __DEFAULT -> -## wild_00 }) wild_00 } Numeric/FastMath/Approximation.hs:103:1: Warning: RULE left-hand side too complicated to desugar Optimised lhs: case divideFloat# y2 x of wild_00 { __DEFAULT -> (case divideFloat# y1 x of wild_X2 { __DEFAULT -> minusFloat# wild_X2 }) wild_00 } Orig lhs: case divideFloat# y2 x of wild_00 { __DEFAULT -> (case divideFloat# y1 x of wild_00 { __DEFAULT -> minusFloat# wild_00 }) wild_00 } }}} -- Comment: I changed the description to not include the panic from #10699. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:35:29 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:35:29 -0000 Subject: [GHC] #10555: RULE left-hand side too complicated to desugar In-Reply-To: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> References: <046.f79ed2aea9404c40727abba6768bec30@haskell.org> Message-ID: <061.39fe8bbbeb1fdfcce1dead4a9a214780@haskell.org> #10555: RULE left-hand side too complicated to desugar -------------------------------------+------------------------------------- Reporter: yongqli | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.0.4 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: yes Blocked By: | Blocking: Related Tickets: #10699 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * priority: normal => low -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:39:16 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:39:16 -0000 Subject: [GHC] #5001: makeCorePair: arity missing In-Reply-To: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> References: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> Message-ID: <060.d4deb92e4899f006ee4a9c640ad22637@haskell.org> #5001: makeCorePair: arity missing -------------------------------------+------------------------------------- Reporter: maeder | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.4.1 Component: Compiler | Version: 7.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | deSugar/should_compile/T5001, | rename/should_fail/T5001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"b5097fe77f3d610db3eea8f659df927001bfcc10/ghc" b5097fe/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="b5097fe77f3d610db3eea8f659df927001bfcc10" Testsuite: rename rename/should_fail/T5001 to T5001b (#5001) Test names should be unique. This fixes a framework failure. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:40:13 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:40:13 -0000 Subject: [GHC] #5001: makeCorePair: arity missing In-Reply-To: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> References: <045.01643f91fbc10ebef1f612bc5674a3a7@haskell.org> Message-ID: <060.311f274266eda94c974e31fe3b2548f1@haskell.org> #5001: makeCorePair: arity missing -------------------------------------+------------------------------------- Reporter: maeder | Owner: Type: bug | Status: closed Priority: high | Milestone: 7.4.1 Component: Compiler | Version: 7.2.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | deSugar/should_compile/T5001, | rename/should_fail/T5001b Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * testcase: deSugar/should_compile/T5001, rename/should_fail/T5001 => deSugar/should_compile/T5001, rename/should_fail/T5001b -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 19:56:46 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 19:56:46 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.acd1a441614282db57dc6ee9073435cd@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by GregWeber): This probably indicates a general problem with TH pretty-printing. Is the problem the same with -ddump-splices ? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:15:39 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:15:39 -0000 Subject: [GHC] #7287: Primops in RULES generate warnings In-Reply-To: <041.39f3a79557413604c39dd7b5a31448a6@haskell.org> References: <041.39f3a79557413604c39dd7b5a31448a6@haskell.org> Message-ID: <056.04feeb3175052f8057b3c3cbb8a235d3@haskell.org> #7287: Primops in RULES generate warnings -------------------------------------+------------------------------------- Reporter: rl | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.6.2 Component: Compiler | Version: 7.7 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | simplCore/should_compile/T7287 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * owner: simonpj => * status: closed => new * resolution: fixed => Comment: Commit 2d88a531b7e4dbf4016dca4b1ba3b5dc34256cf4 ("Improve warnings for rules that might not fire") effectively cancels the fix in commit 419af69c1bea2cecce7b4bf58162cbfac81526f2 ("Give PrimOps a NOINLINE pragma, to suppress silly warnings from dsRule"). There is a comment in `testsuite/tests/simplCore/should_compile/T7287.hs` that indicates this is intentional. I'm reopening nevertheless, to be sure, since these two commits are so contradictory; maybe 419af69c1bea2cecce7b4bf58162cbfac81526f2 should be reverted? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:18:22 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:18:22 -0000 Subject: [GHC] #7919: Heap corruption (segfault) from large 'let' expression In-Reply-To: <045.3707d678a38441ef54b667e63e238d84@haskell.org> References: <045.3707d678a38441ef54b667e63e238d84@haskell.org> Message-ID: <060.481789322687809d345ae5746c5bdb5f@haskell.org> #7919: Heap corruption (segfault) from large 'let' expression -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Runtime System | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Runtime crash | Test Case: rts/T7919 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1113 -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => rts/T7919 * differential: => Phab:D1113 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:54:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:54:21 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.be874b69d612a27a6045fa19ab8e3aeb@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.3 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"756fa0a3547a5836ff50787a8f89e2db0793f5d3/ghc" 756fa0a/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="756fa0a3547a5836ff50787a8f89e2db0793f5d3" Testsuite: skip T10489 unless compiler_debugged (#10489) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:54:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:54:21 -0000 Subject: [GHC] #8034: Missing ambiguity test for class methods In-Reply-To: <046.d8e44655b32c8bb4060972d42e5657d4@haskell.org> References: <046.d8e44655b32c8bb4060972d42e5657d4@haskell.org> Message-ID: <061.bace1b83fb62ca6d9ab666699c440ed4@haskell.org> #8034: Missing ambiguity test for class methods -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.7 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"58986c4953b045247cb09caa544981cccf14f242/ghc" 58986c4/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="58986c4953b045247cb09caa544981cccf14f242" Testsuite: add typecheck/should_fail/T8034 (#8034) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:54:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:54:21 -0000 Subject: [GHC] #5333: Arrow command combinators and infixr cause the desugarer to fail In-Reply-To: <044.d282e017cea5d9685c27f48c7cf4a590@haskell.org> References: <044.d282e017cea5d9685c27f48c7cf4a590@haskell.org> Message-ID: <059.1dc9eb68acd1ce5ab55a63af0d573b9e@haskell.org> #5333: Arrow command combinators and infixr cause the desugarer to fail -------------------------------------+------------------------------------- Reporter: peteg | Owner: ross Type: bug | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 7.0.3 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"6880277381061593da2c2c19767ba508fb4045e3/ghc" 6880277/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="6880277381061593da2c2c19767ba508fb4045e3" Testsuite: add arrows/should_compile/T5333 (#5333) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:54:21 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:54:21 -0000 Subject: [GHC] #9260: Unnecessary error using GHC.TypeLits In-Reply-To: <051.9b98f43647329b740144a23edc96d4be@haskell.org> References: <051.9b98f43647329b740144a23edc96d4be@haskell.org> Message-ID: <066.fe1ee1b9f110f016c83fde2d06c7f5bc@haskell.org> #9260: Unnecessary error using GHC.TypeLits -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: diatchki Type: bug | Status: new Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: type lits, | data kinds, error message Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"58b5f04483258e55b93390fbf5ce41a1dbe23340/ghc" 58b5f04/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="58b5f04483258e55b93390fbf5ce41a1dbe23340" Testsuite: add typecheck/should_fail/T9260 (#9260) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:56:09 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:56:09 -0000 Subject: [GHC] #8034: Missing ambiguity test for class methods In-Reply-To: <046.d8e44655b32c8bb4060972d42e5657d4@haskell.org> References: <046.d8e44655b32c8bb4060972d42e5657d4@haskell.org> Message-ID: <061.c0f016a8a1945867b657622b7516c4db@haskell.org> #8034: Missing ambiguity test for class methods -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler (Type | Version: 7.7 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T8034 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => typecheck/should_fail/T8034 * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 20:58:55 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 20:58:55 -0000 Subject: [GHC] #9260: Unnecessary error using GHC.TypeLits In-Reply-To: <051.9b98f43647329b740144a23edc96d4be@haskell.org> References: <051.9b98f43647329b740144a23edc96d4be@haskell.org> Message-ID: <066.743674deade122d1436571af0019cac8@haskell.org> #9260: Unnecessary error using GHC.TypeLits -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: diatchki Type: bug | Status: closed Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: type lits, | data kinds, error message Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_fail/T9260 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * testcase: => typecheck/should_fail/T9260 * resolution: => fixed Comment: I don't know which commit fixed it, but this is looking good now. I added a test. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 21:11:34 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 21:11:34 -0000 Subject: [GHC] #5333: Arrow command combinators and infixr cause the desugarer to fail In-Reply-To: <044.d282e017cea5d9685c27f48c7cf4a590@haskell.org> References: <044.d282e017cea5d9685c27f48c7cf4a590@haskell.org> Message-ID: <059.242ef27eb828addb4199027717a9bba5@haskell.org> #5333: Arrow command combinators and infixr cause the desugarer to fail -------------------------------------+------------------------------------- Reporter: peteg | Owner: ross Type: bug | Status: closed Priority: low | Milestone: 7.12.1 Component: Compiler | Version: 7.0.3 (Parser) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | arrows/should_compile/T5333 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * testcase: => arrows/should_compile/T5333 * resolution: => fixed Comment: I added the test from the description, and it is currently passing. Please reopen if there is still work to be done here; I didn't quite read the whole discussion. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 21:38:20 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 21:38:20 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.cf7b6e78000ec0108a8ab725f08e79a2@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Replying to [comment:5 rwbarton]: > I have to say that I still don't understand exactly why > {{{ > a1 *> a2 > == (a1 >>= (\_ -> return id)) >>= (\x2 -> a2 >>= (\x3 -> return (x2 x3))) > }}} > is more than a constant (say 10 times) slower than `a1 >> a2` for this `Assembler` monad. Me neither! An articulate explanation from someone would be v helpful -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 22:13:52 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 22:13:52 -0000 Subject: [GHC] #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing Message-ID: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: base/tests/exceptionsrun001 | Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- The following program, extracted from the test exceptionsrun001, should exit with exitcode 100. Instead, when compiled with `-O1`, it never gets past the ioTest and somehow manages to exit with exitcode 0. {{{ {-# LANGUAGE ScopedTypeVariables #-} module Main where import Control.Exception import System.IO.Error import System.Exit main = do ioTest exitWith (ExitFailure 100) ioTest :: IO () ioTest = (catch (ioError (userError "wibble")) (\(e::IOException) -> return ()) }}} I think this will require a git bisect: * last known good commit: 34bb4605d4ec5b131df57ca4c91d6840b7539194 * first known bad commit: f83aab95f59ae9b29f22fc7924e050512229cb9c. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 22:20:19 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 22:20:19 -0000 Subject: [GHC] #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing In-Reply-To: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> References: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> Message-ID: <060.37c9a74460595057306a67cf5d229891@haskell.org> #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Other tests that are failing with WAY=optasm, all dealing with exceptions of some sort: * T3279 * conc012 * conc014 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 22:29:13 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 22:29:13 -0000 Subject: [GHC] #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing In-Reply-To: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> References: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> Message-ID: <060.18d1607bc58cb240c275f08adf6d2435@haskell.org> #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I'll bisect and see what I find (if you aren't doing so already). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 22:31:32 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 22:31:32 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.ca71c97151c1776abd06a8a6882cce97@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): The selfcontained test contains 195 modules to build highlighting-kate: http://code.haskell.org/~slyfox/T9221__highlighting-kate-build- benchmark.tar.gz To run it you need to tweak a path to your 'ghc=' in '''mk.bash'''. On my 8 core box best results can be achieved by setting -A128M (or larger). The test is handy to run 'perf record' on it. My results for '''./mk.bash -j8 -A128M''': {{{ $ perf record -g ./mk.bash -j8 -A128M $ perf report -g + 15,42% 0,78% ghc_worker libc-2.21.so [.] __sched_yield + 15,08% 1,62% ghc_worker [kernel.vmlinux] [k] entry_SYSCALL_64 + 12,70% 0,38% ghc_worker [kernel.vmlinux] [k] sys_sched_yield + 10,91% 6,47% ghc_worker ghc-stage2 [.] clE_info + 10,50% 0,38% ghc_worker [kernel.vmlinux] [k] schedule + 9,14% 1,58% ghc_worker [kernel.vmlinux] [k] __schedule + 8,60% 0,00% ghc_worker [unknown] [.] 0x48032822f800c748 + 5,85% 5,64% ghc_worker ghc-stage2 [.] evacuate + 3,47% 0,94% ghc_worker ghc-stage2 [.] c7F_info + 2,91% 0,69% ghc_worker [kernel.vmlinux] [k] pick_next_task_fair + 2,70% 0,00% ghc_worker [unknown] [.] 0x0000000000000004 + 2,63% 2,28% ghc_worker ghc-stage2 [.] c2k_info + 2,55% 0,00% ghc_worker [unknown] [.] 0x2280f98148088b48 + 1,90% 0,00% ghc_worker [unknown] [.] 0x834807e283da8948 + 1,90% 0,00% as ld-2.21.so [.] _dl_sysdep_start + 1,89% 0,00% as ld-2.21.so [.] dl_main + 1,83% 0,15% as [kernel.vmlinux] [k] page_fault + 1,81% 0,47% as ld-2.21.so [.] _dl_relocate_object }}} If perf does not lie most of the time is spent cycling over sleeping kernel threads. '''clE_info''' is a 'INFO_TABLE(stg_BLACKHOLE,1,0,BLACKHOLE,"BLACKHOLE","BLACKHOLE")' -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:04:34 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:04:34 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.aa159be911dd8b36a3dbf38f0255611d@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): Replying to [comment:5 GregWeber]: > This probably indicates a general problem with TH pretty-printing. Is the problem the same with -ddump-splices ? Yes, I have updated the test with output from both -dth-dec-file and -ddump-splices -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:04:55 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:04:55 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.856cb9dd4a6bafb5d6b9e4abf8bc3c3e@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:04:55 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:04:55 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.31bb88a57a6b25dc15da6f931f665b8f@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:05:43 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:05:43 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.8095c489c776b3348b616664ffb07e6b@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): Replying to [comment:4 thomie]: > Fabian: if you change your test to not depend on any external libraries, that would be great. The problem is we can't put it in the testsuite ''as is''. > > cc GregWeber, who implemented this feature recently. Done -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:08:18 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:08:18 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.8f87920566835376fe711552a56fe0ff@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:08:18 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:08:18 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.edaecc2d841f23c506637dd3c59c7c66@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:09:46 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:09:46 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.f0bb158db9cbcb52e9c2f8812671ce54@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.2.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:10:14 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:10:14 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.32160ba8a0500d89feed90d4f9ba0bae@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" added. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:10:14 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:10:14 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.92b389dfc941fd7ca9b5036b44fe6d2b@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by Fabian): * Attachment "Test10702.hs" removed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:12:16 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:12:16 -0000 Subject: [GHC] #10702: -fth-dec-file uses qualified names in binding positions In-Reply-To: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> References: <045.7054a56022fd28f17ed99e1aff18777c@haskell.org> Message-ID: <060.17f54cfdda26f0a0733a6e47fbaeba1b@haskell.org> #10702: -fth-dec-file uses qualified names in binding positions -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): I updated the test case to remove the dependency on aeson. Interestingly enough, ddump-splices output (included in the attachment) doesn't have this bug. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:14:11 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:14:11 -0000 Subject: [GHC] #10701: -fth-dec-file uses qualified names from hidden modules In-Reply-To: <045.34230300350f9fc926fd4336a412b885@haskell.org> References: <045.34230300350f9fc926fd4336a412b885@haskell.org> Message-ID: <060.4d58e4f32d64178ba31e5ff6d59f8722@haskell.org> #10701: -fth-dec-file uses qualified names from hidden modules -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): Replying to [comment:6 thomie]: > Fabian: did you add the right test here (filename makes it appear it is for a different ticket)? Yes it's the right file. I made one for several tickets. I have updated all tickets with a new file without the dependency on aeson, and with ddump-splices output included -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:17:09 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:17:09 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.6f2f708440523dd15f834133825a8759@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): I'm not sure what you mean by "invalid case clauses", but it seems to me that the error is that {{{ case e of { ...alts... } foo }}} is not valid syntax for an application, it must be parenthesized like {{{ (case e of { ...alts... }) foo }}} A problem with the case expression itself in its context, not the case clauses. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:29:47 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:29:47 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.275124f422f452e035387405687510a3@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Great. To summarize, the output of `ghc -ddump-splices Test10702.hs` is: {{{ instance Read Name where readsPrec x = \ k_a46F v_a46G -> undefined "test" "test2" }}} And it should be: {{{ instance Read Name where readsPrec x = (\ k_a46F v_a46G -> undefined) "test" "test2" }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:47:46 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:47:46 -0000 Subject: [GHC] #10245: panic in new integer switch logic with "out-of-range" literals In-Reply-To: <047.75ea0dc3feddacd480f06c86ecf69bf6@haskell.org> References: <047.75ea0dc3feddacd480f06c86ecf69bf6@haskell.org> Message-ID: <062.2169e1729d8c0a5528501c2a15a509c7@haskell.org> #10245: panic in new integer switch logic with "out-of-range" literals -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: new Priority: high | Milestone: Component: Compiler | Version: 7.11 (CodeGen) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Compile-time | (amd64) crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"aee19d08ec36b0ec5d0ed4fab2b63c78a80dbc23/ghc" aee19d0/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="aee19d08ec36b0ec5d0ed4fab2b63c78a80dbc23" Testsuite: T10245 is passing for WAY=ghci (#10245) Needed to get closer to passing `validate --slow`. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Thu Jul 30 23:58:53 2015 From: ghc-devs at haskell.org (GHC) Date: Thu, 30 Jul 2015 23:58:53 -0000 Subject: [GHC] #10713: Type family not reducing over data family Message-ID: <046.5ef44ab91bf829939e28ffc1eb7fff9f@haskell.org> #10713: Type family not reducing over data family -------------------------------------+------------------------------------- Reporter: acowley | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Given this code, {{{ type family TEq t s where TEq t t = 'True TEq t s = 'False data family T a }}} I expected this GHCi interaction to reduce: `:kind! TEq (T Int) (T Bool)` But it does not. It does reduce (to `'True`) if you instead ask, `:kind! TEq (T Int) (T Int)` Tested on GHC 7.10.2 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 00:09:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 00:09:20 -0000 Subject: [GHC] #10713: Type family not reducing over data family In-Reply-To: <046.5ef44ab91bf829939e28ffc1eb7fff9f@haskell.org> References: <046.5ef44ab91bf829939e28ffc1eb7fff9f@haskell.org> Message-ID: <061.dea4110d6301d558f5d6008cd04521a5@haskell.org> #10713: Type family not reducing over data family -------------------------------------+------------------------------------- Reporter: acowley | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.4 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * version: 7.10.2 => 7.8.4 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 00:44:51 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 00:44:51 -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.3f872bbdb1ce1357a44eb14a12265899@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Old description: > This is a new proposal for solving #1409. The big addition here is that > we create **two** hs-boot files for each hs file: one that is a full hs- > boot file to be imported by hs files to break loops, and a second which > only includes abstract types for hs-boot files to import. C.f. #10679 > > **Discussion.** Here is a slightly goofy `hs-boot` file I've excerpted > from GHC: > > {{{ > module Packages where > > import {-# SOURCE #-} Module (PackageKey) > import {-# SOURCE #-} DynFlags (DynFlags) > > packageKeyPackageIdString :: DynFlags -> PackageKey -> Maybe String > }}} > > The `hs-boot` file must itself import `hs-boot` files, because this boot > file is used by `Module` and `DynFlags`; without `{-# SOURCE #-}`, the > boot file itself will participate in a cycle! > > But notice that there is something very interesting: a boot file is ONLY > ever interested in importing other modules to get types. Never to import > constructors or functions! > > We can use this observation to give us a mechanical transformation of an > `hs` file to an `hs-boot` file, ASSUMING we can define a "second level" > of `hs-boot` file to record our abstract types. > > **Example.** In this example, we have chosen to break the loop from `A`s > import to `B`. > > {{{ > module A where > import {-# SOURCE #-} B > data A = A B > f :: A -> Bool > f (A (B (A b))) = g b > f _ = True > > module B where > import A > data B = B A > g :: B -> Bool > g (B (A (B b))) = f b > g _ = False > }}} > > The first-level `hs-boot`s are: > > {{{ > module A where -- not actually used > import {-# SOURCE 2 #-} B > data A = A B > f :: A -> Bool > > module B where > import {-# SOURCE 2 #-} A > data B = B A > g :: B -> Bool > }}} > > The second-level `hs-boot`s are: > > {{{ > module A where > data A > > module B where -- not actually used > data B > }}} > > **Commentary.** Here are some remarks: > > 1. Because we have to lift the transitive dependencies of anything we > `{-# SOURCE #-}` import, it doesn't make sense to have a pragma which > explicitly says what to put in the `hs-boot` file; instead, we just put > in everything that we *can* handle in an `hs-boot` file (so exclude > anything with missing type signatures, type families, etc.) Ideally, > these automatic hs-boot files are generated lazily, but they should be > reused as necessary. > > 2. This facility actually makes `{-# SOURCE #-}` a lot more attractive > for increasing separate compilation: you can mark an import `{-# SOURCE > #-}` to ensure that if its implementation changes, you don't have to > recompile this module / you can build the module in parallel with that > module. The downside is that when the imported file is modified, we have > to regenerate the `hs-boot` stub before we conclude that the types have > not changed (as opposed to with separate `hs-boot` files, where a > modification to `hs` would not bump the timestamp on `hs-boot`. > > 3. This seems to definitely suggest that you should never need more than > two levels of hs-boot nesting, or perhaps three with kinding. (But maybe > someone has a fancy type system feature for which this is not true!) > Maybe this applies to signature files too. > > 4. We can't force the first level of `hs-boot` files to be abstract > types, for two reasons: (1) a source file importing the hs-boot file may > really need the selector/constructor, and (2) the `hs-boot` files will > reflect any cycles from the source files, that's no good! Rolling out to > the second level breaks the cycle because abstract types never need any > imports. New description: This is a new proposal for solving #1409. The big addition here is that we create **two** hs-boot files for each hs file: one that is a full hs-boot file to be imported by hs files to break loops, and a second which only includes abstract types for hs-boot files to import. C.f. #10679 **Discussion.** Here is a slightly goofy `hs-boot` file I've excerpted from GHC: {{{ module Packages where import {-# SOURCE #-} Module (PackageKey) import {-# SOURCE #-} DynFlags (DynFlags) packageKeyPackageIdString :: DynFlags -> PackageKey -> Maybe String }}} The `hs-boot` file must itself import `hs-boot` files, because this boot file is used by `Module` and `DynFlags`; without `{-# SOURCE #-}`, the boot file itself will participate in a cycle! But notice that there is something very interesting: a boot file is ONLY ever interested in importing other modules to get types. Never to import constructors or functions! We can use this observation to give us a mechanical transformation of an `hs` file to an `hs-boot` file, ASSUMING we can define a "second level" of `hs-boot` file to record our abstract types. **Example.** In this example, we have chosen to break the loop from `A`s import to `B`. {{{ module A where import {-# SOURCE #-} B data A = A B f :: A -> Bool f (A (B (A b))) = g b f _ = True module B where import A data B = B A g :: B -> Bool g (B (A (B b))) = f b g _ = False }}} The first-level `hs-boot`s are: {{{ module A where -- not actually used import {-# SOURCE 2 #-} B data A = A B f :: A -> Bool module B where import {-# SOURCE 2 #-} A data B = B A g :: B -> Bool }}} The second-level `hs-boot`s are: {{{ module A where data A module B where -- not actually used data B }}} **Commentary.** Here are some remarks: 1. Because we have to lift the transitive dependencies of anything we `{-# SOURCE #-}` import, it doesn't make sense to have a pragma which explicitly says what to put in the `hs-boot` file; instead, we just put in everything that we *can* handle in an `hs-boot` file (so exclude anything with missing type signatures, type families, etc.) Ideally, these automatic hs-boot files are generated lazily, but they should be reused as necessary. 2. This facility actually makes `{-# SOURCE #-}` a lot more attractive for increasing separate compilation: you can mark an import `{-# SOURCE #-}` to ensure that if its implementation changes, you don't have to recompile this module / you can build the module in parallel with that module. The downside is that when the imported file is modified, we have to regenerate the `hs-boot` stub before we conclude that the types have not changed (as opposed to with separate `hs-boot` files, where a modification to `hs` would not bump the timestamp on `hs-boot`. 3. This seems to definitely suggest that you should never need more than two levels of hs-boot nesting, or perhaps three with kinding. (But maybe someone has a fancy type system feature for which this is not true!) Maybe this applies to signature files too. 4. We can't force the first level of `hs-boot` files to be abstract types, for two reasons: (1) a source file importing the hs-boot file may really need the selector/constructor, and (2) the `hs-boot` files will reflect any cycles from the source files, that's no good! Rolling out to the second level breaks the cycle because abstract types never need any imports. 5. What about type class instances? I propose that instances be lifted to the `hs-boot` level (so hs file usages of the instance continue to work), but not the `hs-boot2` level (so that we can still "bottom out"). This can result in some slightly unintuitive behavior, however: {{{ module A where instance Eq (a -> b) where ... module B where import A module C where import {-# SOURCE #-} B }}} In this case, `C` would NOT see the `Eq` instance for functions defined in `A`. -- Comment (by ezyang): Update with a comment about handling type class instances. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 00:44:57 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 00:44:57 -0000 Subject: [GHC] #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing In-Reply-To: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> References: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> Message-ID: <060.2121007befea3334d381f0aff45eddff@haskell.org> #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): Actually I just guessed and checked, 7c0fff41789669450b02dc1db7f5d7babba5dee6 is the bad commit. {{{ catch (ioError (userError "wibble")) (\(e::IOException) -> return ()) }}} amounts to {{{ catch# (raiseIO# (toException (userError "wibble"))) ({- handler -}) st }}} but * `raiseIO#`'s strictness signature claims it returns _|_ * `catch#` is now strict in its first argument, as of the commit 7c0fff41789 so the strictness analyser concludes that `ioTest` will never return, and optimizes `main` to {{{ Main.main1 = \ (@ b_aLH) (s_X2HT [OS=OneShot] :: State# RealWorld) -> case Main.ioTest1 s_X2HT of wild_00 { } }}} and what happens then when `ioTest` really does return is undefined. There are apparently good reasons for each of the two bulleted points, but as this test shows they are incompatible. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 00:59:01 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 00:59:01 -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.2da036bcaf1f5fb113288f4b0e89a315@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: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Old description: > This is a new proposal for solving #1409. The big addition here is that > we create **two** hs-boot files for each hs file: one that is a full hs- > boot file to be imported by hs files to break loops, and a second which > only includes abstract types for hs-boot files to import. C.f. #10679 > > **Discussion.** Here is a slightly goofy `hs-boot` file I've excerpted > from GHC: > > {{{ > module Packages where > > import {-# SOURCE #-} Module (PackageKey) > import {-# SOURCE #-} DynFlags (DynFlags) > > packageKeyPackageIdString :: DynFlags -> PackageKey -> Maybe String > }}} > > The `hs-boot` file must itself import `hs-boot` files, because this boot > file is used by `Module` and `DynFlags`; without `{-# SOURCE #-}`, the > boot file itself will participate in a cycle! > > But notice that there is something very interesting: a boot file is ONLY > ever interested in importing other modules to get types. Never to import > constructors or functions! > > We can use this observation to give us a mechanical transformation of an > `hs` file to an `hs-boot` file, ASSUMING we can define a "second level" > of `hs-boot` file to record our abstract types. > > **Example.** In this example, we have chosen to break the loop from `A`s > import to `B`. > > {{{ > module A where > import {-# SOURCE #-} B > data A = A B > f :: A -> Bool > f (A (B (A b))) = g b > f _ = True > > module B where > import A > data B = B A > g :: B -> Bool > g (B (A (B b))) = f b > g _ = False > }}} > > The first-level `hs-boot`s are: > > {{{ > module A where -- not actually used > import {-# SOURCE 2 #-} B > data A = A B > f :: A -> Bool > > module B where > import {-# SOURCE 2 #-} A > data B = B A > g :: B -> Bool > }}} > > The second-level `hs-boot`s are: > > {{{ > module A where > data A > > module B where -- not actually used > data B > }}} > > **Commentary.** Here are some remarks: > > 1. Because we have to lift the transitive dependencies of anything we > `{-# SOURCE #-}` import, it doesn't make sense to have a pragma which > explicitly says what to put in the `hs-boot` file; instead, we just put > in everything that we *can* handle in an `hs-boot` file (so exclude > anything with missing type signatures, type families, etc.) Ideally, > these automatic hs-boot files are generated lazily, but they should be > reused as necessary. > > 2. This facility actually makes `{-# SOURCE #-}` a lot more attractive > for increasing separate compilation: you can mark an import `{-# SOURCE > #-}` to ensure that if its implementation changes, you don't have to > recompile this module / you can build the module in parallel with that > module. The downside is that when the imported file is modified, we have > to regenerate the `hs-boot` stub before we conclude that the types have > not changed (as opposed to with separate `hs-boot` files, where a > modification to `hs` would not bump the timestamp on `hs-boot`. > > 3. This seems to definitely suggest that you should never need more than > two levels of hs-boot nesting, or perhaps three with kinding. (But maybe > someone has a fancy type system feature for which this is not true!) > Maybe this applies to signature files too. > > 4. We can't force the first level of `hs-boot` files to be abstract > types, for two reasons: (1) a source file importing the hs-boot file may > really need the selector/constructor, and (2) the `hs-boot` files will > reflect any cycles from the source files, that's no good! Rolling out to > the second level breaks the cycle because abstract types never need any > imports. > > 5. What about type class instances? I propose that instances be lifted to > the `hs-boot` level (so hs file usages of the instance continue to work), > but not the `hs-boot2` level (so that we can still "bottom out"). This > can result in some slightly unintuitive behavior, however: > {{{ > module A where > instance Eq (a -> b) where ... > module B where > import A > module C where > import {-# SOURCE #-} B > }}} > In this case, `C` would NOT see the `Eq` instance for functions > defined in `A`. New description: This is a new proposal for solving #1409. The big addition here is that we create **two** hs-boot files for each hs file: one that is a full hs-boot file to be imported by hs files to break loops, and a second which only includes abstract types for hs-boot files to import. C.f. #10679 **Discussion.** Here is a slightly goofy `hs-boot` file I've excerpted from GHC: {{{ module Packages where import {-# SOURCE #-} Module (PackageKey) import {-# SOURCE #-} DynFlags (DynFlags) packageKeyPackageIdString :: DynFlags -> PackageKey -> Maybe String }}} The `hs-boot` file must itself import `hs-boot` files, because this boot file is used by `Module` and `DynFlags`; without `{-# SOURCE #-}`, the boot file itself will participate in a cycle! But notice that there is something very interesting: a boot file is ONLY ever interested in importing other modules to get types. Never to import constructors or functions! We can use this observation to give us a mechanical transformation of an `hs` file to an `hs-boot` file, ASSUMING we can define a "second level" of `hs-boot` file to record our abstract types. **Example.** In this example, we have chosen to break the loop from `A`s import to `B`. {{{ module A where import {-# SOURCE #-} B data A = A B f :: A -> Bool f (A (B (A b))) = g b f _ = True module B where import A data B = B A g :: B -> Bool g (B (A (B b))) = f b g _ = False }}} The first-level `hs-boot`s are: {{{ module A where -- not actually used import {-# SOURCE 2 #-} B data A = A B f :: A -> Bool module B where import {-# SOURCE 2 #-} A data B = B A g :: B -> Bool }}} The second-level `hs-boot`s are: {{{ module A where data A module B where -- not actually used data B }}} **Commentary.** Here are some remarks: 1. Because we have to lift the transitive dependencies of anything we `{-# SOURCE #-}` import, it doesn't make sense to have a pragma which explicitly says what to put in the `hs-boot` file; instead, we just put in everything that we *can* handle in an `hs-boot` file (so exclude anything with missing type signatures, type families, etc.) Ideally, these automatic hs-boot files are generated lazily, but they should be reused as necessary. 2. This facility actually makes `{-# SOURCE #-}` a lot more attractive for increasing separate compilation: you can mark an import `{-# SOURCE #-}` to ensure that if its implementation changes, you don't have to recompile this module / you can build the module in parallel with that module. The downside is that when the imported file is modified, we have to regenerate the `hs-boot` stub before we conclude that the types have not changed (as opposed to with separate `hs-boot` files, where a modification to `hs` would not bump the timestamp on `hs-boot`. 3. With Haskell98, you should never need more than two levels of hs-boot nesting. However, with data kind promotion, you may need arbitrarily many levels of nesting. You could simply exclude promoted data kinds ala **Handling unsupported boot features**; however an alternate thing to do is generalize hs-boot to arbitrarily many levels. However, this might be annoying to implement because dependency analysis needs to know how to determine universe stratification so it can tell how many levels of hs- boot are necessary. 4. We can't force the first level of `hs-boot` files to be abstract types, for two reasons: (1) a source file importing the hs-boot file may really need the selector/constructor, and (2) the `hs-boot` files will reflect any cycles from the source files, that's no good! Rolling out to the second level breaks the cycle because abstract types never need any imports. 5. What about type class instances? I propose that instances be lifted to the `hs-boot` level (so hs file usages of the instance continue to work), but not the `hs-boot2` level (so that we can still "bottom out"). This can result in some slightly unintuitive behavior, however: {{{ module A where instance Eq (a -> b) where ... module B where import A module C where import {-# SOURCE #-} B }}} In this case, `C` would NOT see the `Eq` instance for functions defined in `A`. **Handling unsupported boot features.** Some type-level features in Haskell are not supported at the boot-level (type families, etc), so the automatic generation of `hs-boot` needs a way of transitively(!) excluding these definitions from `hs-boot` files. We can exclude things from the boot file in the following way: 1. If a declaration is not liftable to the `hs-boot` file, we replace it with a "not bootable" declaration, which specifies that there is something with this `Name`, but we don't have any information about it. (This is a sort of generalized version of an abstract type). 2. If we are type-checking a declaration and make reference to a not bootable declaration, the full declaration itself is considered not bootable. Alternately, we can just make sure all language features are supported in boot files. -- Comment (by ezyang): Updated description with some remarks about handling type system features which are not supported by boot files. @goldfire: Intuitively, it seems like if you can figure out your universe hierarchy, you can just write as many levels of `hs-boot` files as you need. Unfortunately, because types and kinds are syntactically merged in your nokinds branch, it's not immediately obvious prior to typechecking what the universes are (the pain of de-stratifying!) which makes it much more difficult to plan compilation. So it seems like it would be much simpler to just not include these types of declarations in hs-boot files. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:03:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:03:02 -0000 Subject: [GHC] #4938: Core2 CPU not detected correctly In-Reply-To: <045.5fd69e7a33d49880c3b3e207dc8b5f35@haskell.org> References: <045.5fd69e7a33d49880c3b3e207dc8b5f35@haskell.org> Message-ID: <060.2596392b034e1d125987fd7d2e72b8c8@haskell.org> #4938: Core2 CPU not detected correctly -------------------------------------+------------------------------------- Reporter: altaic | Owner: Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.1 Resolution: worksforme | Keywords: Operating System: MacOS X | Architecture: Type of failure: Building GHC | Unknown/Multiple failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme * milestone: 7.12.1 => Comment: Cross-compilation support should be better than it was 4 years ago. Please reopen if you're still having problems. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:04:40 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:04:40 -0000 Subject: [GHC] #10714: After implementing new installed package ID (hash of sdist), get rid of package keys Message-ID: <045.13deae8316589a147d8e83f0a90ec4d1@haskell.org> #10714: After implementing new installed package ID (hash of sdist), get rid of package keys -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Package | Version: 7.10.2 system | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- GHC tracking bug for https://github.com/haskell/cabal/issues/2745 Externally, GHC's flags do not have to change much; a user simply passes the installed package ID to the flag currently named `-this-package-key` (but perhaps we should rename this.) Internally, if we can assume that `PackageKey == InstalledPackageId`, we can do away with the `InstalledPackageId` map and get rid of the level of indirection between the bin-pkg-db (which records installed package IDs`) and GHC's guts (which record package keys). Blocked on Cabal not actually using ABI hashes to identify packages. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:05:11 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:05:11 -0000 Subject: [GHC] #10714: After implementing new installed package ID (hash of sdist), get rid of package keys In-Reply-To: <045.13deae8316589a147d8e83f0a90ec4d1@haskell.org> References: <045.13deae8316589a147d8e83f0a90ec4d1@haskell.org> Message-ID: <060.f84e6c295b1050b5f3e04caa4b9a61a4@haskell.org> #10714: After implementing new installed package ID (hash of sdist), get rid of package keys -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: bug | Status: new Priority: normal | Milestone: Component: Package system | Version: 7.10.2 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by ezyang): * keywords: => backpack -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:11:52 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:11:52 -0000 Subject: [GHC] #2514: Add/Expose Binary API that allows dumping of any GHC Binary instance In-Reply-To: <047.57cf723e547f8e60541f4f12c39c26fa@haskell.org> References: <047.57cf723e547f8e60541f4f12c39c26fa@haskell.org> Message-ID: <062.7f1272ee5bfa0c9f8454e96978cb885c@haskell.org> #2514: Add/Expose Binary API that allows dumping of any GHC Binary instance -------------------------------------+------------------------------------- Reporter: nominolo | Owner: nominolo Type: feature request | Status: closed Priority: lowest | Milestone: Component: GHC API | Version: 6.9 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => wontfix * milestone: 7.12.1 => Comment: No response from submitter, closing this (7 year old) feature request. If you still want this, please follow [wiki:WorkingConventions/AddingFeatures] and reopen. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:21:46 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:21:46 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.196cc0a214e1461fbc0bb810f927b7ec@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: fixed => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:24:25 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:24:25 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.8ab86d1505d8d6a89432a59283d6181d@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => merge Comment: Reopening because the commit from comment:15 hasn't been merged yet. > The commit in comment:15 fixes this regression, regardless of the change to the "TEXT literal" rule > > I'll leave this open because > * We might want to merge to 7.10.3 > * There's still an open question about rules for class methods > (see comment:16) > > Simon -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 01:27:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 01:27:33 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.11c9dca12b206958ccd92a67aa4cd9e5@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.3 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Ben: maybe you didn't push that commit yet? It doesn't exist on the ghc-7.10 branch anyway. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 04:21:08 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 04:21:08 -0000 Subject: [GHC] #10680: Make Backpack order-independent (again) In-Reply-To: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> References: <045.acd19a6d5477bb093f22fa6506169d80@haskell.org> Message-ID: <060.6062e6675747fb362472da75c2a5399a@haskell.org> #10680: Make Backpack order-independent (again) -------------------------------------+------------------------------------- Reporter: ezyang | Owner: ezyang Type: task | Status: new Priority: normal | Milestone: Component: Package system | 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 Revisions: -------------------------------------+------------------------------------- Description changed by ezyang: Old description: > When we moved to the new `bkp` file format, we also went back to the a > format which is order-dependent: that is to say, the order in which you > put the declarations matters. So if you write: > > {{{ > unit p where > module A where > import B > module B where > ... > }}} > > this fails to type-check, GHC complaining that `B` is not in scope. I > did this, in part because it's what the Backpack paper described, and > because it was "simpler" to implement. > > I think we should move back to an order-independent scheme, for the > following reasons: > > 1. Haskell users are used to not needing pay particularly close attention > to the ordering of their modules, and forcing people to linearize their > module descriptions would be spectacularly disruptive with large amounts > of modules. So un-ordered modules are "more natural for a traditional > Haskell user. > > 2. Order-independence imposes some constraints on how expressive programs > are (with order-dependent Backpack, you can do some pretty tricky things > by ordering things certain ways); this could simplify some aspects of > compiler implementation and make Backpack easier to explain. > > 3. A particular case of (2): it seems a lot simpler UX-wise to let a user > assume that if you import a module `M` in a unit, it doesn't matter where > you import it: you always get the same set of identifiers brought into > scope. Thus, the incremental results of signatures should not be visible, > c.f. #10679 > > The main idea is that only the surface-syntax is un-ordered: the internal > representation of units is a DAG which we work out in an elaboration > phase, not altogether unsimilar from what `GhcMake` computes. An > important auxiliary idea is that `import A` where `A` is backed by some > signatures depends on EVERY signature in scope. > > Here are the details: > > **The intermediate representation.** We translate into an intermediate > representation which consists of a directed graph between modules, > signatures and includes. Edges in the graph indicate a "depends on" > relation: > > 1. `include p` depends on `include q` if, for some module name `H`, `p` > requires `H` and `q` provides `H`. > 2. A module/signature `M` depends on `include p` if `M` imports a module > provided or required by `p`. > 3. A module/signature `M` depends on a module/signature `S` if `M` > imports `S`. > 4. An `include p` depends on a module `M` if `p` requires a module named > `M`. > > We impose one restriction: a signature cannot depend on a home module. > (But see below for how to eliminate this restriction.) > > Rule (2) is worth remarking upon: if a module imports a signature, it > depends-on every `include` which requires that signature, as well as the > relevant home signature. This could easily result in a cycle; see > refinement 2 for how to break these cycles. The consequence of this, > however, is that we can factor the graph to introduce the node for the > "merge of signatures", which depends on each signature and include which > requires it; we can use this opportunity to build and write out the > merged interface file for the unit which is desirable from an efficiency > perspective. > > **Elaboration.** Take a Backpack file, construct this graph, and topsort > it into a DAG of SCCs. SCCs with a single node are compileable as before. > SCCs with multiple nodes will have to be managed with some mutual > recursion mechanism; see refinements for more thoughts on this. > > **Refinements:** > > 1. **Can a signature depend on a (home) module?** Imports of this kind > require a retypecheck loop. Consider this situation: > {{{ > unit p where > signature H where > data T > module M where > import H > data S = S T > unit q where > include p > module Q where > import M > signature H where > import Q > data T = T S > }}} > Here, signature H in q depends on Q. When we typecheck `Q`, we bring > `M.S` into the type environment with a `TyThing` that describes the > constructor as accepting an abstract type `T`. However, when we > subsequently typecheck the local signature `H`, we must refine all > `TyThing`s of `T` with the true description (e.g. constructor > information). So you'll need to retypecheck `Q` (and `M`) in order to > make sure the `TyThing` is correct. > > 2. **Can an include depend on a (home) module?** If the module has no > (transitive) dependency on signatures, this is fine. However, it's easy > to have a circular dependency. Consider: > {{{ > unit p where > signature A -- imports nothing > signature B -- imports nothing > module M > unit q where > include p > module B where > import A > ... > }}} > `B` depends on `p` for `p/A.hsig`; however, `p` depends on `B` because > this module is filling a requirement. However, if we were to include the > internal graph of `p` into `q`, the resulting graph would not have an > cycles; so this is one possibility of how to untangle this situation. > However, if there's still a cycle (e.g. `A` imports `B`), then you will > need at least a retypecheck loop, and maybe `hs-boot` style compilation. > We're not going to implement this for now. > > 3. **Can we deal with include-include dependency cycles?** Yes! Just use > the Backpack paper's strategy for creating a recursive unit key and > compile the two packages `hs-boot` style. But I'm not planning on > implementing this yet. > > 4. **Can we deal with signature-signature dependency cycles?** Ordered > Backpack would have supported this: > {{{ > unit a-sig where > signature A where > data T > unit ab-sig where > include a-sig > signature B where > import A > data S = S T > signature A where > import B > data T = T S > }}} > In our model, `ab-sig` has a cycle. However, I believe any such cycle > can be broken by creating sufficiently many units: > {{{ > unit a-sig where > signature B where > data T > signature A where > data S = S T > unit b-sig where > signature A where > data S > signature B where > data T = T S > unit ab-sig where > include a-sig > include b-sig > }}} > In principle, GHC could automatically break import cycles by replacing > an import with an import of a reduced signature that simply has abstract > type definitions. See #10681. (I'm not sure this is possible for all > language features.) This technique would also work for normal modules, > assuming that every function is explicitly annotated with a type. New description: When we moved to the new `bkp` file format, we also went back to the a format which is order-dependent: that is to say, the order in which you put the declarations matters. So if you write: {{{ unit p where module A where import B module B where ... }}} this fails to type-check, GHC complaining that `B` is not in scope. I did this, in part because it's what the Backpack paper described, and because it was "simpler" to implement. I think we should move back to an order-independent scheme, for the following reasons: 1. Haskell users are used to not needing pay particularly close attention to the ordering of their modules, and forcing people to linearize their module descriptions would be spectacularly disruptive with large amounts of modules. So un-ordered modules are "more natural for a traditional Haskell user. 2. Order-independence imposes some constraints on how expressive programs are (with order-dependent Backpack, you can do some pretty tricky things by ordering things certain ways); this could simplify some aspects of compiler implementation and make Backpack easier to explain. 3. A particular case of (2): it seems a lot simpler UX-wise to let a user assume that if you import a module `M` in a unit, it doesn't matter where you import it: you always get the same set of identifiers brought into scope. Thus, the incremental results of signatures should not be visible, c.f. #10679 The main idea is that only the surface-syntax is un-ordered: the internal representation of units is a DAG which we work out in an elaboration phase, not altogether unsimilar from what `GhcMake` computes. An important auxiliary idea is that `import A` where `A` is backed by some signatures depends on EVERY signature in scope. Here are the details: **The intermediate representation.** We translate into an intermediate representation which consists of a directed graph of: ? Each source-level module, signature and include, and ? Each unfilled requirement (called a ?signature merge? node). The edges of the directed graph signify a ?depends on? relation, and are defined as follows: ? An include p depends on include q if, for some module name m, p requires m and q provides m. ? An include p depends on a module m if p requires a module named m. ? A module/signature m depends on include p if m imports a module provided by p. ? A module/signature m depends on a module n if m imports n. ? A module/signature m depends on a signature merge n if m imports n. ? A module/signature m depends on a signature n if m {-# SOURCE #-} imports n. ? A signature merge m depends on a local signature m (if it exists). ? A signature merge m depends on a include p, if the (renamed) include requires m. **Elaboration.** Take a Backpack file, construct this graph, and topsort it into a DAG of SCCs. SCCs with a single node are compileable as before. SCCs with multiple nodes will have to be managed with some mutual recursion mechanism; see refinements for more thoughts on this. **Refinements:** 1. **Can a signature depend on a (home) module?** Imports of this kind require a retypecheck loop. Consider this situation: {{{ unit p where signature H where data T module M where import H data S = S T unit q where include p module Q where import M signature H where import Q data T = T S }}} Here, signature H in q depends on Q. When we typecheck `Q`, we bring `M.S` into the type environment with a `TyThing` that describes the constructor as accepting an abstract type `T`. However, when we subsequently typecheck the local signature `H`, we must refine all `TyThing`s of `T` with the true description (e.g. constructor information). So you'll need to retypecheck `Q` (and `M`) in order to make sure the `TyThing` is correct. 2. **Can an include depend on a (home) module?** If the module has no (transitive) dependency on signatures, this is fine. However, it's easy to have a circular dependency. Consider: {{{ unit p where signature A -- imports nothing signature B -- imports nothing module M unit q where include p module B where import A ... }}} `B` depends on `p` for `p/A.hsig`; however, `p` depends on `B` because this module is filling a requirement. However, if we were to include the internal graph of `p` into `q`, the resulting graph would not have an cycles; so this is one possibility of how to untangle this situation. However, if there's still a cycle (e.g. `A` imports `B`), then you will need at least a retypecheck loop, and maybe `hs-boot` style compilation. We're not going to implement this for now. 3. **Can we deal with include-include dependency cycles?** Yes! Just use the Backpack paper's strategy for creating a recursive unit key and compile the two packages `hs-boot` style. But I'm not planning on implementing this yet. 4. **Can we deal with signature-signature dependency cycles?** Ordered Backpack would have supported this: {{{ unit a-sig where signature A where data T unit ab-sig where include a-sig signature B where import A data S = S T signature A where import B data T = T S }}} In our model, `ab-sig` has a cycle. However, I believe any such cycle can be broken by creating sufficiently many units: {{{ unit a-sig where signature B where data T signature A where data S = S T unit b-sig where signature A where data S signature B where data T = T S unit ab-sig where include a-sig include b-sig }}} In principle, GHC could automatically break import cycles by replacing an import with an import of a reduced signature that simply has abstract type definitions. See #10681. (I'm not sure this is possible for all language features.) This technique would also work for normal modules, assuming that every function is explicitly annotated with a type. -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 04:22:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 04:22:27 -0000 Subject: [GHC] #8373: Cross-compiling from x86_64-unknown-linux-gnu to x86_64-sun-solaris2 tries to run target compiled inplace/lib/bin/mkGmpDerivedConstants on host/build In-Reply-To: <048.7d05199162bcbff566de88eaaa54b074@haskell.org> References: <048.7d05199162bcbff566de88eaaa54b074@haskell.org> Message-ID: <063.ccfa43002d8417d3851316a1e9672eb2@haskell.org> #8373: Cross-compiling from x86_64-unknown-linux-gnu to x86_64-sun-solaris2 tries to run target compiled inplace/lib/bin/mkGmpDerivedConstants on host/build -------------------------------------+------------------------------------- Reporter: AlainODea | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Build System | Version: Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 Type of failure: Building GHC | (amd64) failed | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => duplicate Comment: Duplicate of #9982. Also, as discussed on that ticket, not really relevant any more since 7.10 includes a new integer-gmp implementation, which does not use a mkGmpDerivedConstants-like process. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 07:01:38 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 07:01:38 -0000 Subject: [GHC] #10489: Panic in TcEvidence due to wrong role In-Reply-To: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> References: <047.95d344fe6100d51b3187fc04a692030b@haskell.org> Message-ID: <062.a8050f9ce74f7ff497c7b7c6cdc3ec12@haskell.org> #10489: Panic in TcEvidence due to wrong role -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: highest | Milestone: 7.10.3 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_compile/T10489 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Indeed I didn't; there was a small window where I thought it would be necessary to do a 7.10.3 release so I started pulling things. Those plans were thankfully dropped. Regardless, the commit is now pushed. Thanks for the reminder! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 07:41:07 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 07:41:07 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.e9c26affb6eba9e6fed0b82a7aa060c5@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): slyfox, out of curiosity what sort of parallel speed-up did you observe in that test? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 07:49:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 07:49:33 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 Message-ID: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- In upgrading to7.10, code of the form {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible) data X a doCoerce :: Coercible a (X a) => a -> X a doCoerce = coerce }}} fails to compile in 7.10.1 and 7.10.2 with the error {{{ testCoerce.hs:6:13: Could not deduce (a ~ X a) from the context (Coercible a (X a)) bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13-41 ?a? is a rigid type variable bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13 Relevant role signatures: type role X phantom In the ambiguity check for the type signature for ?doCoerce?: doCoerce :: forall a. Coercible a (X a) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ?doCoerce?: doCoerce :: Coercible a (X a) => a -> X a }}} while it works in 7.8.4. Surprisingly (to me at least), the code works in 7.10.1 and 7.10.2 if I change it to {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible) data X a doCoerce :: Coercible a (X b) => a -> X a doCoerce = coerce }}} while it fails to compile in 7.8.4 with the error {{{ testCoerce.hs:6:13: Could not coerce from ?a? to ?X b0? because ?a? and ?X b0? are different types. arising from the ambiguity check for ?doCoerce? from the context (Coercible a (X b)) bound by the type signature for doCoerce :: Coercible a (X b) => a -> X a at testCoerce.hs:6:13-41 The type variable ?b0? is ambiguous In the ambiguity check for: forall a b. Coercible a (X b) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ?doCoerce?: doCoerce :: Coercible a (X b) => a -> X a }}} The coercion pattern may look a bit funny, but it is rather useful when one has newtypes of the form {{{#!hs newtype Y = Y (ForeignPtr Y) }}} which appear naturally when writing bindings to C libraries, and one wants to get access to the underlying ForeignPtr from Y (here X -> ForeignPtr). The relevant Coercible instance here is Coercible Y (ForeignPtr Y), as above. I would have expected the version with context "Coercible a (X a)" to be accepted, as 7.8.4 does, since it seems to be a specialization of the more general coerce, but maybe I am missing something? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 07:50:59 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 07:50:59 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.2785d617f8a66f3cf0b9f367942beddf@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Description changed by inaki: Old description: > In upgrading to7.10, code of the form > {{{#!hs > {-# LANGUAGE FlexibleContexts #-} > import Data.Coerce (coerce, Coercible) > > data X a > > doCoerce :: Coercible a (X a) => a -> X a > doCoerce = coerce > }}} > fails to compile in 7.10.1 and 7.10.2 with the error > {{{ > testCoerce.hs:6:13: > Could not deduce (a ~ X a) > from the context (Coercible a (X a)) > bound by the type signature for > doCoerce :: Coercible a (X a) => a -> X a > at testCoerce.hs:6:13-41 > ?a? is a rigid type variable bound by > the type signature for doCoerce :: Coercible a (X a) => a -> X > a > at testCoerce.hs:6:13 > Relevant role signatures: type role X phantom > In the ambiguity check for the type signature for ?doCoerce?: > doCoerce :: forall a. Coercible a (X a) => a -> X a > To defer the ambiguity check to use sites, enable AllowAmbiguousTypes > In the type signature for ?doCoerce?: > doCoerce :: Coercible a (X a) => a -> X a > }}} > while it works in 7.8.4. > > Surprisingly (to me at least), the code works in 7.10.1 and 7.10.2 if I > change it to > {{{#!hs > {-# LANGUAGE FlexibleContexts #-} > import Data.Coerce (coerce, Coercible) > > data X a > > doCoerce :: Coercible a (X b) => a -> X a > doCoerce = coerce > }}} > while it fails to compile in 7.8.4 with the error > {{{ > testCoerce.hs:6:13: > Could not coerce from ?a? to ?X b0? > because ?a? and ?X b0? are different types. > arising from the ambiguity check for ?doCoerce? > from the context (Coercible a (X b)) > bound by the type signature for > doCoerce :: Coercible a (X b) => a -> X a > at testCoerce.hs:6:13-41 > The type variable ?b0? is ambiguous > In the ambiguity check for: > forall a b. Coercible a (X b) => a -> X a > To defer the ambiguity check to use sites, enable AllowAmbiguousTypes > In the type signature for ?doCoerce?: > doCoerce :: Coercible a (X b) => a -> X a > }}} > > The coercion pattern may look a bit funny, but it is rather useful when > one has newtypes of the form > {{{#!hs > newtype Y = Y (ForeignPtr Y) > }}} > which appear naturally when writing bindings to C libraries, and one > wants to get access to the underlying ForeignPtr from Y (here X -> > ForeignPtr). The relevant Coercible instance here is Coercible Y > (ForeignPtr Y), as above. > > I would have expected the version with context "Coercible a (X a)" to be > accepted, as 7.8.4 does, since it seems to be a specialization of the > more general coerce, but maybe I am missing something? New description: In upgrading to7.10, code of the form {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible) data X a doCoerce :: Coercible a (X a) => a -> X a doCoerce = coerce }}} fails to compile in 7.10.1 and 7.10.2 with the error {{{ testCoerce.hs:6:13: Could not deduce (a ~ X a) from the context (Coercible a (X a)) bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13-41 ?a? is a rigid type variable bound by the type signature for doCoerce :: Coercible a (X a) => a -> X a at testCoerce.hs:6:13 Relevant role signatures: type role X phantom In the ambiguity check for the type signature for ?doCoerce?: doCoerce :: forall a. Coercible a (X a) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ?doCoerce?: doCoerce :: Coercible a (X a) => a -> X a }}} while it works in 7.8.4. Surprisingly (to me at least), the code works in 7.10.1 and 7.10.2 if I change it to {{{#!hs {-# LANGUAGE FlexibleContexts #-} import Data.Coerce (coerce, Coercible) data X a doCoerce :: Coercible a (X b) => a -> X a doCoerce = coerce }}} while it fails to compile in 7.8.4 with the error {{{ testCoerce.hs:6:13: Could not coerce from ?a? to ?X b0? because ?a? and ?X b0? are different types. arising from the ambiguity check for ?doCoerce? from the context (Coercible a (X b)) bound by the type signature for doCoerce :: Coercible a (X b) => a -> X a at testCoerce.hs:6:13-41 The type variable ?b0? is ambiguous In the ambiguity check for: forall a b. Coercible a (X b) => a -> X a To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature for ?doCoerce?: doCoerce :: Coercible a (X b) => a -> X a }}} The coercion pattern may look a bit funny, but it is rather useful when one has newtypes of the form {{{#!hs newtype Y = Y (ForeignPtr Y) }}} which appear naturally when writing bindings to C libraries, and one wants to get access to the underlying ForeignPtr from Y (here X is ForeignPtr). The relevant Coercible instance here is Coercible Y (ForeignPtr Y), as above. I would have expected the version with context "Coercible a (X a)" to be accepted, as 7.8.4 does, since it seems to be a specialization of the more general coerce, but maybe I am missing something? -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 07:58:23 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 07:58:23 -0000 Subject: [GHC] #10528: compile time performance regression with OverloadedStrings and Text In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.f2ab628b1dc7340f5cc7086a84a1d5b7@haskell.org> #10528: compile time performance regression with OverloadedStrings and Text -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: merge Priority: high | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc2 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I think the commit in comment:15 is optional. It's probably a good idea anyway, but any library that needs it probably needs more phase control on its rules! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:09:07 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:09:07 -0000 Subject: [GHC] #10716: Metadata in GHC.Generic should give access to strictness annotation Message-ID: <049.954933c3fdc7ca9d74108b79b667adbd@haskell.org> #10716: Metadata in GHC.Generic should give access to strictness annotation -------------------------------------+------------------------------------- Reporter: StefanWehr | Owner: Type: feature | Status: new request | Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Currently, the metadata in the GHC.Generics module do not give access to the strictness annotations attached to a field of a datatype. It would be great if this piece of information could be added. Background: we are using a class FullyStrict for ensuring that a datatype is fully strict (in the sense that all fields have bang patterns and the types of all fields are also fully strict). Currently we are using TemplateHaskell to derive the instances automatically. The TemplateHaskell function also checks that all fields have bang patterns. To improve compilation speed, I would like to derive the instances with DeriveGeneric. But this is not possible because then I cannot implement the check whether all fields have bang patterns. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:30:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:30:15 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.453c396da7ae4a17741f869de9090134@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): > Experimentally bgamari's test program does ~n2 allocations and takes ~n3 total time in the Applicative version, while the Monad version runs in linear allocations and time. That and the fact that in comment:4 I need the associativity law, sounds like there is a quadratic behavior due to wrongly associated binds. Let?s see if I can evaluate my way by hand through it. {{{#!hs -- These fragments from bgamari?s test case let t n = Thing n cr2 let cr2 = const $ return 2 run (t 1 >> (t 2 >> t 3)) == run (Thing 1 (cr2 >=> (\_ -> (t 2 >> t 3)))) == run ((cr2 1 >=> (\_ -> (t 2 >> t 3))) 1) == run (cr2 1 >>= (\_ -> (t 2 >> t 3))) == run (return 2 >>= (\_ -> (t 2 >> t 3))) == run ((\_ -> (t 2 >> t 3)) 2) == run (t 2 >> t3) == run (Thing 2 (cr2 >=> (\_ -> t 3))) == run ((cr2 2 >=> (\_ -> t 3)) 1) == run (cr2 2 >>= (\_ -> t 3)) == run (return 2 >>= (\_ -> t 3)) == run ((\_ -> t 3) 2) == run (t 3) == run (Thing 3 cr2) == run (cr2 3) == run (return 2) == 2 }}} For the applicative version, based on the empirical implementation, I assume that some parts of the code are kept alive for too long, and possibly be traversed multiple times. So here we go: {{{#!hs let cri = \_ -> return id) let ri = (\x -> return (id x)) run (t 1 *> (t 2 *> t 3)) == run ((t 1 >>= cri) >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3)))) == run ((Thing 1 (cr2 >=> cri)) >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3)))) == run (Thing 1 ((cr2 >=> cri) >=> (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))))) == run (((cr2 >=> cri) >=> (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3)))) 1) == run (((cr2 >=> cri) >=> (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3)))) 1) == run (((cr2 >=> cri) 1 >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))))) == run (((cr2 1 >>= cri) >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))))) == run (((return 2 >>= cri) >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))))) == run (((cri 2) >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))))) == run (((return id) >>= (\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))))) == run ((\x2 -> (t 2 *> t 3) >>= (\x3 -> return (x2 x3))) id) == run ((t 2 *> t 3) >>= ri) -- *? == run (((t 2 >>= cri) >>= (\x2 -> t3) >>= (\x3 -> return (x2 x3)))) >>= ri) == ... -- as before == run ((t 3 >>= ri) >>= ri) == run (Thing 3 (cr2 >=> ri) >>= ri) == run (Thing 3 ((cr2 >=> ri) >=> ri)) -- *? == run (((cr2 >=> ri) >=> ri) 3) == run ((cr2 >=> ri) 3 >>= ri) == run ((cr2 3 >>= ri) >>= ri) == run ((return 2 >>= ri) >>= ri) == run (ri 2 >>= ri) == run (return 2 >>= ri) == run (ri 2) == run (return 2) == 2 }}} `*?`: I think this is interesting. Whereas above, `run (a >> b)` will eventually reduce to `run b`, here we get `run (b >>= complex_return)`, with one `complex_return` for every element in the list. This explains at least some of the blow up: We build this chain, and then we have to eventually tear it down again. `*?` And again we traverse this whole chain of pointless `ri`?s. Hmm, not sure if and how this exposition explains the quadratic blow up in allocations, though. Do we traverse the stack of `>=> ri` once per element somehow, similar to a wrongly associated `++`? But I don?t see it right now. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:43:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:43:15 -0000 Subject: [GHC] #10603: Output of -ddump-splices is parenthesized incorrectly In-Reply-To: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> References: <050.70ab9071ed50ac22038e86553f4b759c@haskell.org> Message-ID: <065.d309d2f8041cf0d0f755cfba5c6a8202@haskell.org> #10603: Output of -ddump-splices is parenthesized incorrectly -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: dnusbaum Type: bug | Status: patch Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10703 | Differential Revisions: Phab:D1114 -------------------------------------+------------------------------------- Changes (by thomie): * differential: D1114 => Phab:D1114 * related: => #10703 * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:44:43 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:44:43 -0000 Subject: [GHC] #10703: -fth-dec-file can't handle lambdas In-Reply-To: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> References: <045.c081efcc1d355b132984e54043eabc1d@haskell.org> Message-ID: <060.786e8d114a06e85165c946dd6f2d6087@haskell.org> #10703: -fth-dec-file can't handle lambdas -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 #10603 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * related: #10701 => #10701 #10603 Comment: This is being worked on in #10603. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:48:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:48:12 -0000 Subject: [GHC] #2530: deriving Show adds extra parens for constructor with record syntax In-Reply-To: <042.b19622be9d3706ab4b282d1c64e9acb0@haskell.org> References: <042.b19622be9d3706ab4b282d1c64e9acb0@haskell.org> Message-ID: <057.319894326a44b0fb0198f99041699a4d@haskell.org> #2530: deriving Show adds extra parens for constructor with record syntax -------------------------------------+------------------------------------- Reporter: spl | Owner: Type: bug | Status: closed Priority: lowest | Milestone: 7.12.1 Component: Compiler | Version: 6.8.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D669 -------------------------------------+------------------------------------- Comment (by nomeata): JFTR if you come across this bug and are worried: A quick test shows that `read . show` still works fine, even if `read` and `show` come from different versions of GHC, in all combinations. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:48:26 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:48:26 -0000 Subject: [GHC] #9385: Additions to Control.Monad In-Reply-To: <042.43d25471e6c4c7993c2ad33f337aca33@haskell.org> References: <042.43d25471e6c4c7993c2ad33f337aca33@haskell.org> Message-ID: <057.48ab6e61b30a5e57e0eef203f1f98dd1@haskell.org> #9385: Additions to Control.Monad -------------------------------------+------------------------------------- Reporter: olf | Owner: ekmett Type: feature request | Status: closed Priority: low | Milestone: Component: Core Libraries | Version: 7.8.2 Resolution: invalid | Keywords: report- | impact Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => invalid Comment: Please reopen with a mandate from the libraries@ list. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:53:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:53:35 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.606be94deec2dd28d8537111fc5c912a@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Changes (by nomeata): * cc: goldfire (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 08:55:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 08:55:32 -0000 Subject: [GHC] #10716: Metadata in GHC.Generic should give access to strictness annotation In-Reply-To: <049.954933c3fdc7ca9d74108b79b667adbd@haskell.org> References: <049.954933c3fdc7ca9d74108b79b667adbd@haskell.org> Message-ID: <064.758ea8c10afde3b28eff298122748f14@haskell.org> #10716: Metadata in GHC.Generic should give access to strictness annotation -------------------------------------+------------------------------------- Reporter: StefanWehr | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: adamgundry, kosmikus, goldfire (added) Comment: I'm all for it. Would you like to describe the design as seen by a user; and maybe offer a patch? Adding Andres to cc. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:09:08 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:09:08 -0000 Subject: [GHC] #8713: Avoid libraries if unneeded (librt, libdl, libpthread) In-Reply-To: <045.e65f03bd077c86ec4c44c9abb727b716@haskell.org> References: <045.e65f03bd077c86ec4c44c9abb727b716@haskell.org> Message-ID: <060.743f5ee97a46b7dd6151650f0543564d@haskell.org> #8713: Avoid libraries if unneeded (librt, libdl, libpthread) -------------------------------+----------------------------------------- Reporter: ip1981 | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 7.6.3 Resolution: | Keywords: Operating System: Other | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------+----------------------------------------- Changes (by thomie): * status: upstream => new Comment: The patch to unix has been merged. I second Karel's suggestion of not introducing any new #ifdefs in the Haskell code. See also [wiki:Commentary/PlatformNaming]. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:09:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:09:17 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.bc145a74257f4499c5bc3e0a874eb0d0@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Another factoid: * It does not help to implement `<$` (used by the default implementation of `*>`) manually. * It does not help to implement `<*>` manually * So `a1 *> a2 = (id <$ a1) <*> a2` indeed seems to be the root of the problem. Do we need to educate people to write `(*>) == (>>)` if they write `(<*>) = ap`? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:20:08 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:20:08 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.d015d46a9bc37042c9d8ec824ca4503c@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: FreeBSD | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Changes (by thomie): * cc: pgj (added) * os: Windows => FreeBSD * status: closed => new * resolution: fixed => * owner: Phyx- => Comment: This patch broke the FreeBSD build: http://haskell.inf.elte.hu/builders /freebsd-amd64-head/705/8.html -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:26:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:26:17 -0000 Subject: [GHC] #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails In-Reply-To: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> References: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> Message-ID: <060.7f42917670e4e2261ca9a16e377c8640@haskell.org> #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails -------------------------------------+------------------------------------- Reporter: troydm | Owner: Type: bug | Status: upstream Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Operating System: Solaris | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * cc: kgardas (added) Comment: troydm: you marked this bug as upstream. Do you suggest it is not a GHC bug? Please mark it 'new' if you think it is. CC kgardas, maybe he can help. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:42:23 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:42:23 -0000 Subject: [GHC] #10707: -fth-dec-file outputs invalid case clauses In-Reply-To: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> References: <045.fdc065ae6f0ee29227ba606c71d9b30e@haskell.org> Message-ID: <060.e0787d0795fbd4093d533cc286caaab1@haskell.org> #10707: -fth-dec-file outputs invalid case clauses -------------------------------------+------------------------------------- Reporter: Fabian | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Template Haskell | Version: 7.10.1 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: #10701 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by Fabian): Replying to [comment:3 rwbarton]: > I'm not sure what you mean by "invalid case clauses", but it seems to me that the error is that > {{{ > case e of { ...alts... } foo > }}} > is not valid syntax for an application, it must be parenthesized like > {{{ > (case e of { ...alts... }) foo > }}} > A problem with the case expression itself in its context, not the case clauses. I wasn't sure exactly what was wrong with the output -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:44:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:44:06 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.b2e4881cea3f2b65629e927a99202dfc@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: FreeBSD | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by Phyx-): It seems that the configure script doesn't force any particular environment. On windows it was always using bash so didn't notice. Whatever shell the freebsd one is using doesn't seem to like functions. I will inline the function calls to fix this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 09:54:26 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 09:54:26 -0000 Subject: [GHC] #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm In-Reply-To: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> References: <046.926df7dc33b426cbfee9f2a989a5cdc6@haskell.org> Message-ID: <061.3dd4e4b7d604d0f7c2716fe1c5a4d8a0@haskell.org> #10711: Defining mapM_ in terms of traverse_ causes substantial blow-up in ByteCodeAsm -------------------------------------+------------------------------------- Reporter: bgamari | Owner: bgamari Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: ghcirun004 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): Indeed I went through a similar [https://gist.github.com/bgamari/484842415e5faf9c02fb exercise] last night and came to a similiar conclusion: smells fishy but I don't necessarily see anything clearly quadratic. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:02:45 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:02:45 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.6fefdbb3c2af15016513651c19602de5@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: darchon Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1115 -------------------------------+----------------------------------------- Changes (by darchon): * owner: => darchon * differential: => Phab:D1115 Comment: I've fixed the GHC part in [https://phabricator.haskell.org/D1115]. The Cabal part remains broken. I think once my patch is merged this issue should be closed, and a new one should be opened on the Cabal bug-tracker. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:08:38 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:08:38 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.f574ffca2bfeedaa7bb1fb11e5faf423@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: FreeBSD | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by pgj): Replying to [comment:5 Phyx-]: > Whatever shell the freebsd one is using doesn't seem to like functions. By default, FreeBSD has the regular Bourne Shell (`/bin/sh`) from the base system, that shall support functions, I have used them a couple of times before. However, the `function` keyword was not needed for that. Removing them from `configure.ac` fixes the problem for me. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:17:43 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:17:43 -0000 Subject: [GHC] #9114: Invalid UTF8 not round-tripped correctly In-Reply-To: <046.a5f7211f47ee3c5c9ca358418466de36@haskell.org> References: <046.a5f7211f47ee3c5c9ca358418466de36@haskell.org> Message-ID: <061.7fca694b2b60ec5dff3a87e7c6de6370@haskell.org> #9114: Invalid UTF8 not round-tripped correctly -------------------------------------+------------------------------------- Reporter: nomeata | Owner: ekmett Type: bug | Status: closed Priority: normal | Milestone: Component: Core Libraries | Version: 7.6.3 Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: infoneeded => closed * resolution: => worksforme -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:24:29 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:24:29 -0000 Subject: [GHC] #10250: API Annotations : add Locations in hsSyn were layout occurs In-Reply-To: <044.e9f7429502526fbd11c0a38b5739b89e@haskell.org> References: <044.e9f7429502526fbd11c0a38b5739b89e@haskell.org> Message-ID: <059.c5d8576ce0ac355b181c02f3859f5add@haskell.org> #10250: API Annotations : add Locations in hsSyn were layout occurs -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: | ApiAnnotations Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D815 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:29:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:29:05 -0000 Subject: [GHC] #10523: Add Monoid instance for IO In-Reply-To: <049.6279cecb8fcd2b294d6df5d83cd891b5@haskell.org> References: <049.6279cecb8fcd2b294d6df5d83cd891b5@haskell.org> Message-ID: <064.0767d7220ed6a78c5520a64c8a5d3886@haskell.org> #10523: Add Monoid instance for IO -------------------------------------+------------------------------------- Reporter: Gabriel439 | Owner: Gabriel439 Type: feature request | Status: closed Priority: normal | Milestone: 7.12.1 Component: libraries/base | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D988 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:30:00 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:30:00 -0000 Subject: [GHC] #10467: user's guide description of "foreign export" is out of date In-Reply-To: <047.ce62d536f877089b14fe11348144e797@haskell.org> References: <047.ce62d536f877089b14fe11348144e797@haskell.org> Message-ID: <062.1f47a0b67615c9f7751ba33515d9d1ff@haskell.org> #10467: user's guide description of "foreign export" is out of date -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Documentation | Version: 7.10.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D951 -------------------------------------+------------------------------------- Changes (by thomie): * status: patch => closed * resolution: => fixed * milestone: => 7.12.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:39:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:39:58 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.4f0543a078b2319886ca2112ee1de239@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: FreeBSD | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by Phyx-): Replying to [comment:6 pgj]: > However, the `function` keyword was not needed for that. Removing them from `configure.ac` fixes the problem for me. Yes it seems that function is a non-POSIX extension in bash: > When using the 'function' keyword, Bash function declarations are not compatible with Bourne/Korn/POSIX scripts (the Korn shell has the same problem when using 'function'), but Bash accepts the same function declaration syntax as the Bourne and Korn shells, and is POSIX-conformant Was not aware of that. Sorry bout that. Removing the keyword is the right fix. I'll be able to send a new diff in about 6 hours. Unless someone else wants to fix it before then. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:45:43 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:45:43 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.8a03806dcc485e48063a4e4873c4a42a@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: new Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: | Keywords: Operating System: FreeBSD | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by Thomas Miedema ): In [changeset:"a442800fd27952bff9bf9773f514ee062f4b55d0/ghc" a442800f/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="a442800fd27952bff9bf9773f514ee062f4b55d0" Build system: remove function keyword from configure.ac (#10705) This fixes the FreeBSD build. }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:46:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:46:35 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.5bff84fe512781e297ad386918c779d8@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * os: FreeBSD => Windows * resolution: => fixed Comment: Ok, I fixed it. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:51:46 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:51:46 -0000 Subject: [GHC] #10250: API Annotations : add Locations in hsSyn were layout occurs In-Reply-To: <044.e9f7429502526fbd11c0a38b5739b89e@haskell.org> References: <044.e9f7429502526fbd11c0a38b5739b89e@haskell.org> Message-ID: <059.2dd7ced160758cbbbb4e59d308ce4c16@haskell.org> #10250: API Annotations : add Locations in hsSyn were layout occurs -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: | ApiAnnotations Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D815 -------------------------------------+------------------------------------- Comment (by alanz): Phab:D815 was never landed for this, the idea was to come back to it after 7.10.2 shipped. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:53:15 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:53:15 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.cb8a32134cc0362d1b4d732ab8f27120@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by nh2): Replying to [comment:23 ezyang]: > I was chatting with one of my colleagues about this problem recently, and they said something very provocative: if GHC is not scaling because there is some global mutable state (e.g. the NameCache) ... > > Do people agree with this viewpoint? Disagree? I disagree. Threads should almost always be more efficient to use as they allow to efficiently/easily share resources when it makes things faster, but that doesn't mean that we have to share all the things. Processes force us to not share anything. If building is faster with separate processes, then we should be able to achieve the same speed with threads by simply not sharing that thing that makes it slow and that processes force us to not share. However, I wouldn't be surprised if this isn't even the problem here. Replying to [comment:28 slyfox]: > If perf does not lie most of the time is spent cycling over sleeping kernel threads This sounds much more like the problem. If I had to make a guess (and based on the very limited look I had into this issue last year) it feels like we are accidentally busy polling something somewhere. When I run some non-build Haskell stuff with `-RTS +N18` on the current generation of 18 core AWS instances, with many more Haskell threads than needed for building a 200 module project, and with shorter thread life times than in this case (e.g. let's say building a module takes around 0.5 seconds), that stuff scales pretty nicely, much better than ghc's `--make` scales here. This makes me think that we might be simply doing something wrong in the parallel upsweep code, and that the rest (compiler, runtime etc.) is doing quite OK. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 10:59:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 10:59:33 -0000 Subject: [GHC] #10250: API Annotations : add Locations in hsSyn were layout occurs In-Reply-To: <044.e9f7429502526fbd11c0a38b5739b89e@haskell.org> References: <044.e9f7429502526fbd11c0a38b5739b89e@haskell.org> Message-ID: <059.21a379a81b4c78e24094107cee359072@haskell.org> #10250: API Annotations : add Locations in hsSyn were layout occurs -------------------------------------+------------------------------------- Reporter: alanz | Owner: alanz Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.10.1 Resolution: fixed | Keywords: | ApiAnnotations Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D815 -------------------------------------+------------------------------------- Comment (by thomie): Phab:D815 was landed on master already, so I'm confused by your message. If you're requesting for this to be merged to 7.10.3: just reopen, set the right milestone, and set it to status=merge. Otherwise it gets lost. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 11:29:23 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 11:29:23 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.35d853847623c7f5eba1466964ad6218@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Interesting. HEAD reports {{{ T10715.hs:8:13: error: Could not deduce: Coercible a (X a) from the context: Coercible a (X a) }}} which is even more confusing! Here's what is happening * GHC treats `Coercible a ty` as a representational equality constraint `a ~R ty`. * Given an equlity `a ~R ty`, it tries to rewrites other constraints mentioning `a`, by replacing `a` with `ty`. * But here it can't do that, because `ty` mentions `a`, so we could rewrite forever; a kind of occurs-check problem. And indeed, if we had something like {{{ f :: (a ~ [a]) => blah }}} we really wouldn't expect much to happen because the constraint can't possibly be satisfied. * However, if the given equality is `a ~R X b`, we CAN use it to rewrite the wanted constraint, to get `X b ~R X a`. And that is soluble by decomposition because `X`'s first argument is phantom. Hence your "Surprisingly to me" discovery. * If you write a type signature like {{{ f :: (a ~ [a]) => blah }}} you get an error like {{{ T10715.hs:15:8: error: Couldn't match type ?a? with ?[a]? ?a? is a rigid type variable bound by the type signature for: foo :: (a ~ [a]) => a -> [a] -> Bool at T10715.hs:15:8 Inaccessible code in the type signature for: foo :: (a ~ [a]) => a -> [a] -> Bool }}} Maybe we should do the same for `Coercible`? That would at least give a better error message than "can't deduce A from A"! * It wouldn't help your use-case. But do you have to use `Y` in this strange recursive way. Why not do this? {{{ newtype FY = FY (ForeignPtr Y) data Y }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 11:38:22 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 11:38:22 -0000 Subject: [GHC] #7679: Regression in -fregs-graph performance In-Reply-To: <047.9e26897513125de7441d596a4b30ee54@haskell.org> References: <047.9e26897513125de7441d596a4b30ee54@haskell.org> Message-ID: <062.f0a12b1ce99a923c3e8c84014508cc58@haskell.org> #7679: Regression in -fregs-graph performance -------------------------------------+------------------------------------- Reporter: simonmar | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler (NCG) | Version: 7.6.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7192, #8657 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 11:40:02 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 11:40:02 -0000 Subject: [GHC] #9308: nofib fannkuch-redux runs perpetually with -fllvm In-Reply-To: <042.547b78253c22f834191c24f2af1b28cf@haskell.org> References: <042.547b78253c22f834191c24f2af1b28cf@haskell.org> Message-ID: <057.b9f4bae52f6a0ec06b6aebfde2680c23@haskell.org> #9308: nofib fannkuch-redux runs perpetually with -fllvm -------------------------------------+------------------------------------- Reporter: jrp | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (LLVM) | Version: 7.8.3 Resolution: | Keywords: fannkuch- | redux Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: Incorrect result | Test Case: fannkuch- at runtime | redux Blocked By: 9504 | Blocking: Related Tickets: #5567 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * cc: bgamari (added) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 11:46:45 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 11:46:45 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase 10000% between 7.4.2 and 7.6.3 Message-ID: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> #10717: fannkuch-redux allocations increase 10000% between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- In a recent look at [http://home.smart-cactus.org/~ben/nofib.html historical] nofib trends I noticed that fannkuck-redux appears to regress an almost unbelievable amount in its allocations, == 7.6.3 == {{{ <> }}} == 7.4.2 {{{ <> }}} Given that [FoldrBuildNotes] suggests that this test is quite sensitive to fusion, I suspect something broke here. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 11:47:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 11:47:12 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 (was: fannkuch-redux allocations increase 10000% between 7.4.2 and 7.6.3) In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.dcc57e181706262011ed899c21583edc@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 12:29:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 12:29:27 -0000 Subject: [GHC] #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails In-Reply-To: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> References: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> Message-ID: <060.babd168b3718fbc9e4bf41a6a11089e0@haskell.org> #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails -------------------------------------+------------------------------------- Reporter: troydm | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Operating System: Solaris | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by troydm): * status: upstream => new Comment: kgardas, yeah I'll mark it as new -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 12:33:33 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 12:33:33 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.bedc724f18b95f28fa766375bb5f6ec6@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:3 simonpj]: > Maybe we should do the same for `Coercible`? The problem is that occurs-checks for representational equality don't necessarily mean failure. For example `a ~R b a` is solvable if `b` becomes the `Identity` newtype. However, I ''do'' think that `a ~R X a` is an error if `X` is known to be a datatype. (That is, generative w.r.t. representational equality.) But this will still fail: {{{ oops :: Coercible a (b a) => a -> b a oops = coerce }}} Perhaps a way forward is to detect when an occurs-check problem has happened and add a `NB: The solver for Coercible constraints is incomplete` in the error? Not really sure what to do here, beyond making occurs-check a hard failure when there is a generative type somewhere. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 12:35:52 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 12:35:52 -0000 Subject: [GHC] #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing In-Reply-To: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> References: <045.e7e6b1fe63913ee0ef5a119e69380bb4@haskell.org> Message-ID: <060.eee448cb25200961432e7aa43bc03947@haskell.org> #10712: Regression: make TEST=exceptionsrun001 WAY=optasm is failing -------------------------------------+------------------------------------- Reporter: thomie | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | base/tests/exceptionsrun001 Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by simonpj): * cc: simonmar (added) Comment: Bother. I totally missed that. I think it's reasonable that this should allow the exception to be raised somewhere else (imprecisely): {{{ catch# (\s -> (raise# blah) `seq` blah2) (...) st }}} because `raise#` is in the pure world. But `raiseIO#` is specifically intended to raise an exception precisely at the specified moment, so the new behaviour is unacceptable. Now I think about this more I'm also worried about {{{ let r = \st -> raiseIO# blah st in catch (\st -> ...(r st)..) handler st }}} Now that I'm given `catch` a more aggressive strictness, I'll get a demand `C(S)` for `r`; that is, it is definitly called with one argument. And so it is! But the danger is that we'll feed `C(S)` into `r`'s rhs as the demand of the body, and say that that whole `let` will definitely diverge (which isn't true). However, we ''really'' want this function to be strict in `x`: {{{ f x st = catch (\s -> case x of I# x' -> ...) handler st }}} Getting this strictness was the whole point of the offending commit: {{{ Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- hpg -0.4% -2.9% -0.9% -1.0% +0.0% reverse-complem -0.4% -10.9% +10.7% +10.9% +0.0% simple -0.3% -0.0% +26.2% +26.2% +3.7% sphere -0.3% -6.3% 0.09 0.09 +0.0% -------------------------------------------------------------------------------- Min -0.7% -10.9% -4.6% -4.7% -1.7% Max -0.2% +0.0% +26.2% +26.2% +6.5% Geometric Mean -0.4% -0.3% +2.1% +2.1% +0.1% }}} There's something very special about `catch`: it turns divergence into non-divergence. (The strictness analyser treats divergence and exceptions identically.) I think #8598 is relevant. Bother bother. I'm really not sure what to do. Even if we revert, we should not revert all, just the strictness signatures for the `catch` primops. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 12:37:24 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 12:37:24 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.102ec1514bab1cedee06ef47dfde3b63@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Yes, please investigate!! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 12:43:50 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 12:43:50 -0000 Subject: [GHC] #9613: when giving an error "No instance for C (a -> b)", suggest that a function may be underapplied In-Reply-To: <047.eea63fe88376c060310ab582974460c3@haskell.org> References: <047.eea63fe88376c060310ab582974460c3@haskell.org> Message-ID: <062.83de0eecdf9d820af14448c3d17a7cb7@haskell.org> #9613: when giving an error "No instance for C (a -> b)", suggest that a function may be underapplied -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): The message is now (ghc-7.10.2): {{{ Prelude> print length :2:1: No instance for (Show (t0 a0 -> Int)) (maybe you haven't applied enough arguments to a function?) arising from a use of ?print? In the expression: print length In an equation for ?it?: it = print length }}} In commit bc2289e13d9586be087bd8136943dc35a0130c88: {{{ Author: Mike Izbicki <> Date: Wed Nov 19 18:29:37 2014 -0600 ghc generates more user-friendly error messages Test Plan: Compiled ghc fine. Opened ghci and fed it invalid code. It gave the improved error messages in response. Reviewers: austin Subscribers: thomie, simonpj, spacekitteh, rwbarton, simonmar, carter Differential Revision: https://phabricator.haskell.org/D201 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 13:35:31 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 13:35:31 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.4cf3765f440bcda4fd5a9a30db1cd28d@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): I'm now looking at the ticky output from the testcase run with argument `11` after having confirmed that compiling with `-prof` kills the effect (both compilers produce executables which allocate heavily). The ticky output shows a pretty clear difference. == 7.6 == {{{ ENTERS: 1178454454 of which 1178454454 (100.0%) direct to the entry code [the rest indirected via Node's info ptr] 36288010 ( 3.1%) thunks 0 ( 0.0%) data values 0 ( 0.0%) normal indirections 0 ( 0.0%) permanent indirections ... RETURNS: 354136250 36288000 ( 10.2%) from entering a new constructor [the rest from entering an existing constructor] UPDATE FRAMES: 36288007 (0 omitted from thunks) ... Entries Allocs Arity Stack Kinds Function -------------------------------------------------------------------------------- ... 39916804 108864012 4 0 iiiA $wa3{v s3Cl} (main:Main) }}} == 7.4 == {{{ ENTERS: 1142166456 of which 1142166456 (100.0%) direct to the entry code [the rest indirected via Node's info ptr] 10 ( 0.0%) thunks 0 ( 0.0%) data values 0 ( 0.0%) normal indirections 0 ( 0.0%) permanent indirections ... RETURNS: 317848252 0 ( 0.0%) from entering a new constructor [the rest from entering an existing constructor] UPDATE FRAMES: 7 (0 omitted from thunks) ... Entries Allocs Arity Stack Kinds Function -------------------------------------------------------------------------------- ... 39916804 12 4 0 iiiA $wa3{v s3ad} (main:Main) }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 13:37:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 13:37:18 -0000 Subject: [GHC] #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac In-Reply-To: <045.16a6419c70e069ea547a1b942e636370@haskell.org> References: <045.16a6419c70e069ea547a1b942e636370@haskell.org> Message-ID: <060.06c6a624bd32b58376040940476578e5@haskell.org> #10568: Regression from 7.8.4, loading GLUT into GHCI fails on the Mac -------------------------------+----------------------------------------- Reporter: George | Owner: darchon Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.2-rc1 Resolution: | Keywords: Operating System: MacOS X | Architecture: x86_64 (amd64) Type of failure: GHCi crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1115 -------------------------------+----------------------------------------- Comment (by darchon): Cabal side fixed as [https://github.com/haskell/cabal/pull/2747] -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 13:49:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 13:49:36 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.bf1f2f5823cc23c140297465db5257c6@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): [https://gist.github.com/bgamari/4b64d9d845933fed712c Here] are the STG definitions of the `s3Cl` and `s3ad`. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 14:06:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 14:06:18 -0000 Subject: [GHC] #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails In-Reply-To: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> References: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> Message-ID: <060.f6f04baa57cab514c3983cca6176536d@haskell.org> #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails -------------------------------------+------------------------------------- Reporter: troydm | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Operating System: Solaris | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kgardas): Honestly it's quite strange that w/o -threaded this works for you, since: {{{ karel at silence:/tmp/ttt$ ls -la total 6392 drwxr-xr-x 2 karel karel 178 Jul 31 15:58 . drwxrwxrwt 25 root sys 2823 Jul 31 15:58 .. -rwxr-xr-x 1 karel karel 3261384 Jul 31 15:58 test karel at silence:/tmp/ttt$ mkdir test mkdir: Failed to make directory "test"; File exists karel at silence:/tmp/ttt$ }}} and test also shows the same behaviour: {{{ karel at silence:/tmp/ttt$ ./test test: test: createDirectory: already exists (File exists) karel at silence:/tmp/ttt$ }}} anyway, if I rename test -> textx, then I get: {{{ karel at silence:/tmp/ttt$ ./testx Starting Subprocess testx: ghc: createProcess: runInteractiveProcess: exec: does not exist (No such file or directory) karel at silence:/tmp/ttt$ }}} single-threaded fails in the way like yours: {{{ karel at silence:/tmp/ttt$ ./test-st Starting Subprocess ghc: no input files Usage: For basic information, try the `--help' option. Exit code: ExitFailure 1 karel at silence:/tmp/ttt$ }}} anyway, if I modify test to point directly to ghc (full path), then it works also with -threaded {{{ karel at silence:/tmp/ttt$ ghc -threaded ../test.hs -o test-thr karel at silence:/tmp/ttt$ ./test-thr Starting Subprocess ghc: no input files Usage: For basic information, try the `--help' option. Exit code: ExitFailure 1 karel at silence:/tmp/ttt$ }}} my guess is that environment handling is kind of fishy on Solaris. We also do have few tests in this domain failing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 14:07:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 14:07:18 -0000 Subject: [GHC] #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails In-Reply-To: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> References: <045.760cae9f013a16aed8eac702a0c53725@haskell.org> Message-ID: <060.895dfc7ecb2b01823e3aad8348ea11c4@haskell.org> #8151: ghc-7.4.2 on OpenIndiana (Solaris) createSubprocess fails -------------------------------------+------------------------------------- Reporter: troydm | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.2 Resolution: | Keywords: Operating System: Solaris | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by kgardas): Hm, last note: for tests above I've used Solaris 11.2 and GHC 7.10.1 RC3 build on AMD64. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 14:07:30 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 14:07:30 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.aafc37a93189f985f5cab571dfacfe49@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Don't forget to check for which rules fired `-fddump-rule-firings`. Missing a fusion rule is a big deal -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 14:28:31 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 14:28:31 -0000 Subject: [GHC] #10498: "if ... then \case -> else ..." causes a "missing else clause" error In-Reply-To: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> References: <050.28cad0c5bb9248828a1f63b683a53853@haskell.org> Message-ID: <065.7c33bafa0d20ce74023a494a4f1a98e3@haskell.org> #10498: "if ... then \case -> else ..." causes a "missing else clause" error -------------------------------------+------------------------------------- Reporter: dramforever | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.10.3 Component: Compiler | Version: 7.10.1 (Parser) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: newcomer => Comment: I'm inclined to just the delete the parser changes from Phab:D201. They were supposed to make error messages better, but instead they make them worse. Here's an example from the testsuite (parser/should_fail/readFail020): {{{ f = let x = 42 } in x -- before: parse error on input ?}? -- after: parse error in let binding: missing required 'in' }}} Here's another: {{{ f = if module then True else False -- before: parse error on input ?module? -- after: parse error in if statement: naked if statement }}} For that last one, the parser code looks like this: {{{ | 'if' error {% hintIf (getLoc $1) "naked if statement" } | 'if' exp optSemi error {% ... something ... } | 'if' exp optSemi 'then' error {% ... something ... } | 'if' exp optSemi 'then' exp optSemi error {% ... something ... } | 'if' exp optSemi 'then' exp optSemi 'else' error {% ... something ... } }}} What this means is that a lexical error in the condition of an if- expression, that we don't handle gracefully in the parser, will be reported as "naked if statement". The example from the description has the same cause. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 14:45:49 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 14:45:49 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.f935ade5a35417acd1e14e2e4bf65e88@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by inaki): Replying to [comment:3 simonpj]: Thanks for the explanation! This makes it clear what happens. Just to state what I expected from reading the docs at https://hackage.haskell.org/package/base-4.8.1.0/docs/Data-Coerce.html, the following works: {{{#!hs {-# LANGUAGE FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} -- import Data.Coerce (coerce, Coercible) data X a class Coercible a b where coerce :: a -> b newtype Y = Y (X Y) instance Coercible Y (X Y) where coerce (Y x) = x doCoerce :: Coercible a (X a) => a -> X a doCoerce = coerce test :: Y -> X Y test = doCoerce }}} which embodies what I understand the docs to be saying: because of the newtype, there is (morally) an instance of Coercible Y (X Y). But somehow the actual behavior of Coercible in 7.10 seems different. > * It wouldn't help your use-case. But do you have to use `Y` in this strange recursive way. Why not do this? > {{{ > newtype FY = FY (ForeignPtr Y) > data Y > }}} With the recursive definition for every newtype we automatically know the type of the ForeignPtr inside, while these ForeignPtrs still have distinct types, which comes handy on a number of occasions. It is also the way c2hs defines newtypes, for example {{{ {# pointer *GIBaseInfo as BaseInfo newtype #} }}} becomes {{{#!hs newtype BaseInfo = BaseInfo (Ptr (BaseInfo)) }}} so it is a fairly common idiom in the wild. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 14:51:40 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 14:51:40 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.945ce482a0a996acc0f2bc6235d502e5@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): I'm all for !ForeignPtrs having distinct types. I just don't understand why it has to be a recursive type. What's wrong with this? {{{ newtype FY = FY (ForeignPtr Y) data Y }}} (except that it isn't what c2hs does today) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:05:50 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:05:50 -0000 Subject: [GHC] #9020: Massive blowup of code size on trivial program In-Reply-To: <046.bab0bc7fbd776024468f95f75c63d364@haskell.org> References: <046.bab0bc7fbd776024468f95f75c63d364@haskell.org> Message-ID: <061.95c6ebca8df6a298c62ffa156a0fe96e@haskell.org> #9020: Massive blowup of code size on trivial program -------------------------------------+------------------------------------- Reporter: simonpj | Owner: nomeata Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Compile-time | Test Case: performance bug | perf/compiler/T9020 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D851 -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Compile-time performance bug -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:20:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:20:12 -0000 Subject: [GHC] #8253: example "Core syntax" is ancient In-Reply-To: <047.c3b31fabaa8a2840d3e512d5592d8b22@haskell.org> References: <047.c3b31fabaa8a2840d3e512d5592d8b22@haskell.org> Message-ID: <062.67c042b9887e7b9043dc70b2a9b7a43b@haskell.org> #8253: example "Core syntax" is ancient -------------------------------------+------------------------------------- Reporter: rwbarton | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Documentation | Version: 7.6.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Documentation | Unknown/Multiple bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: In commit a66e1ba60d9be67dda2a57a71bde96bc6f8dc5f0: {{{ Author: Thomas Miedema <> Date: Fri Jul 31 17:15:10 2015 +0200 User's guide: delete ancient "Core syntax" example }}} There are resources online to learn how to read GHC Core, such as: * http://stackoverflow.com/questions/6121146/reading-ghc-core * http://blog.ezyang.com/2011/04/tracing-the-compilation-of-hello- factorial/ If someone feels like contributing a new section on Core to the User's guide, they are of course free to do so. The section I just deleted wasn't doing any good. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:20:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:20:27 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.690c5ee0527164d5486a9a7f4fe183c5@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * owner: => goldfire Comment: In response to comment:5: Despite appearances to the contrary, `Coercible` is '''not''' a class. It is much more a special operator, right along the lines of `~`. (Historical note: when we started developing the idea that became `Coercible`, we thought it would indeed be a normal class, but with compiler-generated instances. And it started life that way. But when pushed, the limitations of the class-based solver became too much, and so `Coercible` evolved. The code in GHC that solves `Coercible` constraints is closely tied to solving of normal equality constraints, and not at all related to the code that solves class constraints.) Perhaps the user manual should be updated to reflect this fact about `Coercible`. Regardless of the solution we settle on, this is in my area, so I'll adopt the ticket. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:20:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:20:35 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.43aab7655b447421a679e2b1b75b817a@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by rwbarton): This was discussed in #7367 though without a real conclusion. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:25:59 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:25:59 -0000 Subject: [GHC] #9522: SPECIALISE pragmas for derived instances In-Reply-To: <046.6cda231aacfa5256df483e3d63fc0ff8@haskell.org> References: <046.6cda231aacfa5256df483e3d63fc0ff8@haskell.org> Message-ID: <061.2c797ceed8a51ca7f86ca48bb7c9eeeb@haskell.org> #9522: SPECIALISE pragmas for derived instances -------------------------------------+------------------------------------- Reporter: simonpj | Owner: 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 Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug * type: bug => feature request -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:29:24 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:29:24 -0000 Subject: [GHC] #9547: Empty constraint tuples are mis-kinded In-Reply-To: <046.4a68986f8009faa587ff75cd38e6aeac@haskell.org> References: <046.4a68986f8009faa587ff75cd38e6aeac@haskell.org> Message-ID: <061.a7139af3e1d1894a5c3209938a040f3f@haskell.org> #9547: Empty constraint tuples are mis-kinded -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 7.8.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Compiler (Type checker) -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:36:12 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:36:12 -0000 Subject: [GHC] #9447: Add support for resizing `MutableByteArray#`s In-Reply-To: <042.51867a8225b599fb4ff13dcceb122580@haskell.org> References: <042.51867a8225b599fb4ff13dcceb122580@haskell.org> Message-ID: <057.0184eb97c1f6d212cc8f1b77f06ab368@haskell.org> #9447: Add support for resizing `MutableByteArray#`s -------------------------------------+------------------------------------- Reporter: hvr | Owner: 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 Revisions: Phab:D133 -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug * type: bug => feature request -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:37:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:37:58 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.67326bc0d4f997320c7f47c9e7987a8d@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by inaki): In response to [comment:6 simonpj]: > I'm all for !ForeignPtrs having distinct types. I just don't understand why it has to be a recursive type. What's wrong with this? > {{{ > newtype FY = FY (ForeignPtr Y) > data Y > }}} > (except that it isn't what c2hs does today) Certainly nothing! In code I write by hand can easily do this. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:46:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:46:10 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.bfa4b023ca477b2f575787109f98f75a@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): OK. So let's fix c2hs! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:47:27 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:47:27 -0000 Subject: [GHC] #9418: Warnings about "INLINE binder is (non-rule) loop breaker" In-Reply-To: <046.872466a3116fcd1a2415e5a6fb1d5342@haskell.org> References: <046.872466a3116fcd1a2415e5a6fb1d5342@haskell.org> Message-ID: <061.71a75a2ef68d653e93d20f12e9810fad@haskell.org> #9418: Warnings about "INLINE binder is (non-rule) loop breaker" -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | 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: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed Comment: I don't see those warnings in the build logs, and also the example from comment:1 compiles without warnings. I guess this is fixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:47:46 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:47:46 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.d73565f5ce84d5c37cebcb0dc5cd81c9@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonpj): Oh yes -- so this is essential a duplicate ticket? If so let's close in favour of the longer discussion there -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 15:57:32 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 15:57:32 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.c06f8e0eccb7644c868b9f30cfb1c173@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by inaki): Replying to [comment:7 goldfire]: > In response to comment:5: Despite appearances to the contrary, `Coercible` is '''not''' a class. It is much more a special operator, right along the lines of `~`. > > (Historical note: when we started developing the idea that became `Coercible`, we thought it would indeed be a normal class, but with compiler-generated instances. And it started life that way. But when pushed, the limitations of the class-based solver became too much, and so `Coercible` evolved. The code in GHC that solves `Coercible` constraints is closely tied to solving of normal equality constraints, and not at all related to the code that solves class constraints.) > > Perhaps the user manual should be updated to reflect this fact about `Coercible`. Thanks for the explanation! An explanation of the subtleties when using Coercible in the manual would certainly help. Another related counterintuitive fact is that coerce itself works fine with the recursive newtype, the following works: {{{#!hs import Data.Coerce (coerce, Coercible) data X a --doCoerce :: Coercible a (X a) => a -> X a --doCoerce = coerce newtype Y = Y (X Y) test :: Y -> X Y test = coerce }}} but it see no way of writing doCoerce in a way that makes ghc 7.10 happy. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 16:02:19 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 16:02:19 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.67204d8cdfe914e075ff7a2bff5f64f6@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by nomeata): Richard , would it be unreasonable to support recursive newtypes where the occurrences of the newtype are all in phantom positions? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 16:02:51 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 16:02:51 -0000 Subject: [GHC] #9227: Coverage Condition cannot be turned off In-Reply-To: <047.00cb6fa9fbf58c6b033bc498f885a9b9@haskell.org> References: <047.00cb6fa9fbf58c6b033bc498f885a9b9@haskell.org> Message-ID: <062.fdd2aa50a3ff58c4634c288f032a1324@haskell.org> #9227: Coverage Condition cannot be turned off -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #1241, #2247, | Differential Revisions: #8356, #8634 | -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: Simon's response is in https://ghc.haskell.org/trac/ghc/ticket/8634#comment:14 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 16:03:52 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 16:03:52 -0000 Subject: [GHC] #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 In-Reply-To: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> References: <044.cc1e9df1bbafaf4fb6388749f2b76941@haskell.org> Message-ID: <059.7a33e7e139828f25d14e2f8ae8a4e935@haskell.org> #10715: Possible regression in Coercible a (X a) between 7.8 and 7.10 -------------------------------------+------------------------------------- Reporter: inaki | Owner: goldfire Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.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 Revisions: -------------------------------------+------------------------------------- Comment (by inaki): Replying to [comment:10 inaki]: > but it see no way of writing doCoerce in a way that makes ghc 7.10 happy. Well, the "surprising" {{{#!hs doCoerce :: Coercible a (X b) => a -> X a doCoerce = coerce }}} definition works in 7.10, but this does not work in 7.8, which I also want to support in my code if at all possible. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 16:19:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 16:19:39 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.6b22a86d0edaab50e104758a7cbeb4fc@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by Phyx-): @thomie Thanks! I have also updated the relevant Wiki pages. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:24:51 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:24:51 -0000 Subject: [GHC] #9070: "Simplifier ticks exhausted" In-Reply-To: <048.992ee320aaea58308e183d3ff9448d87@haskell.org> References: <048.992ee320aaea58308e183d3ff9448d87@haskell.org> Message-ID: <063.05e8c2fec4d716300cd20f2738297989@haskell.org> #9070: "Simplifier ticks exhausted" -------------------------------------+------------------------------------- Reporter: dermesser | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: worksforme | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => worksforme Comment: I compiled epub-metadata-4.0 with ghc-7.8.4, and it required a `-fsimpl- tick-factor` of 110 (the default is 100). I also compiled it with ghc-7.10.2, and then it only required a `-fsimpl-tick-factor` of 10. Case closed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:29:37 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:29:37 -0000 Subject: [GHC] #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 In-Reply-To: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> References: <046.d0b719189e2583c55d137308d4db4df8@haskell.org> Message-ID: <061.d77535cea1d3f02cdcb0f8addfec41f9@haskell.org> #10717: fannkuch-redux allocations increase by factor of 10000 between 7.4.2 and 7.6.3 -------------------------------------+------------------------------------- Reporter: bgamari | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.3 Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #7367 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => duplicate * related: => #7367 Comment: Finally getting back to this after my ISP decided to "fix" my connection. Hmmm, I sometimes do wish Trac's search were a bit better. Closing in favor of #7367. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:30:31 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:30:31 -0000 Subject: [GHC] #7367: float-out causes extra allocation In-Reply-To: <045.fec15abb73687c53fcbc974d115b141d@haskell.org> References: <045.fec15abb73687c53fcbc974d115b141d@haskell.org> Message-ID: <060.65aaf3384fc451d818425c52e0b94cfa@haskell.org> #7367: float-out causes extra allocation -------------------------------------+------------------------------------- Reporter: wurmli | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: Runtime | (amd64) performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by bgamari: Old description: > The Haskell fannkuchredux contribution of Louis Wasserman to "The > Computer Language Benchmarks Game" at shootout.alioth.debian.org times > out on the amd64 machines, but not on the i386. I can reproduce it on my > Debian amd64 machine. > > It turns out that compiling without optimisation or with a simple -O > produces a fast program, but with enourmously large heap space allocated > (10G compared with 67k on a virtual i386 machine) and also more garbage > collector activity. > > The source is below (because I don't find a way to attach the file). At > the end of the source I copied my make command line, run command line > and output produced with option -sstderr. > > --------------------- > > {{{ > {- The Computer Language Benchmarks Game > http://shootout.alioth.debian.org/ > contributed by Louis Wasserman > > This should be compiled with: > -threaded -O2 -fexcess-precision -fasm > and run with: > +RTS -N -RTS > -} > > import Control.Concurrent > import Control.Monad > import System.Environment > import Foreign hiding (rotate) > import Data.Monoid > > type Perm = Ptr Word8 > > data F = F {-# UNPACK #-} !Int {-# UNPACK #-} !Int > > instance Monoid F where > mempty = F 0 0 > F s1 m1 `mappend` F s2 m2 = F (s1 + s2) (max m1 m2) > > incPtr = (`advancePtr` 1) > decPtr = (`advancePtr` (-1)) > > flop :: Int -> Perm -> IO () > flop k xs = flopp xs (xs `advancePtr` k) > where flopp i j = when (i < j) $ swap i j >> flopp (incPtr i) (decPtr j) > swap i j = do > a <- peek i > b <- peek j > poke j a > poke i b > > flopS :: Perm -> (Int -> IO a) -> IO a > flopS !xs f = do > let go !acc = do > k <- peekElemOff xs 0 > if k == 0 then f acc else flop (fromIntegral k) xs >> go > (acc+1) > go 0 > > increment :: Ptr Word8 -> Ptr Word8 -> IO () > increment !p !ct = do > first <- peekElemOff p 1 > pokeElemOff p 1 =<< peekElemOff p 0 > pokeElemOff p 0 first > > let go !i !first = do > ci <- peekElemOff ct i > if fromIntegral ci < i then pokeElemOff ct i (ci+1) else > do > pokeElemOff ct i 0 > let !i' = i + 1 > moveArray p (incPtr p) i' > pokeElemOff p i' first > go i' =<< peekElemOff p 0 > go 1 first > > genPermutations :: Int -> Int -> Int -> Ptr Word8 -> Ptr Word8 -> IO F > genPermutations !n !l !r !perm !count = allocaArray n $ \ destF -> do > let upd j !f run = do > p0 <- peekElemOff perm 0 > if p0 == 0 then increment perm count >> run f else do > copyArray destF perm n > increment perm count > flopS destF $ \ flops -> > run (f `mappend` F (checksum j flops) > flops) > let go j !f = if j >= r then return f else upd j f (go (j+1)) > go l mempty > where checksum i f = if i .&. 1 == 0 then f else -f > > facts :: [Int] > facts = scanl (*) 1 [1..12] > > unrank :: Int -> Int -> (Ptr Word8 -> Ptr Word8 -> IO a) -> IO a > unrank !idx !n f = allocaArray n $ \ p -> allocaArray n $ \ count -> > allocaArray n $ \ pp -> do > mapM_ (\ i -> pokeElemOff p i (fromIntegral i)) [0..n-1] > let go i !idx = when (i >= 0) $ do > let fi = facts !! i > let (q, r) = idx `quotRem` fi > pokeElemOff count i (fromIntegral q) > copyArray pp p (i+1) > let go' j = when (j <= i) $ do > let jq = j + q > pokeElemOff p j =<< peekElemOff pp (if jq <= i > then jq else jq - i - 1) > go' (j+1) > go' 0 > go (i-1) r > go (n-1) idx > f p count > > main = do > n <- fmap (read.head) getArgs > let fact = product [1..n] > let bk = fact `quot` 4 > vars <- forM [0,bk..fact-1] $ \ ix -> do > var <- newEmptyMVar > forkIO (unrank ix n $ \ p -> genPermutations n ix (min fact (ix + > bk)) p >=> putMVar var) > return var > F chksm mflops <- liftM mconcat (mapM takeMVar vars) > putStrLn $ (show chksm) ++ "\nPfannkuchen(" ++ (show n) ++ ") = " ++ > (show $ mflops) > > {- > > wurmli at noah-nofen:~/hpw/haskell/work/fannkuch$ ghc --make > -XBangPatterns -O -threaded -fllvm -rtsopts fannkuchredux.ghc-3.hs > [1 of 1] Compiling Main ( fannkuchredux.ghc-3.hs, > fannkuchredux.ghc-3.o ) > Linking fannkuchredux.ghc-3 ... > wurmli at noah-nofen:~/hpw/haskell/work/fannkuch$ ./fannkuchredux.ghc-3 +RTS > -N4 -sstderr -RTS 12 > 3968050 > Pfannkuchen(12) = 65 > 10,538,122,952 bytes allocated in the heap > 359,512 bytes copied during GC > 47,184 bytes maximum residency (2 sample(s)) > 51,120 bytes maximum slop > 4 MB total memory in use (1 MB lost due to fragmentation) > > Tot time (elapsed) Avg pause Max > pause > Gen 0 6053 colls, 6053 par 0.16s 0.04s 0.0000s > 0.0001s > Gen 1 2 colls, 1 par 0.00s 0.00s 0.0001s > 0.0001s > > Parallel GC work balance: 40.82% (serial 0%, perfect 100%) > > TASKS: 6 (1 bound, 5 peak workers (5 total), using -N4) > > SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled) > > INIT time 0.00s ( 0.00s elapsed) > MUT time 44.73s ( 11.51s elapsed) > GC time 0.16s ( 0.04s elapsed) > EXIT time 0.00s ( 0.00s elapsed) > Total time 44.89s ( 11.55s elapsed) > > Alloc rate 235,589,887 bytes per MUT second > > Productivity 99.6% of total user, 387.3% of total elapsed > > gc_alloc_block_sync: 31024 > whitehole_spin: 0 > gen[0].sync: 0 > gen[1].sync: 0 > > -} > }}} New description: The Haskell fannkuchredux (included in nofib as fannkuch-redux) contribution of Louis Wasserman to "The Computer Language Benchmarks Game" at shootout.alioth.debian.org times out on the amd64 machines, but not on the i386. I can reproduce it on my Debian amd64 machine. It turns out that compiling without optimisation or with a simple -O produces a fast program, but with enormously large heap space allocated (10G compared with 67k on a virtual i386 machine) and also more garbage collector activity. The source is below (because I don't find a way to attach the file). At the end of the source I copied my make command line, run command line and output produced with option -sstderr. --------------------- {{{ {- The Computer Language Benchmarks Game http://shootout.alioth.debian.org/ contributed by Louis Wasserman This should be compiled with: -threaded -O2 -fexcess-precision -fasm and run with: +RTS -N -RTS -} import Control.Concurrent import Control.Monad import System.Environment import Foreign hiding (rotate) import Data.Monoid type Perm = Ptr Word8 data F = F {-# UNPACK #-} !Int {-# UNPACK #-} !Int instance Monoid F where mempty = F 0 0 F s1 m1 `mappend` F s2 m2 = F (s1 + s2) (max m1 m2) incPtr = (`advancePtr` 1) decPtr = (`advancePtr` (-1)) flop :: Int -> Perm -> IO () flop k xs = flopp xs (xs `advancePtr` k) where flopp i j = when (i < j) $ swap i j >> flopp (incPtr i) (decPtr j) swap i j = do a <- peek i b <- peek j poke j a poke i b flopS :: Perm -> (Int -> IO a) -> IO a flopS !xs f = do let go !acc = do k <- peekElemOff xs 0 if k == 0 then f acc else flop (fromIntegral k) xs >> go (acc+1) go 0 increment :: Ptr Word8 -> Ptr Word8 -> IO () increment !p !ct = do first <- peekElemOff p 1 pokeElemOff p 1 =<< peekElemOff p 0 pokeElemOff p 0 first let go !i !first = do ci <- peekElemOff ct i if fromIntegral ci < i then pokeElemOff ct i (ci+1) else do pokeElemOff ct i 0 let !i' = i + 1 moveArray p (incPtr p) i' pokeElemOff p i' first go i' =<< peekElemOff p 0 go 1 first genPermutations :: Int -> Int -> Int -> Ptr Word8 -> Ptr Word8 -> IO F genPermutations !n !l !r !perm !count = allocaArray n $ \ destF -> do let upd j !f run = do p0 <- peekElemOff perm 0 if p0 == 0 then increment perm count >> run f else do copyArray destF perm n increment perm count flopS destF $ \ flops -> run (f `mappend` F (checksum j flops) flops) let go j !f = if j >= r then return f else upd j f (go (j+1)) go l mempty where checksum i f = if i .&. 1 == 0 then f else -f facts :: [Int] facts = scanl (*) 1 [1..12] unrank :: Int -> Int -> (Ptr Word8 -> Ptr Word8 -> IO a) -> IO a unrank !idx !n f = allocaArray n $ \ p -> allocaArray n $ \ count -> allocaArray n $ \ pp -> do mapM_ (\ i -> pokeElemOff p i (fromIntegral i)) [0..n-1] let go i !idx = when (i >= 0) $ do let fi = facts !! i let (q, r) = idx `quotRem` fi pokeElemOff count i (fromIntegral q) copyArray pp p (i+1) let go' j = when (j <= i) $ do let jq = j + q pokeElemOff p j =<< peekElemOff pp (if jq <= i then jq else jq - i - 1) go' (j+1) go' 0 go (i-1) r go (n-1) idx f p count main = do n <- fmap (read.head) getArgs let fact = product [1..n] let bk = fact `quot` 4 vars <- forM [0,bk..fact-1] $ \ ix -> do var <- newEmptyMVar forkIO (unrank ix n $ \ p -> genPermutations n ix (min fact (ix + bk)) p >=> putMVar var) return var F chksm mflops <- liftM mconcat (mapM takeMVar vars) putStrLn $ (show chksm) ++ "\nPfannkuchen(" ++ (show n) ++ ") = " ++ (show $ mflops) {- wurmli at noah-nofen:~/hpw/haskell/work/fannkuch$ ghc --make -XBangPatterns -O -threaded -fllvm -rtsopts fannkuchredux.ghc-3.hs [1 of 1] Compiling Main ( fannkuchredux.ghc-3.hs, fannkuchredux.ghc-3.o ) Linking fannkuchredux.ghc-3 ... wurmli at noah-nofen:~/hpw/haskell/work/fannkuch$ ./fannkuchredux.ghc-3 +RTS -N4 -sstderr -RTS 12 3968050 Pfannkuchen(12) = 65 10,538,122,952 bytes allocated in the heap 359,512 bytes copied during GC 47,184 bytes maximum residency (2 sample(s)) 51,120 bytes maximum slop 4 MB total memory in use (1 MB lost due to fragmentation) Tot time (elapsed) Avg pause Max pause Gen 0 6053 colls, 6053 par 0.16s 0.04s 0.0000s 0.0001s Gen 1 2 colls, 1 par 0.00s 0.00s 0.0001s 0.0001s Parallel GC work balance: 40.82% (serial 0%, perfect 100%) TASKS: 6 (1 bound, 5 peak workers (5 total), using -N4) SPARKS: 0 (0 converted, 0 overflowed, 0 dud, 0 GC'd, 0 fizzled) INIT time 0.00s ( 0.00s elapsed) MUT time 44.73s ( 11.51s elapsed) GC time 0.16s ( 0.04s elapsed) EXIT time 0.00s ( 0.00s elapsed) Total time 44.89s ( 11.55s elapsed) Alloc rate 235,589,887 bytes per MUT second Productivity 99.6% of total user, 387.3% of total elapsed gc_alloc_block_sync: 31024 whitehole_spin: 0 gen[0].sync: 0 gen[1].sync: 0 -} }}} -- -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:37:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:37:42 -0000 Subject: [GHC] #9173: Better type error messages In-Reply-To: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> References: <046.f8f24aa2ddaa3d579bc40f0b6f04f6b7@haskell.org> Message-ID: <061.513d172d667dda614e65d1b97b8e50d1@haskell.org> #9173: Better type error messages -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: newcomer Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * keywords: => newcomer Comment: This seems like a nice and easy ticket to handle by a newcomer. The function to change is `misMatchMsg` in `compiler/typecheck/TcErrors.hs`. Don't forget to update the expected test output. Use 'make accept', see [wiki:Building/RunningTests/Updating]. Please make sure you get all of them (grep for the old error message). -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:41:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:41:10 -0000 Subject: [GHC] #9230: Make -fwarn-tabs the default In-Reply-To: <045.44ab9aa6c5c4554ed8d149c327b464d2@haskell.org> References: <045.44ab9aa6c5c4554ed8d149c327b464d2@haskell.org> Message-ID: <060.a67f5ffcc3bbb3b3d34f7ff3adc49a90@haskell.org> #9230: Make -fwarn-tabs the default -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: mlen Type: feature request | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D255, | Phab:D399 -------------------------------------+------------------------------------- Comment (by yokto): This default is clearly in favour of people using spaces. A more neutral option would be to just warn when character counts and tabs are being mixed. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:46:18 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:46:18 -0000 Subject: [GHC] #5463: SPECIALISE pragmas generated from Template Haskell are ignored In-Reply-To: <052.5da0a08d27fdc8dd517b247a84e49319@haskell.org> References: <052.5da0a08d27fdc8dd517b247a84e49319@haskell.org> Message-ID: <067.0d5f5a4cf7911da0c7f800757319ead1@haskell.org> #5463: SPECIALISE pragmas generated from Template Haskell are ignored -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.2.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug * milestone: 7.12.1 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 17:55:44 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 17:55:44 -0000 Subject: [GHC] #5355: Link plugins against existing libHSghc In-Reply-To: <053.90d96b1c121110f57a47511594fdcf0f@haskell.org> References: <053.90d96b1c121110f57a47511594fdcf0f@haskell.org> Message-ID: <068.6bb0c4061922aaa62ae9ad5e7a6b4105@haskell.org> #5355: Link plugins against existing libHSghc -------------------------------------+------------------------------------- Reporter: batterseapower | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.0.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: 5987 | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug * milestone: 7.12.1 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:16:48 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:16:48 -0000 Subject: [GHC] #9331: Release Cabal 1.22 before GHC 7.10 release In-Reply-To: <045.bbcbad638a01bcc0aa536c05de8920b5@haskell.org> References: <045.bbcbad638a01bcc0aa536c05de8920b5@haskell.org> Message-ID: <060.584a012a78d7f4e697d6034022b5a1cc@haskell.org> #9331: Release Cabal 1.22 before GHC 7.10 release -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: task | Status: closed Priority: normal | Milestone: Component: Package 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 Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed * milestone: 7.12.1 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:18:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:18:05 -0000 Subject: [GHC] #7919: Heap corruption (segfault) from large 'let' expression In-Reply-To: <045.3707d678a38441ef54b667e63e238d84@haskell.org> References: <045.3707d678a38441ef54b667e63e238d84@haskell.org> Message-ID: <060.c8d9c57c6f1f0d51937c4a5bd9c4b972@haskell.org> #7919: Heap corruption (segfault) from large 'let' expression -------------------------------------+------------------------------------- Reporter: duncan | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Runtime System | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: x86_64 | (amd64) Type of failure: Runtime crash | Test Case: rts/T7919 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1113 -------------------------------------+------------------------------------- Comment (by Simon Marlow ): In [changeset:"7cf87dfbf93f9839fa1e3b66a0233ac86f85a5f7/ghc" 7cf87dfb/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="7cf87dfbf93f9839fa1e3b66a0233ac86f85a5f7" Fix #7919 (again) Summary: The fix is a bit clunky, and is perhaps not the best fix, but I'm not sure how much work it would be to fix it the other way (see comments for more info). Test Plan: T7919 doesn't crash Reviewers: austin, rwbarton, ezyang, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1113 GHC Trac Issues: #7919 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:21:48 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:21:48 -0000 Subject: [GHC] #10481: raise# should have an open kind in its return type In-Reply-To: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> References: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> Message-ID: <064.ecb3c1e939729cc746f9f05d3e0a11c2@haskell.org> #10481: raise# should have an open kind in its return type -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 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 Revisions: Phab:D1116 -------------------------------------+------------------------------------- Changes (by rwbarton): * differential: => Phab:D1116 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:33:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:33:06 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.dd446b18ae1841c343174fabfb9b8dd3@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by simonmar): It sounds like there might be a lot of threads hitting blackholes, with consequent context-switching churn. Finding out which blackhole would be good - probably something in a shared data structure (NameCache or the FastString table, perhaps). ThreadScope would be a good next step. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:47:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:47:20 -0000 Subject: [GHC] #9951: OverloadedLists breaks exhaustiveness check In-Reply-To: <048.8197b1daa9c7ccdc6beab4f061e20643@haskell.org> References: <048.8197b1daa9c7ccdc6beab4f061e20643@haskell.org> Message-ID: <063.93d871db3f19fd04d9c9bd88c2b29df2@haskell.org> #9951: OverloadedLists breaks exhaustiveness check -------------------------------------+------------------------------------- Reporter: Feuerbach | 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: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by thomie): Also reported as #10393. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:47:42 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:47:42 -0000 Subject: [GHC] #10393: Bogus warning with OverloadedLists In-Reply-To: <047.4f31e76bb02b814e66f057431b9409d9@haskell.org> References: <047.4f31e76bb02b814e66f057431b9409d9@haskell.org> Message-ID: <062.0da25330b95b10d18a03aed7a581ad73@haskell.org> #10393: Bogus warning with OverloadedLists -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 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: #9951 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate * related: => #9951 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:49:23 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:49:23 -0000 Subject: [GHC] #10718: bitmap-0.0.2 SPECIALIZE pragma panic (GHC 7.10.1) Message-ID: <047.e921279d9d9e76ea3b8fe5290377e4ed@haskell.org> #10718: bitmap-0.0.2 SPECIALIZE pragma panic (GHC 7.10.1) -------------------------------------+------------------------------------- Reporter: NCrashed | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Linux Architecture: x86_64 | Type of failure: GHC doesn't work (amd64) | at all Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- Building with stack `bitmap-0.0.2` {{{ Configuring bitmap-0.0.2... Building bitmap-0.0.2... Preprocessing library bitmap-0.0.2... [ 1 of 10] Compiling Data.Bitmap.Internal ( Data/Bitmap/Internal.hs, .stack-work/dist/x86_64-linux/Cabal-1.22.2.0/build/Data/Bitmap/Internal.o ) [ 2 of 10] Compiling Data.Bitmap.Base ( Data/Bitmap/Base.hs, .stack- work/dist/x86_64-linux/Cabal-1.22.2.0/build/Data/Bitmap/Base.o ) [ 3 of 10] Compiling Data.Bitmap.IO ( Data/Bitmap/IO.hs, .stack- work/dist/x86_64-linux/Cabal-1.22.2.0/build/Data/Bitmap/IO.o ) Data/Bitmap/IO.hs:1248:1: Warning: SPECIALISE pragma for non-overloaded function ?myPlusPtr? Data/Bitmap/IO.hs:1249:1: Warning: SPECIALISE pragma for non-overloaded function ?myPlusPtr? ghc: panic! (the 'impossible' happened) (GHC version 7.10.1 for x86_64-unknown-linux): Template variable unbound in rewrite rule $fPixelComponentFloat3_X2Rc [$fPixelComponentFloat3_X2Rc] [$fPixelComponentFloat3_X2Rc] [] [] Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 18:54:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 18:54:20 -0000 Subject: [GHC] #10718: bitmap-0.0.2 SPECIALIZE pragma panic (GHC 7.10.1) In-Reply-To: <047.e921279d9d9e76ea3b8fe5290377e4ed@haskell.org> References: <047.e921279d9d9e76ea3b8fe5290377e4ed@haskell.org> Message-ID: <062.ab9226742169d3ba0b3540a7acde84e1@haskell.org> #10718: bitmap-0.0.2 SPECIALIZE pragma panic (GHC 7.10.1) -------------------------------------+------------------------------------- Reporter: NCrashed | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: duplicate | Keywords: Operating System: Linux | Architecture: x86_64 Type of failure: GHC doesn't work | (amd64) at all | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => duplicate Comment: Reported many times before already. Please upgrade to 7.10.2, should be fixed! -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:11:06 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:11:06 -0000 Subject: [GHC] #10377: Remove double negative of ("Unregisterised", "NO") In-Reply-To: <044.31181ac18eac612460803bc88434cef8@haskell.org> References: <044.31181ac18eac612460803bc88434cef8@haskell.org> Message-ID: <059.9abbd2f1e8d5b934b8682795ab30824d@haskell.org> #10377: Remove double negative of ("Unregisterised", "NO") -------------------------------------+------------------------------------- Reporter: erikd | Owner: erikd Type: bug | Status: new Priority: normal | Milestone: 7.12.1 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 Revisions: -------------------------------------+------------------------------------- Comment (by thomie): I agree with Reid here: wontfix. It's not just the settings file either, grep shows over 100 uses of the word unregisterised. * platformUnregisterised * targetUnregisterised * "Compiler unregisterised" * etc. Only changing the name in configure/settings file would just make things confusing. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:15:05 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:15:05 -0000 Subject: [GHC] #6070: Fun with the demand analyser In-Reply-To: <046.c6530061559c47a83051d5bf2c366594@haskell.org> References: <046.c6530061559c47a83051d5bf2c366594@haskell.org> Message-ID: <061.6e8e3d51bbe03abe071ab31cb7c427a8@haskell.org> #6070: Fun with the demand analyser -------------------------------------+------------------------------------- Reporter: simonpj | Owner: simonpj Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * failure: None/Unknown => Runtime performance bug * milestone: 7.12.1 => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:40:45 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:40:45 -0000 Subject: =?utf-8?q?Re=3A_=5BGHC=5D_=2310515=3A_ghc=3A_panic=3A_tyThingTyC?= =?utf-8?b?b24gSWRlbnRpZmllciDigJgkZlN0ZW5jaWw6LmEoLCwsLCk34oCZ?= In-Reply-To: <046.1a69329a1db1e1b89b8b31699fd5aae1@haskell.org> References: <046.1a69329a1db1e1b89b8b31699fd5aae1@haskell.org> Message-ID: <061.482deec0d0ce7dff902e1502f1e3318d@haskell.org> #10515: ghc: panic: tyThingTyCon Identifier ?$fStencil:.a(,,,,)7? -------------------------------------+------------------------------------- Reporter: yongqli | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => infoneeded Comment: yongqli: please attach or copy-paste a small program to reproduce the bug, see [wiki:ReportABug#Fulldescription:whatinformationtoprovideinthebodyofyourbugreport]: * as small as possible * zero cabal dependencies * including build and run instructions Thanks -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:44:35 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:44:35 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.591344189a65a2ee3fa4ca976a759863@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by bgamari): simonmar, can ThreadScope help point one in the direction of which blackhole is to blame? I was under the impression that blackhole performance debugging an area where our current tools fell a little short, but maybe I've missed something. Somewhere around here I have the beginnings of a patch adding support for profiling of blackhole block events but I wonder if our new DWARF capabilities might be a better fit for this sort of performance work. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:44:41 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:44:41 -0000 Subject: [GHC] #10098: Refactor wild card renaming In-Reply-To: <052.6e4b7f96cd090e4532413a4e30b58f3a@haskell.org> References: <052.6e4b7f96cd090e4532413a4e30b58f3a@haskell.org> Message-ID: <067.1f7c0596ff492c603d9e1d0da71c4faa@haskell.org> #10098: Refactor wild card renaming -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: thomasw Type: task | Status: new Priority: normal | Milestone: 7.12.1 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: #9922 | Differential Revisions: Phab:D613 -------------------------------------+------------------------------------- Changes (by thomie): * type: bug => task Comment: I think this is done. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:44:49 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:44:49 -0000 Subject: [GHC] #10098: Refactor wild card renaming In-Reply-To: <052.6e4b7f96cd090e4532413a4e30b58f3a@haskell.org> References: <052.6e4b7f96cd090e4532413a4e30b58f3a@haskell.org> Message-ID: <067.a02019c671d316e2e74a22fbdb9d0da9@haskell.org> #10098: Refactor wild card renaming -------------------------------------+------------------------------------- Reporter: thoughtpolice | Owner: thomasw Type: task | Status: closed Priority: normal | Milestone: 7.12.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: #9922 | Differential Revisions: Phab:D613 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:50:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:50:39 -0000 Subject: [GHC] #9861: ghc readme provides out of date git clone directions In-Reply-To: <045.ee10b522121d648c9ddb8fa0d461111b@haskell.org> References: <045.ee10b522121d648c9ddb8fa0d461111b@haskell.org> Message-ID: <060.c8002db772b66d56db7ddb1e3166bc54@haskell.org> #9861: ghc readme provides out of date git clone directions -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: phab:D555 -------------------------------------+------------------------------------- Changes (by thomie): * status: closed => new * resolution: fixed => -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 19:56:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 19:56:47 -0000 Subject: [GHC] #9861: ghc readme provides out of date git clone directions In-Reply-To: <045.ee10b522121d648c9ddb8fa0d461111b@haskell.org> References: <045.ee10b522121d648c9ddb8fa0d461111b@haskell.org> Message-ID: <060.1b5dd1d0a53542b5c4bdd05d7b4c9299@haskell.org> #9861: ghc readme provides out of date git clone directions -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: merge Priority: normal | Milestone: 7.10.3 Component: Compiler | 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 Revisions: phab:D555 -------------------------------------+------------------------------------- Changes (by thomie): * status: new => merge * milestone: => 7.10.3 Comment: Please merge the following commit to ghc-7.10. It updates the build instructions for ghc-7.10 in the README and the HACKING file. {{{ commit a592e9ffcfb288cd154bad60dc8003b781355533 Author: Thomas Miedema <> Date: Tue Jul 14 17:15:12 2015 +0200 Remove all references to sync-all }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 20:12:10 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 20:12:10 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.c8d8b13c69678cc063538c7aff7e84a7@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by thomie): irc user eacameron makes a good point: the build instructions on the wiki don't work for ghc-7.10 now, or earlier releases. Not sure what to do about this. Coincidentally, the build instructions in the README file are also out of date. This is tracked in #9861. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:06:20 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:06:20 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.dead7cbbd780cf78cde4948402e7bff9@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by Phyx-): Well, for 7.8.x there is https://ghc.haskell.org/trac/ghc/wiki/Building/GettingTheSources/Legacy Would an idea be to extend this page to include 7.10 and link to it from the build instructions? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:08:57 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:08:57 -0000 Subject: [GHC] #10481: raise# should have an open kind in its return type In-Reply-To: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> References: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> Message-ID: <064.6f6dd758a537a8ca0855243a11b83468@haskell.org> #10481: raise# should have an open kind in its return type -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: new Priority: normal | Milestone: 7.12.1 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 Revisions: Phab:D1116 -------------------------------------+------------------------------------- Comment (by Reid Barton ): In [changeset:"ad089f58be522cb68c0306c21c5df9d72b6c0aff/ghc" ad089f58/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="ad089f58be522cb68c0306c21c5df9d72b6c0aff" Give raise# a return type of open kind (#10481) Test Plan: validate Reviewers: austin, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D1116 GHC Trac Issues: #10481 }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:09:09 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:09:09 -0000 Subject: [GHC] #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. In-Reply-To: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> References: <044.6a0cbb38e795506560cf63dc7c2184b5@haskell.org> Message-ID: <059.0e9e1022e3c663b2b1cb1090061da271@haskell.org> #10705: make configure warn when ghc-tarballs is missing on windows and provide guidance to download it. -------------------------------------+------------------------------------- Reporter: Phyx- | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.12.1 Component: Build System | Version: 7.11 Resolution: fixed | Keywords: Operating System: Windows | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9218 | Differential Revisions: Phab:D1108 -------------------------------------+------------------------------------- Comment (by thomie): eacameron said they were going to do so -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:09:17 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:09:17 -0000 Subject: [GHC] #10481: raise# should have an open kind in its return type In-Reply-To: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> References: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> Message-ID: <064.a0def7334affb1cd736715f90ecab7d0@haskell.org> #10481: raise# should have an open kind in its return type -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.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 Revisions: Phab:D1116 -------------------------------------+------------------------------------- Changes (by rwbarton): * status: new => closed * resolution: => fixed -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:13:36 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:13:36 -0000 Subject: [GHC] #10481: raise# should have an open kind in its return type In-Reply-To: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> References: <049.c95a2960ea81fc257ca0a55576d368d7@haskell.org> Message-ID: <064.0344bdcdb18fb64948bee0c6cd2a45f0@haskell.org> #10481: raise# should have an open kind in its return type -------------------------------------+------------------------------------- Reporter: gridaphobe | Owner: Type: bug | Status: closed Priority: normal | Milestone: 7.12.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | primops/should_run/T10481 Blocked By: | Blocking: Related Tickets: | Differential Revisions: Phab:D1116 -------------------------------------+------------------------------------- Changes (by simonpj): * testcase: => primops/should_run/T10481 Comment: Thanks; don't forget to fill in the Test Case field though. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:31:41 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:31:41 -0000 Subject: [GHC] #8060: Undefined symbols when using Template Haskell linked from another object with unexposed modules In-Reply-To: <044.730164fd4456e5107de56b5da1c9dd5d@haskell.org> References: <044.730164fd4456e5107de56b5da1c9dd5d@haskell.org> Message-ID: <059.186ecd420029f983ba4cd763506c8586@haskell.org> #8060: Undefined symbols when using Template Haskell linked from another object with unexposed modules -------------------------------------+------------------------------------- Reporter: tvynr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple crash | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Template Haskell Comment: tvynr: I'm guessing this problem didn't magically go away, with recent compiler versions? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 21:53:03 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 21:53:03 -0000 Subject: [GHC] #8387: View patterns + pattern bindings: finnicky about scoping In-Reply-To: <049.80a7a96a249f935479042170f7e059ae@haskell.org> References: <049.80a7a96a249f935479042170f7e059ae@haskell.org> Message-ID: <064.301ebe8f4e92616c7ad2609bcc38bd66@haskell.org> #8387: View patterns + pattern bindings: finnicky about scoping -------------------------------------+------------------------------------- Reporter: tinctorius | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: wontfix | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #4061 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * status: new => closed * resolution: => wontfix * related: => #4061 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 22:01:47 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 22:01:47 -0000 Subject: [GHC] #9221: (super!) linear slowdown of parallel builds on 40 core machine In-Reply-To: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> References: <045.6b727a84a1bea97c8d082954a0b9425e@haskell.org> Message-ID: <060.9de53b5820510801629493b99daa8b51@haskell.org> #9221: (super!) linear slowdown of parallel builds on 40 core machine -------------------------------------+------------------------------------- Reporter: carter | Owner: Type: bug | Status: new Priority: high | Milestone: 7.12.1 Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #910 | Differential Revisions: -------------------------------------+------------------------------------- Comment (by slyfox): Replying to [comment:29 bgamari]: > slyfox, out of curiosity what sort of parallel speed-up did you observe in that test? At best I get ~2.5 speedup (-j8 -A128M): - -j1 : 41.1s - -j8 -A128M : 17.4s Replying to [comment:31 simonmar]: > It sounds like there might be a lot of threads hitting blackholes, with consequent context-switching churn. Finding out which blackhole would be good - probably something in a shared data structure (NameCache or the FastString table, perhaps). ThreadScope would be a good next step. Tried to run as: '''./mk.bash -j8 +RTS -A128m -l''': http://code.haskell.org/~slyfox/T9221-A128M-j8-l.eventlog I see a chain of 'thread yields', 'blocked on an MVar' there, but can't draw any conclusions. Can I somehow get callers of blackhole? I guess 'perf report -G' will lie as stacks are lost, but here goes it's output: {{{ Children Self Command Shared Object Symbol + 15,92% 0,81% ghc_worker libc-2.21.so [.] __sched_yield + 15,54% 1,69% ghc_worker [kernel.vmlinux] [k] entry_SYSCALL_64 + 13,11% 0,40% ghc_worker [kernel.vmlinux] [k] sys_sched_yield - 10,85% 6,43% ghc_worker ghc-stage2 [.] clI_info - 40,76% clI_info (stg_BLACKHOLE_info) + 2,23% c8E2_info (ghc_Pretty_reduceDoc_info) + 1,81% c9p9_info (ghc_Pretty_vcatzugo_info) + 1,65% cJw6_info (ghczmprim_GHCziClasses_divIntzh_info) + 1,62% c8zA_info (...others) + 1,62% ca_info + 1,39% apic_timer_interrupt + 1,34% c4nL_info + 1,33% c3ZK_info + 1,27% c2k_info + 1,04% cmKx_info + 1,03% cp2g_info 0,92% cp_info + 0,89% shV8_info + 0,88% strlen + 0,88% c9r1_info + 0,87% r63b_info + 0,79% s1P5_info + 0,73% c4IG_info + 0,69% c4uY_info + 0,63% r117_info + 0,62% sw4Y_info 0,62% cqIM_info 0,61% caEA_info + 0,58% c2l_info 0,57% cyqt_info + 0,52% c9xp_info 33,29% 0x480328785000c748 + 1,82% 0x4b7202f9834807e1 + 1,54% 0x4808588b48f8e083 + 0,87% 0x438b482677000003 + 0,87% 0x8d3b49307507c1f6 + 0,82% 0x4640cd24fffc498b + 0,81% 0xf07f98348fc498b + 0,75% 0x9b820f02f8 + 0,65% 0x24ff07e283da8948 + 0,63% 0x11d820f0af883 + 0,61% 0xf4b8b4807438b48 + 0,53% 0x58c48349677202f8 + 0,50% 0x48074b8b48d88948 + 10,79% 0,38% ghc_worker [kernel.vmlinux] [k] schedule + 9,44% 1,60% ghc_worker [kernel.vmlinux] [k] __schedule }}} -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 22:06:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 22:06:58 -0000 Subject: [GHC] #8510: Clear up what extensions are needed at a Template Haskell splice site In-Reply-To: <046.31fc5da448545a65cf9e299ef73abdd3@haskell.org> References: <046.31fc5da448545a65cf9e299ef73abdd3@haskell.org> Message-ID: <061.7838ea0f5fb647ede1c168cce931548b@haskell.org> #8510: Clear up what extensions are needed at a Template Haskell splice site -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template Haskell | 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 Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * component: Compiler => Template Haskell -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 22:25:39 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 22:25:39 -0000 Subject: [GHC] #8488: Annotations should not distinguish type and value In-Reply-To: <046.0175c19cfd098f66da3cc70b6a5deec4@haskell.org> References: <046.0175c19cfd098f66da3cc70b6a5deec4@haskell.org> Message-ID: <061.9d98cbec06aaac19bc1eda4ef497728c@haskell.org> #8488: Annotations should not distinguish type and value -------------------------------------+------------------------------------- Reporter: simonpj | Owner: errge Type: task | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by thomie): * type: bug => task Comment: errge: what is the status of this? Still stuck? -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 23:01:26 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 23:01:26 -0000 Subject: [GHC] #9331: Release Cabal 1.22 before GHC 7.10 release In-Reply-To: <045.bbcbad638a01bcc0aa536c05de8920b5@haskell.org> References: <045.bbcbad638a01bcc0aa536c05de8920b5@haskell.org> Message-ID: <060.756b91833403cbd88d3390522b10a5e6@haskell.org> #9331: Release Cabal 1.22 before GHC 7.10 release -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: task | Status: closed Priority: normal | Milestone: 7.10.1 Component: Package 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 Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * milestone: => 7.10.1 -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 31 23:41:48 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 31 Jul 2015 23:41:48 -0000 Subject: [GHC] #10719: Malformed data type quotation accepted Message-ID: <048.6b945575ed583054da28b46717dca1a6@haskell.org> #10719: Malformed data type quotation accepted -------------------------------------+------------------------------------- Reporter: heisenbug | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Revisions: | -------------------------------------+------------------------------------- This is accepted: Prelude Language.Haskell.TH> {{{$(stringE . show =<< [d| data A where C :: C |])}}} "[DataD [] A_1627402878 [] [ForallC [] [] (NormalC C_1627402879 [])] []]" In contrast this is rejected: Prelude Language.Haskell.TH> {{{$(stringE . show =<< [d| data A p where C :: C |])}}} :29:22: Malformed constructor result type: C However it would make sense to form an equality constraint (for later kind/type checking) in these cases, something along the lines of: {{{#!hs data A p where C :: (A p ~ C) => C }}} as there could be type synonym (or family) `C`. I have tested various versions >= 7.8.3 and all seem to behave the same. -- Ticket URL: GHC The Glasgow Haskell Compiler From ghc-devs at haskell.org Fri Jul 24 13:19:58 2015 From: ghc-devs at haskell.org (GHC) Date: Fri, 24 Jul 2015 13:19:58 -0000 Subject: [GHC] #10528: compile time performance regression on big literal In-Reply-To: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> References: <048.98ab82d16d4bd14b388cfa4fc2b927d4@haskell.org> Message-ID: <063.8d8b43de21f33764e4012a406093798c@haskell.org> #10528: compile time performance regression on big literal -------------------------------------+------------------------------------- Reporter: jakewheat | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: Resolution: | Keywords: Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Description changed by thomie: Old description: > There is a big performance regression in the compile time from ghc 7.10.1 > to ghc 7.10.1.20150612 > > I believe it is in this file which has a huge literal value which also > contains overloaded strings using Text: > > https://github.com/JakeWheat/hssqlppp/blob/master/hssqlppp/src/Database/HsSqlPpp/Internals/Catalog/DefaultTemplate1Catalog.lhs > > {{{ > time cabal build with ghc 7.10.1 > > real 1m20.449s > user 2m5.040s > sys 0m48.504s > > time cabal build with ghc 7.10.1.20150612 > > real 9m3.447s > user 12m19.704s > sys 3m25.724s > }}} > > I am running debian 64 bit unstable with the ghc binary tarballs from > here: https://www.haskell.org/ghc/ > > Here is a transcript: > > {{{ > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ ghc --version > The Glorious Glasgow Haskell Compilation System, version 7.10.1 > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ cabal sandbox init > Writing a default package environment file to > /home/jake/wd/hssqlppp/trunk/hssqlppp/cabal.sandbox.config > Creating a new sandbox at /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal- > sandbox > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ time cabal install happy > Resolving dependencies... > Notice: installing into a sandbox located at > /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal-sandbox > Configuring mtl-2.2.1... > Building mtl-2.2.1... > Installed mtl-2.2.1 > Configuring happy-1.19.5... > Building happy-1.19.5... > Installed happy-1.19.5 > > real 0m18.442s > user 0m16.896s > sys 0m0.940s > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ time cabal install --only- > dependencies > Resolving dependencies... > Notice: installing into a sandbox located at > /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal-sandbox > Configuring old-locale-1.0.0.7... > Configuring syb-0.4.4... > Configuring text-1.2.1.1... > Building old-locale-1.0.0.7... > Building syb-0.4.4... > Building text-1.2.1.1... > Installed old-locale-1.0.0.7 > Configuring old-time-1.1.0.3... > Building old-time-1.1.0.3... > Installed syb-0.4.4 > Installed old-time-1.1.0.3 > Installed text-1.2.1.1 > Configuring hashable-1.2.3.2... > Configuring parsec-3.1.9... > Configuring polyparse-1.11... > Building hashable-1.2.3.2... > Building polyparse-1.11... > Building parsec-3.1.9... > Installed hashable-1.2.3.2 > Configuring scientific-0.3.3.8... > Configuring unordered-containers-0.2.5.1... > Building scientific-0.3.3.8... > Building unordered-containers-0.2.5.1... > Installed scientific-0.3.3.8 > Configuring attoparsec-0.12.1.6... > Installed parsec-3.1.9 > Building attoparsec-0.12.1.6... > Installed polyparse-1.11 > Configuring cpphs-1.19... > Installed unordered-containers-0.2.5.1 > Configuring uniplate-1.6.12... > Building cpphs-1.19... > Building uniplate-1.6.12... > Installed cpphs-1.19 > Configuring haskell-src-exts-1.16.0.1... > Installed uniplate-1.6.12 > Building haskell-src-exts-1.16.0.1... > Installed attoparsec-0.12.1.6 > Installed haskell-src-exts-1.16.0.1 > Configuring groom-0.1.2... > Building groom-0.1.2... > Installed groom-0.1.2 > > real 5m15.306s > user 6m16.976s > sys 0m5.476s > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ time cabal build > Package has never been configured. Configuring with default flags. If > this > fails, please run configure manually. > Resolving dependencies... > Configuring hssqlppp-0.5.18... > Building hssqlppp-0.5.18... > Preprocessing library hssqlppp-0.5.18... > [ 1 of 23] Compiling Database.HsSqlPpp.Parsing.ParseErrors ( > src/Database/HsSqlPpp/Parsing/ParseErrors.lhs, > dist/build/Database/HsSqlPpp/Parsing/ParseErrors.o ) > [ 2 of 23] Compiling Database.HsSqlPpp.Utils.Utils ( > src/Database/HsSqlPpp/Utils/Utils.lhs, > dist/build/Database/HsSqlPpp/Utils/Utils.o ) > > src/Database/HsSqlPpp/Utils/Utils.lhs:9:3: Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > [ 3 of 23] Compiling Database.HsSqlPpp.Internals.TypesInternal ( > src/Database/HsSqlPpp/Internals/TypesInternal.lhs, > dist/build/Database/HsSqlPpp/Internals/TypesInternal.o ) > [ 4 of 23] Compiling Database.HsSqlPpp.Types ( > src/Database/HsSqlPpp/Types.lhs, dist/build/Database/HsSqlPpp/Types.o ) > [ 5 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.OldTediousTypeUtils ( > src/Database/HsSqlPpp/Internals/TypeChecking/OldTediousTypeUtils.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/OldTediousTypeUtils.o > ) > [ 6 of 23] Compiling Database.HsSqlPpp.SqlDialect ( > src/Database/HsSqlPpp/SqlDialect.lhs, > dist/build/Database/HsSqlPpp/SqlDialect.o ) > [ 7 of 23] Compiling Database.HsSqlPpp.LexicalSyntax ( > src/Database/HsSqlPpp/LexicalSyntax.lhs, > dist/build/Database/HsSqlPpp/LexicalSyntax.o ) > [ 8 of 23] Compiling Database.HsSqlPpp.Internals.Catalog.CatalogInternal > ( src/Database/HsSqlPpp/Internals/Catalog/CatalogInternal.lhs, > dist/build/Database/HsSqlPpp/Internals/Catalog/CatalogInternal.o ) > [ 9 of 23] Compiling > Database.HsSqlPpp.Internals.Catalog.DefaultTemplate1Catalog ( > src/Database/HsSqlPpp/Internals/Catalog/DefaultTemplate1Catalog.lhs, > dist/build/Database/HsSqlPpp/Internals/Catalog/DefaultTemplate1Catalog.o > ) > [10 of 23] Compiling > Database.HsSqlPpp.Internals.Catalog.DefaultTSQLCatalog ( > src/Database/HsSqlPpp/Internals/Catalog/DefaultTSQLCatalog.lhs, > dist/build/Database/HsSqlPpp/Internals/Catalog/DefaultTSQLCatalog.o ) > [11 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.OldTypeConversion ( > src/Database/HsSqlPpp/Internals/TypeChecking/OldTypeConversion.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/OldTypeConversion.o ) > [12 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.SqlTypeConversion ( > src/Database/HsSqlPpp/Internals/TypeChecking/SqlTypeConversion.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/SqlTypeConversion.o ) > [13 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.TypeConversion ( > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.o ) > > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs:22:8: > Warning: > The export item ‘MatchAppLiteralList(..)’ suggests that > ‘MatchAppLiteralList’ has (in-scope) constructors or class methods, > but it has none > > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs:34:3: > Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs:43:3: > Warning: > The import of ‘Debug.Trace’ is redundant > except perhaps to import instances from ‘Debug.Trace’ > To import instances alone, use: import Debug.Trace() > [14 of 23] Compiling Database.HsSqlPpp.Internals.TypeChecking.Environment > ( src/Database/HsSqlPpp/Internals/TypeChecking/Environment.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/Environment.o ) > > src/Database/HsSqlPpp/Internals/TypeChecking/Environment.lhs:228:41: > Warning: > Defined but not used: ‘j’ > [15 of 23] Compiling Database.HsSqlPpp.Catalog ( > src/Database/HsSqlPpp/Catalog.lhs, dist/build/Database/HsSqlPpp/Catalog.o > ) > [16 of 23] Compiling Database.HsSqlPpp.Internals.AstInternal ( > src/Database/HsSqlPpp/Internals/AstInternal.hs, > dist/build/Database/HsSqlPpp/Internals/AstInternal.o ) > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:30: Warning: > Defined but not used: data constructor ‘Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:53: Warning: > Defined but not used: ‘cat_Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:90: Warning: > Defined but not used: ‘flags_Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:139: Warning: > Defined but not used: ‘imCast_Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:849:30: Warning: > Defined but not used: data constructor ‘Syn_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:849:53: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:849:110: Warning: > Defined but not used: ‘originalTree_Syn_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:853:1: Warning: > Defined but not used: ‘wrap_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:35: Warning: > Defined but not used: data constructor ‘Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:63: Warning: > Defined but not used: ‘cat_Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:105: > Warning: > Defined but not used: ‘flags_Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:159: > Warning: > Defined but not used: ‘imCast_Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1288:35: Warning: > Defined but not used: data constructor ‘Syn_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1288:63: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1288:130: > Warning: > Defined but not used: ‘originalTree_Syn_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1292:1: Warning: > Defined but not used: ‘wrap_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:29: Warning: > Defined but not used: data constructor ‘Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:51: Warning: > Defined but not used: ‘cat_Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:87: Warning: > Defined but not used: ‘flags_Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:135: > Warning: > Defined but not used: ‘imCast_Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1452:29: Warning: > Defined but not used: data constructor ‘Syn_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1452:51: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1452:106: > Warning: > Defined but not used: ‘originalTree_Syn_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1456:1: Warning: > Defined but not used: ‘wrap_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:33: Warning: > Defined but not used: data constructor ‘Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:59: Warning: > Defined but not used: ‘cat_Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:99: Warning: > Defined but not used: ‘flags_Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:151: > Warning: > Defined but not used: ‘imCast_Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1833:33: Warning: > Defined but not used: data constructor ‘Syn_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1833:59: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1833:122: > Warning: > Defined but not used: ‘originalTree_Syn_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1837:1: Warning: > Defined but not used: ‘wrap_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:32: Warning: > Defined but not used: data constructor ‘Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:57: Warning: > Defined but not used: ‘cat_Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:96: Warning: > Defined but not used: ‘flags_Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:147: > Warning: > Defined but not used: ‘imCast_Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2006:32: Warning: > Defined but not used: data constructor ‘Syn_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2006:57: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2006:118: > Warning: > Defined but not used: ‘originalTree_Syn_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2010:1: Warning: > Defined but not used: ‘wrap_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:23: Warning: > Defined but not used: data constructor ‘Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:39: Warning: > Defined but not used: ‘cat_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:69: Warning: > Defined but not used: ‘flags_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:111: > Warning: > Defined but not used: ‘imCast_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:154: > Warning: > Defined but not used: ‘tpe_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2321:23: Warning: > Defined but not used: data constructor ‘Syn_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2321:39: Warning: > Defined but not used: ‘annotatedTree_Syn_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2321:82: Warning: > Defined but not used: ‘originalTree_Syn_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2325:1: Warning: > Defined but not used: ‘wrap_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:25: Warning: > Defined but not used: data constructor ‘Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:43: Warning: > Defined but not used: ‘cat_Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:75: Warning: > Defined but not used: ‘flags_Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:119: > Warning: > Defined but not used: ‘imCast_Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2386:25: Warning: > Defined but not used: data constructor ‘Syn_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2386:43: Warning: > Defined but not used: ‘annotatedTree_Syn_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2386:90: Warning: > Defined but not used: ‘originalTree_Syn_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2390:1: Warning: > Defined but not used: ‘wrap_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:29: Warning: > Defined but not used: data constructor ‘Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:51: Warning: > Defined but not used: ‘cat_Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:87: Warning: > Defined but not used: ‘flags_Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:135: > Warning: > Defined but not used: ‘imCast_Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2594:29: Warning: > Defined but not used: data constructor ‘Syn_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2594:51: Warning: > Defined but not used: ‘annotatedTree_Syn_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2594:106: > Warning: > Defined but not used: ‘originalTree_Syn_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2598:1: Warning: > Defined but not used: ‘wrap_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:45: Warning: > Defined but not used: > data constructor ‘Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:83: Warning: > Defined but not used: ‘cat_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:135: > Warning: > Defined but not used: > ‘downEnv_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:195: > Warning: > Defined but not used: ‘flags_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:259: > Warning: > Defined but not used: ‘imCast_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:324: > Warning: > Defined but not used: > ‘thenExpectedType_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:399: > Warning: > Defined but not used: > ‘whenExpectedType_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:45: Warning: > Defined but not used: > data constructor ‘Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:83: Warning: > Defined but not used: > ‘annotatedTree_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:170: > Warning: > Defined but not used: > ‘originalTree_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:256: > Warning: > Defined but not used: > ‘thenType_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:323: > Warning: > Defined but not used: > ‘upTypes_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:391: > Warning: > Defined but not used: > ‘whenTypes_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2760:1: Warning: > Defined but not used: ‘wrap_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:49: Warning: > Defined but not used: > data constructor ‘Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:91: Warning: > Defined but not used: > ‘cat_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:147: > Warning: > Defined but not used: > ‘downEnv_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:211: > Warning: > Defined but not used: > ‘flags_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:279: > Warning: > Defined but not used: > ‘imCast_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:348: > Warning: > Defined but not used: > ‘thenExpectedType_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:427: > Warning: > Defined but not used: > ‘whenExpectedType_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:49: Warning: > Defined but not used: > data constructor ‘Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:91: Warning: > Defined but not used: > ‘annotatedTree_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:186: > Warning: > Defined but not used: > ‘originalTree_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:280: > Warning: > Defined but not used: > ‘thenTypes_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:354: > Warning: > Defined but not used: > ‘upTypes_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:426: > Warning: > Defined but not used: > ‘whenTypes_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2963:1: Warning: > Defined but not used: ‘wrap_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:23: Warning: > Defined but not used: data constructor ‘Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:39: Warning: > Defined but not used: ‘cat_Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:69: Warning: > Defined but not used: ‘flags_Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:111: > Warning: > Defined but not used: ‘imCast_Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3244:23: Warning: > Defined but not used: data constructor ‘Syn_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3244:39: Warning: > Defined but not used: ‘annotatedTree_Syn_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3244:82: Warning: > Defined but not used: ‘originalTree_Syn_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3248:1: Warning: > Defined but not used: ‘wrap_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:27: Warning: > Defined but not used: data constructor ‘Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:47: Warning: > Defined but not used: ‘cat_Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:81: Warning: > Defined but not used: ‘flags_Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:127: > Warning: > Defined but not used: ‘imCast_Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3637:27: Warning: > Defined but not used: data constructor ‘Syn_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3637:47: Warning: > Defined but not used: ‘annotatedTree_Syn_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3637:98: Warning: > Defined but not used: ‘originalTree_Syn_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3641:1: Warning: > Defined but not used: ‘wrap_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:19: Warning: > Defined but not used: data constructor ‘Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:31: Warning: > Defined but not used: ‘cat_Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:57: Warning: > Defined but not used: ‘flags_Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:95: Warning: > Defined but not used: ‘imCast_Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3800:19: Warning: > Defined but not used: data constructor ‘Syn_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3800:31: Warning: > Defined but not used: ‘annotatedTree_Syn_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3800:66: Warning: > Defined but not used: ‘originalTree_Syn_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3804:1: Warning: > Defined but not used: ‘wrap_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:19: Warning: > Defined but not used: data constructor ‘Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:31: Warning: > Defined but not used: ‘cat_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:57: Warning: > Defined but not used: ‘downEnv_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:91: Warning: > Defined but not used: ‘expectedCast_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:123: > Warning: > Defined but not used: ‘expectedType_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:168: > Warning: > Defined but not used: ‘flags_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:206: > Warning: > Defined but not used: ‘imCast_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:19: Warning: > Defined but not used: data constructor ‘Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:31: Warning: > Defined but not used: ‘annotatedTree_Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:66: Warning: > Defined but not used: ‘listType_Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:120: > Warning: > Defined but not used: ‘originalTree_Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4042:1: Warning: > Defined but not used: ‘wrap_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:21: Warning: > Defined but not used: data constructor ‘Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:35: Warning: > Defined but not used: ‘cat_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:63: Warning: > Defined but not used: ‘downEnv_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:99: Warning: > Defined but not used: ‘flags_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:139: > Warning: > Defined but not used: ‘imCast_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4348:21: Warning: > Defined but not used: data constructor ‘Syn_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4348:35: Warning: > Defined but not used: ‘annotatedTree_Syn_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4348:74: Warning: > Defined but not used: ‘originalTree_Syn_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4352:1: Warning: > Defined but not used: ‘wrap_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:26: Warning: > Defined but not used: data constructor ‘Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:45: Warning: > Defined but not used: ‘cat_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:78: Warning: > Defined but not used: ‘downEnv_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:119: > Warning: > Defined but not used: ‘flags_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:164: > Warning: > Defined but not used: ‘imCast_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4587:26: Warning: > Defined but not used: data constructor ‘Syn_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4587:45: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4587:94: Warning: > Defined but not used: ‘originalTree_Syn_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4591:1: Warning: > Defined but not used: ‘wrap_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4720:1: Warning: > Defined but not used: ‘sem_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4726:35: Warning: > Defined but not used: data constructor ‘Inh_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4727:35: Warning: > Defined but not used: data constructor ‘Syn_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4731:1: Warning: > Defined but not used: ‘wrap_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4732:10: Warning: > This pattern-binding binds no variables: () = sem > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4736:1: Warning: > Defined but not used: ‘sem_MaybeNameComponentList_Just’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4736:33: Warning: > Defined but not used: ‘just_’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4740:1: Warning: > Defined but not used: ‘sem_MaybeNameComponentList_Nothing’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:28: Warning: > Defined but not used: data constructor ‘Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:49: Warning: > Defined but not used: ‘cat_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:84: Warning: > Defined but not used: ‘downEnv_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:127: > Warning: > Defined but not used: ‘expectedCast_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:168: > Warning: > Defined but not used: ‘expectedType_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:222: > Warning: > Defined but not used: ‘flags_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:269: > Warning: > Defined but not used: ‘imCast_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:28: Warning: > Defined but not used: data constructor ‘Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:49: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:102: > Warning: > Defined but not used: ‘originalTree_Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:154: > Warning: > Defined but not used: ‘upType_Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4789:1: Warning: > Defined but not used: ‘wrap_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:28: Warning: > Defined but not used: data constructor ‘Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:49: Warning: > Defined but not used: ‘cat_Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:84: Warning: > Defined but not used: ‘flags_Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:131: > Warning: > Defined but not used: ‘imCast_Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4960:28: Warning: > Defined but not used: data constructor ‘Syn_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4960:49: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4960:102: > Warning: > Defined but not used: ‘originalTree_Syn_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4964:1: Warning: > Defined but not used: ‘wrap_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:35: Warning: > Defined but not used: data constructor ‘Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:63: Warning: > Defined but not used: ‘cat_Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:105: > Warning: > Defined but not used: ‘flags_Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:159: > Warning: > Defined but not used: ‘imCast_Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5116:35: Warning: > Defined but not used: data constructor ‘Syn_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5116:63: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5116:130: > Warning: > Defined but not used: ‘originalTree_Syn_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5120:1: Warning: > Defined but not used: ‘wrap_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:17: Warning: > Defined but not used: data constructor ‘Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:27: Warning: > Defined but not used: ‘cat_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:51: Warning: > Defined but not used: ‘flags_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:87: Warning: > Defined but not used: ‘imCast_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:124: > Warning: > Defined but not used: ‘tpe_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5254:17: Warning: > Defined but not used: data constructor ‘Syn_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5254:27: Warning: > Defined but not used: ‘annotatedTree_Syn_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5254:58: Warning: > Defined but not used: ‘originalTree_Syn_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5258:1: Warning: > Defined but not used: ‘wrap_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5374:1: Warning: > Defined but not used: ‘sem_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5378:30: Warning: > Defined but not used: data constructor ‘Inh_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5379:30: Warning: > Defined but not used: data constructor ‘Syn_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5383:1: Warning: > Defined but not used: ‘wrap_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5384:10: Warning: > This pattern-binding binds no variables: () = sem > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5389:1: Warning: > Defined but not used: ‘sem_NameComponentList_Cons’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5389:28: Warning: > Defined but not used: ‘hd_’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5389:32: Warning: > Defined but not used: ‘tl_’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5393:1: Warning: > Defined but not used: ‘sem_NameComponentList_Nil’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:33: Warning: > Defined but not used: data constructor ‘Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:59: Warning: > Defined but not used: ‘cat_Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:99: Warning: > Defined but not used: ‘flags_Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:151: > Warning: > Defined but not used: ‘imCast_Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5426:33: Warning: > Defined but not used: data constructor ‘Syn_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5426:59: Warning: > Defined but not used: ‘annotatedTree_Syn_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5426:122: > Warning: > Defined but not used: ‘originalTree_Syn_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5430:1: Warning: > Defined but not used: ‘wrap_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:37: Warning: > Defined but not used: > data constructor ‘Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:67: Warning: > Defined but not used: ‘cat_Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:111: > Warning: > Defined but not used: ‘flags_Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:167: > Warning: > Defined but not used: ‘imCast_Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5558:37: Warning: > Defined but not used: > data constructor ‘Syn_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5558:67: Warning: > Defined but not used: ‘annotatedTree_Syn_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5558:138: > Warning: > Defined but not used: ‘originalTree_Syn_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5562:1: Warning: > Defined but not used: ‘wrap_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:19: Warning: > Defined but not used: data constructor ‘Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:31: Warning: > Defined but not used: ‘cat_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:57: Warning: > Defined but not used: ‘downEnv_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:91: Warning: > Defined but not used: ‘flags_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:129: > Warning: > Defined but not used: ‘imCast_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5718:19: Warning: > Defined but not used: data constructor ‘Syn_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5718:31: Warning: > Defined but not used: ‘annotatedTree_Syn_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5718:66: Warning: > Defined but not used: ‘originalTree_Syn_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5722:1: Warning: > Defined but not used: ‘wrap_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:21: Warning: > Defined but not used: data constructor ‘Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:35: Warning: > Defined but not used: ‘cat_Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:63: Warning: > Defined but not used: ‘flags_Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:103: > Warning: > Defined but not used: ‘imCast_Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5865:21: Warning: > Defined but not used: data constructor ‘Syn_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5865:35: Warning: > Defined but not used: ‘annotatedTree_Syn_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5865:74: Warning: > Defined but not used: ‘originalTree_Syn_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5869:1: Warning: > Defined but not used: ‘wrap_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:25: Warning: > Defined but not used: data constructor ‘Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:43: Warning: > Defined but not used: ‘cat_Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:75: Warning: > Defined but not used: ‘flags_Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:119: > Warning: > Defined but not used: ‘imCast_Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6091:25: Warning: > Defined but not used: data constructor ‘Syn_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6091:43: Warning: > Defined but not used: ‘annotatedTree_Syn_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6091:90: Warning: > Defined but not used: ‘originalTree_Syn_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6095:1: Warning: > Defined but not used: ‘wrap_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:22: Warning: > Defined but not used: data constructor ‘Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:37: Warning: > Defined but not used: ‘cat_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:66: Warning: > Defined but not used: ‘expectedType_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:116: > Warning: > Defined but not used: ‘flags_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:157: > Warning: > Defined but not used: ‘imCast_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:199: > Warning: > Defined but not used: ‘outerDownEnv_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:22: Warning: > Defined but not used: data constructor ‘Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:37: Warning: > Defined but not used: ‘annotatedTree_Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:78: Warning: > Defined but not used: ‘originalTree_Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:118: > Warning: > Defined but not used: ‘upType_Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6329:1: Warning: > Defined but not used: ‘wrap_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7235:58: Warning: > Defined but not used: ‘originalTree_Syn_Root’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:26: Warning: > Defined but not used: data constructor ‘Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:45: Warning: > Defined but not used: ‘cat_Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:78: Warning: > Defined but not used: ‘flags_Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:123: > Warning: > Defined but not used: ‘imCast_Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7390:26: Warning: > Defined but not used: data constructor ‘Syn_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7390:45: Warning: > Defined but not used: ‘annotatedTree_Syn_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7390:94: Warning: > Defined but not used: ‘originalTree_Syn_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7394:1: Warning: > Defined but not used: ‘wrap_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:30: Warning: > Defined but not used: data constructor ‘Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:53: Warning: > Defined but not used: ‘cat_Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:90: Warning: > Defined but not used: ‘flags_Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:139: > Warning: > Defined but not used: ‘imCast_Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7979:30: Warning: > Defined but not used: data constructor ‘Syn_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7979:53: Warning: > Defined but not used: ‘annotatedTree_Syn_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7979:110: > Warning: > Defined but not used: ‘originalTree_Syn_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7983:1: Warning: > Defined but not used: ‘wrap_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:23: Warning: > Defined but not used: data constructor ‘Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:39: Warning: > Defined but not used: ‘cat_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:69: Warning: > Defined but not used: ‘downEnv_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:107: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:143: > Warning: > Defined but not used: ‘expectedType_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:192: > Warning: > Defined but not used: ‘flags_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:234: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:23: Warning: > Defined but not used: data constructor ‘Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:39: Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:82: Warning: > Defined but not used: ‘colExprs_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:156: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:198: > Warning: > Defined but not used: ‘upType_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8487:1: Warning: > Defined but not used: ‘wrap_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:36: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:65: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:108: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:159: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:214: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13384:36: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13384:65: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13384:134: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13388:1: Warning: > Defined but not used: ‘wrap_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:40: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:73: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:120: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:175: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:234: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13510:40: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13510:73: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13510:150: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13514:1: Warning: > Defined but not used: ‘wrap_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:27: > Warning: > Defined but not used: data constructor ‘Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:47: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:81: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:123: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:163: > Warning: > Defined but not used: ‘expectedTypes_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:213: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:259: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:27: > Warning: > Defined but not used: data constructor ‘Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:47: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:98: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:148: > Warning: > Defined but not used: ‘upTypes_Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13694:1: Warning: > Defined but not used: ‘wrap_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:31: > Warning: > Defined but not used: data constructor ‘Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:55: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:93: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:139: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:183: > Warning: > Defined but not used: ‘expectedType_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:242: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:292: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:31: > Warning: > Defined but not used: data constructor ‘Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:55: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:114: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:172: > Warning: > Defined but not used: ‘upType_Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13919:1: Warning: > Defined but not used: ‘wrap_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:44: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:81: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:132: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:195: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14140:44: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14140:81: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14140:166: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14144:1: Warning: > Defined but not used: ‘wrap_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:48: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:89: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:144: > Warning: > Defined but not used: > ‘flags_Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:211: > Warning: > Defined but not used: > ‘imCast_Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14287:48: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14287:89: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14287:182: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14291:1: Warning: > Defined but not used: ‘wrap_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14440:98: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprRoot’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:40: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:73: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:120: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:179: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14558:40: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14558:73: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14558:150: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14562:1: Warning: > Defined but not used: ‘wrap_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:44: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:81: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:132: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:195: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14706:44: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14706:81: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14706:166: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14710:1: Warning: > Defined but not used: ‘wrap_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:37: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:67: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:111: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:161: > Warning: > Defined but not used: ‘expectedType_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:226: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:282: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:37: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:67: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:138: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:208: > Warning: > Defined but not used: ‘upType_Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14872:1: Warning: > Defined but not used: ‘wrap_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:23: > Warning: > Defined but not used: data constructor ‘Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:39: > Warning: > Defined but not used: ‘cat_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:69: > Warning: > Defined but not used: ‘downEnv_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:107: > Warning: > Defined but not used: ‘expectedCast_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:143: > Warning: > Defined but not used: ‘expectedType_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:192: > Warning: > Defined but not used: ‘flags_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:234: > Warning: > Defined but not used: ‘imCast_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:23: > Warning: > Defined but not used: data constructor ‘Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:39: > Warning: > Defined but not used: ‘annotatedTree_Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:82: > Warning: > Defined but not used: ‘colExprs_Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:156: > Warning: > Defined but not used: ‘originalTree_Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15099:1: Warning: > Defined but not used: ‘wrap_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:27: > Warning: > Defined but not used: data constructor ‘Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:47: > Warning: > Defined but not used: ‘cat_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:81: > Warning: > Defined but not used: ‘downEnv_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:123: > Warning: > Defined but not used: ‘expectedCast_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:163: > Warning: > Defined but not used: ‘expectedType_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:218: > Warning: > Defined but not used: ‘flags_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:264: > Warning: > Defined but not used: ‘imCast_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:27: > Warning: > Defined but not used: data constructor ‘Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:47: > Warning: > Defined but not used: ‘annotatedTree_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:98: > Warning: > Defined but not used: ‘colExprs_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:176: > Warning: > Defined but not used: ‘originalTree_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:226: > Warning: > Defined but not used: ‘upEnv_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:266: > Warning: > Defined but not used: ‘upType_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15408:1: Warning: > Defined but not used: ‘wrap_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:23: > Warning: > Defined but not used: data constructor ‘Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:39: > Warning: > Defined but not used: ‘cat_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:69: > Warning: > Defined but not used: ‘downEnv_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:107: > Warning: > Defined but not used: ‘expectedCast_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:143: > Warning: > Defined but not used: ‘expectedType_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:194: > Warning: > Defined but not used: ‘flags_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:236: > Warning: > Defined but not used: ‘imCast_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:23: > Warning: > Defined but not used: data constructor ‘Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:39: > Warning: > Defined but not used: ‘annotatedTree_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:82: > Warning: > Defined but not used: ‘colExprs_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:156: > Warning: > Defined but not used: ‘originalTree_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:198: > Warning: > Defined but not used: ‘upEnv_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:234: > Warning: > Defined but not used: ‘upType_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15693:1: Warning: > Defined but not used: ‘wrap_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:22: > Warning: > Defined but not used: data constructor ‘Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:37: > Warning: > Defined but not used: ‘cat_Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:66: > Warning: > Defined but not used: ‘flags_Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:107: > Warning: > Defined but not used: ‘imCast_Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15877:22: > Warning: > Defined but not used: data constructor ‘Syn_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15877:37: > Warning: > Defined but not used: ‘annotatedTree_Syn_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15877:78: > Warning: > Defined but not used: ‘originalTree_Syn_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15881:1: Warning: > Defined but not used: ‘wrap_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:26: > Warning: > Defined but not used: data constructor ‘Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:45: > Warning: > Defined but not used: ‘cat_Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:78: > Warning: > Defined but not used: ‘flags_Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:123: > Warning: > Defined but not used: ‘imCast_Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16148:26: > Warning: > Defined but not used: data constructor ‘Syn_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16148:45: > Warning: > Defined but not used: ‘annotatedTree_Syn_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16148:94: > Warning: > Defined but not used: ‘originalTree_Syn_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16152:1: Warning: > Defined but not used: ‘wrap_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:22: > Warning: > Defined but not used: data constructor ‘Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:37: > Warning: > Defined but not used: ‘cat_Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:66: > Warning: > Defined but not used: ‘flags_Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:107: > Warning: > Defined but not used: ‘imCast_Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16863:22: > Warning: > Defined but not used: data constructor ‘Syn_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16863:37: > Warning: > Defined but not used: ‘annotatedTree_Syn_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16863:78: > Warning: > Defined but not used: ‘originalTree_Syn_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16867:1: Warning: > Defined but not used: ‘wrap_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:26: > Warning: > Defined but not used: data constructor ‘Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:45: > Warning: > Defined but not used: ‘cat_Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:78: > Warning: > Defined but not used: ‘flags_Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:123: > Warning: > Defined but not used: ‘imCast_Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23093:26: > Warning: > Defined but not used: data constructor ‘Syn_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23093:45: > Warning: > Defined but not used: ‘annotatedTree_Syn_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23093:94: > Warning: > Defined but not used: ‘originalTree_Syn_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23097:1: Warning: > Defined but not used: ‘wrap_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:30: > Warning: > Defined but not used: data constructor ‘Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:53: > Warning: > Defined but not used: ‘cat_Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:90: > Warning: > Defined but not used: ‘flags_Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:139: > Warning: > Defined but not used: ‘imCast_Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23249:30: > Warning: > Defined but not used: data constructor ‘Syn_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23249:53: > Warning: > Defined but not used: ‘annotatedTree_Syn_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23249:110: > Warning: > Defined but not used: ‘originalTree_Syn_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23253:1: Warning: > Defined but not used: ‘wrap_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:21: > Warning: > Defined but not used: data constructor ‘Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:35: > Warning: > Defined but not used: ‘cat_Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:63: > Warning: > Defined but not used: ‘flags_Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:103: > Warning: > Defined but not used: ‘imCast_Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:21: > Warning: > Defined but not used: data constructor ‘Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:35: > Warning: > Defined but not used: ‘annotatedTree_Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:74: > Warning: > Defined but not used: ‘originalTree_Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:112: > Warning: > Defined but not used: ‘upEnv_Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23434:1: Warning: > Defined but not used: ‘wrap_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:25: > Warning: > Defined but not used: data constructor ‘Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:43: > Warning: > Defined but not used: ‘cat_Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:75: > Warning: > Defined but not used: ‘flags_Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:119: > Warning: > Defined but not used: ‘imCast_Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:25: > Warning: > Defined but not used: data constructor ‘Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:43: > Warning: > Defined but not used: ‘annotatedTree_Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:90: > Warning: > Defined but not used: ‘originalTree_Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:136: > Warning: > Defined but not used: ‘upEnv_Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24455:1: Warning: > Defined but not used: ‘wrap_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:29: > Warning: > Defined but not used: data constructor ‘Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:51: > Warning: > Defined but not used: ‘cat_Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:87: > Warning: > Defined but not used: ‘flags_Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:135: > Warning: > Defined but not used: ‘imCast_Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24626:29: > Warning: > Defined but not used: data constructor ‘Syn_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24626:51: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24626:106: > Warning: > Defined but not used: ‘originalTree_Syn_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24630:1: Warning: > Defined but not used: ‘wrap_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:33: > Warning: > Defined but not used: data constructor ‘Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:59: > Warning: > Defined but not used: ‘cat_Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:99: > Warning: > Defined but not used: ‘flags_Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:151: > Warning: > Defined but not used: ‘imCast_Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24760:33: > Warning: > Defined but not used: data constructor ‘Syn_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24760:59: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24760:122: > Warning: > Defined but not used: ‘originalTree_Syn_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24764:1: Warning: > Defined but not used: ‘wrap_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:21: > Warning: > Defined but not used: data constructor ‘Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:35: > Warning: > Defined but not used: ‘cat_Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:63: > Warning: > Defined but not used: ‘flags_Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:103: > Warning: > Defined but not used: ‘imCast_Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:21: > Warning: > Defined but not used: data constructor ‘Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:35: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:74: > Warning: > Defined but not used: ‘namedType_Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:118: > Warning: > Defined but not used: ‘originalTree_Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24963:1: Warning: > Defined but not used: ‘wrap_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:25: > Warning: > Defined but not used: data constructor ‘Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:43: > Warning: > Defined but not used: ‘cat_Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:75: > Warning: > Defined but not used: ‘flags_Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:119: > Warning: > Defined but not used: ‘imCast_Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25557:25: > Warning: > Defined but not used: data constructor ‘Syn_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25557:43: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25557:90: > Warning: > Defined but not used: ‘originalTree_Syn_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25561:1: Warning: > Defined but not used: ‘wrap_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:19: > Warning: > Defined but not used: data constructor ‘Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:31: > Warning: > Defined but not used: ‘cat_Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:57: > Warning: > Defined but not used: ‘flags_Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:95: > Warning: > Defined but not used: ‘imCast_Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25734:19: > Warning: > Defined but not used: data constructor ‘Syn_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25734:31: > Warning: > Defined but not used: ‘annotatedTree_Syn_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25734:66: > Warning: > Defined but not used: ‘originalTree_Syn_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25738:1: Warning: > Defined but not used: ‘wrap_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:23: > Warning: > Defined but not used: data constructor ‘Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:39: > Warning: > Defined but not used: ‘cat_Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:69: > Warning: > Defined but not used: ‘flags_Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:111: > Warning: > Defined but not used: ‘imCast_Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26035:23: > Warning: > Defined but not used: data constructor ‘Syn_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26035:39: > Warning: > Defined but not used: ‘annotatedTree_Syn_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26035:82: > Warning: > Defined but not used: ‘originalTree_Syn_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26039:1: Warning: > Defined but not used: ‘wrap_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:22: > Warning: > Defined but not used: data constructor ‘Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:37: > Warning: > Defined but not used: ‘cat_Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:66: > Warning: > Defined but not used: ‘flags_Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:107: > Warning: > Defined but not used: ‘imCast_Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26191:22: > Warning: > Defined but not used: data constructor ‘Syn_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26191:37: > Warning: > Defined but not used: ‘annotatedTree_Syn_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26191:78: > Warning: > Defined but not used: ‘originalTree_Syn_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26195:1: Warning: > Defined but not used: ‘wrap_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:26: > Warning: > Defined but not used: data constructor ‘Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:45: > Warning: > Defined but not used: ‘cat_Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:78: > Warning: > Defined but not used: ‘flags_Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:123: > Warning: > Defined but not used: ‘imCast_Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26340:26: > Warning: > Defined but not used: data constructor ‘Syn_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26340:45: > Warning: > Defined but not used: ‘annotatedTree_Syn_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26340:94: > Warning: > Defined but not used: ‘originalTree_Syn_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26344:1: Warning: > Defined but not used: ‘wrap_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:75:38: > Warning: > Fields of ‘Inh_ScalarExprRoot’ not initialised: > downEnv_Inh_ScalarExprRoot > In the second argument of ‘wrap_ScalarExprRoot’, namely > ‘Inh_ScalarExprRoot > {cat_Inh_ScalarExprRoot = cat, flags_Inh_ScalarExprRoot = f}’ > In the first argument of ‘annotatedTree_Syn_ScalarExprRoot’, namely > ‘(wrap_ScalarExprRoot > t > (Inh_ScalarExprRoot > {cat_Inh_ScalarExprRoot = cat, flags_Inh_ScalarExprRoot = > f}))’ > In the expression: > (annotatedTree_Syn_ScalarExprRoot > (wrap_ScalarExprRoot > t > (Inh_ScalarExprRoot > {cat_Inh_ScalarExprRoot = cat, flags_Inh_ScalarExprRoot = > f}))) > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:260:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:261:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:262:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:268:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:269:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:270:1: > Warning: > Tab character > > src/Database/HsSqlPpp/Internals/AstInternal.hs:119:1: Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > [17 of 23] Compiling Database.HsSqlPpp.Annotation ( > src/Database/HsSqlPpp/Annotation.lhs, > dist/build/Database/HsSqlPpp/Annotation.o ) > [18 of 23] Compiling Database.HsSqlPpp.TypeChecker ( > src/Database/HsSqlPpp/TypeChecker.lhs, > dist/build/Database/HsSqlPpp/TypeChecker.o ) > [19 of 23] Compiling Database.HsSqlPpp.Ast ( > src/Database/HsSqlPpp/Ast.lhs, dist/build/Database/HsSqlPpp/Ast.o ) > [20 of 23] Compiling Database.HsSqlPpp.Parsing.ParserInternal ( > src/Database/HsSqlPpp/Parsing/ParserInternal.lhs, > dist/build/Database/HsSqlPpp/Parsing/ParserInternal.o ) > > src/Database/HsSqlPpp/Parsing/ParserInternal.lhs:38:3: Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > [21 of 23] Compiling Database.HsSqlPpp.Parser ( > src/Database/HsSqlPpp/Parser.lhs, dist/build/Database/HsSqlPpp/Parser.o ) > [22 of 23] Compiling Database.HsSqlPpp.Utility ( > src/Database/HsSqlPpp/Utility.lhs, dist/build/Database/HsSqlPpp/Utility.o > ) > [23 of 23] Compiling Database.HsSqlPpp.Pretty ( > src/Database/HsSqlPpp/Pretty.lhs, dist/build/Database/HsSqlPpp/Pretty.o ) > > src/Database/HsSqlPpp/Pretty.lhs:103:3: Warning: > Pattern match(es) are non-exhaustive > In an equation for ‘statement’: > Patterns not matched: > _ _ _ (CreateUser _ _ _) > _ _ _ (CreateLogin _ _ _) > _ _ _ (AlterUser _ _ _) > _ _ _ (AlterLogin _ _ _) > > src/Database/HsSqlPpp/Pretty.lhs:781:31: Warning: > Pattern match(es) are overlapped > In a case alternative: _ -> ... > In-place registering hssqlppp-0.5.18... > > real 1m20.449s > user 2m5.040s > sys 0m48.504s > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ ghc --version > The Glorious Glasgow Haskell Compilation System, version 7.10.1.20150612 > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ cabal clean > cleaning... > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ cabal sandbox delete > Deleting the sandbox located at > /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal-sandbox > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ cabal sandbox init > Writing a default package environment file to > /home/jake/wd/hssqlppp/trunk/hssqlppp/cabal.sandbox.config > Creating a new sandbox at /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal- > sandbox > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ time cabal install happy > Resolving dependencies... > Notice: installing into a sandbox located at > /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal-sandbox > Configuring mtl-2.2.1... > Building mtl-2.2.1... > Installed mtl-2.2.1 > Configuring happy-1.19.5... > Building happy-1.19.5... > Installed happy-1.19.5 > > real 0m17.994s > user 0m16.496s > sys 0m0.852s > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ time cabal install --only- > dependencies > Resolving dependencies... > Notice: installing into a sandbox located at > /home/jake/wd/hssqlppp/trunk/hssqlppp/.cabal-sandbox > Configuring old-locale-1.0.0.7... > Configuring syb-0.4.4... > Configuring text-1.2.1.1... > Building syb-0.4.4... > Building old-locale-1.0.0.7... > Building text-1.2.1.1... > Installed old-locale-1.0.0.7 > Configuring old-time-1.1.0.3... > Building old-time-1.1.0.3... > Installed syb-0.4.4 > Installed old-time-1.1.0.3 > Installed text-1.2.1.1 > Configuring hashable-1.2.3.2... > Configuring parsec-3.1.9... > Configuring polyparse-1.11... > Building parsec-3.1.9... > Building hashable-1.2.3.2... > Building polyparse-1.11... > Installed hashable-1.2.3.2 > Configuring scientific-0.3.3.8... > Configuring unordered-containers-0.2.5.1... > Building scientific-0.3.3.8... > Building unordered-containers-0.2.5.1... > Installed scientific-0.3.3.8 > Configuring attoparsec-0.12.1.6... > Installed parsec-3.1.9 > Building attoparsec-0.12.1.6... > Installed polyparse-1.11 > Configuring cpphs-1.19... > Installed unordered-containers-0.2.5.1 > Configuring uniplate-1.6.12... > Building cpphs-1.19... > Building uniplate-1.6.12... > Installed cpphs-1.19 > Configuring haskell-src-exts-1.16.0.1... > Installed uniplate-1.6.12 > Building haskell-src-exts-1.16.0.1... > Installed attoparsec-0.12.1.6 > Installed haskell-src-exts-1.16.0.1 > Configuring groom-0.1.2... > Building groom-0.1.2... > Installed groom-0.1.2 > > real 4m42.127s > user 5m45.548s > sys 0m5.040s > > jake at debian:~/wd/hssqlppp/trunk/hssqlppp$ time cabal build > Package has never been configured. Configuring with default flags. If > this > fails, please run configure manually. > Resolving dependencies... > Configuring hssqlppp-0.5.18... > Building hssqlppp-0.5.18... > Preprocessing library hssqlppp-0.5.18... > [ 1 of 23] Compiling Database.HsSqlPpp.Parsing.ParseErrors ( > src/Database/HsSqlPpp/Parsing/ParseErrors.lhs, > dist/build/Database/HsSqlPpp/Parsing/ParseErrors.o ) > [ 2 of 23] Compiling Database.HsSqlPpp.Utils.Utils ( > src/Database/HsSqlPpp/Utils/Utils.lhs, > dist/build/Database/HsSqlPpp/Utils/Utils.o ) > > src/Database/HsSqlPpp/Utils/Utils.lhs:9:3: Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > [ 3 of 23] Compiling Database.HsSqlPpp.Internals.TypesInternal ( > src/Database/HsSqlPpp/Internals/TypesInternal.lhs, > dist/build/Database/HsSqlPpp/Internals/TypesInternal.o ) > [ 4 of 23] Compiling Database.HsSqlPpp.Types ( > src/Database/HsSqlPpp/Types.lhs, dist/build/Database/HsSqlPpp/Types.o ) > [ 5 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.OldTediousTypeUtils ( > src/Database/HsSqlPpp/Internals/TypeChecking/OldTediousTypeUtils.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/OldTediousTypeUtils.o > ) > [ 6 of 23] Compiling Database.HsSqlPpp.SqlDialect ( > src/Database/HsSqlPpp/SqlDialect.lhs, > dist/build/Database/HsSqlPpp/SqlDialect.o ) > [ 7 of 23] Compiling Database.HsSqlPpp.LexicalSyntax ( > src/Database/HsSqlPpp/LexicalSyntax.lhs, > dist/build/Database/HsSqlPpp/LexicalSyntax.o ) > [ 8 of 23] Compiling Database.HsSqlPpp.Internals.Catalog.CatalogInternal > ( src/Database/HsSqlPpp/Internals/Catalog/CatalogInternal.lhs, > dist/build/Database/HsSqlPpp/Internals/Catalog/CatalogInternal.o ) > [ 9 of 23] Compiling > Database.HsSqlPpp.Internals.Catalog.DefaultTemplate1Catalog ( > src/Database/HsSqlPpp/Internals/Catalog/DefaultTemplate1Catalog.lhs, > dist/build/Database/HsSqlPpp/Internals/Catalog/DefaultTemplate1Catalog.o > ) > [10 of 23] Compiling > Database.HsSqlPpp.Internals.Catalog.DefaultTSQLCatalog ( > src/Database/HsSqlPpp/Internals/Catalog/DefaultTSQLCatalog.lhs, > dist/build/Database/HsSqlPpp/Internals/Catalog/DefaultTSQLCatalog.o ) > [11 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.OldTypeConversion ( > src/Database/HsSqlPpp/Internals/TypeChecking/OldTypeConversion.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/OldTypeConversion.o ) > [12 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.SqlTypeConversion ( > src/Database/HsSqlPpp/Internals/TypeChecking/SqlTypeConversion.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/SqlTypeConversion.o ) > [13 of 23] Compiling > Database.HsSqlPpp.Internals.TypeChecking.TypeConversion ( > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.o ) > > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs:22:8: > Warning: > The export item ‘MatchAppLiteralList(..)’ suggests that > ‘MatchAppLiteralList’ has (in-scope) constructors or class methods, > but it has none > > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs:34:3: > Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > > src/Database/HsSqlPpp/Internals/TypeChecking/TypeConversion.lhs:43:3: > Warning: > The import of ‘Debug.Trace’ is redundant > except perhaps to import instances from ‘Debug.Trace’ > To import instances alone, use: import Debug.Trace() > [14 of 23] Compiling Database.HsSqlPpp.Internals.TypeChecking.Environment > ( src/Database/HsSqlPpp/Internals/TypeChecking/Environment.lhs, > dist/build/Database/HsSqlPpp/Internals/TypeChecking/Environment.o ) > > src/Database/HsSqlPpp/Internals/TypeChecking/Environment.lhs:228:41: > Warning: > Defined but not used: ‘j’ > [15 of 23] Compiling Database.HsSqlPpp.Catalog ( > src/Database/HsSqlPpp/Catalog.lhs, dist/build/Database/HsSqlPpp/Catalog.o > ) > [16 of 23] Compiling Database.HsSqlPpp.Internals.AstInternal ( > src/Database/HsSqlPpp/Internals/AstInternal.hs, > dist/build/Database/HsSqlPpp/Internals/AstInternal.o ) > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:30: Warning: > Defined but not used: data constructor ‘Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:53: Warning: > Defined but not used: ‘cat_Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:90: Warning: > Defined but not used: ‘flags_Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:848:139: Warning: > Defined but not used: ‘imCast_Inh_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:849:30: Warning: > Defined but not used: data constructor ‘Syn_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:849:53: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:849:110: Warning: > Defined but not used: ‘originalTree_Syn_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:853:1: Warning: > Defined but not used: ‘wrap_AlterColumnAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:35: Warning: > Defined but not used: data constructor ‘Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:63: Warning: > Defined but not used: ‘cat_Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:105: > Warning: > Defined but not used: ‘flags_Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1287:159: > Warning: > Defined but not used: ‘imCast_Inh_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1288:35: Warning: > Defined but not used: data constructor ‘Syn_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1288:63: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1288:130: > Warning: > Defined but not used: ‘originalTree_Syn_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1292:1: Warning: > Defined but not used: ‘wrap_AlterDatabaseOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:29: Warning: > Defined but not used: data constructor ‘Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:51: Warning: > Defined but not used: ‘cat_Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:87: Warning: > Defined but not used: ‘flags_Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1451:135: > Warning: > Defined but not used: ‘imCast_Inh_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1452:29: Warning: > Defined but not used: data constructor ‘Syn_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1452:51: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1452:106: > Warning: > Defined but not used: ‘originalTree_Syn_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1456:1: Warning: > Defined but not used: ‘wrap_AlterTableAction’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:33: Warning: > Defined but not used: data constructor ‘Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:59: Warning: > Defined but not used: ‘cat_Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:99: Warning: > Defined but not used: ‘flags_Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1832:151: > Warning: > Defined but not used: ‘imCast_Inh_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1833:33: Warning: > Defined but not used: data constructor ‘Syn_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1833:59: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1833:122: > Warning: > Defined but not used: ‘originalTree_Syn_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:1837:1: Warning: > Defined but not used: ‘wrap_AlterTableActionList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:32: Warning: > Defined but not used: data constructor ‘Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:57: Warning: > Defined but not used: ‘cat_Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:96: Warning: > Defined but not used: ‘flags_Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2005:147: > Warning: > Defined but not used: ‘imCast_Inh_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2006:32: Warning: > Defined but not used: data constructor ‘Syn_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2006:57: Warning: > Defined but not used: ‘annotatedTree_Syn_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2006:118: > Warning: > Defined but not used: ‘originalTree_Syn_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2010:1: Warning: > Defined but not used: ‘wrap_AlterTableOperation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:23: Warning: > Defined but not used: data constructor ‘Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:39: Warning: > Defined but not used: ‘cat_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:69: Warning: > Defined but not used: ‘flags_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:111: > Warning: > Defined but not used: ‘imCast_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2320:154: > Warning: > Defined but not used: ‘tpe_Inh_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2321:23: Warning: > Defined but not used: data constructor ‘Syn_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2321:39: Warning: > Defined but not used: ‘annotatedTree_Syn_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2321:82: Warning: > Defined but not used: ‘originalTree_Syn_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2325:1: Warning: > Defined but not used: ‘wrap_Annotation’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:25: Warning: > Defined but not used: data constructor ‘Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:43: Warning: > Defined but not used: ‘cat_Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:75: Warning: > Defined but not used: ‘flags_Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2385:119: > Warning: > Defined but not used: ‘imCast_Inh_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2386:25: Warning: > Defined but not used: data constructor ‘Syn_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2386:43: Warning: > Defined but not used: ‘annotatedTree_Syn_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2386:90: Warning: > Defined but not used: ‘originalTree_Syn_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2390:1: Warning: > Defined but not used: ‘wrap_AttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:29: Warning: > Defined but not used: data constructor ‘Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:51: Warning: > Defined but not used: ‘cat_Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:87: Warning: > Defined but not used: ‘flags_Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2593:135: > Warning: > Defined but not used: ‘imCast_Inh_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2594:29: Warning: > Defined but not used: data constructor ‘Syn_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2594:51: Warning: > Defined but not used: ‘annotatedTree_Syn_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2594:106: > Warning: > Defined but not used: ‘originalTree_Syn_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2598:1: Warning: > Defined but not used: ‘wrap_AttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:45: Warning: > Defined but not used: > data constructor ‘Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:83: Warning: > Defined but not used: ‘cat_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:135: > Warning: > Defined but not used: > ‘downEnv_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:195: > Warning: > Defined but not used: ‘flags_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:259: > Warning: > Defined but not used: ‘imCast_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:324: > Warning: > Defined but not used: > ‘thenExpectedType_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2755:399: > Warning: > Defined but not used: > ‘whenExpectedType_Inh_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:45: Warning: > Defined but not used: > data constructor ‘Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:83: Warning: > Defined but not used: > ‘annotatedTree_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:170: > Warning: > Defined but not used: > ‘originalTree_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:256: > Warning: > Defined but not used: > ‘thenType_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:323: > Warning: > Defined but not used: > ‘upTypes_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2756:391: > Warning: > Defined but not used: > ‘whenTypes_Syn_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2760:1: Warning: > Defined but not used: ‘wrap_CaseScalarExprListScalarExprPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:49: Warning: > Defined but not used: > data constructor ‘Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:91: Warning: > Defined but not used: > ‘cat_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:147: > Warning: > Defined but not used: > ‘downEnv_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:211: > Warning: > Defined but not used: > ‘flags_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:279: > Warning: > Defined but not used: > ‘imCast_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:348: > Warning: > Defined but not used: > ‘thenExpectedType_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2958:427: > Warning: > Defined but not used: > ‘whenExpectedType_Inh_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:49: Warning: > Defined but not used: > data constructor ‘Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:91: Warning: > Defined but not used: > ‘annotatedTree_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:186: > Warning: > Defined but not used: > ‘originalTree_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:280: > Warning: > Defined but not used: > ‘thenTypes_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:354: > Warning: > Defined but not used: > ‘upTypes_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2959:426: > Warning: > Defined but not used: > ‘whenTypes_Syn_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:2963:1: Warning: > Defined but not used: ‘wrap_CaseScalarExprListScalarExprPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:23: Warning: > Defined but not used: data constructor ‘Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:39: Warning: > Defined but not used: ‘cat_Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:69: Warning: > Defined but not used: ‘flags_Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3243:111: > Warning: > Defined but not used: ‘imCast_Inh_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3244:23: Warning: > Defined but not used: data constructor ‘Syn_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3244:39: Warning: > Defined but not used: ‘annotatedTree_Syn_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3244:82: Warning: > Defined but not used: ‘originalTree_Syn_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3248:1: Warning: > Defined but not used: ‘wrap_Constraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:27: Warning: > Defined but not used: data constructor ‘Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:47: Warning: > Defined but not used: ‘cat_Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:81: Warning: > Defined but not used: ‘flags_Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3636:127: > Warning: > Defined but not used: ‘imCast_Inh_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3637:27: Warning: > Defined but not used: data constructor ‘Syn_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3637:47: Warning: > Defined but not used: ‘annotatedTree_Syn_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3637:98: Warning: > Defined but not used: ‘originalTree_Syn_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3641:1: Warning: > Defined but not used: ‘wrap_ConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:19: Warning: > Defined but not used: data constructor ‘Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:31: Warning: > Defined but not used: ‘cat_Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:57: Warning: > Defined but not used: ‘flags_Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3799:95: Warning: > Defined but not used: ‘imCast_Inh_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3800:19: Warning: > Defined but not used: data constructor ‘Syn_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3800:31: Warning: > Defined but not used: ‘annotatedTree_Syn_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3800:66: Warning: > Defined but not used: ‘originalTree_Syn_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:3804:1: Warning: > Defined but not used: ‘wrap_FnBody’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:19: Warning: > Defined but not used: data constructor ‘Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:31: Warning: > Defined but not used: ‘cat_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:57: Warning: > Defined but not used: ‘downEnv_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:91: Warning: > Defined but not used: ‘expectedCast_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:123: > Warning: > Defined but not used: ‘expectedType_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:168: > Warning: > Defined but not used: ‘flags_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4037:206: > Warning: > Defined but not used: ‘imCast_Inh_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:19: Warning: > Defined but not used: data constructor ‘Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:31: Warning: > Defined but not used: ‘annotatedTree_Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:66: Warning: > Defined but not used: ‘listType_Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4038:120: > Warning: > Defined but not used: ‘originalTree_Syn_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4042:1: Warning: > Defined but not used: ‘wrap_InList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:21: Warning: > Defined but not used: data constructor ‘Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:35: Warning: > Defined but not used: ‘cat_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:63: Warning: > Defined but not used: ‘downEnv_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:99: Warning: > Defined but not used: ‘flags_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4347:139: > Warning: > Defined but not used: ‘imCast_Inh_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4348:21: Warning: > Defined but not used: data constructor ‘Syn_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4348:35: Warning: > Defined but not used: ‘annotatedTree_Syn_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4348:74: Warning: > Defined but not used: ‘originalTree_Syn_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4352:1: Warning: > Defined but not used: ‘wrap_JoinExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:26: Warning: > Defined but not used: data constructor ‘Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:45: Warning: > Defined but not used: ‘cat_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:78: Warning: > Defined but not used: ‘downEnv_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:119: > Warning: > Defined but not used: ‘flags_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4586:164: > Warning: > Defined but not used: ‘imCast_Inh_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4587:26: Warning: > Defined but not used: data constructor ‘Syn_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4587:45: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4587:94: Warning: > Defined but not used: ‘originalTree_Syn_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4591:1: Warning: > Defined but not used: ‘wrap_MaybeBoolExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4720:1: Warning: > Defined but not used: ‘sem_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4726:35: Warning: > Defined but not used: data constructor ‘Inh_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4727:35: Warning: > Defined but not used: data constructor ‘Syn_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4731:1: Warning: > Defined but not used: ‘wrap_MaybeNameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4732:10: Warning: > This pattern-binding binds no variables: () = sem > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4736:1: Warning: > Defined but not used: ‘sem_MaybeNameComponentList_Just’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4736:33: Warning: > Defined but not used: ‘just_’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4740:1: Warning: > Defined but not used: ‘sem_MaybeNameComponentList_Nothing’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:28: Warning: > Defined but not used: data constructor ‘Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:49: Warning: > Defined but not used: ‘cat_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:84: Warning: > Defined but not used: ‘downEnv_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:127: > Warning: > Defined but not used: ‘expectedCast_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:168: > Warning: > Defined but not used: ‘expectedType_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:222: > Warning: > Defined but not used: ‘flags_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4784:269: > Warning: > Defined but not used: ‘imCast_Inh_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:28: Warning: > Defined but not used: data constructor ‘Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:49: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:102: > Warning: > Defined but not used: ‘originalTree_Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4785:154: > Warning: > Defined but not used: ‘upType_Syn_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4789:1: Warning: > Defined but not used: ‘wrap_MaybeScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:28: Warning: > Defined but not used: data constructor ‘Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:49: Warning: > Defined but not used: ‘cat_Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:84: Warning: > Defined but not used: ‘flags_Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4959:131: > Warning: > Defined but not used: ‘imCast_Inh_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4960:28: Warning: > Defined but not used: data constructor ‘Syn_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4960:49: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4960:102: > Warning: > Defined but not used: ‘originalTree_Syn_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:4964:1: Warning: > Defined but not used: ‘wrap_MaybeSelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:35: Warning: > Defined but not used: data constructor ‘Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:63: Warning: > Defined but not used: ‘cat_Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:105: > Warning: > Defined but not used: ‘flags_Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5115:159: > Warning: > Defined but not used: ‘imCast_Inh_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5116:35: Warning: > Defined but not used: data constructor ‘Syn_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5116:63: Warning: > Defined but not used: ‘annotatedTree_Syn_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5116:130: > Warning: > Defined but not used: ‘originalTree_Syn_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5120:1: Warning: > Defined but not used: ‘wrap_MaybeTablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:17: Warning: > Defined but not used: data constructor ‘Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:27: Warning: > Defined but not used: ‘cat_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:51: Warning: > Defined but not used: ‘flags_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:87: Warning: > Defined but not used: ‘imCast_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5253:124: > Warning: > Defined but not used: ‘tpe_Inh_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5254:17: Warning: > Defined but not used: data constructor ‘Syn_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5254:27: Warning: > Defined but not used: ‘annotatedTree_Syn_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5254:58: Warning: > Defined but not used: ‘originalTree_Syn_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5258:1: Warning: > Defined but not used: ‘wrap_Name’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5374:1: Warning: > Defined but not used: ‘sem_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5378:30: Warning: > Defined but not used: data constructor ‘Inh_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5379:30: Warning: > Defined but not used: data constructor ‘Syn_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5383:1: Warning: > Defined but not used: ‘wrap_NameComponentList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5384:10: Warning: > This pattern-binding binds no variables: () = sem > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5389:1: Warning: > Defined but not used: ‘sem_NameComponentList_Cons’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5389:28: Warning: > Defined but not used: ‘hd_’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5389:32: Warning: > Defined but not used: ‘tl_’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5393:1: Warning: > Defined but not used: ‘sem_NameComponentList_Nil’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:33: Warning: > Defined but not used: data constructor ‘Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:59: Warning: > Defined but not used: ‘cat_Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:99: Warning: > Defined but not used: ‘flags_Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5425:151: > Warning: > Defined but not used: ‘imCast_Inh_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5426:33: Warning: > Defined but not used: data constructor ‘Syn_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5426:59: Warning: > Defined but not used: ‘annotatedTree_Syn_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5426:122: > Warning: > Defined but not used: ‘originalTree_Syn_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5430:1: Warning: > Defined but not used: ‘wrap_NameTypeNameListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:37: Warning: > Defined but not used: > data constructor ‘Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:67: Warning: > Defined but not used: ‘cat_Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:111: > Warning: > Defined but not used: ‘flags_Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5557:167: > Warning: > Defined but not used: ‘imCast_Inh_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5558:37: Warning: > Defined but not used: > data constructor ‘Syn_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5558:67: Warning: > Defined but not used: ‘annotatedTree_Syn_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5558:138: > Warning: > Defined but not used: ‘originalTree_Syn_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5562:1: Warning: > Defined but not used: ‘wrap_NameTypeNameListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:19: Warning: > Defined but not used: data constructor ‘Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:31: Warning: > Defined but not used: ‘cat_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:57: Warning: > Defined but not used: ‘downEnv_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:91: Warning: > Defined but not used: ‘flags_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5717:129: > Warning: > Defined but not used: ‘imCast_Inh_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5718:19: Warning: > Defined but not used: data constructor ‘Syn_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5718:31: Warning: > Defined but not used: ‘annotatedTree_Syn_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5718:66: Warning: > Defined but not used: ‘originalTree_Syn_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5722:1: Warning: > Defined but not used: ‘wrap_OnExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:21: Warning: > Defined but not used: data constructor ‘Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:35: Warning: > Defined but not used: ‘cat_Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:63: Warning: > Defined but not used: ‘flags_Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5864:103: > Warning: > Defined but not used: ‘imCast_Inh_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5865:21: Warning: > Defined but not used: data constructor ‘Syn_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5865:35: Warning: > Defined but not used: ‘annotatedTree_Syn_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5865:74: Warning: > Defined but not used: ‘originalTree_Syn_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:5869:1: Warning: > Defined but not used: ‘wrap_ParamDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:25: Warning: > Defined but not used: data constructor ‘Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:43: Warning: > Defined but not used: ‘cat_Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:75: Warning: > Defined but not used: ‘flags_Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6090:119: > Warning: > Defined but not used: ‘imCast_Inh_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6091:25: Warning: > Defined but not used: data constructor ‘Syn_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6091:43: Warning: > Defined but not used: ‘annotatedTree_Syn_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6091:90: Warning: > Defined but not used: ‘originalTree_Syn_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6095:1: Warning: > Defined but not used: ‘wrap_ParamDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:22: Warning: > Defined but not used: data constructor ‘Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:37: Warning: > Defined but not used: ‘cat_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:66: Warning: > Defined but not used: ‘expectedType_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:116: > Warning: > Defined but not used: ‘flags_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:157: > Warning: > Defined but not used: ‘imCast_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6324:199: > Warning: > Defined but not used: ‘outerDownEnv_Inh_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:22: Warning: > Defined but not used: data constructor ‘Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:37: Warning: > Defined but not used: ‘annotatedTree_Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:78: Warning: > Defined but not used: ‘originalTree_Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6325:118: > Warning: > Defined but not used: ‘upType_Syn_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:6329:1: Warning: > Defined but not used: ‘wrap_QueryExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7235:58: Warning: > Defined but not used: ‘originalTree_Syn_Root’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:26: Warning: > Defined but not used: data constructor ‘Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:45: Warning: > Defined but not used: ‘cat_Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:78: Warning: > Defined but not used: ‘flags_Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7389:123: > Warning: > Defined but not used: ‘imCast_Inh_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7390:26: Warning: > Defined but not used: data constructor ‘Syn_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7390:45: Warning: > Defined but not used: ‘annotatedTree_Syn_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7390:94: Warning: > Defined but not used: ‘originalTree_Syn_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7394:1: Warning: > Defined but not used: ‘wrap_RowConstraint’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:30: Warning: > Defined but not used: data constructor ‘Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:53: Warning: > Defined but not used: ‘cat_Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:90: Warning: > Defined but not used: ‘flags_Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7978:139: > Warning: > Defined but not used: ‘imCast_Inh_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7979:30: Warning: > Defined but not used: data constructor ‘Syn_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7979:53: Warning: > Defined but not used: ‘annotatedTree_Syn_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7979:110: > Warning: > Defined but not used: ‘originalTree_Syn_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:7983:1: Warning: > Defined but not used: ‘wrap_RowConstraintList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:23: Warning: > Defined but not used: data constructor ‘Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:39: Warning: > Defined but not used: ‘cat_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:69: Warning: > Defined but not used: ‘downEnv_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:107: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:143: > Warning: > Defined but not used: ‘expectedType_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:192: > Warning: > Defined but not used: ‘flags_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8482:234: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:23: Warning: > Defined but not used: data constructor ‘Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:39: Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:82: Warning: > Defined but not used: ‘colExprs_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:156: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8483:198: > Warning: > Defined but not used: ‘upType_Syn_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:8487:1: Warning: > Defined but not used: ‘wrap_ScalarExpr’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:36: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:65: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:108: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:159: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13383:214: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13384:36: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13384:65: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13384:134: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13388:1: Warning: > Defined but not used: ‘wrap_ScalarExprDirectionPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:40: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:73: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:120: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:175: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13509:234: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13510:40: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13510:73: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13510:150: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13514:1: Warning: > Defined but not used: ‘wrap_ScalarExprDirectionPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:27: > Warning: > Defined but not used: data constructor ‘Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:47: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:81: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:123: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:163: > Warning: > Defined but not used: ‘expectedTypes_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:213: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13689:259: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:27: > Warning: > Defined but not used: data constructor ‘Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:47: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:98: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13690:148: > Warning: > Defined but not used: ‘upTypes_Syn_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13694:1: Warning: > Defined but not used: ‘wrap_ScalarExprList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:31: > Warning: > Defined but not used: data constructor ‘Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:55: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:93: > Warning: > Defined but not used: ‘downEnv_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:139: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:183: > Warning: > Defined but not used: ‘expectedType_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:242: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13914:292: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:31: > Warning: > Defined but not used: data constructor ‘Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:55: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:114: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13915:172: > Warning: > Defined but not used: ‘upType_Syn_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:13919:1: Warning: > Defined but not used: ‘wrap_ScalarExprListList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:44: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:81: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:132: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14139:195: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14140:44: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14140:81: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14140:166: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14144:1: Warning: > Defined but not used: ‘wrap_ScalarExprListStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:48: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:89: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:144: > Warning: > Defined but not used: > ‘flags_Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14286:211: > Warning: > Defined but not used: > ‘imCast_Inh_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14287:48: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14287:89: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14287:182: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14291:1: Warning: > Defined but not used: ‘wrap_ScalarExprListStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14440:98: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprRoot’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:40: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:73: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:120: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14557:179: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14558:40: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14558:73: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14558:150: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14562:1: Warning: > Defined but not used: ‘wrap_ScalarExprStatementListPair’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:44: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:81: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:132: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14705:195: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14706:44: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14706:81: > Warning: > Defined but not used: > ‘annotatedTree_Syn_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14706:166: > Warning: > Defined but not used: > ‘originalTree_Syn_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14710:1: Warning: > Defined but not used: ‘wrap_ScalarExprStatementListPairList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:37: > Warning: > Defined but not used: > data constructor ‘Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:67: > Warning: > Defined but not used: ‘cat_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:111: > Warning: > Defined but not used: ‘expectedCast_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:161: > Warning: > Defined but not used: ‘expectedType_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:226: > Warning: > Defined but not used: ‘flags_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14867:282: > Warning: > Defined but not used: ‘imCast_Inh_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:37: > Warning: > Defined but not used: > data constructor ‘Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:67: > Warning: > Defined but not used: ‘annotatedTree_Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:138: > Warning: > Defined but not used: ‘originalTree_Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14868:208: > Warning: > Defined but not used: ‘upType_Syn_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:14872:1: Warning: > Defined but not used: ‘wrap_ScalarExprTransposedList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:23: > Warning: > Defined but not used: data constructor ‘Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:39: > Warning: > Defined but not used: ‘cat_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:69: > Warning: > Defined but not used: ‘downEnv_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:107: > Warning: > Defined but not used: ‘expectedCast_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:143: > Warning: > Defined but not used: ‘expectedType_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:192: > Warning: > Defined but not used: ‘flags_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15094:234: > Warning: > Defined but not used: ‘imCast_Inh_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:23: > Warning: > Defined but not used: data constructor ‘Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:39: > Warning: > Defined but not used: ‘annotatedTree_Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:82: > Warning: > Defined but not used: ‘colExprs_Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15095:156: > Warning: > Defined but not used: ‘originalTree_Syn_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15099:1: Warning: > Defined but not used: ‘wrap_SelectItem’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:27: > Warning: > Defined but not used: data constructor ‘Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:47: > Warning: > Defined but not used: ‘cat_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:81: > Warning: > Defined but not used: ‘downEnv_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:123: > Warning: > Defined but not used: ‘expectedCast_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:163: > Warning: > Defined but not used: ‘expectedType_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:218: > Warning: > Defined but not used: ‘flags_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15403:264: > Warning: > Defined but not used: ‘imCast_Inh_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:27: > Warning: > Defined but not used: data constructor ‘Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:47: > Warning: > Defined but not used: ‘annotatedTree_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:98: > Warning: > Defined but not used: ‘colExprs_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:176: > Warning: > Defined but not used: ‘originalTree_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:226: > Warning: > Defined but not used: ‘upEnv_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15404:266: > Warning: > Defined but not used: ‘upType_Syn_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15408:1: Warning: > Defined but not used: ‘wrap_SelectItemList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:23: > Warning: > Defined but not used: data constructor ‘Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:39: > Warning: > Defined but not used: ‘cat_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:69: > Warning: > Defined but not used: ‘downEnv_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:107: > Warning: > Defined but not used: ‘expectedCast_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:143: > Warning: > Defined but not used: ‘expectedType_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:194: > Warning: > Defined but not used: ‘flags_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15688:236: > Warning: > Defined but not used: ‘imCast_Inh_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:23: > Warning: > Defined but not used: data constructor ‘Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:39: > Warning: > Defined but not used: ‘annotatedTree_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:82: > Warning: > Defined but not used: ‘colExprs_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:156: > Warning: > Defined but not used: ‘originalTree_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:198: > Warning: > Defined but not used: ‘upEnv_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15689:234: > Warning: > Defined but not used: ‘upType_Syn_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15693:1: Warning: > Defined but not used: ‘wrap_SelectList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:22: > Warning: > Defined but not used: data constructor ‘Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:37: > Warning: > Defined but not used: ‘cat_Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:66: > Warning: > Defined but not used: ‘flags_Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15876:107: > Warning: > Defined but not used: ‘imCast_Inh_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15877:22: > Warning: > Defined but not used: data constructor ‘Syn_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15877:37: > Warning: > Defined but not used: ‘annotatedTree_Syn_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15877:78: > Warning: > Defined but not used: ‘originalTree_Syn_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:15881:1: Warning: > Defined but not used: ‘wrap_SetClause’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:26: > Warning: > Defined but not used: data constructor ‘Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:45: > Warning: > Defined but not used: ‘cat_Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:78: > Warning: > Defined but not used: ‘flags_Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16147:123: > Warning: > Defined but not used: ‘imCast_Inh_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16148:26: > Warning: > Defined but not used: data constructor ‘Syn_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16148:45: > Warning: > Defined but not used: ‘annotatedTree_Syn_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16148:94: > Warning: > Defined but not used: ‘originalTree_Syn_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16152:1: Warning: > Defined but not used: ‘wrap_SetClauseList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:22: > Warning: > Defined but not used: data constructor ‘Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:37: > Warning: > Defined but not used: ‘cat_Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:66: > Warning: > Defined but not used: ‘flags_Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16862:107: > Warning: > Defined but not used: ‘imCast_Inh_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16863:22: > Warning: > Defined but not used: data constructor ‘Syn_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16863:37: > Warning: > Defined but not used: ‘annotatedTree_Syn_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16863:78: > Warning: > Defined but not used: ‘originalTree_Syn_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:16867:1: Warning: > Defined but not used: ‘wrap_Statement’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:26: > Warning: > Defined but not used: data constructor ‘Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:45: > Warning: > Defined but not used: ‘cat_Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:78: > Warning: > Defined but not used: ‘flags_Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23092:123: > Warning: > Defined but not used: ‘imCast_Inh_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23093:26: > Warning: > Defined but not used: data constructor ‘Syn_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23093:45: > Warning: > Defined but not used: ‘annotatedTree_Syn_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23093:94: > Warning: > Defined but not used: ‘originalTree_Syn_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23097:1: Warning: > Defined but not used: ‘wrap_StatementList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:30: > Warning: > Defined but not used: data constructor ‘Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:53: > Warning: > Defined but not used: ‘cat_Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:90: > Warning: > Defined but not used: ‘flags_Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23248:139: > Warning: > Defined but not used: ‘imCast_Inh_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23249:30: > Warning: > Defined but not used: data constructor ‘Syn_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23249:53: > Warning: > Defined but not used: ‘annotatedTree_Syn_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23249:110: > Warning: > Defined but not used: ‘originalTree_Syn_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23253:1: Warning: > Defined but not used: ‘wrap_TablePartitionDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:21: > Warning: > Defined but not used: data constructor ‘Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:35: > Warning: > Defined but not used: ‘cat_Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:63: > Warning: > Defined but not used: ‘flags_Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23429:103: > Warning: > Defined but not used: ‘imCast_Inh_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:21: > Warning: > Defined but not used: data constructor ‘Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:35: > Warning: > Defined but not used: ‘annotatedTree_Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:74: > Warning: > Defined but not used: ‘originalTree_Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23430:112: > Warning: > Defined but not used: ‘upEnv_Syn_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:23434:1: Warning: > Defined but not used: ‘wrap_TableRef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:25: > Warning: > Defined but not used: data constructor ‘Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:43: > Warning: > Defined but not used: ‘cat_Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:75: > Warning: > Defined but not used: ‘flags_Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24450:119: > Warning: > Defined but not used: ‘imCast_Inh_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:25: > Warning: > Defined but not used: data constructor ‘Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:43: > Warning: > Defined but not used: ‘annotatedTree_Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:90: > Warning: > Defined but not used: ‘originalTree_Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24451:136: > Warning: > Defined but not used: ‘upEnv_Syn_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24455:1: Warning: > Defined but not used: ‘wrap_TableRefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:29: > Warning: > Defined but not used: data constructor ‘Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:51: > Warning: > Defined but not used: ‘cat_Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:87: > Warning: > Defined but not used: ‘flags_Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24625:135: > Warning: > Defined but not used: ‘imCast_Inh_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24626:29: > Warning: > Defined but not used: data constructor ‘Syn_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24626:51: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24626:106: > Warning: > Defined but not used: ‘originalTree_Syn_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24630:1: Warning: > Defined but not used: ‘wrap_TypeAttributeDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:33: > Warning: > Defined but not used: data constructor ‘Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:59: > Warning: > Defined but not used: ‘cat_Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:99: > Warning: > Defined but not used: ‘flags_Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24759:151: > Warning: > Defined but not used: ‘imCast_Inh_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24760:33: > Warning: > Defined but not used: data constructor ‘Syn_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24760:59: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24760:122: > Warning: > Defined but not used: ‘originalTree_Syn_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24764:1: Warning: > Defined but not used: ‘wrap_TypeAttributeDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:21: > Warning: > Defined but not used: data constructor ‘Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:35: > Warning: > Defined but not used: ‘cat_Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:63: > Warning: > Defined but not used: ‘flags_Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24958:103: > Warning: > Defined but not used: ‘imCast_Inh_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:21: > Warning: > Defined but not used: data constructor ‘Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:35: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:74: > Warning: > Defined but not used: ‘namedType_Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24959:118: > Warning: > Defined but not used: ‘originalTree_Syn_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:24963:1: Warning: > Defined but not used: ‘wrap_TypeName’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:25: > Warning: > Defined but not used: data constructor ‘Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:43: > Warning: > Defined but not used: ‘cat_Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:75: > Warning: > Defined but not used: ‘flags_Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25556:119: > Warning: > Defined but not used: ‘imCast_Inh_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25557:25: > Warning: > Defined but not used: data constructor ‘Syn_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25557:43: > Warning: > Defined but not used: ‘annotatedTree_Syn_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25557:90: > Warning: > Defined but not used: ‘originalTree_Syn_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25561:1: Warning: > Defined but not used: ‘wrap_TypeNameList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:19: > Warning: > Defined but not used: data constructor ‘Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:31: > Warning: > Defined but not used: ‘cat_Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:57: > Warning: > Defined but not used: ‘flags_Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25733:95: > Warning: > Defined but not used: ‘imCast_Inh_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25734:19: > Warning: > Defined but not used: data constructor ‘Syn_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25734:31: > Warning: > Defined but not used: ‘annotatedTree_Syn_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25734:66: > Warning: > Defined but not used: ‘originalTree_Syn_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:25738:1: Warning: > Defined but not used: ‘wrap_VarDef’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:23: > Warning: > Defined but not used: data constructor ‘Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:39: > Warning: > Defined but not used: ‘cat_Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:69: > Warning: > Defined but not used: ‘flags_Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26034:111: > Warning: > Defined but not used: ‘imCast_Inh_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26035:23: > Warning: > Defined but not used: data constructor ‘Syn_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26035:39: > Warning: > Defined but not used: ‘annotatedTree_Syn_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26035:82: > Warning: > Defined but not used: ‘originalTree_Syn_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26039:1: Warning: > Defined but not used: ‘wrap_VarDefList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:22: > Warning: > Defined but not used: data constructor ‘Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:37: > Warning: > Defined but not used: ‘cat_Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:66: > Warning: > Defined but not used: ‘flags_Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26190:107: > Warning: > Defined but not used: ‘imCast_Inh_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26191:22: > Warning: > Defined but not used: data constructor ‘Syn_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26191:37: > Warning: > Defined but not used: ‘annotatedTree_Syn_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26191:78: > Warning: > Defined but not used: ‘originalTree_Syn_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26195:1: Warning: > Defined but not used: ‘wrap_WithQuery’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:26: > Warning: > Defined but not used: data constructor ‘Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:45: > Warning: > Defined but not used: ‘cat_Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:78: > Warning: > Defined but not used: ‘flags_Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26339:123: > Warning: > Defined but not used: ‘imCast_Inh_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26340:26: > Warning: > Defined but not used: data constructor ‘Syn_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26340:45: > Warning: > Defined but not used: ‘annotatedTree_Syn_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26340:94: > Warning: > Defined but not used: ‘originalTree_Syn_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/AstInternal.hs:26344:1: Warning: > Defined but not used: ‘wrap_WithQueryList’ > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:75:38: > Warning: > Fields of ‘Inh_ScalarExprRoot’ not initialised: > downEnv_Inh_ScalarExprRoot > In the second argument of ‘wrap_ScalarExprRoot’, namely > ‘Inh_ScalarExprRoot > {cat_Inh_ScalarExprRoot = cat, flags_Inh_ScalarExprRoot = f}’ > In the first argument of ‘annotatedTree_Syn_ScalarExprRoot’, namely > ‘(wrap_ScalarExprRoot > t > (Inh_ScalarExprRoot > {cat_Inh_ScalarExprRoot = cat, flags_Inh_ScalarExprRoot = > f}))’ > In the expression: > (annotatedTree_Syn_ScalarExprRoot > (wrap_ScalarExprRoot > t > (Inh_ScalarExprRoot > {cat_Inh_ScalarExprRoot = cat, flags_Inh_ScalarExprRoot = > f}))) > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:260:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:261:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:262:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:268:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:269:1: > Warning: > Tab character > > hssqlppp/src/Database/HsSqlPpp/Internals/TypeChecking/TypeChecking.ag:270:1: > Warning: > Tab character > > src/Database/HsSqlPpp/Internals/AstInternal.hs:119:1: Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > [17 of 23] Compiling Database.HsSqlPpp.Annotation ( > src/Database/HsSqlPpp/Annotation.lhs, > dist/build/Database/HsSqlPpp/Annotation.o ) > [18 of 23] Compiling Database.HsSqlPpp.TypeChecker ( > src/Database/HsSqlPpp/TypeChecker.lhs, > dist/build/Database/HsSqlPpp/TypeChecker.o ) > [19 of 23] Compiling Database.HsSqlPpp.Ast ( > src/Database/HsSqlPpp/Ast.lhs, dist/build/Database/HsSqlPpp/Ast.o ) > [20 of 23] Compiling Database.HsSqlPpp.Parsing.ParserInternal ( > src/Database/HsSqlPpp/Parsing/ParserInternal.lhs, > dist/build/Database/HsSqlPpp/Parsing/ParserInternal.o ) > > src/Database/HsSqlPpp/Parsing/ParserInternal.lhs:38:3: Warning: > The import of ‘Control.Applicative’ is redundant > except perhaps to import instances from ‘Control.Applicative’ > To import instances alone, use: import Control.Applicative() > [21 of 23] Compiling Database.HsSqlPpp.Parser ( > src/Database/HsSqlPpp/Parser.lhs, dist/build/Database/HsSqlPpp/Parser.o ) > [22 of 23] Compiling Database.HsSqlPpp.Utility ( > src/Database/HsSqlPpp/Utility.lhs, dist/build/Database/HsSqlPpp/Utility.o > ) > [23 of 23] Compiling Database.HsSqlPpp.Pretty ( > src/Database/HsSqlPpp/Pretty.lhs, dist/build/Database/HsSqlPpp/Pretty.o ) > > src/Database/HsSqlPpp/Pretty.lhs:103:3: Warning: > Pattern match(es) are non-exhaustive > In an equation for ‘statement’: > Patterns not matched: > _ _ _ (CreateUser _ _ _) > _ _ _ (CreateLogin _ _ _) > _ _ _ (AlterUser _ _ _) > _ _ _ (AlterLogin _ _ _) > > src/Database/HsSqlPpp/Pretty.lhs:781:31: Warning: > Pattern match(es) are overlapped > In a case alternative: _ -> ... > In-place registering hssqlppp-0.5.18... > > real 9m3.447s > user 12m19.704s > sys 3m25.724s > }}} New description: There is a big performance regression in the compile time from ghc 7.10.1 to ghc 7.10.1.20150612 I believe it is in this file which has a huge literal value which also contains overloaded strings using Text: https://github.com/JakeWheat/hssqlppp/blob/master/hssqlppp/src/Database/HsSqlPpp/Internals/Catalog/DefaultTemplate1Catalog.lhs {{{ time cabal build with ghc 7.10.1 real 1m20.449s user 2m5.040s sys 0m48.504s time cabal build with ghc 7.10.1.20150612 real 9m3.447s user 12m19.704s sys 3m25.724s }}} I am running debian 64 bit unstable with the ghc binary tarballs from here: https://www.haskell.org/ghc/ -- -- Ticket URL: GHC The Glasgow Haskell Compiler