[GHC] #12415: Fancy BinIface encoding for tuples is broken for constraint tuples
GHC
ghc-devs at haskell.org
Thu Jul 21 23:31:06 UTC 2016
#12415: Fancy BinIface encoding for tuples is broken for constraint tuples
-------------------------------------+-------------------------------------
Reporter: bgamari | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #12357 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by bgamari):
Earlier today it occurred to me that `putName` already does a finite map
lookup which made me think twice about the approach I took in #12357,
{{{#!hs
knownKeyNamesMap :: UniqFM Name
knownKeyNamesMap = listToUFM_Directly [(nameUnique n, n) | n <-
knownKeyNames]
putName :: BinDictionary -> BinSymbolTable -> BinHandle -> Name -> IO ()
putName _dict BinSymbolTable{...} bh name
| name `elemUFM` knownKeyNamesMap
, let (c, u) = unpkUnique (nameUnique name) -- INVARIANT: (ord c) fits
in 8 bits
= ...
}}}
`knownKeyNamesMap` is currently used for two things,
* A membership check is made when encoding a name in `putName` so we know
that the `Name` can be encoded as just its unique.
* A lookup is done in `getSymtabName` to recover the `Name` from the
unique during deserialization
The fact that we already do a lookup here puts an option for resolving
this issue (as well as the tuple type representation issue of #12357) back
on the table which I had previously ruled out in ticket:12357#comment:29.
The idea is that we simply keep a lookup data structure containing `Name`s
of things that need special treatment during interface file serialization.
Indeed this is precisely what `knownKeyNamesMap` is.
One option here would be to add the `Name`s of constraint tuples to this
map and change it's type a bit,
{{{#!hs
data KnownKeyThing
= -- | Tuple things get a fancy encoding of their own.
-- While tuple type and data constructors are wired-in and therefore
-- easy to spot, type reps are merely known key so we need to
identify
-- them by a look-up in 'knownKeyThingsMap'.
TupleTypeRep !TupleSort !Arity
-- | Constraint tuples. Only the 'TyCon's of these are known key.
| CTupleTyCon !Arity
-- | Boxed and unboxed sums (these have a similar encoding to
tuples)
| SumTyCon !Boxity !Arity
| SumDataCon !Boxity !Arity !ConTagZ
-- | Something which we know the key of; these things
-- we encode in the interface file as just their 'Unique'
| KnownKeyName Name
knownKeyThingsMap :: NameEnv KnownKeyThing
knownKeyThingsMap = mkNameEnv $
known_key_things ++ tuple_typerep_things ++ ctuple_things
where
known_key_things =
[ (name, KnownKeyName name)
| names <- knownKeyNames
]
ctuple_things =
[ (cTupleTyConName arity, CTupleTyCon arity)
| arity <- [2..mAX_TUPLE_SIZE]
]
tuple_typerep_things =
[ (rep_name, TupleTypeRep tup_sort arity)
| tup_sort <- [BoxedTuple, UnboxedTuple]
, arity <- [2..mAX_TUPLE_SIZE]
, let Just rep_name = tyConRepName_maybe $ tupleTyCon boxity arity
]
}}}
We'd then just modify the logic in `putName` to do the appropriate thing
with the result of the lookup from this map.
The deserialization side of things should be similarly straightforward
(decoding the encoded `KnownKeyThing` and then doing what is necessary to
turn it into a `Name`).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12415#comment:4>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list