[GHC] #12088: Promote data family instance constructors
GHC
ghc-devs at haskell.org
Thu Jun 16 12:16:01 UTC 2016
#12088: Promote data family instance constructors
-------------------------------------+-------------------------------------
Reporter: alexvieth | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords: TypeInType
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11348 | Differential Rev(s): Phab:D2272
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
The more I look at the draft patch Phab:D2272 the more I think it's not
quite right yet.
At the root of it, we currently have
{{{
data TyClGroup name -- See Note [TyClGroups and dependency analysis]
= TyClGroup { group_tyclds :: [LTyClDecl name]
, group_roles :: [LRoleAnnotDecl name]
, group_instds :: [ [LInstDecl name] ] }
}}}
and we typecheck groups one by one. But actually, as commentary on Phab
shows, type declarations can depend (via promoted data constructors) on
`data instance` declarations, ''and `data instance` declarations can
depend on each other''. The `[[LInstdecl name]]` is clearly a bit of a
hack, becuase it is itself effectively a sequence of (non-recursive) SCCs.
Let's flatten it out: I think we want
{{{
data TyClGroup name -- See Note [TyClGroups and dependency analysis]
= TyClGroup { group_tyclds :: [LTyClDecl name]
, group_roles :: [LRoleAnnotDecl name] }
| InstGroup (LInstDecl name)
}}}
Now a list of `TyClGroup` tells us the order. Instances can't be mutually
recursive, so singletons are what we need.
How to construct the order? Alex suggests adding a potentially large
number of extra edges, and thene doing standard SCC. But that seems a bit
artifical, and I don't think it's easy to construct precisely the right
extra edges. How about this?
* A "node" of the dependency graph contains either a single `TyClDecl` or
a single `InstDecl`.
* Each node needs a "key"; which is fine for `TyClDecls` (use the `Name`)
but not for `InstDecl`s. Solution; simply number off the nodes 1,2,3.
* Build a `[TCINode]`, with `Int` keys, using `Node` comes from `Digraph`:
{{{
type Node key payload = (payload, key, [key]) -- In Digraph
type TCIKey = Int
type TCINode = Node TCIKey (Either TyClDecl InstDecl)
}}}
To do this we'll need an auxiliary mapping from `TyCon`/`DataCon` names
to `TCIKey`.
* Do SCC analysis in the usual way, using
`stronglyConnCompFromEdgedVerticesR`
So far it's all as usual. But we want to make sure that the instance
declarations occur as early as possible in the sequence, consistent with
the dependencies. So:
* ''Partition the `InstDecl` nodes from the `TyClDecl` nodes''; there
should be no `InstDecl` in a `CyclicSCC`. Or at least if there are we
should reject the program. So we can cleanly separate the two.
* Run down the list of `TyClDecl` SCCS. After each one, add all the
`InstDecl` nodes ''that depend only on keys that occur earlier in the
sequence''. We may need to iterate this process. The key function might
look like
{{{
addInstDecls :: Set TCIKey -- TCIKeys that occur
earlier
-> [SCC (Node TCIKey TyClDecl)] -- TyClDecl SCCs
-> [Node TCIKey InstDecl] -- InstDecls to add
-> [TyClGroup] -- Final groups in order
addInstDecls _ [] ids
= [InstDeclGroup id | (_, id, _) <- ids]
addInstDecls so_far sccs ids
| (dump_ids, keep_ids) <- pickInstDecls so_far ids
, not (null dump_ids) -- Drop some instance declarations here
= dump_ids ++
addInstDecls (so-far `add` keysOf sump_ids) sccs keep_ids
addInstDecls so_far (scc : sccs) ids
= scc : addInstDecls (so_far `add` keysOf scc) sccs ids
}}}
The first case is easy. The second dumps any `InstDecls` that depend
only on
earlier declarations The third dumps the `TyClDecl`.
And that's about it. There is a bit of potential inefficienty in the
repeated traversals
by `pickInstDecls` but we don't expect to see a lot of instance
declarations anyway, and if that
becomes a problem we can think about a more efficient data structure than
a plain list.
Does that sound reasonable? I like that it's very comprehensible!
Minor alternative. Instead of the existing `TyClGroup` (constructed by the
renamer,
consumed by the type checker), use `SCC TyClNode`,
where
{{{
data TyClNode name
= TyClDeclNode (LTyClDecl name)
(Maybe (LRoleAnnots name))
| InstDeclNode (LInstDecl name)
}}}
Now we can use `TyClNode` instead of `Either TyClDecl InstDecl` in the
above, which is nice.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12088#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list