[GHC] #10681: Teach GHC to interpret all hs files as two types of hs-boot files (abstract types only/full types + values)

GHC ghc-devs at haskell.org
Fri Jul 24 04:48:06 UTC 2015


#10681: Teach GHC to interpret all hs files as two types of hs-boot files (abstract
types only/full types + values)
-------------------------------------+-------------------------------------
              Reporter:  ezyang      |             Owner:  ezyang
                  Type:  feature     |            Status:  new
  request                            |
              Priority:  normal      |         Milestone:
             Component:  Compiler    |           Version:  7.11
              Keywords:              |  Operating System:  Unknown/Multiple
          Architecture:              |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
             Test Case:              |        Blocked By:
              Blocking:              |   Related Tickets:
Differential Revisions:              |
-------------------------------------+-------------------------------------
 This is a new proposal for solving #1409. The big addition here is that we
 create **two** hs-boot files for each hs file: one that is a full hs-boot
 file to be imported by hs files to break loops, and a second which only
 includes abstract types for hs-boot files to import.  C.f. #10679

 **Discussion.** Here is a slightly goofy `hs-boot` file I've excerpted
 from GHC:

 {{{
 module Packages where

 import {-# SOURCE #-} Module (PackageKey)
 import {-# SOURCE #-} DynFlags (DynFlags)

 packageKeyPackageIdString :: DynFlags -> PackageKey -> Maybe String
 }}}

 The `hs-boot` file must itself import `hs-boot` files, because this boot
 file is used by `Module` and `DynFlags`; without `{-# SOURCE #-}`, the
 boot file itself will participate in a cycle!

 But notice that there is something very interesting: a boot file is ONLY
 ever interested in importing other modules to get types. Never to import
 constructors or functions!

 We can use this observation to give us a mechanical transformation of an
 `hs` file to an `hs-boot` file, ASSUMING we can define a "second level" of
 `hs-boot` file to record our abstract types.

 **Example.** In this example, we have chosen to break the loop from `A`s
 import to `B`.

 {{{
 module A where
   import {-# SOURCE #-} B
   data A = A B
   f :: A -> Bool
   f (A (B (A b))) = g b
   f _ = True

 module B where
   import A
   data B = B A
   g :: B -> Bool
   g (B (A (B b))) = f b
   g _ = False
 }}}

 The first-level `hs-boot`s are:

 {{{
 module A where -- not actually used
   import {-# SOURCE 2 #-} B
   data A = A B
   f :: A -> Bool

 module B where
   import {-# SOURCE 2 #-} A
   data B = B A
   g :: B -> Bool
 }}}

 The second-level `hs-boot`s are:

 {{{
 module A where
   data A

 module B where -- not actually used
   data B
 }}}

 **Commentary.** Here are some remarks:

 1. Because we have to lift the transitive dependencies of anything we `{-#
 SOURCE #-}` import, it doesn't make sense to have a pragma which
 explicitly says what to put in the `hs-boot` file; instead, we just put in
 everything that we *can* handle in an `hs-boot` file (so exclude anything
 with missing type signatures, type families, etc.)  Ideally, these
 automatic hs-boot files are generated lazily, but they should be reused as
 necessary.

 2. This facility actually makes `{-# SOURCE #-}` a lot more attractive for
 increasing separate compilation: you can mark an import `{-# SOURCE #-}`
 to ensure that if its implementation changes, you don't have to recompile
 this module / you can build the module in parallel with that module.  The
 downside is that when the imported file is modified, we have to regenerate
 the `hs-boot` stub before we conclude that the types have not changed (as
 opposed to with separate `hs-boot` files, where a modification to `hs`
 would not bump the timestamp on `hs-boot`.

 3. This seems to definitely suggest that you should never need more than
 two levels of hs-boot nesting, or perhaps three with kinding. (But maybe
 someone has a fancy type system feature for which this is not true!)
 Maybe this applies to signature files too.

 4. We can't force the first level of `hs-boot` files to be abstract types,
 for two reasons: (1) a source file importing the hs-boot file may really
 need the selector/constructor, and (2) the `hs-boot` files will reflect
 any cycles from the source files, that's no good! Rolling out to the
 second level breaks the cycle because abstract types never need any
 imports.

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10681>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list