module Distribution.Backpack (
OpenUnitId(..),
openUnitIdFreeHoles,
mkOpenUnitId,
DefUnitId,
unDefUnitId,
mkDefUnitId,
OpenModule(..),
openModuleFreeHoles,
OpenModuleSubst,
dispOpenModuleSubst,
dispOpenModuleSubstEntry,
parseOpenModuleSubst,
parseOpenModuleSubstEntry,
parsecOpenModuleSubst,
parsecOpenModuleSubstEntry,
openModuleSubstFreeHoles,
abstractUnitId,
hashModuleSubst,
) where
import Distribution.Compat.Prelude hiding (mod)
import Distribution.Compat.ReadP ((<++))
import Distribution.Parsec.Class
import Distribution.Pretty
import Prelude ()
import Text.PrettyPrint (hcat)
import qualified Distribution.Compat.CharParsing as P
import qualified Distribution.Compat.ReadP as Parse
import qualified Text.PrettyPrint as Disp
import Distribution.ModuleName
import Distribution.Text
import Distribution.Types.ComponentId
import Distribution.Types.Module
import Distribution.Types.UnitId
import Distribution.Utils.Base62
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
data OpenUnitId
= IndefFullUnitId ComponentId OpenModuleSubst
| DefiniteUnitId DefUnitId
deriving (Generic, Read, Show, Eq, Ord, Typeable, Data)
instance Binary OpenUnitId
instance NFData OpenUnitId where
rnf (IndefFullUnitId cid subst) = rnf cid `seq` rnf subst
rnf (DefiniteUnitId uid) = rnf uid
instance Pretty OpenUnitId where
pretty (IndefFullUnitId cid insts)
| Map.null insts = pretty cid
| otherwise = pretty cid <<>> Disp.brackets (dispOpenModuleSubst insts)
pretty (DefiniteUnitId uid) = pretty uid
instance Parsec OpenUnitId where
parsec = P.try parseOpenUnitId <|> fmap DefiniteUnitId parsec
where
parseOpenUnitId = do
cid <- parsec
insts <- P.between (P.char '[') (P.char ']')
parsecOpenModuleSubst
return (IndefFullUnitId cid insts)
instance Text OpenUnitId where
parse = parseOpenUnitId <++ fmap DefiniteUnitId parse
where
parseOpenUnitId = do
cid <- parse
insts <- Parse.between (Parse.char '[') (Parse.char ']')
parseOpenModuleSubst
return (IndefFullUnitId cid insts)
openUnitIdFreeHoles :: OpenUnitId -> Set ModuleName
openUnitIdFreeHoles (IndefFullUnitId _ insts) = openModuleSubstFreeHoles insts
openUnitIdFreeHoles _ = Set.empty
mkOpenUnitId :: UnitId -> ComponentId -> OpenModuleSubst -> OpenUnitId
mkOpenUnitId uid cid insts =
if Set.null (openModuleSubstFreeHoles insts)
then DefiniteUnitId (unsafeMkDefUnitId uid)
else IndefFullUnitId cid insts
mkDefUnitId :: ComponentId -> Map ModuleName Module -> DefUnitId
mkDefUnitId cid insts =
unsafeMkDefUnitId (mkUnitId
(unComponentId cid ++ maybe "" ("+"++) (hashModuleSubst insts)))
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 Pretty OpenModule where
pretty (OpenModule uid mod_name) =
hcat [pretty uid, Disp.text ":", pretty mod_name]
pretty (OpenModuleVar mod_name) =
hcat [Disp.char '<', pretty mod_name, Disp.char '>']
instance Parsec OpenModule where
parsec = parsecModuleVar <|> parsecOpenModule
where
parsecOpenModule = do
uid <- parsec
_ <- P.char ':'
mod_name <- parsec
return (OpenModule uid mod_name)
parsecModuleVar = do
_ <- P.char '<'
mod_name <- parsec
_ <- P.char '>'
return (OpenModuleVar mod_name)
instance Text OpenModule where
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)
openModuleFreeHoles :: OpenModule -> Set ModuleName
openModuleFreeHoles (OpenModuleVar mod_name) = Set.singleton mod_name
openModuleFreeHoles (OpenModule uid _n) = openUnitIdFreeHoles uid
type OpenModuleSubst = Map ModuleName OpenModule
dispOpenModuleSubst :: OpenModuleSubst -> Disp.Doc
dispOpenModuleSubst subst
= Disp.hcat
. Disp.punctuate Disp.comma
$ map dispOpenModuleSubstEntry (Map.toAscList subst)
dispOpenModuleSubstEntry :: (ModuleName, OpenModule) -> Disp.Doc
dispOpenModuleSubstEntry (k, v) = disp k <<>> Disp.char '=' <<>> disp v
parseOpenModuleSubst :: Parse.ReadP r OpenModuleSubst
parseOpenModuleSubst = fmap Map.fromList
. flip Parse.sepBy (Parse.char ',')
$ parseOpenModuleSubstEntry
parseOpenModuleSubstEntry :: Parse.ReadP r (ModuleName, OpenModule)
parseOpenModuleSubstEntry =
do k <- parse
_ <- Parse.char '='
v <- parse
return (k, v)
parsecOpenModuleSubst :: CabalParsing m => m OpenModuleSubst
parsecOpenModuleSubst = fmap Map.fromList
. flip P.sepBy (P.char ',')
$ parsecOpenModuleSubstEntry
parsecOpenModuleSubstEntry :: CabalParsing m => m (ModuleName, OpenModule)
parsecOpenModuleSubstEntry =
do k <- parsec
_ <- P.char '='
v <- parsec
return (k, v)
openModuleSubstFreeHoles :: OpenModuleSubst -> Set ModuleName
openModuleSubstFreeHoles insts = Set.unions (map openModuleFreeHoles (Map.elems insts))
abstractUnitId :: OpenUnitId -> UnitId
abstractUnitId (DefiniteUnitId def_uid) = unDefUnitId def_uid
abstractUnitId (IndefFullUnitId cid _) = newSimpleUnitId cid
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]