[GHC] #9111: base should export Typeable instances of its promoted data constructors

#9111: base should export Typeable instances of its promoted data constructors ------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- As initially reported in #8486, `base` does not export `Typeable` instances for its promoted data constructors, as witnessed by this: {{{ {-# LANGUAGE DataKinds #-} import Data.Typeable x = typeRep (Proxy :: Proxy True) }}} yields {{{ No instance for (Typeable 'True) arising from a use of ‘typeRep’ In the expression: typeRep (Proxy :: Proxy True) In an equation for ‘x’: x = typeRep (Proxy :: Proxy True) }}} It is indeed possible to derive these instances locally with standalone deriving, but that seems very problematic, should multiple modules do that independently. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by aavogt): This one doesn't work with standalone deriving either: {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE StandaloneDeriving #-} import Data.Proxy import Data.Typeable y = typeRep (Proxy :: Proxy "y") deriving instance Typeable "y" }}} The message is {{{ Can't make a derived instance of ‘Typeable "y"’: The last argument of the instance must be a data or newtype application In the stand-alone deriving instance for ‘Typeable "y"’ }}} This issue breaks http://code.haskell.org/HList/examples/cmdargs.hs on ghc-7.8. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by simonpj): * cc: core-libraries-committee@… (added) Comment: What precisely is being requested here? Which instances? Would you care to offer a patch? I'm adding the core libraries committee to cc. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): My original report was intended to suggest instances for all promotable types in base/ghc-prim that export `Typeable` instances for the unpromoted types, like `[]`, `Bool`, `Maybe`, `Either`, `Ordering`, tuples, etc. While we're at it, we should probably export `Typeable` instances for ''classes'', too, like `Eq` and `Monad`, among many others. If no one sees a downside to adding these instances, I can submit a patch yes. For the problem reported in the first comment -- about a `Typeable` instance for `Symbol`s (and presumably `Nat`s) -- the implementation technique is somewhat different and might best be something for Iavor. [http://www.haskell.org/pipermail/haskell-cafe/2013-August/109993.html This message] from August 2013 suggests that he is on it, but I don't know if there has been progress since then. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): It makes sense to me that everything that can be `Typeable` should be. Even `Typeable`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): Should deriving Typeable on a type just also derive Typeable for its promoted constructors as well? That would cover most enduser use cases. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by snoyberg): Let me ask a possibly absurd question: should GHC just automatically derive Typeable for every single type, regardless of the presence of a deriving Typeable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): It would be a lot less brittle than the current situation. Every time I turn around some package I need forgot to write the instance. The safety of Typeable comes from the Typeable requirement at the use site. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Deriving `Typeable` automatically is exactly what `AutoDeriveTypeable` is for (see [http://www.haskell.org/ghc/docs/latest/html/users_guide/deriving.html #auto-derive-typeable user manual]) Moreover the manual claims that `AutoDeriveTypeable` will also derive `Typeable` for the promoted data constructors. I think we should probably switch it on for the entire `base` package, and the chair of the core libraries committee seems to agree. That would be simpler than a lot of ad-hoc instances. (Indeed I kind of wonder '''whether it is ever useful NOT to derive `Typeable`'''? If not, we could just derive `Typeable` automatically for everything. In implementation terms it would mean we could get rid of all the instance declarations in the interface file, since they would all be there by implication.) Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by hvr): Replying to [comment:8 simonpj]:
I think we should probably switch it on for the entire `base` package, and the chair of the core libraries committee seems to agree. That would be simpler than a lot of ad-hoc instances.
Btw, I just tried to enable it globally in order to get a list of additional `Typeable` instances becoming available by that, but you have to avoid using `AutoDeriveTypeable` at the same time with `NoImplicitPrelude`, as otherwise you get the error {{{ Failed to load interface for ‘Data.Typeable.Internal’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by hvr): Replying to [comment:9 hvr]:
have to avoid using `AutoDeriveTypeable` at the same time with `NoImplicitPrelude`, as otherwise you get the error
Nevermind that, as all modules in `base` obviously have to have `NoImplicitPrelude` on. There's something else causing that error, as `Data.Monoid` and `Control.Applicative` work fine having `AutoDeriveTypeable` and `NoImplicitPrelude` enabled at the same time. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by goldfire): See [https://ghc.haskell.org/trac/ghc/ticket/8950#comment:7 this comment] in #8950. I can't quite tell there if `AutoDeriveTypeable` derives for promoted data constructors without `DataKinds`. Would universally deriving `Typeable` break some abstraction guarantees? That is, if a library wanted to hide some types, could they be gotten through their (unhideable) `Typeable` instances? Template Haskell can surely do this, but I might be willing to ignore that particular attack. Are there others? What if a type is known but not the constructors? (I don't think `Typeable` can do this.) What about if a type synonym is known but the RHS isn't exported? (I bet it can do this.) I'm not strongly against this idea, but I just want to understand the ramifications of it. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Would universally deriving `Typeable` break some abstraction guarantees? That is, if a library wanted to hide some types, could they be gotten
#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by dreixel): Replying to [comment:11 goldfire]: through their (unhideable) `Typeable` instances? Template Haskell can surely do this, but I might be willing to ignore that particular attack. Are there others? What if a type is known but not the constructors? (I don't think `Typeable` can do this.) What about if a type synonym is known but the RHS isn't exported? (I bet it can do this.) `Typeable` knows nothing about the RHS of its type, so constructors are safe. Also, if you don't export a type nor any of its constructors, I don't see how you could use its |typeRep|, so I guess you're safe too (ignoring Template Haskell, of course). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): You could in theory go through it and find it inside of something else that is `Data`, (abusing `showsTypeRep` for instance), but that `Data` instance couldn't have been written without `Typeable` for the part before anyways. This doesn't strike me as a serious problem, personally. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Replying to [comment:9 hvr]:
Replying to [comment:8 simonpj]:
I think we should probably switch it on for the entire `base` package, and the chair of the core libraries committee seems to agree. That would be simpler than a lot of ad-hoc instances.
Btw, I just tried to enable it globally in order to get a list of additional `Typeable` instances becoming available by that, but you have to avoid using `AutoDeriveTypeable` at the same time with `NoImplicitPrelude`, as otherwise you get the error
{{{ Failed to load interface for ‘Data.Typeable.Internal’ }}}
Can you explain how to reproduce this error. Just add `AutoDeriveTypeable` to `base.cabal`? Or what? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by hvr): Replying to [comment:14 simonpj]:
{{{ Failed to load interface for ‘Data.Typeable.Internal’ }}}
btw, that message is just asking to add an `import Data.Typeable.Internal` in the module triggering that error (which often isn't possible due to import-cycles)
Can you explain how to reproduce this error. Just add `AutoDeriveTypeable` to `base.cabal`? Or what?
Adding `default-extension: AutoDeriveTypeable` to `base.cabal` is one way. But a more interesting case to try out is to enable `AutoDeriveTypeable` just inside a single module such as `GHC/Flaot.lhs` which doesn't `import Data.Typeable` -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): Ah yes I see. * The key module is `Data.Typeable.Internal`. * It declares the `Typeable` class, which mentions the data type `TypeRep`. * In turn `TypeRep` uses `Fingerprint` from `GHC.Fingerprint.Type` * And fingerprints use various `Word` types to do grungy stuff. As a result, `Data.Typeable.Internal` has to depend on `GHC.Word` etc. It also depends on a bunch of other things and I'm not sure they are all necessary. It would be good to make it depend on as little as possible. Regardless, * the modules "below" `Data.Typeable.Internal` (i.e. the modules on which `D.T.I` depends) can't be compiled with `DeriveAutoTypeable`; instead there are `deriving instance Typeable T` declarations in `D.T.I` for all of their types. * all other modules in `base` can have `DeriveAutoTypeable`. Does that make sense? Who would like to do it? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors
-------------------------------------+------------------------------------
Reporter: goldfire | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture: Unknown/Multiple
Type of failure: None/Unknown | Difficulty: Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
-------------------------------------+------------------------------------
Comment (by Herbert Valerio Riedel

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------ Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by crockeea): Replying to [comment:3 goldfire]:
For the problem reported in the first comment -- about a `Typeable` instance for `Symbol`s (and presumably `Nat`s) -- the implementation technique is somewhat different and might best be something for Iavor. [http://www.haskell.org/pipermail/haskell-cafe/2013-August/109993.html This message] from August 2013 suggests that he is on it, but I don't know if there has been progress since then.
I just asked Iavor about that message. His response (6/4/14): "I don't think anything has happened with this, but we discussed it some time ago and as far as I recall there were no theoretical or technical difficulties ---it just has to get done. I'll put it on my (now getting longish :-) todo list." -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -----------------------------------------------+--------------------------- Reporter: goldfire | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: libraries/base/tests/T9111 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: -----------------------------------------------+--------------------------- Changes (by goldfire): * testcase: => libraries/base/tests/T9111 Comment: Patch on the way... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors
-----------------------------------------------+---------------------------
Reporter: goldfire | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: libraries/base/tests/T9111 | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
-----------------------------------------------+---------------------------
Comment (by Richard Eisenberg

#9111: base should export Typeable instances of its promoted data constructors
-----------------------------------------------+---------------------------
Reporter: goldfire | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Test Case: libraries/base/tests/T9111 | Difficulty: Unknown
Blocking: | Blocked By:
| Related Tickets:
-----------------------------------------------+---------------------------
Comment (by Richard Eisenberg

#9111: base should export Typeable instances of its promoted data constructors -----------------------------------------------+--------------------------- Reporter: goldfire | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Test Case: libraries/base/tests/T9111 | Difficulty: Unknown Blocking: | Blocked By: | Related Tickets: -----------------------------------------------+--------------------------- Changes (by goldfire): * status: new => closed * resolution: => fixed Comment: The above commit should make all `base` types be `Typeable`, along with promoted data constructors. See #8778 about `Typeable` for `Nat` and `Symbol` types. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | libraries/base/tests/T9111 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by crockeea): Is this going to make 7.10? I don't see #9111 or #8486 in the [https://ghc.haskell.org/trac/ghc/wiki/Status/GHC-7.10.1 plans for 7.10]. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9111: base should export Typeable instances of its promoted data constructors -------------------------------------+------------------------------------- Reporter: goldfire | Owner: Type: feature request | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.8.2 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: None/Unknown | Unknown/Multiple Blocked By: | Test Case: Related Tickets: | libraries/base/tests/T9111 | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by hvr): * milestone: => 7.10.1 Comment: Replying to [comment:23 crockeea]:
Is this going to make 7.10?
Afaics, this landed in GHC HEAD long before GHC 7.10 was frozen, so it's already part of GHC 7.10.1RC; if you're missing some `Typeable` instances, please tell us -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9111#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC