Re: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

#1409: Allow recursively dependent modules transparently (without .hs-boot or anything) -------------------------------------+------------------------------------- Reporter: Isaac Dupree | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: ⊥ Component: Compiler | Version: 6.10.2 Resolution: | Keywords: backpack Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #9256 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Would it be possible to generate the hs-boot file (or some equivalent) as a by-product of a module dependency analysis? E.g. {{{ module A where import B data Flip = MkFlip Flop flip :: Int -> Flip flip _ = MkFlip (flop []) module B where import A data Flop = MkFlop Flip flop :: [a] -> Flop flop _ = MkFlop (flip 42) }}} Dependency analysis based just on names finds out that `B` uses `A(Flip, flip)` and `A` uses `B(Flop, flop)`. The compiler could then pick one of (see below) the two modules and generate the hs-boot file: {{{ module A where data Flip flip :: Int -> Flip }}} This has the advantage of keeping the current model of separate compilation instead of starting to merge huge SCCs of the dependency graph into one module that takes eons to compile. I'm not sure if Haskell projects would be affected by the same trend, but large Java projects tend to have SCCs comprised of [https://link.springer.com/article/10.1007/s10664-006-9033-1 hundreds, if not thousands of files]. Of course, I just hand-waved over many technical challenges in my proposal above. I'm pretty certain the above approach would need actual involvement from the type-checker in complicated cases. I don't dare to think about handling type families this way, but wouldn't a name resolution approach get rid of 90% of the cases where we would need hs-boot files? Note that the compiler can still yell at you if it doesn't find a proper solution, or a solution that would involve the type-checker. Imagine that we didn't provide a type signature for `flip` or for `flop`. The above idea would not be able to synthesize the boot file for either `A` or `B`, because it doesn't do actual type-checking across modules. I imagine an error like: {{{ Couldn't infer any type of recursive group {A.flip, B.flop} Provide type signatures or an hs-boot file for any of the occuring modules to fix this. }}} Note that if we only leave out the type signature of `flip`, we still have enough information to compute the hs-boot file for `B` instead of `A`. In general, deciding which module to generate the boot file for could take other criteria, like minimality, into account. We could also have a look at how the D language does things, which has both strong meta-programming capabilities and allows circular module dependencies. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/1409#comment:79 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC