[GHC] #13002: :set -O does not work in .ghci file

#13002: :set -O does not work in .ghci file --------------------------------------+---------------------------- Reporter: George | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Keywords: | Operating System: MacOS X Architecture: x86_64 (amd64) | Type of failure: Other Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+---------------------------- {{{#!hs {-# OPTIONS_GHC -Wall #-} module Foo where testFromTo :: Int -> Int testFromTo n = length ([0..(10^n)] :: [Int]) }}} {{{ cat ~/.ghci :set +s :set -fobject-code :set -O bash-3.2$ touch Foo.hs bash-3.2$ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/gcolpitts/.ghci Prelude> :load Foo :load Foo [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) Ok, modules loaded: Foo (Foo.o). (0.15 secs,) Prelude Foo> testFromTo 5 testFromTo 5 100001 (0.02 secs, 8,885,888 bytes) Prelude Foo> :quit :quit Leaving GHCi. bash-3.2$ touch Foo.hs bash-3.2$ ghci -fobject-code -O GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/gcolpitts/.ghci Prelude> :load Foo :load Foo [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) Ok, modules loaded: Foo (Foo.o). (0.15 secs,) Prelude Foo> testFromTo 5 testFromTo 5 100001 (0.02 secs, 98,400 bytes) }}} While supplying -fobject-code -O as an argument to ghci seems like an easy workaround that isn't feasible as far as I know when using emacs thus setting priority to normal rather than low. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Other | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * os: MacOS X => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * failure: Other => Runtime performance bug Comment: In the context of ghci, the ignored -O in the .ghci file results in a runtime performance bug. Thus I changed the type of failure to runtime performance bug (in the context of ghci which is the component). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by George): present in 8.2.1-rc1 also -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: => 8.2.1 Comment: It would be nice if we could get this fixed for 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 Comment: Bump off to 8.4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: => RecompilationCheck -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by George: Old description:
{{{#!hs {-# OPTIONS_GHC -Wall #-}
module Foo where
testFromTo :: Int -> Int testFromTo n = length ([0..(10^n)] :: [Int]) }}} {{{ cat ~/.ghci :set +s :set -fobject-code :set -O bash-3.2$ touch Foo.hs bash-3.2$ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/gcolpitts/.ghci Prelude> :load Foo :load Foo [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) Ok, modules loaded: Foo (Foo.o). (0.15 secs,) Prelude Foo> testFromTo 5 testFromTo 5 100001 (0.02 secs, 8,885,888 bytes) Prelude Foo> :quit :quit Leaving GHCi. bash-3.2$ touch Foo.hs bash-3.2$ ghci -fobject-code -O GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/gcolpitts/.ghci Prelude> :load Foo :load Foo [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) Ok, modules loaded: Foo (Foo.o). (0.15 secs,) Prelude Foo> testFromTo 5 testFromTo 5 100001 (0.02 secs, 98,400 bytes) }}}
While supplying -fobject-code -O as an argument to ghci seems like an easy workaround that isn't feasible as far as I know when using emacs thus setting priority to normal rather than low.
New description: {{{#!hs {-# OPTIONS_GHC -Wall #-} module Foo where testFromTo :: Int -> Int testFromTo n = length ([0..(10^n)] :: [Int]) }}} {{{ cat ~/.ghci :set +s :set -fobject-code :set -O bash-3.2$ touch Foo.hs bash-3.2$ ghci GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/gcolpitts/.ghci Prelude> :load Foo :load Foo [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) Ok, modules loaded: Foo (Foo.o). (0.15 secs,) Prelude Foo> testFromTo 5 testFromTo 5 100001 (0.02 secs, 8,885,888 bytes) Prelude Foo> :quit :quit Leaving GHCi. bash-3.2$ touch Foo.hs bash-3.2$ ghci -fobject-code -O GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /Users/gcolpitts/.ghci Prelude> :load Foo :load Foo [1 of 1] Compiling Foo ( Foo.hs, Foo.o ) Ok, modules loaded: Foo (Foo.o). (0.15 secs,) Prelude Foo> testFromTo 5 testFromTo 5 100001 (0.02 secs, 98,400 bytes) }}} While supplying -fobject-code -O as an argument to ghci seems like an easy workaround; it isn't feasible, as far as I know, when using emacs thus setting priority to normal rather than low. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: worksforme | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => closed * resolution: => worksforme * milestone: 8.4.1 => 8.0.3 Comment: I'm not at all convinced that this bug is valid at all. I suspect the timing difference you saw was some sort of insignificant artifact; perhaps the extra command line options are affecting GC timings. I tested with a version that includes an utterly bogus `RULES` pragma: {{{#!hs {-# OPTIONS_GHC -Wall #-} module T13002 where testFromTo :: Int -> Int testFromTo n = length ([0..(10^n)] :: [Int]) {-# NOINLINE testFromTo #-} test :: Int -> Int test x = testFromTo x {-# RULES "bogus" forall x. testFromTo x = 12 #-} }}} This produces semantically different `test` functions depending on whether optimizations are enabled or not, and the change occurs as expected when I add `-O` to the `.ghci` file. It works for me under 8.0, 8.2, and HEAD. So I'm going to close this for now; if you disagree, I suggest you add a more robust test case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: worksforme | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): That is, GHC's processing of its own command line could affect GC timings in some tiny way that is enough to lead to the difference you experienced. Just to make really sure, I turned on `-ddump-simpl` and saw that the core produced when loading the test file had all the signs of having been optimized (e.g., strictness annotations, unfoldings, and worker/wrapper pairs). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: worksforme | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: dfeuer (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by George): * status: closed => new * resolution: worksforme => Comment: Thanks for taking the time to investigate, I should have been more explicit, the bug is not about the small timing difference; it is about the large allocation difference: 8,885,888 bytes vs 98,400 bytes. That is not insignficant right? think it is the difference between fusion occurring and not occurring. I agree that the ddump-simpl output seems to show that it is not a bug but the allocation difference indicates to me that it is not optimizing i.e.doing list fusion. I thought it worth double checking. If you are still not convinced feel free to close and I will try to come up with a more robust test case or convince myself that I am wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I'm ''guessing'' that the allocation difference is caused by what GHCi does ''before'' it loads the module, and quite possibly even before it loads the `.ghci` file. How could I check this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): No, my last comment was bogus. The `.o` file for the one that allocates a lot of memory is larger! The `.hi` files are identical. Very strange. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): No, no, no. I'm wrong again. The `.hi` files are only the same for my modified version. The originals are different. I'll attach them. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * Attachment "Foo-if" added. The interface produced with -O on the command line -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.0.3 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * Attachment "Foo-if-leak" added. The interface produced *without* -O on the command line -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: RolandSenn Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #8635 #9370 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RolandSenn): * owner: (none) => RolandSenn * related: => #8635 #9370 Comment: I debugged this ticket and found the following: **The Issue** GHC has a dynamic flag `Opt_IgnoreInterfacePragmas` or `-fignore- interface-pragmas`. The setting of this flag is dependent on the optimization flag `-O`. `-O0` will set the Opt_IgnoreInterfacePragmas flag On, `-O1` and `-O2` will set it Off. If the Opt_IgnoreInterfacePragmas flag is On, then GHC(i) does not store optimization data (eg inline pragmas or rewrite rules) from the interface files. See `compiler/iface/LoadIface.hs:loadInterface`. The field containing the rules is `eps_rule_base`, the one containig the pragmas is `eps_PTE` both in the ExternalPackageState (EPS) record. The default optimization is -O0, so Opt_IgnoreInterfacePragmas is On. During startup, GHCi processes the interface `GHC.Prim` containing the `fold/build` rule. As Opt_IgnoreInterfacePragmas is On, GHCi does not store any rules in the EPS record. Only after this, we get the possibility to set the optimization flag to -O1 either in the `.ghci` file or with a `:set` command. But it's already too late, the `fold/build` rule wasn't stored, the simplifier doesn't know the rule and cannot optimize the loop: GHCi needs 8800000 bytes to process the example in this ticket. If we specify -O1 as a command line parameter everything is fine: Opt_IgnoreInterfacePragmas is Off, ghci stores the fold/build rule, the simplifier knows and uses the rule, and processing our example needs less than 100000 bytes! **The History** This is an old, well known and heavily discussed issue. See tickets #8635 and #9370. The simplest of the proposed solutions was just to store all the information from the interface files independently of the Opt_IgnoreInterfacePragmas flag. Then @richardfung provided a patch Phab:D2485 for #9370. Unsurprisingly the validation run showed some stats error, because storing all the optimization needed more space. @simonmar commented:
I care a lot about unoptimized compile-time performance - couldn't this make things worse by forcing GHC to read all the interface pragmas from interface files, even with -O0?
However, @simonmar also made two suggestions how to solve this issue. The first one was:
Lazily load the pragma info, so that it doesn't cost anything if we don't use it. The simplifier should use Opt_IgnoreInterfacePragmas to decide whether to use the pragma info from external Ids or not.
After this, @richardfung abandonded his patch. **The Proposed Solution:** I think the above suggestion of @simonmar is the way to go: 1. If the Opt_IgnoreInterfacePragmas flag is set On, we continue to ignore the optimization data in the interface files. However if we ignore the optimization data, we store the module name in a new list, probably also in the ExternalPackageState (EPS) record. 2. <Somewhere in the code>™: If the Opt_IgnoreInterfacePragmas is set Off and there are module entries in the new list, we reload and reprocess the interface files, ignore everything but the optimization data previously excluded by Opt_IgnoreInterfacePragmas. We add this information to the EPS record. Then we clear the new list. (I still have to investigate where to put this functionality...) 3. We use wrapper functions to access the fields `eps_rule_base` and `eps_PTE`: If Opt_IgnoreInterfacePragmas is Off, the wrapper functions return all the data, else they return the initial values, without any optimization data from the interface files. All comments are welcome! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: RolandSenn Type: bug | Status: patch Priority: normal | Milestone: 8.10.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: T13002 Blocked By: | Blocking: Related Tickets: #8635 #9370 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/480 -------------------------------------+------------------------------------- Changes (by RolandSenn): * status: new => patch * testcase: => T13002 * differential: => https://gitlab.haskell.org/ghc/ghc/merge_requests/480 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13002: :set -O does not work in .ghci file -------------------------------------+------------------------------------- Reporter: George | Owner: RolandSenn Type: bug | Status: patch Priority: normal | Milestone: 8.10.1 Component: GHCi | Version: 8.0.1 Resolution: | Keywords: | RecompilationCheck Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: T13002 Blocked By: | Blocking: Related Tickets: #8635 #9370 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/480 -------------------------------------+------------------------------------- Changes (by nh2): * cc: nh2 (added) Comment: Subscribing since #12847 was marked as a duplicate of this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13002#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC