Skip to content

Commit

Permalink
Merge pull request #3672 from ezyang/backpack
Browse files Browse the repository at this point in the history
Backpack
  • Loading branch information
ezyang committed Oct 6, 2016
2 parents f8095ac + cf7e331 commit 8fa4d2e
Show file tree
Hide file tree
Showing 163 changed files with 4,991 additions and 974 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
# trivial gitignore file
.cabal-sandbox/
cabal.sandbox.config
cabal.project.local
cabal-dev/
.hpc/
*.hi
Expand Down
74 changes: 74 additions & 0 deletions Cabal/Cabal.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,15 @@ extra-source-files:
tests/PackageTests/AllowOlder/benchmarks/Bench.hs
tests/PackageTests/AllowOlder/src/Foo.hs
tests/PackageTests/AllowOlder/tests/Test.hs
tests/PackageTests/Ambiguity/p/Dupe.hs
tests/PackageTests/Ambiguity/p/p.cabal
tests/PackageTests/Ambiguity/package-import/A.hs
tests/PackageTests/Ambiguity/package-import/package-import.cabal
tests/PackageTests/Ambiguity/q/Dupe.hs
tests/PackageTests/Ambiguity/q/q.cabal
tests/PackageTests/Ambiguity/reexport-test/Main.hs
tests/PackageTests/Ambiguity/reexport-test/reexport-test.cabal
tests/PackageTests/Ambiguity/reexport/reexport.cabal
tests/PackageTests/AutogenModules/Package/Dummy.hs
tests/PackageTests/AutogenModules/Package/MyBenchModule.hs
tests/PackageTests/AutogenModules/Package/MyExeModule.hs
Expand All @@ -54,6 +63,44 @@ extra-source-files:
tests/PackageTests/AutogenModules/SrcDist/MyLibrary.hs
tests/PackageTests/AutogenModules/SrcDist/MyTestModule.hs
tests/PackageTests/AutogenModules/SrcDist/my.cabal
tests/PackageTests/Backpack/Includes1/A.hs
tests/PackageTests/Backpack/Includes1/B.hs
tests/PackageTests/Backpack/Includes1/Includes1.cabal
tests/PackageTests/Backpack/Includes2/Includes2.cabal
tests/PackageTests/Backpack/Includes2/exe/Main.hs
tests/PackageTests/Backpack/Includes2/exe/exe.cabal
tests/PackageTests/Backpack/Includes2/fail.cabal
tests/PackageTests/Backpack/Includes2/mylib/Mine.hs
tests/PackageTests/Backpack/Includes2/mylib/mylib.cabal
tests/PackageTests/Backpack/Includes2/mysql/Database/MySQL.hs
tests/PackageTests/Backpack/Includes2/mysql/mysql.cabal
tests/PackageTests/Backpack/Includes2/postgresql/Database/PostgreSQL.hs
tests/PackageTests/Backpack/Includes2/postgresql/postgresql.cabal
tests/PackageTests/Backpack/Includes2/src/App.hs
tests/PackageTests/Backpack/Includes2/src/src.cabal
tests/PackageTests/Backpack/Includes3/Includes3.cabal
tests/PackageTests/Backpack/Includes3/exe/Main.hs
tests/PackageTests/Backpack/Includes3/exe/exe.cabal
tests/PackageTests/Backpack/Includes3/indef/Foo.hs
tests/PackageTests/Backpack/Includes3/indef/indef.cabal
tests/PackageTests/Backpack/Includes3/sigs/sigs.cabal
tests/PackageTests/Backpack/Includes4/Includes4.cabal
tests/PackageTests/Backpack/Includes4/Main.hs
tests/PackageTests/Backpack/Includes4/impl/A.hs
tests/PackageTests/Backpack/Includes4/impl/B.hs
tests/PackageTests/Backpack/Includes4/impl/Rec.hs
tests/PackageTests/Backpack/Includes4/indef/C.hs
tests/PackageTests/Backpack/Includes5/A.hs
tests/PackageTests/Backpack/Includes5/B.hs
tests/PackageTests/Backpack/Includes5/Includes5.cabal
tests/PackageTests/Backpack/Includes5/impl/Foobar.hs
tests/PackageTests/Backpack/Includes5/impl/Quxbaz.hs
tests/PackageTests/Backpack/Indef1/Indef1.cabal
tests/PackageTests/Backpack/Indef1/Provide.hs
tests/PackageTests/Backpack/Reexport1/p/P.hs
tests/PackageTests/Backpack/Reexport1/p/p.cabal
tests/PackageTests/Backpack/Reexport1/q/Q.hs
tests/PackageTests/Backpack/Reexport1/q/q.cabal
tests/PackageTests/BenchmarkExeV10/Foo.hs
tests/PackageTests/BenchmarkExeV10/benchmarks/bench-Foo.hs
tests/PackageTests/BenchmarkExeV10/my.cabal
Expand Down Expand Up @@ -207,6 +254,13 @@ extra-source-files:
tests/PackageTests/PreProcessExtraSources/Foo.hsc
tests/PackageTests/PreProcessExtraSources/Main.hs
tests/PackageTests/PreProcessExtraSources/my.cabal
tests/PackageTests/ReexportedModules/containers-dupe/Data/Map.hs
tests/PackageTests/ReexportedModules/containers-dupe/containers-dupe.cabal
tests/PackageTests/ReexportedModules/p/Private.hs
tests/PackageTests/ReexportedModules/p/Public.hs
tests/PackageTests/ReexportedModules/p/fail-ambiguous.cabal
tests/PackageTests/ReexportedModules/p/fail-missing.cabal
tests/PackageTests/ReexportedModules/p/fail-other.cabal
tests/PackageTests/ReexportedModules/p/p.cabal
tests/PackageTests/ReexportedModules/q/A.hs
tests/PackageTests/ReexportedModules/q/q.cabal
Expand Down Expand Up @@ -310,6 +364,16 @@ library
-Wnoncanonical-monadfail-instances

exposed-modules:
Distribution.Backpack
Distribution.Backpack.Configure
Distribution.Backpack.ComponentsGraph
Distribution.Backpack.ConfiguredComponent
Distribution.Backpack.FullUnitId
Distribution.Backpack.LinkedComponent
Distribution.Backpack.ModSubst
Distribution.Backpack.ModuleShape
Distribution.Utils.LogProgress
Distribution.Utils.MapAccum
Distribution.Compat.CreatePipe
Distribution.Compat.Environment
Distribution.Compat.Exception
Expand Down Expand Up @@ -395,6 +459,7 @@ library
Distribution.Types.Library
Distribution.Types.ModuleReexport
Distribution.Types.ModuleRenaming
Distribution.Types.IncludeRenaming
Distribution.Types.SetupBuildInfo
Distribution.Types.TestSuite
Distribution.Types.TestSuiteInterface
Expand All @@ -411,12 +476,21 @@ library
Distribution.Types.TargetInfo
Distribution.Utils.NubList
Distribution.Utils.ShortText
Distribution.Utils.Progress
Distribution.Verbosity
Distribution.Version
Language.Haskell.Extension
Distribution.Compat.Binary

other-modules:
Distribution.Backpack.PreExistingComponent
Distribution.Backpack.ReadyComponent
Distribution.Backpack.MixLink
Distribution.Backpack.ModuleScope
Distribution.Backpack.UnifyM
Distribution.Backpack.Id
Distribution.Utils.UnionFind
Distribution.Utils.Base62
Distribution.Compat.CopyFile
Distribution.Compat.GetShortPathName
Distribution.Compat.MonadFail
Expand Down
248 changes: 248 additions & 0 deletions Cabal/Distribution/Backpack.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,248 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-- | This module defines the core data types for Backpack. For more
-- details, see:
--
-- <https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst>

module Distribution.Backpack (
-- * OpenUnitId
OpenUnitId(..),
openUnitIdComponentId,
openUnitIdFreeHoles,
mkOpenUnitId,

-- * DefUnitId
DefUnitId,
unDefUnitId,
mkDefUnitId,

-- * OpenModule
OpenModule(..),
openModuleFreeHoles,

-- * OpenModuleSubst
OpenModuleSubst,
dispOpenModuleSubst,
dispOpenModuleSubstEntry,
parseOpenModuleSubst,
parseOpenModuleSubstEntry,
openModuleSubstFreeHoles,

-- * Conversions to 'UnitId'
abstractUnitId,
hashModuleSubst,
) where

import Prelude ()
import Distribution.Compat.Prelude hiding (mod)
import Distribution.Compat.ReadP
import qualified Distribution.Compat.ReadP as Parse
import qualified Text.PrettyPrint as Disp
import Text.PrettyPrint (hcat)

import Distribution.ModuleName
import Distribution.Package
import Distribution.Text
import Distribution.Utils.Base62

import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set

-----------------------------------------------------------------------
-- OpenUnitId

-- | An 'OpenUnitId' describes a (possibly partially) instantiated
-- Backpack component, with a description of how the holes are filled
-- in. Unlike 'OpenUnitId', the 'ModuleSubst' is kept in a structured
-- form that allows for substitution (which fills in holes.) This form
-- of unit cannot be installed. It must first be converted to a
-- 'UnitId'.
--
-- In the absence of Backpack, there are no holes to fill, so any such
-- component always has an empty module substitution; thus we can lossly
-- represent it as an 'OpenUnitId uid'.
--
-- For a source component using Backpack, however, there is more
-- structure as components may be parametrized over some signatures, and
-- these \"holes\" may be partially or wholly filled.
--
-- OpenUnitId plays an important role when we are mix-in linking,
-- and is recorded to the installed packaged database for indefinite
-- packages; however, for compiled packages that are fully instantiated,
-- we instantiate 'OpenUnitId' into 'UnitId'.
--
-- For more details see the Backpack spec
-- <https://github.com/ezyang/ghc-proposals/blob/backpack/proposals/0000-backpack.rst>
--

data OpenUnitId
-- | Identifies a component which may have some unfilled holes;
-- specifying its 'ComponentId' and its 'OpenModuleSubst'.
-- TODO: Invariant that 'OpenModuleSubst' is non-empty?
-- See also the Text instance.
= IndefFullUnitId ComponentId OpenModuleSubst
-- | Identifies a fully instantiated component, which has
-- been compiled and abbreviated as a hash. The embedded 'UnitId'
-- MUST NOT be for an indefinite component; an 'OpenUnitId'
-- is guaranteed not to have any holes.
| DefiniteUnitId DefUnitId
deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
-- TODO: cache holes?

instance Binary OpenUnitId

instance NFData OpenUnitId where
rnf (IndefFullUnitId cid subst) = rnf cid `seq` rnf subst
rnf (DefiniteUnitId uid) = rnf uid

instance Text OpenUnitId where
disp (IndefFullUnitId cid insts)
-- TODO: arguably a smart constructor to enforce invariant would be
-- better
| Map.null insts = disp cid
| otherwise = disp cid <<>> Disp.brackets (dispOpenModuleSubst insts)
disp (DefiniteUnitId uid) = disp uid
parse = parseOpenUnitId <++ fmap DefiniteUnitId parse
where
parseOpenUnitId = do
cid <- parse
insts <- Parse.between (Parse.char '[') (Parse.char ']')
parseOpenModuleSubst
return (IndefFullUnitId cid insts)

-- | Get the 'ComponentId' of an 'OpenUnitId'.
openUnitIdComponentId :: OpenUnitId -> ComponentId
openUnitIdComponentId (IndefFullUnitId cid _) = cid
openUnitIdComponentId (DefiniteUnitId def_uid) = unitIdComponentId (unDefUnitId def_uid)

-- | Get the set of holes ('ModuleVar') embedded in a 'UnitId'.
openUnitIdFreeHoles :: OpenUnitId -> Set ModuleName
openUnitIdFreeHoles (IndefFullUnitId _ insts) = openModuleSubstFreeHoles insts
openUnitIdFreeHoles _ = Set.empty

-- | Safe constructor from a UnitId. The only way to do this safely
-- is if the instantiation is provided.
mkOpenUnitId :: UnitId -> OpenModuleSubst -> OpenUnitId
mkOpenUnitId uid insts =
if Set.null (openModuleSubstFreeHoles insts)
then DefiniteUnitId (unsafeMkDefUnitId uid) -- invariant holds!
else IndefFullUnitId (unitIdComponentId uid) insts

-----------------------------------------------------------------------
-- DefUnitId

-- | Create a 'DefUnitId' from a 'ComponentId' and an instantiation
-- with no holes.
mkDefUnitId :: ComponentId -> Map ModuleName Module -> DefUnitId
mkDefUnitId cid insts =
unsafeMkDefUnitId (UnitId cid (hashModuleSubst insts)) -- impose invariant!

-----------------------------------------------------------------------
-- OpenModule

-- | Unlike a 'Module', an 'OpenModule' is either an ordinary
-- module from some unit, OR an 'OpenModuleVar', representing a
-- hole that needs to be filled in. Substitutions are over
-- module variables.
data OpenModule
= OpenModule OpenUnitId ModuleName
| OpenModuleVar ModuleName
deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)

instance Binary OpenModule

instance NFData OpenModule where
rnf (OpenModule uid mod_name) = rnf uid `seq` rnf mod_name
rnf (OpenModuleVar mod_name) = rnf mod_name

instance Text OpenModule where
disp (OpenModule uid mod_name) =
hcat [disp uid, Disp.text ":", disp mod_name]
disp (OpenModuleVar mod_name) =
hcat [Disp.char '<', disp mod_name, Disp.char '>']
parse = parseModuleVar <++ parseOpenModule
where
parseOpenModule = do
uid <- parse
_ <- Parse.char ':'
mod_name <- parse
return (OpenModule uid mod_name)
parseModuleVar = do
_ <- Parse.char '<'
mod_name <- parse
_ <- Parse.char '>'
return (OpenModuleVar mod_name)

-- | Get the set of holes ('ModuleVar') embedded in a 'Module'.
openModuleFreeHoles :: OpenModule -> Set ModuleName
openModuleFreeHoles (OpenModuleVar mod_name) = Set.singleton mod_name
openModuleFreeHoles (OpenModule uid _n) = openUnitIdFreeHoles uid

-----------------------------------------------------------------------
-- OpenModuleSubst

-- | An explicit substitution on modules.
--
-- NB: These substitutions are NOT idempotent, for example, a
-- valid substitution is (A -> B, B -> A).
type OpenModuleSubst = Map ModuleName OpenModule

-- | Pretty-print the entries of a module substitution, suitable
-- for embedding into a 'OpenUnitId' or passing to GHC via @--instantiate-with@.
dispOpenModuleSubst :: OpenModuleSubst -> Disp.Doc
dispOpenModuleSubst subst
= Disp.hcat
. Disp.punctuate Disp.comma
$ map dispOpenModuleSubstEntry (Map.toAscList subst)

-- | Pretty-print a single entry of a module substitution.
dispOpenModuleSubstEntry :: (ModuleName, OpenModule) -> Disp.Doc
dispOpenModuleSubstEntry (k, v) = disp k <<>> Disp.char '=' <<>> disp v

-- | Inverse to 'dispModSubst'.
parseOpenModuleSubst :: ReadP r OpenModuleSubst
parseOpenModuleSubst = fmap Map.fromList
. flip Parse.sepBy (Parse.char ',')
$ parseOpenModuleSubstEntry

-- | Inverse to 'dispModSubstEntry'.
parseOpenModuleSubstEntry :: ReadP r (ModuleName, OpenModule)
parseOpenModuleSubstEntry =
do k <- parse
_ <- Parse.char '='
v <- parse
return (k, v)

-- | Get the set of holes ('ModuleVar') embedded in a 'OpenModuleSubst'.
-- This is NOT the domain of the substitution.
openModuleSubstFreeHoles :: OpenModuleSubst -> Set ModuleName
openModuleSubstFreeHoles insts = Set.unions (map openModuleFreeHoles (Map.elems insts))

-----------------------------------------------------------------------
-- Conversions to UnitId

-- | When typechecking, we don't demand that a freshly instantiated
-- 'IndefFullUnitId' be compiled; instead, we just depend on the
-- installed indefinite unit installed at the 'ComponentId'.
abstractUnitId :: OpenUnitId -> UnitId
abstractUnitId (DefiniteUnitId def_uid) = unDefUnitId def_uid
abstractUnitId (IndefFullUnitId cid _) = newSimpleUnitId cid

-- | Take a module substitution and hash it into a string suitable for
-- 'UnitId'. Note that since this takes 'Module', not 'OpenModule',
-- you are responsible for recursively converting 'OpenModule'
-- into 'Module'. See also "Distribution.Backpack.ReadyComponent".
hashModuleSubst :: Map ModuleName Module -> Maybe String
hashModuleSubst subst
| Map.null subst = Nothing
| otherwise =
Just . hashToBase62 $
concat [ display mod_name ++ "=" ++ display m ++ "\n"
| (mod_name, m) <- Map.toList subst]

0 comments on commit 8fa4d2e

Please sign in to comment.