{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Module
(
ModuleName,
pprModuleName,
moduleNameFS,
moduleNameString,
moduleNameSlashes, moduleNameColons,
moduleStableString,
moduleFreeHoles,
moduleIsDefinite,
mkModuleName,
mkModuleNameFS,
stableModuleNameCmp,
ComponentId(..),
UnitId(..),
unitIdFS,
unitIdKey,
IndefUnitId(..),
IndefModule(..),
indefUnitIdToUnitId,
indefModuleToModule,
InstalledUnitId(..),
toInstalledUnitId,
ShHoleSubst,
unitIdIsDefinite,
unitIdString,
unitIdFreeHoles,
newUnitId,
newIndefUnitId,
newSimpleUnitId,
hashUnitId,
fsToUnitId,
stringToUnitId,
stableUnitIdCmp,
renameHoleUnitId,
renameHoleModule,
renameHoleUnitId',
renameHoleModule',
splitModuleInsts,
splitUnitIdInsts,
generalizeIndefUnitId,
generalizeIndefModule,
parseModuleName,
parseUnitId,
parseComponentId,
parseModuleId,
parseModSubst,
primUnitId,
integerUnitId,
baseUnitId,
rtsUnitId,
thUnitId,
dphSeqUnitId,
dphParUnitId,
mainUnitId,
thisGhcUnitId,
isHoleModule,
interactiveUnitId, isInteractiveModule,
wiredInUnitIds,
Module(Module),
moduleUnitId, moduleName,
pprModule,
mkModule,
mkHoleModule,
stableModuleCmp,
HasModule(..),
ContainsModule(..),
InstalledModule(..),
InstalledModuleEnv,
installedModuleEq,
installedUnitIdEq,
installedUnitIdString,
fsToInstalledUnitId,
componentIdToInstalledUnitId,
stringToInstalledUnitId,
emptyInstalledModuleEnv,
lookupInstalledModuleEnv,
extendInstalledModuleEnv,
filterInstalledModuleEnv,
delInstalledModuleEnv,
DefUnitId(..),
ModLocation(..),
addBootSuffix, addBootSuffix_maybe, addBootSuffixLocn,
ModuleEnv,
elemModuleEnv, extendModuleEnv, extendModuleEnvList,
extendModuleEnvList_C, plusModuleEnv_C,
delModuleEnvList, delModuleEnv, plusModuleEnv, lookupModuleEnv,
lookupWithDefaultModuleEnv, mapModuleEnv, mkModuleEnv, emptyModuleEnv,
moduleEnvKeys, moduleEnvElts, moduleEnvToList,
unitModuleEnv, isEmptyModuleEnv,
extendModuleEnvWith, filterModuleEnv,
ModuleNameEnv, DModuleNameEnv,
ModuleSet,
emptyModuleSet, mkModuleSet, moduleSetElts,
extendModuleSet, extendModuleSetList, delModuleSet,
elemModuleSet, intersectModuleSet, minusModuleSet, unionModuleSet,
unitModuleSet
) where
import GhcPrelude
import Config
import Outputable
import Unique
import UniqFM
import UniqDFM
import UniqDSet
import FastString
import Binary
import Util
import Data.List
import Data.Ord
import GHC.PackageDb (BinaryStringRep(..), DbUnitIdModuleRep(..), DbModule(..), DbUnitId(..))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as BS
import qualified Data.ByteString.Char8 as BS.Char8
import System.IO.Unsafe
import Foreign.Ptr (castPtr)
import GHC.Fingerprint
import Encoding
import qualified Text.ParserCombinators.ReadP as Parse
import Text.ParserCombinators.ReadP (ReadP, (<++))
import Data.Char (isAlphaNum)
import Control.DeepSeq
import Data.Coerce
import Data.Data
import Data.Function
import Data.Map (Map)
import Data.Set (Set)
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified FiniteMap as Map
import System.FilePath
import {-# SOURCE #-} DynFlags (DynFlags)
import {-# SOURCE #-} Packages (componentIdString, improveUnitId, PackageConfigMap, getPackageConfigMap, displayInstalledUnitId)
data ModLocation
= ModLocation {
ml_hs_file :: Maybe FilePath,
ml_hi_file :: FilePath,
ml_obj_file :: FilePath
} deriving Show
instance Outputable ModLocation where
ppr = text . show
addBootSuffix :: FilePath -> FilePath
addBootSuffix path = path ++ "-boot"
addBootSuffix_maybe :: Bool -> FilePath -> FilePath
addBootSuffix_maybe is_boot path
| is_boot = addBootSuffix path
| otherwise = path
addBootSuffixLocn :: ModLocation -> ModLocation
addBootSuffixLocn locn
= locn { ml_hs_file = fmap addBootSuffix (ml_hs_file locn)
, ml_hi_file = addBootSuffix (ml_hi_file locn)
, ml_obj_file = addBootSuffix (ml_obj_file locn) }
newtype ModuleName = ModuleName FastString
instance Uniquable ModuleName where
getUnique (ModuleName nm) = getUnique nm
instance Eq ModuleName where
nm1 == nm2 = getUnique nm1 == getUnique nm2
instance Ord ModuleName where
nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2
instance Outputable ModuleName where
ppr = pprModuleName
instance Binary ModuleName where
put_ bh (ModuleName fs) = put_ bh fs
get bh = do fs <- get bh; return (ModuleName fs)
instance BinaryStringRep ModuleName where
fromStringRep = mkModuleNameFS . mkFastStringByteString
toStringRep = fastStringToByteString . moduleNameFS
instance Data ModuleName where
toConstr _ = abstractConstr "ModuleName"
gunfold _ _ = error "gunfold"
dataTypeOf _ = mkNoRepType "ModuleName"
instance NFData ModuleName where
rnf x = x `seq` ()
stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering
stableModuleNameCmp n1 n2 = moduleNameFS n1 `compare` moduleNameFS n2
pprModuleName :: ModuleName -> SDoc
pprModuleName (ModuleName nm) =
getPprStyle $ \ sty ->
if codeStyle sty
then ztext (zEncodeFS nm)
else ftext nm
moduleNameFS :: ModuleName -> FastString
moduleNameFS (ModuleName mod) = mod
moduleNameString :: ModuleName -> String
moduleNameString (ModuleName mod) = unpackFS mod
moduleStableString :: Module -> String
moduleStableString Module{..} =
"$" ++ unitIdString moduleUnitId ++ "$" ++ moduleNameString moduleName
mkModuleName :: String -> ModuleName
mkModuleName s = ModuleName (mkFastString s)
mkModuleNameFS :: FastString -> ModuleName
mkModuleNameFS s = ModuleName s
moduleNameSlashes :: ModuleName -> String
moduleNameSlashes = dots_to_slashes . moduleNameString
where dots_to_slashes = map (\c -> if c == '.' then pathSeparator else c)
moduleNameColons :: ModuleName -> String
moduleNameColons = dots_to_colons . moduleNameString
where dots_to_colons = map (\c -> if c == '.' then ':' else c)
data Module = Module {
moduleUnitId :: !UnitId,
moduleName :: !ModuleName
}
deriving (Eq, Ord)
moduleFreeHoles :: Module -> UniqDSet ModuleName
moduleFreeHoles m
| isHoleModule m = unitUniqDSet (moduleName m)
| otherwise = unitIdFreeHoles (moduleUnitId m)
moduleIsDefinite :: Module -> Bool
moduleIsDefinite = isEmptyUniqDSet . moduleFreeHoles
mkHoleModule :: ModuleName -> Module
mkHoleModule = mkModule holeUnitId
instance Uniquable Module where
getUnique (Module p n) = getUnique (unitIdFS p `appendFS` moduleNameFS n)
instance Outputable Module where
ppr = pprModule
instance Binary Module where
put_ bh (Module p n) = put_ bh p >> put_ bh n
get bh = do p <- get bh; n <- get bh; return (Module p n)
instance Data Module where
toConstr _ = abstractConstr "Module"
gunfold _ _ = error "gunfold"
dataTypeOf _ = mkNoRepType "Module"
instance NFData Module where
rnf x = x `seq` ()
stableModuleCmp :: Module -> Module -> Ordering
stableModuleCmp (Module p1 n1) (Module p2 n2)
= (p1 `stableUnitIdCmp` p2) `thenCmp`
(n1 `stableModuleNameCmp` n2)
mkModule :: UnitId -> ModuleName -> Module
mkModule = Module
pprModule :: Module -> SDoc
pprModule mod@(Module p n) = getPprStyle doc
where
doc sty
| codeStyle sty =
(if p == mainUnitId
then empty
else ztext (zEncodeFS (unitIdFS p)) <> char '_')
<> pprModuleName n
| qualModule sty mod =
if isHoleModule mod
then angleBrackets (pprModuleName n)
else ppr (moduleUnitId mod) <> char ':' <> pprModuleName n
| otherwise =
pprModuleName n
class ContainsModule t where
extractModule :: t -> Module
class HasModule m where
getModule :: m Module
instance DbUnitIdModuleRep InstalledUnitId ComponentId UnitId ModuleName Module where
fromDbModule (DbModule uid mod_name) = mkModule uid mod_name
fromDbModule (DbModuleVar mod_name) = mkHoleModule mod_name
fromDbUnitId (DbUnitId cid insts) = newUnitId cid insts
fromDbUnitId (DbInstalledUnitId iuid) = DefiniteUnitId (DefUnitId iuid)
toDbModule = error "toDbModule: not implemented"
toDbUnitId = error "toDbUnitId: not implemented"
newtype ComponentId = ComponentId FastString deriving (Eq, Ord)
instance BinaryStringRep ComponentId where
fromStringRep = ComponentId . mkFastStringByteString
toStringRep (ComponentId s) = fastStringToByteString s
instance Uniquable ComponentId where
getUnique (ComponentId n) = getUnique n
instance Outputable ComponentId where
ppr cid@(ComponentId fs) =
getPprStyle $ \sty ->
sdocWithDynFlags $ \dflags ->
case componentIdString dflags cid of
Just str | not (debugStyle sty) -> text str
_ -> ftext fs
data UnitId
= IndefiniteUnitId {-# UNPACK #-} !IndefUnitId
| DefiniteUnitId {-# UNPACK #-} !DefUnitId
deriving (Typeable)
unitIdFS :: UnitId -> FastString
unitIdFS (IndefiniteUnitId x) = indefUnitIdFS x
unitIdFS (DefiniteUnitId (DefUnitId x)) = installedUnitIdFS x
unitIdKey :: UnitId -> Unique
unitIdKey (IndefiniteUnitId x) = indefUnitIdKey x
unitIdKey (DefiniteUnitId (DefUnitId x)) = installedUnitIdKey x
data IndefUnitId
= IndefUnitId {
indefUnitIdFS :: FastString,
indefUnitIdKey :: Unique,
indefUnitIdComponentId :: !ComponentId,
indefUnitIdInsts :: ![(ModuleName, Module)],
indefUnitIdFreeHoles :: UniqDSet ModuleName
} deriving (Typeable)
instance Eq IndefUnitId where
u1 == u2 = indefUnitIdKey u1 == indefUnitIdKey u2
instance Ord IndefUnitId where
u1 `compare` u2 = indefUnitIdFS u1 `compare` indefUnitIdFS u2
instance Binary IndefUnitId where
put_ bh indef = do
put_ bh (indefUnitIdComponentId indef)
put_ bh (indefUnitIdInsts indef)
get bh = do
cid <- get bh
insts <- get bh
let fs = hashUnitId cid insts
return IndefUnitId {
indefUnitIdComponentId = cid,
indefUnitIdInsts = insts,
indefUnitIdFreeHoles = unionManyUniqDSets (map (moduleFreeHoles.snd) insts),
indefUnitIdFS = fs,
indefUnitIdKey = getUnique fs
}
newIndefUnitId :: ComponentId -> [(ModuleName, Module)] -> IndefUnitId
newIndefUnitId cid insts =
IndefUnitId {
indefUnitIdComponentId = cid,
indefUnitIdInsts = sorted_insts,
indefUnitIdFreeHoles = unionManyUniqDSets (map (moduleFreeHoles.snd) insts),
indefUnitIdFS = fs,
indefUnitIdKey = getUnique fs
}
where
fs = hashUnitId cid sorted_insts
sorted_insts = sortBy (stableModuleNameCmp `on` fst) insts
indefUnitIdToUnitId :: DynFlags -> IndefUnitId -> UnitId
indefUnitIdToUnitId dflags iuid =
improveUnitId (getPackageConfigMap dflags) $
IndefiniteUnitId iuid
data IndefModule = IndefModule {
indefModuleUnitId :: IndefUnitId,
indefModuleName :: ModuleName
} deriving (Typeable, Eq, Ord)
instance Outputable IndefModule where
ppr (IndefModule uid m) =
ppr uid <> char ':' <> ppr m
indefModuleToModule :: DynFlags -> IndefModule -> Module
indefModuleToModule dflags (IndefModule iuid mod_name) =
mkModule (indefUnitIdToUnitId dflags iuid) mod_name
newtype InstalledUnitId =
InstalledUnitId {
installedUnitIdFS :: FastString
}
deriving (Typeable)
instance Binary InstalledUnitId where
put_ bh (InstalledUnitId fs) = put_ bh fs
get bh = do fs <- get bh; return (InstalledUnitId fs)
instance BinaryStringRep InstalledUnitId where
fromStringRep bs = InstalledUnitId (mkFastStringByteString bs)
toStringRep = error "BinaryStringRep InstalledUnitId: not implemented"
instance Eq InstalledUnitId where
uid1 == uid2 = installedUnitIdKey uid1 == installedUnitIdKey uid2
instance Ord InstalledUnitId where
u1 `compare` u2 = installedUnitIdFS u1 `compare` installedUnitIdFS u2
instance Uniquable InstalledUnitId where
getUnique = installedUnitIdKey
instance Outputable InstalledUnitId where
ppr uid@(InstalledUnitId fs) =
getPprStyle $ \sty ->
sdocWithDynFlags $ \dflags ->
case displayInstalledUnitId dflags uid of
Just str | not (debugStyle sty) -> text str
_ -> ftext fs
installedUnitIdKey :: InstalledUnitId -> Unique
installedUnitIdKey = getUnique . installedUnitIdFS
toInstalledUnitId :: UnitId -> InstalledUnitId
toInstalledUnitId (DefiniteUnitId (DefUnitId iuid)) = iuid
toInstalledUnitId (IndefiniteUnitId indef) =
componentIdToInstalledUnitId (indefUnitIdComponentId indef)
installedUnitIdString :: InstalledUnitId -> String
installedUnitIdString = unpackFS . installedUnitIdFS
instance Outputable IndefUnitId where
ppr uid =
ppr cid <>
(if not (null insts)
then
brackets (hcat
(punctuate comma $
[ ppr modname <> text "=" <> ppr m
| (modname, m) <- insts]))
else empty)
where
cid = indefUnitIdComponentId uid
insts = indefUnitIdInsts uid
data InstalledModule = InstalledModule {
installedModuleUnitId :: !InstalledUnitId,
installedModuleName :: !ModuleName
}
deriving (Eq, Ord)
instance Outputable InstalledModule where
ppr (InstalledModule p n) =
ppr p <> char ':' <> pprModuleName n
fsToInstalledUnitId :: FastString -> InstalledUnitId
fsToInstalledUnitId fs = InstalledUnitId fs
componentIdToInstalledUnitId :: ComponentId -> InstalledUnitId
componentIdToInstalledUnitId (ComponentId fs) = fsToInstalledUnitId fs
stringToInstalledUnitId :: String -> InstalledUnitId
stringToInstalledUnitId = fsToInstalledUnitId . mkFastString
installedModuleEq :: InstalledModule -> Module -> Bool
installedModuleEq imod mod =
fst (splitModuleInsts mod) == imod
installedUnitIdEq :: InstalledUnitId -> UnitId -> Bool
installedUnitIdEq iuid uid =
fst (splitUnitIdInsts uid) == iuid
newtype DefUnitId = DefUnitId { unDefUnitId :: InstalledUnitId }
deriving (Eq, Ord, Typeable)
instance Outputable DefUnitId where
ppr (DefUnitId uid) = ppr uid
instance Binary DefUnitId where
put_ bh (DefUnitId uid) = put_ bh uid
get bh = do uid <- get bh; return (DefUnitId uid)
newtype InstalledModuleEnv elt = InstalledModuleEnv (Map InstalledModule elt)
emptyInstalledModuleEnv :: InstalledModuleEnv a
emptyInstalledModuleEnv = InstalledModuleEnv Map.empty
lookupInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> Maybe a
lookupInstalledModuleEnv (InstalledModuleEnv e) m = Map.lookup m e
extendInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> a -> InstalledModuleEnv a
extendInstalledModuleEnv (InstalledModuleEnv e) m x = InstalledModuleEnv (Map.insert m x e)
filterInstalledModuleEnv :: (InstalledModule -> a -> Bool) -> InstalledModuleEnv a -> InstalledModuleEnv a
filterInstalledModuleEnv f (InstalledModuleEnv e) =
InstalledModuleEnv (Map.filterWithKey f e)
delInstalledModuleEnv :: InstalledModuleEnv a -> InstalledModule -> InstalledModuleEnv a
delInstalledModuleEnv (InstalledModuleEnv e) m = InstalledModuleEnv (Map.delete m e)
unitIdFreeHoles :: UnitId -> UniqDSet ModuleName
unitIdFreeHoles (IndefiniteUnitId x) = indefUnitIdFreeHoles x
unitIdFreeHoles (DefiniteUnitId _) = emptyUniqDSet
instance Show UnitId where
show = unitIdString
unitIdIsDefinite :: UnitId -> Bool
unitIdIsDefinite = isEmptyUniqDSet . unitIdFreeHoles
hashUnitId :: ComponentId -> [(ModuleName, Module)] -> FastString
hashUnitId cid sorted_holes =
mkFastStringByteString
. fingerprintUnitId (toStringRep cid)
$ rawHashUnitId sorted_holes
rawHashUnitId :: [(ModuleName, Module)] -> Fingerprint
rawHashUnitId sorted_holes =
fingerprintByteString
. BS.concat $ do
(m, b) <- sorted_holes
[ toStringRep m, BS.Char8.singleton ' ',
fastStringToByteString (unitIdFS (moduleUnitId b)), BS.Char8.singleton ':',
toStringRep (moduleName b), BS.Char8.singleton '\n']
fingerprintByteString :: BS.ByteString -> Fingerprint
fingerprintByteString bs = unsafePerformIO
. BS.unsafeUseAsCStringLen bs
$ \(p,l) -> fingerprintData (castPtr p) l
fingerprintUnitId :: BS.ByteString -> Fingerprint -> BS.ByteString
fingerprintUnitId prefix (Fingerprint a b)
= BS.concat
$ [ prefix
, BS.Char8.singleton '-'
, BS.Char8.pack (toBase62Padded a)
, BS.Char8.pack (toBase62Padded b) ]
newUnitId :: ComponentId -> [(ModuleName, Module)] -> UnitId
newUnitId cid [] = newSimpleUnitId cid
newUnitId cid insts = IndefiniteUnitId $ newIndefUnitId cid insts
pprUnitId :: UnitId -> SDoc
pprUnitId (DefiniteUnitId uid) = ppr uid
pprUnitId (IndefiniteUnitId uid) = ppr uid
instance Eq UnitId where
uid1 == uid2 = unitIdKey uid1 == unitIdKey uid2
instance Uniquable UnitId where
getUnique = unitIdKey
instance Ord UnitId where
nm1 `compare` nm2 = stableUnitIdCmp nm1 nm2
instance Data UnitId where
toConstr _ = abstractConstr "UnitId"
gunfold _ _ = error "gunfold"
dataTypeOf _ = mkNoRepType "UnitId"
instance NFData UnitId where
rnf x = x `seq` ()
stableUnitIdCmp :: UnitId -> UnitId -> Ordering
stableUnitIdCmp p1 p2 = unitIdFS p1 `compare` unitIdFS p2
instance Outputable UnitId where
ppr pk = pprUnitId pk
instance Binary UnitId where
put_ bh (DefiniteUnitId def_uid) = do
putByte bh 0
put_ bh def_uid
put_ bh (IndefiniteUnitId indef_uid) = do
putByte bh 1
put_ bh indef_uid
get bh = do b <- getByte bh
case b of
0 -> fmap DefiniteUnitId (get bh)
_ -> fmap IndefiniteUnitId (get bh)
instance Binary ComponentId where
put_ bh (ComponentId fs) = put_ bh fs
get bh = do { fs <- get bh; return (ComponentId fs) }
newSimpleUnitId :: ComponentId -> UnitId
newSimpleUnitId (ComponentId fs) = fsToUnitId fs
fsToUnitId :: FastString -> UnitId
fsToUnitId = DefiniteUnitId . DefUnitId . InstalledUnitId
stringToUnitId :: String -> UnitId
stringToUnitId = fsToUnitId . mkFastString
unitIdString :: UnitId -> String
unitIdString = unpackFS . unitIdFS
type ShHoleSubst = ModuleNameEnv Module
renameHoleModule :: DynFlags -> ShHoleSubst -> Module -> Module
renameHoleModule dflags = renameHoleModule' (getPackageConfigMap dflags)
renameHoleUnitId :: DynFlags -> ShHoleSubst -> UnitId -> UnitId
renameHoleUnitId dflags = renameHoleUnitId' (getPackageConfigMap dflags)
renameHoleModule' :: PackageConfigMap -> ShHoleSubst -> Module -> Module
renameHoleModule' pkg_map env m
| not (isHoleModule m) =
let uid = renameHoleUnitId' pkg_map env (moduleUnitId m)
in mkModule uid (moduleName m)
| Just m' <- lookupUFM env (moduleName m) = m'
| otherwise = m
renameHoleUnitId' :: PackageConfigMap -> ShHoleSubst -> UnitId -> UnitId
renameHoleUnitId' pkg_map env uid =
case uid of
(IndefiniteUnitId
IndefUnitId{ indefUnitIdComponentId = cid
, indefUnitIdInsts = insts
, indefUnitIdFreeHoles = fh })
-> if isNullUFM (intersectUFM_C const (udfmToUfm fh) env)
then uid
else improveUnitId pkg_map $
newUnitId cid
(map (\(k,v) -> (k, renameHoleModule' pkg_map env v)) insts)
_ -> uid
splitModuleInsts :: Module -> (InstalledModule, Maybe IndefModule)
splitModuleInsts m =
let (uid, mb_iuid) = splitUnitIdInsts (moduleUnitId m)
in (InstalledModule uid (moduleName m),
fmap (\iuid -> IndefModule iuid (moduleName m)) mb_iuid)
splitUnitIdInsts :: UnitId -> (InstalledUnitId, Maybe IndefUnitId)
splitUnitIdInsts (IndefiniteUnitId iuid) =
(componentIdToInstalledUnitId (indefUnitIdComponentId iuid), Just iuid)
splitUnitIdInsts (DefiniteUnitId (DefUnitId uid)) = (uid, Nothing)
generalizeIndefUnitId :: IndefUnitId -> IndefUnitId
generalizeIndefUnitId IndefUnitId{ indefUnitIdComponentId = cid
, indefUnitIdInsts = insts } =
newIndefUnitId cid (map (\(m,_) -> (m, mkHoleModule m)) insts)
generalizeIndefModule :: IndefModule -> IndefModule
generalizeIndefModule (IndefModule uid n) = IndefModule (generalizeIndefUnitId uid) n
parseModuleName :: ReadP ModuleName
parseModuleName = fmap mkModuleName
$ Parse.munch1 (\c -> isAlphaNum c || c `elem` "_.")
parseUnitId :: ReadP UnitId
parseUnitId = parseFullUnitId <++ parseDefiniteUnitId <++ parseSimpleUnitId
where
parseFullUnitId = do
cid <- parseComponentId
insts <- parseModSubst
return (newUnitId cid insts)
parseDefiniteUnitId = do
s <- Parse.munch1 (\c -> isAlphaNum c || c `elem` "-_.+")
return (stringToUnitId s)
parseSimpleUnitId = do
cid <- parseComponentId
return (newSimpleUnitId cid)
parseComponentId :: ReadP ComponentId
parseComponentId = (ComponentId . mkFastString) `fmap` Parse.munch1 abi_char
where abi_char c = isAlphaNum c || c `elem` "-_."
parseModuleId :: ReadP Module
parseModuleId = parseModuleVar <++ parseModule
where
parseModuleVar = do
_ <- Parse.char '<'
modname <- parseModuleName
_ <- Parse.char '>'
return (mkHoleModule modname)
parseModule = do
uid <- parseUnitId
_ <- Parse.char ':'
modname <- parseModuleName
return (mkModule uid modname)
parseModSubst :: ReadP [(ModuleName, Module)]
parseModSubst = Parse.between (Parse.char '[') (Parse.char ']')
. flip Parse.sepBy (Parse.char ',')
$ do k <- parseModuleName
_ <- Parse.char '='
v <- parseModuleId
return (k, v)
integerUnitId, primUnitId,
baseUnitId, rtsUnitId,
thUnitId, dphSeqUnitId, dphParUnitId,
mainUnitId, thisGhcUnitId, interactiveUnitId :: UnitId
primUnitId = fsToUnitId (fsLit "ghc-prim")
integerUnitId = fsToUnitId (fsLit n)
where
n = case cIntegerLibraryType of
IntegerGMP -> "integer-gmp"
IntegerSimple -> "integer-simple"
baseUnitId = fsToUnitId (fsLit "base")
rtsUnitId = fsToUnitId (fsLit "rts")
thUnitId = fsToUnitId (fsLit "template-haskell")
dphSeqUnitId = fsToUnitId (fsLit "dph-seq")
dphParUnitId = fsToUnitId (fsLit "dph-par")
thisGhcUnitId = fsToUnitId (fsLit "ghc")
interactiveUnitId = fsToUnitId (fsLit "interactive")
mainUnitId = fsToUnitId (fsLit "main")
holeUnitId :: UnitId
holeUnitId = fsToUnitId (fsLit "hole")
isInteractiveModule :: Module -> Bool
isInteractiveModule mod = moduleUnitId mod == interactiveUnitId
isHoleModule :: Module -> Bool
isHoleModule mod = moduleUnitId mod == holeUnitId
wiredInUnitIds :: [UnitId]
wiredInUnitIds = [ primUnitId,
integerUnitId,
baseUnitId,
rtsUnitId,
thUnitId,
thisGhcUnitId,
dphSeqUnitId,
dphParUnitId ]
newtype ModuleEnv elt = ModuleEnv (Map NDModule elt)
newtype NDModule = NDModule { unNDModule :: Module }
deriving Eq
instance Ord NDModule where
compare (NDModule (Module p1 n1)) (NDModule (Module p2 n2)) =
(getUnique p1 `nonDetCmpUnique` getUnique p2) `thenCmp`
(getUnique n1 `nonDetCmpUnique` getUnique n2)
filterModuleEnv :: (Module -> a -> Bool) -> ModuleEnv a -> ModuleEnv a
filterModuleEnv f (ModuleEnv e) =
ModuleEnv (Map.filterWithKey (f . unNDModule) e)
elemModuleEnv :: Module -> ModuleEnv a -> Bool
elemModuleEnv m (ModuleEnv e) = Map.member (NDModule m) e
extendModuleEnv :: ModuleEnv a -> Module -> a -> ModuleEnv a
extendModuleEnv (ModuleEnv e) m x = ModuleEnv (Map.insert (NDModule m) x e)
extendModuleEnvWith :: (a -> a -> a) -> ModuleEnv a -> Module -> a
-> ModuleEnv a
extendModuleEnvWith f (ModuleEnv e) m x =
ModuleEnv (Map.insertWith f (NDModule m) x e)
extendModuleEnvList :: ModuleEnv a -> [(Module, a)] -> ModuleEnv a
extendModuleEnvList (ModuleEnv e) xs =
ModuleEnv (Map.insertList [(NDModule k, v) | (k,v) <- xs] e)
extendModuleEnvList_C :: (a -> a -> a) -> ModuleEnv a -> [(Module, a)]
-> ModuleEnv a
extendModuleEnvList_C f (ModuleEnv e) xs =
ModuleEnv (Map.insertListWith f [(NDModule k, v) | (k,v) <- xs] e)
plusModuleEnv_C :: (a -> a -> a) -> ModuleEnv a -> ModuleEnv a -> ModuleEnv a
plusModuleEnv_C f (ModuleEnv e1) (ModuleEnv e2) =
ModuleEnv (Map.unionWith f e1 e2)
delModuleEnvList :: ModuleEnv a -> [Module] -> ModuleEnv a
delModuleEnvList (ModuleEnv e) ms =
ModuleEnv (Map.deleteList (map NDModule ms) e)
delModuleEnv :: ModuleEnv a -> Module -> ModuleEnv a
delModuleEnv (ModuleEnv e) m = ModuleEnv (Map.delete (NDModule m) e)
plusModuleEnv :: ModuleEnv a -> ModuleEnv a -> ModuleEnv a
plusModuleEnv (ModuleEnv e1) (ModuleEnv e2) = ModuleEnv (Map.union e1 e2)
lookupModuleEnv :: ModuleEnv a -> Module -> Maybe a
lookupModuleEnv (ModuleEnv e) m = Map.lookup (NDModule m) e
lookupWithDefaultModuleEnv :: ModuleEnv a -> a -> Module -> a
lookupWithDefaultModuleEnv (ModuleEnv e) x m =
Map.findWithDefault x (NDModule m) e
mapModuleEnv :: (a -> b) -> ModuleEnv a -> ModuleEnv b
mapModuleEnv f (ModuleEnv e) = ModuleEnv (Map.mapWithKey (\_ v -> f v) e)
mkModuleEnv :: [(Module, a)] -> ModuleEnv a
mkModuleEnv xs = ModuleEnv (Map.fromList [(NDModule k, v) | (k,v) <- xs])
emptyModuleEnv :: ModuleEnv a
emptyModuleEnv = ModuleEnv Map.empty
moduleEnvKeys :: ModuleEnv a -> [Module]
moduleEnvKeys (ModuleEnv e) = sort $ map unNDModule $ Map.keys e
moduleEnvElts :: ModuleEnv a -> [a]
moduleEnvElts e = map snd $ moduleEnvToList e
moduleEnvToList :: ModuleEnv a -> [(Module, a)]
moduleEnvToList (ModuleEnv e) =
sortBy (comparing fst) [(m, v) | (NDModule m, v) <- Map.toList e]
unitModuleEnv :: Module -> a -> ModuleEnv a
unitModuleEnv m x = ModuleEnv (Map.singleton (NDModule m) x)
isEmptyModuleEnv :: ModuleEnv a -> Bool
isEmptyModuleEnv (ModuleEnv e) = Map.null e
type ModuleSet = Set NDModule
mkModuleSet :: [Module] -> ModuleSet
mkModuleSet = Set.fromList . coerce
extendModuleSet :: ModuleSet -> Module -> ModuleSet
extendModuleSet s m = Set.insert (NDModule m) s
extendModuleSetList :: ModuleSet -> [Module] -> ModuleSet
extendModuleSetList s ms = foldl' (coerce . flip Set.insert) s ms
emptyModuleSet :: ModuleSet
emptyModuleSet = Set.empty
moduleSetElts :: ModuleSet -> [Module]
moduleSetElts = sort . coerce . Set.toList
elemModuleSet :: Module -> ModuleSet -> Bool
elemModuleSet = Set.member . coerce
intersectModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
intersectModuleSet = coerce Set.intersection
minusModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
minusModuleSet = coerce Set.difference
delModuleSet :: ModuleSet -> Module -> ModuleSet
delModuleSet = coerce (flip Set.delete)
unionModuleSet :: ModuleSet -> ModuleSet -> ModuleSet
unionModuleSet = coerce Set.union
unitModuleSet :: Module -> ModuleSet
unitModuleSet = coerce Set.singleton
type ModuleNameEnv elt = UniqFM elt
type DModuleNameEnv elt = UniqDFM elt