[GHC] #7897: MakeTypeRep fingerprints be proper, robust fingerprints

#7897: MakeTypeRep fingerprints be proper, robust fingerprints ---------------------------------+------------------------------------------ Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ A `TypeRep` currently looks like this: {{{ data TypeRep = TypeRep Fingerprint TyCon [TypeRep] data TyCon = TyCon { tyConHash :: Fingerprint, tyConPackage :: String, tyConModule :: String, tyConName :: String } }}} If two `TypeRep`s have the same fingerprint they should really describe identical types. But that's not really true today, becuase today the fingerprint for a `TyCon` is obtained by hashing the ''name'' of the type constructor (e.g. `base:Data.Maybe.Maybe`), but not its ''structure''. To see how this is non-robust, imagine that {{{ module M where data T = MkT S deriving( Typeable ) data S = S1 Int | S2 Bool deriving( Typeable ) }}} Now I do this: * Write a program that costructs a value `v::T`, and serialises into a file (a) the `TypeRep` for `v`, and (b) `v` itself. * Now I alter the data type declaration for `S` * Now I recompile and run the program again, which attempts to read the value back in from the file. It carefully compares `TypeRep`s to be sure that the types are the same... yes, still "M.T". * But alas the de-serialisation fails because `S` has been changed. What we really want is for the fingerprint in a `TypeRep` to really be a hash of the definition of `T` (not just its name), including transitively the fingerprints of all the types mentioned in that definition. In effect, a `TypeRep` is a dynamic type check, and it should jolly well be a robust dynamic type check. This might also matter in a Cloud Haskell application with different components upgraded at different times. As it happens, GHC already computes these fingerprints, to put in interface files. But they aren't used when making the `Typeable` instances for `T`. I think it should be. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7897 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7897: MakeTypeRep fingerprints be proper, robust fingerprints ---------------------------------+------------------------------------------ Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Comment(by dreixel): Just to add two comments as to why this might not have a good cost/benefit ratio: 1) The problem is not easily seen in practice. In Cloud Haskell, all nodes are supposed to run the same binary (currently, at least). And even in the example given, the result is a failed deserialisation (possibly with a sensible runtime failure), not a segfault. 2) This will complicate giving `Typeable` instances for data families. Right now, since `Typeable` only depends on the LHS of a data declaration, we can give a `Typeable` instance as soon as the family is declared; this `Typeable` instance it will work for all data instances, current and future. If we have to look at the RHS, though, we will need one separate `Typeable` instance per data family instance. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7897#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7897: MakeTypeRep fingerprints be proper, robust fingerprints ---------------------------------+------------------------------------------ Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Comment(by simonpj): Re data families, see #5863 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7897#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7897: MakeTypeRep fingerprints be proper, robust fingerprints ---------------------------------+------------------------------------------ Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: | ---------------------------------+------------------------------------------ Comment(by simonpj): Both Pedro's (dreixel) points above are good ones. The data-family question is particularly problematic; but as things stand it's very simple. So the status quo,in which `TypeRep`s are essentially compared by name, is looking more attractive. No one is aruging for this change. So I propose to park it for now. But I'll leave the ticket as a placeholder for discussion. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7897#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC