[GHC] #14963: ghci -fdefer-type-errors can't run IO action from another module

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This is enough to trigger a crash on OS X and Linux: Bug1.hs: {{{ module Bug1.hs where import qualified Bug2 test :: IO Bool test = Bug2.failure }}} Bug2.hs: {{{ module Bug2 where failure :: IO Bool failure = return False }}} Shell: {{{ % ghci -fdefer-type-errors -ignore-dot-ghci GHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Prelude> :load Bug [1 of 2] Compiling Bug2 ( Bug2.hs, interpreted ) [2 of 2] Compiling Bug ( Bug.hs, interpreted ) Ok, two modules loaded. *Bug> test ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-apple-darwin): nameModule system $dShow_a1LX Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Name.hs:241:3 in ghc:Name Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} This is specific to 8.4.1, in 8.0.2 I get "False" as expected. If I leave off -fdefer-type-errors, it works. It also seems to be ghci only, compiling with -fdefer-type-errors doesn't have the problem. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by chak): * cc: chak@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): The same happens with just one module: {{{ test :: IO Bool test = return True }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I must be doing something wrong here. I created a file named `Bug.hs` with the contents of comment:2, and tried loading it like so: {{{ $ ~/Software/ghc-8.4.1/bin/ghci -fdefer-type-errors -ignore-dot-ghciGHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Prelude> :load Bug [1 of 1] Compiling Main ( Bug.hs, interpreted ) Ok, one module loaded. }}} Which appears to work without issue. What am I missing? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I can repro the original 2-module report, with the GHC 8.4.2 branch, and with HEAD. Definite bug here! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by monoidal): After `:load Bug` you need to examine the value `test` in ghci. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Oops, I overlooked that important detail! Commit a211dca8236fb8c7ec632278f761121beeac1438 (`Fix defer-out-of-scope- variables`) is what caused this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * priority: normal => high * milestone: => 8.4.2 Comment: Since this is a regression from 8.2, I'm opting to change the milestone and priority. Do change if you feel this isn't warranted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module
-------------------------------------+-------------------------------------
Reporter: elaforge | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.2
Component: GHCi | Version: 8.4.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
It took me quite a while to find out what was going on here.
I started with a file containing only
{{{
test :: IO Bool
test = return True
}}}
Then load into GHCi, with `-fdefer-type-errors`
{{{
ghc --interactive -fdefer-type-errors Foo.hs
}}}
Now just evaluate `test`. Here's what I see from `-ddump-tc -ddump-ds`
with a little extra debug tracing, when evaluating `test` at the GHCi
prompt:
{{{
Typechecked expr do it_a1PP <- {>>=: GHC.Base.bindIO @ Bool
@ [()]{let {EvBinds{[W] $dShow_a1Qg =
GHC.Show.$fShowBool}} <>, <>}
{<> |>

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): PS: using `WpFun` would mean you could return a single `HsWrapper` to wrap around the bind function, rather than returning wrappers for the function, the arguments, and the result. See its use in `TcUnify.tc_sub_type_ds`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): There's always room for simplification, of course, but I think the room here is limited. This whole mechanism came into being when `ExpType`s were introduced. `ExpType`s are "holes" -- places to write a type once we infer it; they replaced `SigmaTv` tyvars that were used previously. I forget what aspect of `ExpType`s specifically forced the rewrite of rebindable syntax, but I do remember that this was more-or-less forced. The reason for the complication is that we want to allow for the possibility that `(>>=) :: blah -> (forall x. x -> x) -> wurble`, where the arguments might have a higher-rank type. This, in turn, requires skolemization while type-checking. That problem with the current setup is that the two arguments are checked in the same `thing_inside`, where they should really be in ''different'' contexts. But that would make the whole scheme even more complicated. So I'm a bit stuck really on how you would want to simplify this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): After a long discussion of design possibilities, Simon and I came to the following: 1. The current design is broken, as described in this ticket. 2. If we want to handle all rebindable syntax in a general fashion, we were unable to come up with anything simpler than the "impenetrable" code that exists. And, indeed, to fix the current flaw would likely require adding `HList`s or some such, making it even worse. 3. Much of the current complication comes from the handling of `>>=`, which has an intricate type. Specifically, we need `(>>=) :: ty1 -> (ty2 -> ty3) -> ty4`. However, it would also be quite cool if something like `(>>=) :: ty1 -> (forall a. ty2 -> ty3) -> ty4` were allowed. This effectively means that a `<-` operator in a `do` could bind an existential variable without using a pattern-match. And, if the user wrote `(>>=)` literally (without `do`), then this would indeed be possible. So it would be nice. The complication specifically stems from the fact that the code processing `BindStmt`s needs to know `ty2` and `ty3`, so we must decompose the type of `(>>=)`'s second argument. In order to do this, we need to skolemize any `forall`d variables, and skolemization requires an implication constraint, causing the bug in this ticket. 4. Rebindable syntax that decomposes list constructors suffers a similar fate, but that's not nearly as painful as `(>>=)`. Though I'm still not fully convinced, we resolved to make the treatment of rebindable syntax simpler and less general. Specifically: a. Reduce `SyntaxOpType` to have two constructors: `SynAny :: SyntaxOpType` and `SynType :: ExpType -> SyntaxOpType`. b. Make new functions `tcBindOp`, `tcFromListOp`, and `tcFromListNOp` that handle the special cases for `(>>=)` and the list functions. These won't use general mechanisms, but just be a bit repetitive with `tcSyntaxOp`. c. The `SynRho` case of `tcSyntaxOp` will be dropped. Instead, clients of `tcSyntaxOp` that need rho-types will arrange to instantiate/skolemize the sigma-types that `tcSyntaxOp` provides as needed. This will duplicate code, but it means that `tcSyntaxOp` no longer needs to be written in CPS style. It will also allow this ticket to be resolved. d. This still won't handle cases like `fromListN :: (forall a. Int) -> [b] -> c`, where one parameter of a bit of rebindable syntax has a known type, but that known type might be redundantly quantified. Handling such a case would require CPSing again, and so we won't. This means that rebindable syntax will be a bit less expressive than the manual has heretofore promised. But the only lost cases are surely of the form above, where there is an unused quantified type variable. We can arrange for a suitable error message in these cases. This change will require a user manual update. e. When all this is done, the extra flexibility in the `SyntaxExpr` type -- with its argument wrappers and result wrapper -- won't be needed. Instead, `tcSyntaxOp` can return a plain old `HsExpr`, suitably wrapped. Accommodations will have to be made in `BindStmt` and the places where list operators might crop up to store extra `HsWrapper`s to be applied to arguments. f. A Note will be placed near `tcSyntaxOp` and the bind/list functions describing this design plan. If, in the future, we want more rebindable syntax, it might encourage us to re-adopt the more general -- but more complicated -- scheme currently in place. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by elaforge): This is just a peanut-gallery comment, so forgive the naivety, but my impression is that Idris treats `do` desugaring purely syntactically, so e.g. you don't even need a Monad class or the expected types, just something called (>>=) and pure in scope. Idris of course does a lot of things fundamentally differently, not the least of which is type-directed name overloading, but that seems orthogonal. What's the problem with treating `do` as a syntax macro before even getting to typechecking? I gather the problem above is all rebindable syntax not just `do` and (>>=), but it made me curious about that one thing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I actually proposed doing exactly that when working this out with Simon. The problem is that doing so would ruin error messages, because we could report errors only with respect to the expanded syntax, instead of what the user actually wrote. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by elaforge): Yeah, macros in general would need to store the original form and somehow get back to it for errors. I'm sure this has been thought about quite a bit over the decades and the devil is in that "somehow." I don't know anything about that previous work, so I'll leave it at that :) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by chak): Given that this didn't make it into 8.4.2, may I ask, what is the plan here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): As a short term fix how bad would it be to make `-fdefer-type-errors` incompatible with GHCi? We could apply that fix to HEAD (until we fix this ticket properly) and perhaps even to 8.4.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by tdammers): * owner: (none) => tdammers -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I actually proposed doing exactly that when working this out with Simon. The problem is that doing so would ruin error messages, because we could report errors only with respect to the expanded syntax, instead of what
#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:13 goldfire]: the user actually wrote. My gut feeling (by all means correct me if I'm wrong!) is that this would still amount to a more elegant solution, everything considered. We would have to extend `HsSyn` to retain the original (sugared) notation, and treat such annotated syntax specially when printing error messages, but as far as type checking etc. are concerned, I would expect this to be mostly transparent. Personally, I wouldn't even mind getting error messages in desugared form, but I can understand if others feel strongly about this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

As a short term fix how bad would it be to make `-fdefer-type-errors` incompatible with GHCi?
We could apply that fix to HEAD (until we fix this ticket properly) and
#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:16 simonpj]: perhaps even to 8.4.3. I wouldn't be surprised to find that this breaks someone's workflow. Maybe we could get some opinions on this from the community? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by elaforge): Surely those people's workflows are already broken by the fact that you can't evaluate much of anything without causing a panic. If they are just loading the modules to check types and not actually running them, then they don't need `-fdefer-type-errors` in the first place. So if someone's tool is thrown by an extra warning msg, they can probably just remove the flag. I also think it's reasonable to expect tools to be robust against unexpected messages at startup before the prompt comes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Surely those people's workflows are already broken by the fact that you can't evaluate much of anything without causing a panic.
If they are just loading the modules to check types and not actually running them, then they don't need `-fdefer-type-errors` in the first
#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:20 elaforge]: place. So if someone's tool is thrown by an extra warning msg, they can probably just remove the flag. I also think it's reasonable to expect tools to be robust against unexpected messages at startup before the prompt comes. The use case for `-fdefer-type-errors` is so that you can run (and test) your module even when parts of it don't typecheck yet. E.g. suppose you write this: {{{#!hs module Pluralize where suffix :: Int -> String suffix 1 = "" suffix _ = "s" pluralize :: Int -> String -> String pluralize i s = s ++ i -- TODO }}} ...then you might want to load it into GHCi to play with the `suffix` function, or you may want to run unit tests on it, even though `pluralize` doesn't work yet (and doesn't typecheck). Deferring type errors is *especially* (some would argue *only*) useful in an interactive REPL: there isn't really a sharp workflow distinction between "compile time" and "runtime", so it is less important to produce type errors at compile time. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): As discussed in Hangouts, the problem is even more specific: it only appears for expressions entered at the GHCi prompt while defer-type-errors is active. Loading modules with defer-type-errors on, then turning it off and *then* evaluating expressions at the prompt works just fine. Hence, the quick fix for 8.6 will be to selectively disable deferred type checking for expressions entered interactively. This way, we will not disrupt any workflows (the error would have appeared right there and then one way or another), while still avoiding the crash. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:22 tdammers]:
As discussed in Hangouts, the problem is even more specific: it only appears for expressions entered at the GHCi prompt while defer-type-errors is active. Loading modules with defer-type-errors on, then turning it off and *then* evaluating expressions at the prompt works just fine.
It actually turns out that this isn't the case, as the following sample GHCi session illustrates: {{{ tobias@zoidberg:~/well-typed/devel/ghc-disable-defer-type-errors/ > ghc --interactive Foo.hs -fdefer-type-errors GHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/tobias/dotfiles/ghc/.ghc/ghci.conf [1 of 1] Compiling Main ( Foo.hs, interpreted ) Ok, one module loaded. λ> test ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-unknown-linux): nameModule system $dShow_a22M Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Name.hs:241:3 in ghc:Name Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug λ> :set -fno-defer-type-errors λ> test ghc: panic! (the 'impossible' happened) (GHC version 8.4.1 for x86_64-unknown-linux): nameModule system $dShow_a289 Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/utils/Outputable.hs:1150:37 in ghc:Outputable pprPanic, called at compiler/basicTypes/Name.hs:241:3 in ghc:Name Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} However this probably just means that `:set` doesn't properly unset the `fdefer-type-errors` flag. Hmm. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): The `:set` turns out to work just fine; I trapped the DynFlags right where GHCi runs those expressions, and both flags that control deferred type errors are now forced off; yet the panic still occurs when running ghci with `-fdefer-type-errors`. From the error message, it seems to me like GHCi is trying to print a module name, but fails, and this only happens when starting up with deferred type errors. I assume the module in question is the `Foo` module just loaded. Another data point is that the panic does not occur when I change the `Foo` module like so: {{{ module Foo where test :: IO () test = return () }}} My hypothesis here is that because GHCi does not print the result of an IO action if its type is `()`, so the whole pretty-printing machinery doesn't run. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): Another data point; the Core ghci generates with `-fdefer-type-errors` is slightly different from the normal output: {{{#!diff --- Foo-defer.dump-simpl 2018-06-06 17:53:34.436841703 +0200 +++ Foo.dump-simpl 2018-06-06 19:44:00.385228438 +0200 @@ -1,39 +1,39 @@ ==================== Tidy Core ==================== -2018-06-06 15:53:34.440330463 UTC +2018-06-06 17:44:00.38910864 UTC Result size of Tidy Core = {terms: 19, types: 9, coercions: 0, joins: 0/0} --- RHS size: {terms: 4, types: 2, coercions: 0, joins: 0/0} -test :: IO Int -[GblId] -test - = break<0>() return @ IO GHC.Base.$fMonadIO @ Int (GHC.Types.I# 1#) - -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$trModule1_r1Ss :: GHC.Prim.Addr# +$trModule1_r1Sr :: GHC.Prim.Addr# [GblId, Caf=NoCafRefs, Unf=OtherCon []] -$trModule1_r1Ss = "main"# +$trModule1_r1Sr = "main"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -$trModule2_r1SD :: GHC.Types.TrName +$trModule2_r1SC :: GHC.Types.TrName [GblId, Caf=NoCafRefs, Unf=OtherCon []] -$trModule2_r1SD = GHC.Types.TrNameS $trModule1_r1Ss +$trModule2_r1SC = GHC.Types.TrNameS $trModule1_r1Sr -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$trModule3_r1SE :: GHC.Prim.Addr# +$trModule3_r1SD :: GHC.Prim.Addr# [GblId, Caf=NoCafRefs, Unf=OtherCon []] -$trModule3_r1SE = "Main"# +$trModule3_r1SD = "Main"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -$trModule4_r1SF :: GHC.Types.TrName +$trModule4_r1SE :: GHC.Types.TrName [GblId, Caf=NoCafRefs, Unf=OtherCon []] -$trModule4_r1SF = GHC.Types.TrNameS $trModule3_r1SE +$trModule4_r1SE = GHC.Types.TrNameS $trModule3_r1SD -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} Main.$trModule :: GHC.Types.Module [GblId, Caf=NoCafRefs, Unf=OtherCon []] -Main.$trModule = GHC.Types.Module $trModule2_r1SD $trModule4_r1SF +Main.$trModule = GHC.Types.Module $trModule2_r1SC $trModule4_r1SE + +-- RHS size: {terms: 4, types: 2, coercions: 0, joins: 0/0} +test :: IO Int +[GblId] +test + = break<0>() return @ IO GHC.Base.$fMonadIO @ Int (GHC.Types.I# 1#) }}} The only differences however are due to uniques not matching up, and putting `main` first instead of last. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): However the dumped Core for the interactive expression itself seems to depend only on whether type error deferring was active while loading the module. Evaluating `test` interactively without `-fdefer-type-errors`: {{{ ==================== Simplified expression ==================== GHC.Base.returnIO @ [()] (GHC.Types.: @ () ((GHC.Base.. @ (GHC.Types.IO GHC.Base.String) @ (GHC.Types.IO GHC.Base.String) @ [GHC.Types.Char] (GHC.GHCi.ghciStepIO @ GHC.Types.IO GHC.GHCi.$fGHCiSandboxIOIO @ GHC.Base.String) (\ (s_a1z7 :: [GHC.Types.Char]) -> GHC.Base.$ @ 'GHC.Types.LiftedRep @ [GHC.Types.Char] @ (GHC.Types.IO GHC.Base.String) (GHC.Base.return @ GHC.Types.IO GHC.Base.$fMonadIO @ [GHC.Types.Char]) (GHC.Base.++ @ GHC.Types.Char (GHC.CString.unpackCString# ":! pointfree \""#) (GHC.Base.++ @ GHC.Types.Char s_a1z7 (GHC.CString.unpackCString# "\""#))))) `cast` (UnsafeCo representational (GHC.Base.String -> GHC.Types.IO GHC.Base.String) () :: (GHC.Base.String -> GHC.Types.IO GHC.Base.String) ~R# ())) (GHC.Types.[] @ ())) }}} With `-fdefer-type-errors`: {{{ ==================== Simplified expression ==================== GHC.Base.bindIO @ GHC.Types.Int @ [()] (GHC.GHCi.ghciStepIO @ GHC.Types.IO GHC.GHCi.$fGHCiSandboxIOIO @ GHC.Types.Int Main.test) (\ (it_a1CU :: GHC.Types.Int) -> GHC.Base.thenIO @ () @ [()] (System.IO.print @ GHC.Types.Int $dShow_a1Rt it_a1CU) (GHC.Base.returnIO @ [()] (GHC.Types.: @ () (it_a1CU `cast` (UnsafeCo representational GHC.Types.Int () :: GHC.Types.Int ~R# ())) (GHC.Types.[] @ ())))) }}} Whether I issue `:set -fno-defer-type-errors` before invoking `test` or not makes absolutely no difference. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:26 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by oerjan): * cc: oerjan (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): I've done some more dumping. The situation can be traced back to the desugar phase at least. In all 4 test cases, I did the same thing: - start up `ghci` on the `Foo.hs` module, with `-fforce-recomp -ddump-ds -dsuppress-all`; adding `-fdefer-type-errors` or not depending on the test case. - depending on the test case, `:set -fno-defer-type-errors` or `-fdefer- type-errors` to override the command-line setting - evaluate `test` in `ghci` It turns out that the desugared output is almost entirely identical (save for mismatching Uniques), except for the final GHCI invocation of `test`. The desugared output for that is identical between the three cases that involve deferred type errors anywhere, but different for the case that doesn't defer type errors anywhere. To wit: With deferred type errors in either or both module compilation and interactive session: {{{ ==================== Desugared ==================== bindIO (let { $dShow_a1Rt $dShow_a1Rt = $fShowInt } in (\ @ a_a1Dg -> let { $dGHCiSandboxIO_a1Di $dGHCiSandboxIO_a1Di = $fGHCiSandboxIOIO } in ghciStepIO $dGHCiSandboxIO_a1Di) test) (\ it_a1CU -> thenIO (print $dShow_a1Rt it_a1CU) (returnIO (: (unsafeCoerce# it_a1CU) []))) }}} Without deferred type errors: {{{ ==================== Desugared ==================== let { $dShow_a1Rq $dShow_a1Rq = $fShowInt } in bindIO ((\ @ a_a1De -> let { $dGHCiSandboxIO_a1Dg $dGHCiSandboxIO_a1Dg = $fGHCiSandboxIOIO } in ghciStepIO $dGHCiSandboxIO_a1Dg) test) (\ it_a1CT -> thenIO (print $dShow_a1Rq it_a1CT) (returnIO (: (unsafeCoerce# it_a1CT) []))) }}} Ignoring uniques entirely, the only real difference is whether or not the `dShow...` binding is floated out. So the questions are: why does it get floated out when type errors are deferred; and how does that lead to GHC calling `nameModule` on the `dShow...` part. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): But wait! The version with `-fdefer-type-errors` is actually horribly wrong, because `dShow_...` is used outside of the `let` binding that defines it! This cannot possibly work, can it? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The code in `TcUnify` described in comment:8 is {{{ implicationNeeded skol_tvs given | null skol_tvs , null given = -- Empty skolems and givens do { tc_lvl <- getTcLevel ; if not (isTopTcLevel tc_lvl) -- No implication needed if we are then return False -- already inside an implication else do { dflags <- getDynFlags -- If any deferral can happen, -- we must build an implication ; return (gopt Opt_DeferTypeErrors dflags || gopt Opt_DeferTypedHoles dflags || gopt Opt_DeferOutOfScopeVariables dflags) } } }}} So you have to switch of all three of `Opt_DeferTypeErrors`, `Opt_DeferTypedHoles` and `Opt_DeferOutOfScopeVariables`. But NB that ''the first implies the other two''; so I guess that you need to switch all three of them off in the workaround. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: new Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by tdammers): OK, disabling all three does indeed "fix" it. Patch incoming. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D4833 Wiki Page: | -------------------------------------+------------------------------------- Changes (by tdammers): * testcase: => ghci/should_run/T14963 * status: new => patch * differential: => D4833 Comment: I have put up a patch (https://phabricator.haskell.org/D4833), however it turns out that while disabling these three flags for interactive statements avoids the panic, it also seems to break a number of other tests. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): D4833 D4830 Wiki Page: | -------------------------------------+------------------------------------- Changes (by tdammers): * differential: D4833 => D4833 D4830 Comment: D4830 looks like a cleaner solution than D4833; suggest we run with the former. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4833 Wiki Page: | Phab:D4830 -------------------------------------+------------------------------------- Changes (by sighingnow): * differential: D4833 D4830 => Phab:D4833 Phab:D4830 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4833 Wiki Page: | Phab:D4830 -------------------------------------+------------------------------------- Comment (by tdammers): Quick thought on the side: `-fdefer-type-errors` currently implies `-fdefer-type-holes` and `-fdefer-out-of-scope-variables`, which makes sense; however, the way implied flags currently work in GHC leads to unexpected results in GHCi when you turn a flag on and then off again. You'd expect `:set -fdefer-type-errors; :set -fno-defer-type-errors` to be a no-op, but it's not, because it turns `-fdefer-type-holes` and `-fdefer- out-of-scope-variables` on and never off again. So my thought was that maybe it would be better to use two sets of `DynFlags` here: one set to represent what the user explicitly requested, not setting any of the implied flags; and one set of "effective" flags, containing the explicitly requested ones plus all the implied ones. The latter would be calculated on the fly, just before compiling, based on the former. This way, we can trivially tell the difference between flags explicitly requested by the user, and flags that are active because some other flag implies them, and unsetting the explicit flag will take the implicit flags with it unless they were also requested explicitly. If people think this would make sense, I'll file it as a separate ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4833 Wiki Page: | Phab:D4830 -------------------------------------+------------------------------------- Comment (by simonpj): Let's not go overboard on this. At the moment we are just implementing a workaround for a bug that we will fix. Moreover the workaround is a one- line addition to Phab:D4830. DO we need to do more? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4833 Wiki Page: | Phab:D4830 -------------------------------------+------------------------------------- Comment (by tdammers): Replying to [comment:36 simonpj]:
Let's not go overboard on this. At the moment we are just implementing a workaround for a bug that we will fix. Moreover the workaround is a one-line addition to Phab:D4830. DO we need to do more?
Oh, of course the proposal is not going to help with the issue at hand. I just noticed some unintuitive behavior, and a possible fix. If it's not deemed fix-worthy, then you'll never hear me about it again. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module
-------------------------------------+-------------------------------------
Reporter: elaforge | Owner: tdammers
Type: bug | Status: patch
Priority: high | Milestone: 8.4.2
Component: GHCi | Version: 8.4.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| ghci/should_run/T14963
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D4833
Wiki Page: | Phab:D4830
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4833 Wiki Page: | Phab:D4830 -------------------------------------+------------------------------------- Changes (by Remi): * cc: remi.turk@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14963: ghci -fdefer-type-errors can't run IO action from another module -------------------------------------+------------------------------------- Reporter: elaforge | Owner: tdammers Type: bug | Status: patch Priority: high | Milestone: 8.4.2 Component: GHCi | Version: 8.4.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ghci/should_run/T14963 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D4833 Wiki Page: | Phab:D4830 -------------------------------------+------------------------------------- Comment (by goldfire): See #15598 for another example of trouble in this water. That example might be simpler than this one. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14963#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC