[GHC] #11120: Missing type representations

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 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 Rev(s): | Wiki Page: -------------------------------------+------------------------------------- When I say {{{ {-# LANGUAGE DataKinds #-} module Bug where import Data.Typeable foo = typeRep (Proxy :: Proxy '[]) }}} I get {{{ GHC error in desugarer lookup in Bug: Can't find interface-file declaration for variable tc'[] Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20151120 for x86_64-apple-darwin): initDs IOEnv failure }}} And I think there may be more trouble. Below are notes I have written to ghc-devs: ------------------------------ I'm a bit confused by the new handling of `Typeable`. 1. You say (in `Note [Grand plan for Typeable]`) that there is trouble making the `TyCon`/`Module` information for the types in `GHC.Types`. But what precisely goes wrong? I agree that it seems a bit fishy, but I don't actually see the spot where trouble lurks. Did you try this? 2. Even more bizarre would be putting `TyCon`/`Module` info for `GHC.Prim` stuff (I'm thinking about the super-magical `TYPE` from my branch) right in `GHC.Prim`. But still I can't quite articulate what goes wrong. There is no Prim.hi file that would be wonky. And, provided that `GHC.Types` itself doesn't try to solve a `Typeable` constraint, no one would ever notice the weird dependency. I recognize that this means we'd have to build the info somewhere manually in GHC, but I don't think that would be too hard -- and I think easier than the current story around name-mangling just so that you can write the typereps by hand in `Data.Typeable.Internal`. There's also not very many lifted tycons in `GHC.Prim`. I count `TYPE` and `RealWorld`, and that's it. For what it's worth, a weird dependency from `GHC.Prim` to `GHC.Types` actually works in practice. I put `Levity` in `GHC.Types` but `TYPE :: Levity -> TYPE 'Lifted` in `GHC.Prim`. No one complained. 3. Let's assume that we really can't clean up this mess. It still seems that several `TyCon`s are missing from `Data.Typeable.Internal`. Like promoted nil and cons, and `Nat`, and `Symbol`. At the least, we should put a loud comment in the export list of `GHC.Types` saying that everything defined there must be accompanied by a definition in `Data.Typeable.Internal`. 4. `Data.Typeable.Internal` uses `mkGhcTypesTyCon`, which refers to `GHC.Types`. But this function is used also for things from `GHC.Prim`, like `(->)`. Solving `Typeable (->)` works fine. But I'm sure there's trouble lurking here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): While I'm learning more about this, I stumbled across the following, in !TcTypeable: {{{#!hs mkTyConRepBinds :: TypeableStuff -> TyCon -> LHsBinds Id mkTyConRepBinds (dflags, mod_expr, pkg_str, mod_str, tr_datacon, trn_datacon) tycon = ... where Fingerprint high low | gopt Opt_SuppressUniques dflags = Fingerprint 0 0 | otherwise = fingerprintString hashThis }}} That looks like the tycon's fingerprint is bogus whenever the module is compiled with `-dsuppress-uniques`. But I always understood `-dsuppress- uniques` to be a flag used only to control output, and that it should affect only the pretty-printer. So I'm very dubious of this code. However, in looking through !TcTypeable, I understand why you're worried about typerep-generation in GHC.Types: this module looks up the datacons, etc., from the type environment. I had blithely assumed that the typerep types were truly wired in, in all their glory, making the lookup unnecessary. Looking them up never even occurred to me. So: Is it better to 1. look them up, forgo wiring in all the details, and have special-casing around GHC.Prim and GHC.Types? or 2. wire them in fully, but then have a much simpler story around GHC.Types and GHC.Prim. But now at least I understand what the tradeoff is (I think). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
1. You say (in Note [Grand plan for Typeable]) that there is trouble making the TyCon/Module information for the types in GHC.Types. But what precisely goes wrong? I agree that it seems a bit fishy, but I don't actually see the spot where trouble lurks. Did you try this?
The difficulty is we can't generate the `TyCon` and `Module` for things in `GHC.Types` when `TyCon` and `Module` are not yet defined. The Grand Plan comment says: It's hard to generate the TyCon/Module bindings when the types TyCon and Module aren't yet available; i.e. when compiling GHC.Types Now what we ''could'' do (and it'd probably be a goodea) would be to put * TyCon * Module * Char * List * TrName in `GHC.Types`, and move the other types (eg `Float`, `Double`) out, so that their type-reps *can* be derived by the normal mechanism.
3. Let's assume that we really can't clean up this mess. It still seems that several TyCons are missing from Data.Typeable.Internal. Like promoted nil and cons, and Nat, and Symbol. At the least, we should put a loud comment in the export list of GHC.Types saying that everything defined there must be accompanied by a definition in Data.Typeable.Internal.
You are right. The above might ameliorate the problem. If it'd make your kind-equality work easier by all means do this.
2. Even more bizarre would be putting TyCon/Module info for GHC.Prim stuff (I'm thinking about the super-magical TYPE) right in GHC.Prim.
But currently `TyCon` uses list and `Char`. Do you want to put them in `GHC.Prim`? How would that differ, really, from what we have now. And `TyCon` and `Module` both require actual code, whereas `GHC.Prim` types have no code. To respond to your suggestion more clearly I'd need more info on what you have in mind.
4. `Data.Typeable.Internal` uses `mkGhcTypesTyCon`, which refers to `GHC.Types`
I don't understand the issue here.
That looks like the tycon's fingerprint is bogus whenever the module is compiled with `-dsuppress-uniques`. But I always understood `-dsuppress- uniques` to be a flag used only to control output, and that it should affect only the pretty-printer. So I'm very dubious of this code.
Good point. But failing to suppress means that `-ddump-simpl` will show some unique values. Maybe that's ok. It's mainly use to reduce test- suite wobbles. I'm honestly not sure what to do here, but not too bothered either way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Replying to [comment:2 simonpj]:
1. You say (in Note [Grand plan for Typeable]) that there is trouble making the TyCon/Module information for the types in GHC.Types. But what precisely goes wrong? I agree that it seems a bit fishy, but I don't actually see the spot where trouble lurks. Did you try this?
The difficulty is we can't generate the `TyCon` and `Module` for things in `GHC.Types` when `TyCon` and `Module` are not yet defined.
Perhaps I'm being dense, but why is this problematic? What panic or other undesirable situation will arise? To be clear: I'm proposing to keep `TyCon` and `Module` and such in `GHC.Types`. But also to put the representations for things defined in `GHC.Types` in `GHC.Types`.
The Grand Plan comment says:
It's hard to generate the TyCon/Module bindings when the types TyCon and Module aren't yet available; i.e. when compiling GHC.Types
Now what we ''could'' do (and it'd probably be a goodea) would be to put * TyCon * Module * Char * List * TrName
in `GHC.Types`,
These are already in `GHC.Types`.
and move the other types (eg `Float`, `Double`) out, so that their type-reps *can* be derived by the normal mechanism.
That seems possible. But I don't think it's necessary, as I've explained above.
3. Let's assume that we really can't clean up this mess. It still
seems
that several TyCons are missing from Data.Typeable.Internal. Like promoted nil and cons, and Nat, and Symbol. At the least, we should put a loud comment in the export list of GHC.Types saying that everything defined there must be accompanied by a definition in Data.Typeable.Internal.
You are right. The above might ameliorate the problem. If it'd make your kind-equality work easier by all means do this.
This isn't holding me up. I just had to shuffle a bunch of `GHC.Types` and `GHC.Prim` stuff around and wanted to do it right, so I had to understand the `Typeable` stuff. And that led to questions.
2. Even more bizarre would be putting TyCon/Module info for GHC.Prim stuff (I'm thinking about the super-magical TYPE) right in GHC.Prim.
But currently `TyCon` uses list and `Char`. Do you want to put them in
`GHC.Prim`? No. I want definitions in `GHC.Prim` to depend on `TyCon` and friends, which would remain in `GHC.Types`. This is highly bizarre. But it doesn't seem to break anything. And indeed I have this in my branch (`TYPE` is in `GHC.Prim` but `Levity` is in `GHC.Types`) and nothing complains.
How would that differ, really, from what we have now.
And `TyCon` and `Module` both require actual code, whereas `GHC.Prim` types have no code.
Yes, my proposal means hard-coding `TyCon`s for `TYPE` and `#` (the only lifted types left in `GHC.Prim` in my branch). These would be `Id`s in `MkId` presumably.
To respond to your suggestion more clearly I'd need more info on what you have in mind.
4. `Data.Typeable.Internal` uses `mkGhcTypesTyCon`, which refers to
`GHC.Types`
I don't understand the issue here.
`mkGhcTypesTyCon` uses `GHC.Types` as the module whenever it's used. But sometimes it's for `GHC.Prim` types, not `GHC.Types` types.
That looks like the tycon's fingerprint is bogus whenever the module
is compiled with `-dsuppress-uniques`. But I always understood `-dsuppress-uniques` to be a flag used only to control output, and that it should affect only the pretty-printer. So I'm very dubious of this code.
Good point. But failing to suppress means that `-ddump-simpl` will show
some unique values. Maybe that's ok. It's mainly use to reduce test- suite wobbles. I'm honestly not sure what to do here, but not too bothered either way. But isn't the fingerprint Very Important? As in: don't we rely critically on fingerprints being unique when doing type comparison? If I understand this correctly, the current implementation means that `-dsuppress-uniques` makes the whole `Typeable` story unsound. And `-dsuppress-uniques` is meant to be a pretty-printing flag. To reduce testsuite wibbles, we should just add something to the post- processor we already have. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): It seems like this might be worth trying to fix for 8.0.
Perhaps I'm being dense, but why is this problematic? What panic or other undesirable situation will arise? To be clear: I'm proposing to keep `TyCon` and `Module` and such in `GHC.Types`. But also to put the representations for things defined in `GHC.Types` in `GHC.Types`.
I can't think of any reason why this should be tricky. Simon, perhaps you could elaborate on the reasons for this being so tricky?
But isn't the fingerprint Very Important? As in: don't we rely critically on fingerprints being unique when doing type comparison? If I understand this correctly, the current implementation means that `-dsuppress-uniques` makes the whole Typeable story unsound. And `-dsuppress-uniques` is meant to be a pretty-printing flag.
Indeed this is quite an unexpected effect for what ought to be a debugging flag. I've opened Phab:D1629 replacing the bogus fingerprint logic with a testsuite normaliser. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I think the high-priority bits here are `-dsuppress-uniques` issue (already ably addressed in Phab:D1629) and the missing definitions in `Data.Typeable.Internal`. I'm a little worried about `mkGhcTypesTyCon` using the wrong module name for the `GHC.Prim` stuff, but I don't actually think anyone will trip over it. I think removing the `GHC.Types` special case would be great, but that's merely a refactoring and need not be done for 8.0. So, TODO: Make sure all types (and data constructors) exported from `GHC.Types` have representations in `Data.Typeable.Internal`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The `-dsuppress-uniques` issue has been addressed by D1629, which was merged in 786d528e8f949daeb62d34e0daa5e35f642065fc. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: => Phab:D1769 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => patch -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Description changed by bgamari: Old description:
When I say
{{{ {-# LANGUAGE DataKinds #-}
module Bug where
import Data.Typeable
foo = typeRep (Proxy :: Proxy '[]) }}}
I get
{{{ GHC error in desugarer lookup in Bug: Can't find interface-file declaration for variable tc'[] Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20151120 for x86_64-apple-darwin): initDs IOEnv failure }}}
And I think there may be more trouble. Below are notes I have written to ghc-devs:
------------------------------
I'm a bit confused by the new handling of `Typeable`.
1. You say (in `Note [Grand plan for Typeable]`) that there is trouble making the `TyCon`/`Module` information for the types in `GHC.Types`. But what precisely goes wrong? I agree that it seems a bit fishy, but I don't actually see the spot where trouble lurks. Did you try this?
2. Even more bizarre would be putting `TyCon`/`Module` info for `GHC.Prim` stuff (I'm thinking about the super-magical `TYPE` from my branch) right in `GHC.Prim`. But still I can't quite articulate what goes wrong. There is no Prim.hi file that would be wonky. And, provided that `GHC.Types` itself doesn't try to solve a `Typeable` constraint, no one would ever notice the weird dependency. I recognize that this means we'd have to build the info somewhere manually in GHC, but I don't think that would be too hard -- and I think easier than the current story around name-mangling just so that you can write the typereps by hand in `Data.Typeable.Internal`. There's also not very many lifted tycons in `GHC.Prim`. I count `TYPE` and `RealWorld`, and that's it.
For what it's worth, a weird dependency from `GHC.Prim` to `GHC.Types` actually works in practice. I put `Levity` in `GHC.Types` but `TYPE :: Levity -> TYPE 'Lifted` in `GHC.Prim`. No one complained.
3. Let's assume that we really can't clean up this mess. It still seems that several `TyCon`s are missing from `Data.Typeable.Internal`. Like promoted nil and cons, and `Nat`, and `Symbol`. At the least, we should put a loud comment in the export list of `GHC.Types` saying that everything defined there must be accompanied by a definition in `Data.Typeable.Internal`.
4. `Data.Typeable.Internal` uses `mkGhcTypesTyCon`, which refers to `GHC.Types`. But this function is used also for things from `GHC.Prim`, like `(->)`. Solving `Typeable (->)` works fine. But I'm sure there's trouble lurking here.
New description: When I say {{{#!hs {-# LANGUAGE DataKinds #-} module Bug where import Data.Typeable foo = typeRep (Proxy :: Proxy '[]) }}} I get {{{ GHC error in desugarer lookup in Bug: Can't find interface-file declaration for variable tc'[] Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.11.20151120 for x86_64-apple-darwin): initDs IOEnv failure }}} And I think there may be more trouble. Below are notes I have written to ghc-devs: ------------------------------ I'm a bit confused by the new handling of `Typeable`. 1. You say (in `Note [Grand plan for Typeable]`) that there is trouble making the `TyCon`/`Module` information for the types in `GHC.Types`. But what precisely goes wrong? I agree that it seems a bit fishy, but I don't actually see the spot where trouble lurks. Did you try this? 2. Even more bizarre would be putting `TyCon`/`Module` info for `GHC.Prim` stuff (I'm thinking about the super-magical `TYPE` from my branch) right in `GHC.Prim`. But still I can't quite articulate what goes wrong. There is no Prim.hi file that would be wonky. And, provided that `GHC.Types` itself doesn't try to solve a `Typeable` constraint, no one would ever notice the weird dependency. I recognize that this means we'd have to build the info somewhere manually in GHC, but I don't think that would be too hard -- and I think easier than the current story around name-mangling just so that you can write the typereps by hand in `Data.Typeable.Internal`. There's also not very many lifted tycons in `GHC.Prim`. I count `TYPE` and `RealWorld`, and that's it. For what it's worth, a weird dependency from `GHC.Prim` to `GHC.Types` actually works in practice. I put `Levity` in `GHC.Types` but `TYPE :: Levity -> TYPE 'Lifted` in `GHC.Prim`. No one complained. 3. Let's assume that we really can't clean up this mess. It still seems that several `TyCon`s are missing from `Data.Typeable.Internal`. Like promoted nil and cons, and `Nat`, and `Symbol`. At the least, we should put a loud comment in the export list of `GHC.Types` saying that everything defined there must be accompanied by a definition in `Data.Typeable.Internal`. 4. `Data.Typeable.Internal` uses `mkGhcTypesTyCon`, which refers to `GHC.Types`. But this function is used also for things from `GHC.Prim`, like `(->)`. Solving `Typeable (->)` works fine. But I'm sure there's trouble lurking here. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: patch
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1769
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: patch
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1769
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Commit is good. But we should keep this ticket open, or open a new one, to do this in a better way. There is much in comment:3 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This might have been mentioned already (hard to tell, since I don't really understand the technical details here), but it's still possible to trigger GHC panics pretty easily due to (what I assume are) inadequate type representations: {{{ $ inplace/bin/ghc-stage2 --interactive GHCi, version 8.1.20160113: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /nfs/nfs4/home/rgscott/.ghci λ> :set -XTypeInType -XMagicHash λ> :m + Data.Typeable GHC.Prim GHC.Exts λ> data CharHash = CharHash Char# λ> typeOf (Proxy :: Proxy 'CharHash) ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160109 for x86_64-unknown-linux): tyConRep Char# Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug λ> typeOf (Proxy :: Proxy 'C#) GHC error in desugarer lookup in Ghci2: Can't find interface-file declaration for variable tc'C# Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.1.20160109 for x86_64-unknown-linux): initDs IOEnv failure Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Oh dear, yes, I suppose we need to handle everything in `GHC.Prim` as well. If we include all of the generated SIMD types this adds up to a substantial amount of work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): So I have a very rough cut of Richard's proposal. The primary wrinkle that I ran into here is that you are forced to produce the `GHC.Prim` representations as `CoreExpr`s in order to wire them in (as wired-in identifiers are just identifiers without a definition but instead a compulsory unfolding, which is Core). This is a bit unfortunate as in the usual case we produce representations as standard `HsExpr`s, meaning we must duplicate the code for producing type representations. There are three options I can see here, 1. Accept the code duplication and move on with life 2. Use compulsory unfoldings for all type representations, allowing us to drop the current `HsExpr` logic in `TcTypeable` 3. Instead make the `GHC.Prim` representations merely known-key and inject the bindings into some other module (like `GHC.Types`, since `GHC.Prim` doesn't have associated object code). This means we'd keep some of the special-case that we currently have, but on the other hand we could drop the hand-written type representations. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): While looking for another bug I stumbled upon #10343, which describes another, related hole in our typeable story: there is no way to extract a representation of the kind of a type. This seems quite straightforward to provide. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Yes, please! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1769 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): We appear to be on to Phab:D1774 now, correct? Change the Phab link? Like Richard I'm getting lost. That Phab seems to be spiraling out of control. Let's take one thing at at time. * Is `Proxy Char#` a valid type? Not currently: we get {{{ Illegal unlifted type: Char# }}} But there is no reason for this to be rejected! `Proxy :: forall k. k ->*`, and I see no reason why we can't instantiate `k` with `TYPE Unlifted`. Looking further, the error message comes not from the kind- unifier, but later in `TcValidity`; see `check_lifted`. I think we can probably simply remove all calls to `check_lifted`. * Can you have `TypeRep Char#` or `typeRep @Char#`, or `Typeable Char#`. Again, you can't right now, but actually I think you could; they are all kind-polymorphic, and the instantiating kind could be `TYPE Unlifted`. * If we did, we might be faced with solving `Typeable Char#`. That would mean adding a type rep for `Char#`; but we could simply make it insoluble for now, and report a type error. * Could solving `Typeable Char#` come up in GHC today (i.e. without fixing `TcValidity`)? Yes: consider `typeRep (undefined :: Proxy (Char# -> Int)`. Nothing wrong with that on the face of it. So we generate `Typeable (Char# -> Int)` constraint, and then decompose to `Typeable Char#` and `Typeable Int`. And then we fail in solving `Typeable Char#` * What about ''promoted'' data constructors? {{{ data CH = DCH Char# }}} Now suppose (comment:14) that we ask for `typeOf (Proxy :: Proxy 'DCH)`. This gives `Typeable 'DCH`. At the moment I can't see why that would need a type-rep for `Char#` as comment:14 suggests. Any ideas? So my proposal is: * Let's NOT (yet) have type-reps for primitive types * Let's fix the Typeable solver so that it fails gracefully on `Typeable Char#`. * And let's try the effect of removing the `check_unlifted` in `TcValidity`. Would that be a good start? That still leaves open the questions in comment:3. But first things first. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * differential: Phab:D1769 => Phab:D1774 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
Like Richard I'm getting lost. That Phab seems to be spiraling out of control. Let's take one thing at at time.
Indeed, that is my fault for conflating several concerns. The situation isn't as complex as it appears. To recap, * Phab:D1774 is primarily a refactoring of how we produce representations for types that were previously handled explicitly in `Data.Typeable.Internal`. In particular, instead of writing them by hand we now lead their production to the compiler. This is a significant simplification from the previous scheme as its almost entirely consistent with the codepath used for user-defined types. * This new approach also allows us to trivially produce representations for the primitive types in `GHC.Prim` without the boiler-plate required previously. * All of the above currently works. * The kind representation work is quite unrelated to the Phab:D1774 (although perhaps made easier by it) * I have also not touched the `TcValidity` check although was asking about it on the Diff, which caused a bit of confusion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Fully agreed with all points in comment:19. And, in response to comment:21, the !TcValidity check is not new. But, as Simon suggests, it may have outlived its usefulness. Does it date back to some point in prehistory when the kind system didn't distinguish `*` from `#`? It seems like it to me (though I haven't actually looked through the history). In any case, let's resolve type representations on this ticket by either getting representation for `Char#` and the like, or gracefully erroring. (I prefer the latter, given the date.) Then we can post a new ticket to look into the !TcValidity issue. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: patch
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1774
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: patch Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The TcValidity issue is now being tracked on #11465. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:25 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: merge
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1774
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: "Rework derivation of type representations for wired-in things" merged to `ghc-8.0` as 19dc3cb3a73f72d62bc758e73a1fb3fee5039185. There is, however, more to this story. Simon's removal of the `check_lifted` checks have uncovered some deeper issues. See #11465 for details. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:27 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by luite): Unfortunately the fix breaks cross compilation due to a hardcoded `WORD_SIZE_IN_BITS` dependency in `TysWiredIn`. If the cross compilation target has a different word size than the build machine, the types become inconsistent. (This makes GHCJS unusable with a 64 bit GHC 8.0.1rc2; it fails to compile `ghc-prim`) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:28 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by rwbarton): * status: closed => new * resolution: fixed => -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:29 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: luite, I'm afraid I'll need a bit more detail. On looking at this it appears that `WORD_SIZE_IN_BITS` should be the word size of the target, so I don't see what could be going on here. Can you open another ticket describing the issue that you are observing in detail? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:30 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by luite): Oh I'm sorry, I expected the problem to be known due to the `TODO: This should be for the target, no?` remark in the code. GHCJS configures the GHC API through `DynFlags` to produce 32 bit code. The GHC code was reworked to support changing the target dynamically. For example in `PrelRules` the `WORD_SIZE_IN_BITS` constant was replaced by `wordSizeInBits dflags`(which in turn uses `targetPlatform` from `dflags`) in various places. Unfortunately the use of the `WORD_SIZE_IN_BITS` macro in `TysWiredIn` means that `TyCon` gets `Word#` fields with a 64 bit GHC library, even if `wordSizeInBits dflags == 32`. It should get `Word64#` fields. GHC should really use the `DynFlags` word size value in `trTyConDataCon` (similar to for example `PrelRules.shiftRightLogical`) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:31 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The code is {{{ trTyConDataCon :: DataCon trTyConDataCon = pcDataCon trTyConDataConName [] [fprint, fprint, trModuleTy, trNameTy] trTyConTyCon where -- TODO: This should be for the target, no? #if WORD_SIZE_IN_BITS < 64 fprint = word64PrimTy #else fprint = wordPrimTy #endif }}} Question: why is `trTyConTyCon` wired in at all? Its only use is in `TcTypeable` which could perfectly well look it up in the envt (it would need to be a known-key name). We should never wire-in type constructors without a pressing reason. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:32 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I suspect that simonpj is right and we can get away without wiring in `TyCon`. I'll quickly give this a shot. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:33 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The principle difficulty here is the following: * The first thing that we do during type checking is construct a `GHC.Types.Module` binding to represent the module being compiled. This is necessary since we must refer to this binding when generating implicits for the data types which we later typecheck * When we compile `GHC.Types` `Module` is not yet in scope, since it is defined in the module we are currently compiling Similar issues occur with the `TyCon` and `TrName` types. I thought it would be possible to finagle the order of typechecking such that we could ensure that everything was in scope when needed. After playing around with a few ideas I suspect that, while this might be possible, the result will be too fragile to offset the benefit of unwiring these types. Sadly wiring-in really does seem like the simplest option here. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:34 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I've put up the quick, easy, but dirty approach to fixing this as Phab:D1904. It's really quite foul, but I'm not sure I see a better way. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:35 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
* When we compile `GHC.Types` `Module` is not yet in scope, since it is defined in the module we are currently compiling
Yes it is! We typecheck the module before generating those extra bindings. So the definitions will be in the type environment, won't they. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:36 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
Yes it is! We typecheck the module before generating those extra bindings.
Hmm, in that case I'm a bit stumped as to why my `wip/typeable-unwired` branch fails while building `GHC.Types` with, {{{ libraries/ghc-prim/GHC/Types.hs:1:1: error: GHC internal error: ‘TyCon’ is not in scope during type checking, but it passed the renamer }}} This appears to occur at some point between the `Tc3` and `Tc4` trace points. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:37 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
Yes it is! We typecheck the module before generating those extra bindings. So the definitions will be in the type environment, won't they?
Ahh, I think we were talking about different things. The `TyCon` bindings are indeed generated after type checking the module's type declarations. However, this is not the case for the `Module` binding: Generating it is literally the first thing done by `tcRnSrcDecls`, {{{#!hs tcRnSrcDecls explicit_mod_hdr decls = do { -- Create a binding for $trModule -- Do this before processing any data type declarations, -- which need tcg_tr_module to be initialised ; tcg_env <- mkModIdBindings ; tcg_env <- setGblEnv tcg_env mkPrimTypeableBinds -- Do all the declarations ; ((tcg_env, tcl_env), lie) <- setGblEnv tcg_env $ captureConstraints $ do { (tcg_env, tcl_env) <- tc_rn_src_decls decls ; ; tcg_env <- setEnvs (tcg_env, tcl_env) $ checkMain explicit_mod_hdr ; return (tcg_env, tcl_env) } ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:38 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): That's only because we do `mkTypeableBinds` on a group by group basis. Instead we could * Typecheck all the type/class decls * Do `mkModIdBindings` * Do `mkTypeableBindings` That might also mean that we could generate type representations for all types in `GHC.Types` instead of the weird stuff that happens now, with them being manually defined elsewhere -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:39 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
That's only because we do mkTypeableBinds on a group by group basis.
That might also mean that we could generate type representations for all types in `GHC.Types` instead of the weird stuff that happens now, with
That is a fair point. I can give this a try. them being manually defined elsewhere Actually since my refactoring there is no oddness in the handling of `GHC.Types`; since `TyCon`, et al. are wired-in we allow the usual codepath to generate the representations for types defined in this module. The only oddness at this point is the handling of `GHC.Prim`, which needs to have its representations injected into `GHC.Types`. Performing the refactoring you mention above would allow us to retain the consistent handling of `GHC.Types` while un-wiring `TyCon` and friends. Currently type constructor representations are produced by `tcAddImplicits`. Should we move the entire `tcAddImplicits` step until after all groups have been typechecked or only extract the typeable handling? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:40 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj):
Currently type constructor representations are produced by tcAddImplicits. Should we move the entire tcAddImplicits step until after all groups have been typechecked or only extract the typeable handling?
Yes I think we could do that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:41 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): I have a stab at this that seems to be compiling in Phab:D1906. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:42 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: closed
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1774
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: closed => merge Comment: luite, the above un-wired the typeable representation types and in so doing removes the ugly word-size dependence. I'll be merging this to `ghc-8.0` shortly. If you have time it would be great to know whether this is all that is necessary to get ghcjs working with the `ghc-8.0` branch. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:44 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: merge Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by luite): Thanks, I've been testing with your earlier `unsafeGlobalDynFlags` patch and I can build `ghc-prim` with that, but I'm still fighting some issues with Cabal and a problem desugaring `foreign import javascript` (looks like it's caused by the new levity arguments, this part of the desugarer is hooked, so it should be fixable on my side), causing the build to fail a little bit later. I'll rebuild using your new patch and report back as soon as I find a solution for the other things, hopefully before the weekend. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:45 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged to `ghc-8.0` as 6013321dd013aeb34f0f1a7f7c1c4cd42683ea6e. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:46 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Thanks for the update, luite. Let me know if I can be of help. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:47 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Sadly this is issue isn't quite fixed. See #12082. Happily the fix is quite simple. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:48 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => typecheck/should_run/TypeOf, typecheck/should_run/TypeRep -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:49 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: closed
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| typecheck/should_run/TypeOf,
| typecheck/should_run/TypeRep
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1774
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11120: Missing type representations
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: bug | Status: closed
Priority: high | Milestone: 8.0.1
Component: Compiler | Version: 7.11
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
| typecheck/should_run/TypeOf,
| typecheck/should_run/TypeRep
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D1774
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by magesh.b): Does this fix the representation for lifted tuple as well? I'm getting following error when tried to typeOf with lifted tuple {{{ Prelude> :set -XDataKinds Prelude> import Data.Typeable as T Prelude T> import Data.Proxy as P Prelude T P> typeOf (Proxy :: Proxy '(1,2)) GHC error in desugarer lookup in Ghci1: Can't find interface-file declaration for variable $tc'(,) Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ghc: panic! (the 'impossible' happened) (GHC version 8.0.1 for x86_64-unknown-linux): initDs IOEnv failure Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:52 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: closed => new * resolution: fixed => Comment: Fails in HEAD too. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:53 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Typeable -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:54 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: new Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): By the way, I have been slowly chipping away at this one. I suspect I'll have a fix tomorrow. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:55 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11120: Missing type representations -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: bug | Status: closed Priority: high | Milestone: 8.0.1 Component: Compiler | Version: 7.11 Resolution: fixed | Keywords: Typeable Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_run/TypeOf, | typecheck/should_run/TypeRep Blocked By: | Blocking: Related Tickets: #12132 | Differential Rev(s): Phab:D1774 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed * related: => #12132 Comment: I've opened up #12132 to track the issue in comment:52 so we can keep these issues distinct. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11120#comment:56 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC