[GHC] #7897: MakeTypeRep fingerprints be proper, robust fingerprints
GHC
cvs-ghc at haskell.org
Wed May 8 16:44:34 CEST 2013
#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
More information about the ghc-tickets
mailing list