module Module.ProcessMetadata (
MetadataMap,
createCachedDir,
createCachePath,
eraseCachedData,
findSourceFiles,
getCachedPath,
getCacheRelativePath,
getExprMap,
getIncludePathsForDeps,
getLibrariesForDeps,
getLinkFlagsForDeps,
getNamespacesForDeps,
getObjectFilesForDeps,
getObjectFileResolver,
getRealPathsForDeps,
getRecompilePath,
isPathConfigured,
isPathUpToDate,
isPrivateSource,
isPublicSource,
isTestSource,
loadModuleGlobals,
loadModuleMetadata,
loadPrivateDeps,
loadPublicDeps,
loadRecompile,
loadTestingDeps,
mapMetadata,
readPossibleTraces,
resolveCategoryDeps,
resolveObjectDeps,
sortCompiledFiles,
writeCachedFile,
writeMetadata,
writePossibleTraces,
writeRecompile,
) where
import Control.Applicative ((<|>))
import Control.Monad (when)
import Data.List (isSuffixOf,nub)
import Data.Maybe (isJust)
import Data.Time.Clock (UTCTime)
import System.Directory
import System.FilePath
import System.IO
import qualified Data.Map as Map
import qualified Data.Set as Set
import Base.CompilerError
import Base.TrackedErrors
import Cli.CompileOptions
import Cli.Programs (VersionHash(..))
import Compilation.ProcedureContext (ExprMap)
import CompilerCxx.CxxFiles (CxxOutput(..))
import Module.CompileMetadata
import Module.ParseMetadata
import Module.Paths
import Parser.SourceFile
import Parser.TextParser (SourceContext)
import Types.Procedure
import Types.TypeCategory
import Types.TypeInstance
cachedDataPath :: FilePath
cachedDataPath :: FilePath
cachedDataPath = FilePath
".zeolite-cache"
moduleFilename :: FilePath
moduleFilename :: FilePath
moduleFilename = FilePath
".zeolite-module"
metadataFilename :: FilePath
metadataFilename :: FilePath
metadataFilename = FilePath
"compile-metadata"
tracesFilename :: FilePath
tracesFilename :: FilePath
tracesFilename = FilePath
"traced-lines"
isPublicSource :: FilePath -> Bool
isPublicSource :: FilePath -> Bool
isPublicSource = forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".0rp"
isPrivateSource :: FilePath -> Bool
isPrivateSource :: FilePath -> Bool
isPrivateSource = forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".0rx"
isTestSource :: FilePath -> Bool
isTestSource :: FilePath -> Bool
isTestSource = forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".0rt"
type MetadataMap = Map.Map FilePath CompileMetadata
mapMetadata :: [CompileMetadata] -> MetadataMap
mapMetadata :: [CompileMetadata] -> MetadataMap
mapMetadata [CompileMetadata]
cs = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> FilePath
cmPath [CompileMetadata]
cs) [CompileMetadata]
cs
loadRecompile :: FilePath -> TrackedErrorsIO ModuleConfig
loadRecompile :: FilePath -> TrackedErrorsIO ModuleConfig
loadRecompile FilePath
p = do
let f :: FilePath
f = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
moduleFilename
Bool
isFile <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
p
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isFile forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Path \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" is not a directory"
Bool
isDir <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
p
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
isDir) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Path \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" does not exist"
Bool
filePresent <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
filePresent) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Module \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" has not been configured yet"
FilePath
c <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
readFile FilePath
f
ModuleConfig
m <- forall a (m :: * -> *).
(ConfigFormat a, ErrorContextM m) =>
FilePath -> FilePath -> m a
autoReadConfig FilePath
f FilePath
c forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<!!
FilePath
"Could not parse metadata from \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\"; please reconfigure"
FilePath
p0 <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
let p1 :: FilePath
p1 = ModuleConfig -> FilePath
mcRoot ModuleConfig
m FilePath -> FilePath -> FilePath
</> ModuleConfig -> FilePath
mcPath ModuleConfig
m
FilePath
p2 <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath forall a b. (a -> b) -> a -> b
$ FilePath
p0 FilePath -> FilePath -> FilePath
</> FilePath
p1
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (FilePath
p2 forall a. Eq a => a -> a -> Bool
/= FilePath
p0) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Expected module path from " forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++
FilePath
" to match " forall a. [a] -> [a] -> [a]
++ FilePath
moduleFilename forall a. [a] -> [a] -> [a]
++
FilePath
" location but got " forall a. [a] -> [a] -> [a]
++ FilePath
p2 forall a. [a] -> [a] -> [a]
++
FilePath
" (resolved from root: \"" forall a. [a] -> [a] -> [a]
++ ModuleConfig -> FilePath
mcRoot ModuleConfig
m forall a. [a] -> [a] -> [a]
++
FilePath
"\" and path: \"" forall a. [a] -> [a] -> [a]
++ ModuleConfig -> FilePath
mcPath ModuleConfig
m forall a. [a] -> [a] -> [a]
++ FilePath
"\")"
forall (m :: * -> *) a. Monad m => a -> m a
return ModuleConfig
m
isPathUpToDate :: VersionHash -> ForceMode -> FilePath -> TrackedErrorsIO Bool
isPathUpToDate :: VersionHash -> ForceMode -> FilePath -> TrackedErrorsT IO Bool
isPathUpToDate VersionHash
h ForceMode
f FilePath
p = do
TrackedErrors [CompileMetadata]
m <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ ForceMode
-> VersionHash
-> MetadataMap
-> Set FilePath
-> (CompileMetadata -> [FilePath])
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadDepsCommon ForceMode
f VersionHash
h forall k a. Map k a
Map.empty forall a. Set a
Set.empty (\CompileMetadata
m2 -> CompileMetadata -> [FilePath]
cmPublicDeps CompileMetadata
m2 forall a. [a] -> [a] -> [a]
++ CompileMetadata -> [FilePath]
cmPrivateDeps CompileMetadata
m2) [FilePath
p]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors [CompileMetadata]
m
isPathConfigured :: FilePath -> FilePath -> TrackedErrorsIO Bool
isPathConfigured :: FilePath -> FilePath -> TrackedErrorsT IO Bool
isPathConfigured FilePath
p FilePath
d = do
TrackedErrors ModuleConfig
m <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ FilePath -> TrackedErrorsIO ModuleConfig
loadRecompile (FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
d)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrors ModuleConfig
m
writeMetadata :: FilePath -> CompileMetadata -> UTCTime -> TrackedErrorsIO ()
writeMetadata :: FilePath -> CompileMetadata -> UTCTime -> TrackedErrorsT IO ()
writeMetadata FilePath
p CompileMetadata
m UTCTime
t = do
FilePath
p' <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"Writing metadata for \"" forall a. [a] -> [a] -> [a]
++ FilePath
p' forall a. [a] -> [a] -> [a]
++ FilePath
"\"."
FilePath
m' <- forall a (m :: * -> *).
(ConfigFormat a, CollectErrorsM m) =>
a -> m FilePath
autoWriteConfig CompileMetadata
m forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
"In data for " forall a. [a] -> [a] -> [a]
++ FilePath
p
FilePath
-> FilePath
-> FilePath
-> Maybe UTCTime
-> FilePath
-> TrackedErrorsT IO ()
writeCachedFile FilePath
p' FilePath
"" FilePath
metadataFilename (forall a. a -> Maybe a
Just UTCTime
t) FilePath
m'
writeRecompile :: FilePath -> ModuleConfig -> TrackedErrorsIO ()
writeRecompile :: FilePath -> ModuleConfig -> TrackedErrorsT IO ()
writeRecompile FilePath
p ModuleConfig
m = do
FilePath
p' <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
let f :: FilePath
f = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
moduleFilename
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"Updating config for \"" forall a. [a] -> [a] -> [a]
++ FilePath
p' forall a. [a] -> [a] -> [a]
++ FilePath
"\"."
FilePath
m' <- forall a (m :: * -> *).
(ConfigFormat a, CollectErrorsM m) =>
a -> m FilePath
autoWriteConfig ModuleConfig
m forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<?? FilePath
"In data for " forall a. [a] -> [a] -> [a]
++ FilePath
p
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
writeFile FilePath
f FilePath
m'
writePossibleTraces :: FilePath -> Set.Set String -> TrackedErrorsIO ()
writePossibleTraces :: FilePath -> Set FilePath -> TrackedErrorsT IO ()
writePossibleTraces FilePath
p Set FilePath
ts = do
FilePath
p' <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
FilePath
-> FilePath
-> FilePath
-> Maybe UTCTime
-> FilePath
-> TrackedErrorsT IO ()
writeCachedFile FilePath
p' FilePath
"" FilePath
tracesFilename forall a. Maybe a
Nothing forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. [a] -> [a] -> [a]
++FilePath
"\n") forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
Set.toList Set FilePath
ts
readPossibleTraces :: FilePath -> TrackedErrorsIO (Set.Set String)
readPossibleTraces :: FilePath -> TrackedErrorsIO (Set FilePath)
readPossibleTraces FilePath
p = do
FilePath
p' <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
FilePath
c <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
readFile (FilePath -> FilePath -> FilePath -> FilePath
getCachedPath FilePath
p' FilePath
"" FilePath
tracesFilename)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath]
lines FilePath
c
getRecompilePath :: FilePath -> TrackedErrorsIO FilePath
getRecompilePath :: FilePath -> TrackedErrorsT IO FilePath
getRecompilePath FilePath
p = do
FilePath
p' <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ FilePath
p' FilePath -> FilePath -> FilePath
</> FilePath
moduleFilename
eraseCachedData :: FilePath -> TrackedErrorsIO ()
eraseCachedData :: FilePath -> TrackedErrorsT IO ()
eraseCachedData FilePath
p = do
let d :: FilePath
d = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cachedDataPath
Bool
dirExists <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
d
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
dirExists forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO ()
removeDirectoryRecursive FilePath
d
createCachePath :: FilePath -> TrackedErrorsIO ()
createCachePath :: FilePath -> TrackedErrorsT IO ()
createCachePath FilePath
p = do
let f :: FilePath
f = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cachedDataPath
Bool
exists <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
False FilePath
f
createCachedDir :: FilePath -> FilePath -> TrackedErrorsIO FilePath
createCachedDir :: FilePath -> FilePath -> TrackedErrorsT IO FilePath
createCachedDir FilePath
p FilePath
d = do
FilePath -> TrackedErrorsT IO ()
createCachePath FilePath
p
let d2 :: FilePath
d2 = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cachedDataPath FilePath -> FilePath -> FilePath
</> FilePath
d
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
False FilePath
d2
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
d2
writeCachedFile :: FilePath -> String -> FilePath -> Maybe UTCTime -> String -> TrackedErrorsIO ()
writeCachedFile :: FilePath
-> FilePath
-> FilePath
-> Maybe UTCTime
-> FilePath
-> TrackedErrorsT IO ()
writeCachedFile FilePath
p FilePath
ns FilePath
f Maybe UTCTime
t FilePath
c = do
FilePath -> TrackedErrorsT IO ()
createCachePath FilePath
p
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
False forall a b. (a -> b) -> a -> b
$ FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cachedDataPath FilePath -> FilePath -> FilePath
</> FilePath
ns
let filename :: FilePath
filename = FilePath -> FilePath -> FilePath -> FilePath
getCachedPath FilePath
p FilePath
ns FilePath
f
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO ()
writeFile FilePath
filename FilePath
c
case Maybe UTCTime
t of
Just UTCTime
t2 -> forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> UTCTime -> IO ()
setModificationTime FilePath
filename UTCTime
t2
Maybe UTCTime
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
getCachedPath :: FilePath -> String -> FilePath -> FilePath
getCachedPath :: FilePath -> FilePath -> FilePath -> FilePath
getCachedPath FilePath
p FilePath
ns FilePath
f = FilePath -> FilePath
fixPath forall a b. (a -> b) -> a -> b
$ FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cachedDataPath FilePath -> FilePath -> FilePath
</> FilePath
ns FilePath -> FilePath -> FilePath
</> FilePath
f
getCacheRelativePath :: FilePath -> FilePath
getCacheRelativePath :: FilePath -> FilePath
getCacheRelativePath FilePath
f = FilePath
".." FilePath -> FilePath -> FilePath
</> FilePath
f
findSourceFiles :: FilePath -> [FilePath] -> TrackedErrorsIO ([FilePath],[FilePath],[FilePath])
findSourceFiles :: FilePath
-> [FilePath]
-> TrackedErrorsIO ([FilePath], [FilePath], [FilePath])
findSourceFiles FilePath
p0 = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([FilePath] -> ([FilePath], [FilePath], [FilePath])
select forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m [FilePath]
find where
find :: FilePath -> m [FilePath]
find FilePath
p = do
let absolute :: FilePath
absolute = FilePath
p0 FilePath -> FilePath -> FilePath
</> FilePath
p
Bool
isFile <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
absolute
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isFile forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Path \"" forall a. [a] -> [a] -> [a]
++ FilePath
absolute forall a. [a] -> [a] -> [a]
++ FilePath
"\" is not a directory"
Bool
isDir <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
absolute
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
isDir) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Path \"" forall a. [a] -> [a] -> [a]
++ FilePath
absolute forall a. [a] -> [a] -> [a]
++ FilePath
"\" does not exist"
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO [FilePath]
getDirectoryContents FilePath
absolute forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (FilePath
p FilePath -> FilePath -> FilePath
</>)
select :: [FilePath] -> ([FilePath], [FilePath], [FilePath])
select [FilePath]
ds = ([FilePath]
ps,[FilePath]
xs,[FilePath]
ts) where
ps :: [FilePath]
ps = forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
isPublicSource [FilePath]
ds
xs :: [FilePath]
xs = forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
isPrivateSource [FilePath]
ds
ts :: [FilePath]
ts = forall a. Eq a => [a] -> [a]
nub forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
isTestSource [FilePath]
ds
getExprMap :: FilePath -> ModuleConfig -> TrackedErrorsIO (ExprMap SourceContext)
getExprMap :: FilePath -> ModuleConfig -> TrackedErrorsIO (ExprMap SourceContext)
getExprMap FilePath
p ModuleConfig
m = do
FilePath
path <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath (FilePath
p FilePath -> FilePath -> FilePath
</> ModuleConfig -> FilePath
mcRoot ModuleConfig
m FilePath -> FilePath -> FilePath
</> ModuleConfig -> FilePath
mcPath ModuleConfig
m)
let defaults :: [(MacroName, Expression c)]
defaults = [(FilePath -> MacroName
MacroName FilePath
"MODULE_PATH",forall c. ValueLiteral c -> Expression c
Literal (forall c. [c] -> FilePath -> ValueLiteral c
StringLiteral [] FilePath
path))]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ ModuleConfig -> [(MacroName, Expression SourceContext)]
mcExprMap ModuleConfig
m forall a. [a] -> [a] -> [a]
++ forall {c}. [(MacroName, Expression c)]
defaults
getRealPathsForDeps :: [CompileMetadata] -> [FilePath]
getRealPathsForDeps :: [CompileMetadata] -> [FilePath]
getRealPathsForDeps = forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> FilePath
cmPath
getSourceFilesForDeps :: [CompileMetadata] -> [(FilePath,[FilePath])]
getSourceFilesForDeps :: [CompileMetadata] -> [(FilePath, [FilePath])]
getSourceFilesForDeps = forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> (FilePath, [FilePath])
extract where
extract :: CompileMetadata -> (FilePath, [FilePath])
extract CompileMetadata
m = (CompileMetadata -> FilePath
cmRoot CompileMetadata
m,forall a. (a -> Bool) -> [a] -> [a]
filter FilePath -> Bool
isPublicSource forall a b. (a -> b) -> a -> b
$ CompileMetadata -> [FilePath]
cmPublicFiles CompileMetadata
m forall a. [a] -> [a] -> [a]
++ CompileMetadata -> [FilePath]
cmPrivateFiles CompileMetadata
m)
getNamespacesForDeps :: [CompileMetadata] -> [Namespace]
getNamespacesForDeps :: [CompileMetadata] -> [Namespace]
getNamespacesForDeps = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Namespace -> Bool
isNoNamespace) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> Namespace
cmPublicNamespace
getIncludePathsForDeps :: [CompileMetadata] -> [FilePath]
getIncludePathsForDeps :: [CompileMetadata] -> [FilePath]
getIncludePathsForDeps = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> [FilePath]
cmPublicSubdirs
getLinkFlagsForDeps :: [CompileMetadata] -> [String]
getLinkFlagsForDeps :: [CompileMetadata] -> [FilePath]
getLinkFlagsForDeps = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> [FilePath]
cmLinkFlags
getLibrariesForDeps :: [CompileMetadata] -> [FilePath]
getLibrariesForDeps :: [CompileMetadata] -> [FilePath]
getLibrariesForDeps = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> [FilePath]
cmLibraries
getObjectFilesForDeps :: [CompileMetadata] -> [ObjectFile]
getObjectFilesForDeps :: [CompileMetadata] -> [ObjectFile]
getObjectFilesForDeps = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> [ObjectFile]
cmObjectFiles
loadModuleMetadata :: VersionHash -> ForceMode -> MetadataMap -> FilePath ->
TrackedErrorsIO CompileMetadata
loadModuleMetadata :: VersionHash
-> ForceMode
-> MetadataMap
-> FilePath
-> TrackedErrorsIO CompileMetadata
loadModuleMetadata VersionHash
h ForceMode
f MetadataMap
ca = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForceMode
-> VersionHash
-> MetadataMap
-> Set FilePath
-> (CompileMetadata -> [FilePath])
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadDepsCommon ForceMode
f VersionHash
h MetadataMap
ca forall a. Set a
Set.empty (forall a b. a -> b -> a
const []) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])
loadPublicDeps :: VersionHash -> ForceMode -> MetadataMap -> [FilePath] ->
TrackedErrorsIO [CompileMetadata]
loadPublicDeps :: VersionHash
-> ForceMode
-> MetadataMap
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadPublicDeps VersionHash
h ForceMode
f MetadataMap
ca = ForceMode
-> VersionHash
-> MetadataMap
-> Set FilePath
-> (CompileMetadata -> [FilePath])
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadDepsCommon ForceMode
f VersionHash
h MetadataMap
ca forall a. Set a
Set.empty CompileMetadata -> [FilePath]
cmPublicDeps
loadTestingDeps :: VersionHash -> ForceMode -> MetadataMap -> CompileMetadata ->
TrackedErrorsIO [CompileMetadata]
loadTestingDeps :: VersionHash
-> ForceMode
-> MetadataMap
-> CompileMetadata
-> TrackedErrorsIO [CompileMetadata]
loadTestingDeps VersionHash
h ForceMode
f MetadataMap
ca CompileMetadata
m = ForceMode
-> VersionHash
-> MetadataMap
-> Set FilePath
-> (CompileMetadata -> [FilePath])
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadDepsCommon ForceMode
f VersionHash
h MetadataMap
ca (forall a. Ord a => [a] -> Set a
Set.fromList [CompileMetadata -> FilePath
cmPath CompileMetadata
m]) CompileMetadata -> [FilePath]
cmPublicDeps (CompileMetadata -> [FilePath]
cmPublicDeps CompileMetadata
m forall a. [a] -> [a] -> [a]
++ CompileMetadata -> [FilePath]
cmPrivateDeps CompileMetadata
m)
loadPrivateDeps :: VersionHash -> ForceMode -> MetadataMap -> [CompileMetadata] ->
TrackedErrorsIO [CompileMetadata]
loadPrivateDeps :: VersionHash
-> ForceMode
-> MetadataMap
-> [CompileMetadata]
-> TrackedErrorsIO [CompileMetadata]
loadPrivateDeps VersionHash
h ForceMode
f MetadataMap
ca [CompileMetadata]
ms = do
[CompileMetadata]
new <- ForceMode
-> VersionHash
-> MetadataMap
-> Set FilePath
-> (CompileMetadata -> [FilePath])
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadDepsCommon ForceMode
f VersionHash
h MetadataMap
ca Set FilePath
pa (\CompileMetadata
m -> CompileMetadata -> [FilePath]
cmPublicDeps CompileMetadata
m forall a. [a] -> [a] -> [a]
++ CompileMetadata -> [FilePath]
cmPrivateDeps CompileMetadata
m) [FilePath]
paths
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [CompileMetadata]
ms forall a. [a] -> [a] -> [a]
++ [CompileMetadata]
new where
paths :: [FilePath]
paths = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\CompileMetadata
m -> CompileMetadata -> [FilePath]
cmPublicDeps CompileMetadata
m forall a. [a] -> [a] -> [a]
++ CompileMetadata -> [FilePath]
cmPrivateDeps CompileMetadata
m) [CompileMetadata]
ms
pa :: Set FilePath
pa = forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> FilePath
cmPath [CompileMetadata]
ms
loadDepsCommon :: ForceMode -> VersionHash -> MetadataMap -> Set.Set FilePath ->
(CompileMetadata -> [FilePath]) -> [FilePath] -> TrackedErrorsIO [CompileMetadata]
loadDepsCommon :: ForceMode
-> VersionHash
-> MetadataMap
-> Set FilePath
-> (CompileMetadata -> [FilePath])
-> [FilePath]
-> TrackedErrorsIO [CompileMetadata]
loadDepsCommon ForceMode
f VersionHash
h MetadataMap
ca Set FilePath
pa0 CompileMetadata -> [FilePath]
getDeps [FilePath]
ps = do
(Set FilePath
_,[(FilePath, CompileMetadata)]
processed) <- TrackedErrorsT IO [FilePath]
fixedPaths forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Set FilePath, [(FilePath, CompileMetadata)])
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
collect (Set FilePath
pa0,[])
let cached :: MetadataMap
cached = forall k a. Ord k => Map k a -> Map k a -> Map k a
Map.union MetadataMap
ca (forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(FilePath, CompileMetadata)]
processed)
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall {m :: * -> *}.
MonadIO m =>
MetadataMap
-> (FilePath, CompileMetadata) -> TrackedErrorsT m CompileMetadata
check MetadataMap
cached) [(FilePath, CompileMetadata)]
processed where
enforce :: Bool
enforce = ForceMode
f forall a. Eq a => a -> a -> Bool
/= ForceMode
ForceAll
fixedPaths :: TrackedErrorsT IO [FilePath]
fixedPaths = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath) [FilePath]
ps
collect :: (Set FilePath, [(FilePath, CompileMetadata)])
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
collect xa :: (Set FilePath, [(FilePath, CompileMetadata)])
xa@(Set FilePath
pa,[(FilePath, CompileMetadata)]
xs) (FilePath
p:[FilePath]
ps2)
| FilePath
p forall a. Ord a => a -> Set a -> Bool
`Set.member` Set FilePath
pa = (Set FilePath, [(FilePath, CompileMetadata)])
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
collect (Set FilePath, [(FilePath, CompileMetadata)])
xa [FilePath]
ps2
| Bool
otherwise = do
let continue :: CompileMetadata
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
continue CompileMetadata
m [FilePath]
ds = (Set FilePath, [(FilePath, CompileMetadata)])
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
collect (FilePath
p forall a. Ord a => a -> Set a -> Set a
`Set.insert` Set FilePath
pa,[(FilePath, CompileMetadata)]
xs forall a. [a] -> [a] -> [a]
++ [(FilePath
p,CompileMetadata
m)]) ([FilePath]
ps2 forall a. [a] -> [a] -> [a]
++ [FilePath]
ds)
case FilePath
p forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` MetadataMap
ca of
Just CompileMetadata
m2 -> CompileMetadata
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
continue CompileMetadata
m2 []
Maybe CompileMetadata
Nothing -> do
forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ Handle -> FilePath -> IO ()
hPutStrLn Handle
stderr forall a b. (a -> b) -> a -> b
$ FilePath
"Loading metadata for module \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\"."
CompileMetadata
m2 <- MetadataMap -> FilePath -> TrackedErrorsIO CompileMetadata
loadMetadata MetadataMap
ca FilePath
p
let ds :: [FilePath]
ds = CompileMetadata -> [FilePath]
getDeps CompileMetadata
m2
CompileMetadata
-> [FilePath]
-> TrackedErrorsT IO (Set FilePath, [(FilePath, CompileMetadata)])
continue CompileMetadata
m2 [FilePath]
ds
collect (Set FilePath, [(FilePath, CompileMetadata)])
xa [FilePath]
_ = forall (m :: * -> *) a. Monad m => a -> m a
return (Set FilePath, [(FilePath, CompileMetadata)])
xa
check :: MetadataMap
-> (FilePath, CompileMetadata) -> TrackedErrorsT m CompileMetadata
check MetadataMap
cm (FilePath
p,CompileMetadata
m)
| FilePath
p forall k a. Ord k => k -> Map k a -> Bool
`Map.member` MetadataMap
ca = forall (m :: * -> *) a. Monad m => a -> m a
return CompileMetadata
m
| Bool
otherwise = do
FilePath
p' <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CompileMetadata -> FilePath
cmPath CompileMetadata
m forall a. Eq a => a -> a -> Bool
/= FilePath
p') forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Module \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" has an invalid cache path and must be recompiled"
TrackedErrors ()
fresh <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
TrackedErrorsT m a -> m (TrackedErrors a)
toTrackedErrors forall a b. (a -> b) -> a -> b
$ VersionHash
-> MetadataMap
-> FilePath
-> CompileMetadata
-> TrackedErrorsT IO ()
checkModuleFreshness VersionHash
h MetadataMap
cm FilePath
p CompileMetadata
m forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<!!
FilePath
"Module \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" is out of date and should be recompiled"
if Bool
enforce
then forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m a
fromTrackedErrors TrackedErrors ()
fresh
else forall (m :: * -> *) a.
Monad m =>
TrackedErrors a -> TrackedErrorsT m ()
asCompilerWarnings TrackedErrors ()
fresh
forall (m :: * -> *) a. Monad m => a -> m a
return CompileMetadata
m
loadMetadata :: MetadataMap -> FilePath -> TrackedErrorsIO CompileMetadata
loadMetadata :: MetadataMap -> FilePath -> TrackedErrorsIO CompileMetadata
loadMetadata MetadataMap
ca FilePath
p = do
FilePath
path <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath FilePath
p
case FilePath
path forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` MetadataMap
ca of
Just CompileMetadata
cm -> forall (m :: * -> *) a. Monad m => a -> m a
return CompileMetadata
cm
Maybe CompileMetadata
Nothing -> do
let f :: FilePath
f = FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
cachedDataPath FilePath -> FilePath -> FilePath
</> FilePath
metadataFilename
Bool
isFile <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
p
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
isFile forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Path \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" is not a directory"
Bool
isDir <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
p
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
isDir) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Path \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" does not exist"
Bool
filePresent <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
filePresent) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Module \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" has not been compiled yet"
FilePath
c <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
readFile FilePath
f
(forall a (m :: * -> *).
(ConfigFormat a, ErrorContextM m) =>
FilePath -> FilePath -> m a
autoReadConfig FilePath
f FilePath
c) forall (m :: * -> *) a. ErrorContextM m => m a -> FilePath -> m a
<!!
FilePath
"Could not parse metadata from \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\"; please recompile"
sortCompiledFiles :: [FilePath] -> ([FilePath],[FilePath],[FilePath])
sortCompiledFiles :: [FilePath] -> ([FilePath], [FilePath], [FilePath])
sortCompiledFiles = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl ([FilePath], [FilePath], [FilePath])
-> FilePath -> ([FilePath], [FilePath], [FilePath])
split ([],[],[]) where
split :: ([FilePath], [FilePath], [FilePath])
-> FilePath -> ([FilePath], [FilePath], [FilePath])
split fs :: ([FilePath], [FilePath], [FilePath])
fs@([FilePath]
hxx,[FilePath]
cxx,[FilePath]
os) FilePath
f
| forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".hpp" FilePath
f = ([FilePath]
hxxforall a. [a] -> [a] -> [a]
++[FilePath
f],[FilePath]
cxx,[FilePath]
os)
| forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".h" FilePath
f = ([FilePath]
hxxforall a. [a] -> [a] -> [a]
++[FilePath
f],[FilePath]
cxx,[FilePath]
os)
| forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".cpp" FilePath
f = ([FilePath]
hxx,[FilePath]
cxxforall a. [a] -> [a] -> [a]
++[FilePath
f],[FilePath]
os)
| forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".cc" FilePath
f = ([FilePath]
hxx,[FilePath]
cxxforall a. [a] -> [a] -> [a]
++[FilePath
f],[FilePath]
os)
| forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".a" FilePath
f = ([FilePath]
hxx,[FilePath]
cxx,[FilePath]
osforall a. [a] -> [a] -> [a]
++[FilePath
f])
| forall a. Eq a => [a] -> [a] -> Bool
isSuffixOf FilePath
".o" FilePath
f = ([FilePath]
hxx,[FilePath]
cxx,[FilePath]
osforall a. [a] -> [a] -> [a]
++[FilePath
f])
| Bool
otherwise = ([FilePath], [FilePath], [FilePath])
fs
checkModuleVersionHash :: VersionHash -> CompileMetadata -> Bool
checkModuleVersionHash :: VersionHash -> CompileMetadata -> Bool
checkModuleVersionHash VersionHash
h CompileMetadata
m = CompileMetadata -> VersionHash
cmVersionHash CompileMetadata
m forall a. Eq a => a -> a -> Bool
== VersionHash
h
checkModuleFreshness :: VersionHash -> MetadataMap -> FilePath -> CompileMetadata -> TrackedErrorsIO ()
checkModuleFreshness :: VersionHash
-> MetadataMap
-> FilePath
-> CompileMetadata
-> TrackedErrorsT IO ()
checkModuleFreshness VersionHash
h MetadataMap
ca FilePath
p m :: CompileMetadata
m@(CompileMetadata VersionHash
_ FilePath
p2 FilePath
d [FilePath]
ep Namespace
_ Namespace
_ [FilePath]
is [FilePath]
is2 [CategoryName]
_ [CategoryName]
_ [FilePath]
_ [FilePath]
_ [FilePath]
ps [FilePath]
xs [FilePath]
ts [FilePath]
hxx [FilePath]
cxx [FilePath]
bs [FilePath]
ls [FilePath]
_ [ObjectFile]
os) = do
UTCTime
time <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO UTCTime
getModificationTime forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> FilePath -> FilePath
getCachedPath FilePath
p FilePath
"" FilePath
metadataFilename
([FilePath]
ps2,[FilePath]
xs2,[FilePath]
ts2) <- FilePath
-> [FilePath]
-> TrackedErrorsIO ([FilePath], [FilePath], [FilePath])
findSourceFiles FilePath
p2 (FilePath
dforall a. a -> [a] -> [a]
:[FilePath]
ep)
let rs :: [CategoryIdentifier]
rs = forall a. Set a -> [a]
Set.toList forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ObjectFile -> [CategoryIdentifier]
getRequires [ObjectFile]
os
[FilePath]
expectedFiles <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
p2FilePath -> FilePath -> FilePath
</>)) ([FilePath]
psforall a. [a] -> [a] -> [a]
++[FilePath]
xsforall a. [a] -> [a] -> [a]
++[FilePath]
ts)
[FilePath]
actualFiles <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
p2FilePath -> FilePath -> FilePath
</>)) ([FilePath]
ps2forall a. [a] -> [a] -> [a]
++[FilePath]
xs2forall a. [a] -> [a] -> [a]
++[FilePath]
ts2)
[FilePath]
inputFiles <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
p2FilePath -> FilePath -> FilePath
</>)) ([FilePath]
psforall a. [a] -> [a] -> [a]
++[FilePath]
xs)
[FilePath]
testFiles <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
p2FilePath -> FilePath -> FilePath
</>)) [FilePath]
ts
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, CollectErrorsM m) =>
f (m a) -> m ()
collectAllM_ forall a b. (a -> b) -> a -> b
$ [
TrackedErrorsT IO ()
checkHash,
forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
UTCTime -> FilePath -> m ()
checkInput UTCTime
time (FilePath
p FilePath -> FilePath -> FilePath
</> FilePath
moduleFilename),
forall {m :: * -> *}.
CollectErrorsM m =>
[FilePath] -> [FilePath] -> m ()
checkMissing [FilePath]
expectedFiles [FilePath]
actualFiles
] forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map (UTCTime -> FilePath -> TrackedErrorsT IO ()
checkDep UTCTime
time) forall a b. (a -> b) -> a -> b
$ [FilePath]
is forall a. [a] -> [a] -> [a]
++ [FilePath]
is2) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map (forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
UTCTime -> FilePath -> m ()
checkInput UTCTime
time) [FilePath]
inputFiles) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m ()
checkPresent [FilePath]
testFiles) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map (forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
UTCTime -> FilePath -> m ()
checkInput UTCTime
time forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath -> FilePath -> FilePath
getCachedPath FilePath
d FilePath
"") forall a b. (a -> b) -> a -> b
$ [FilePath]
hxx forall a. [a] -> [a] -> [a]
++ [FilePath]
cxx) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m ()
checkOutput [FilePath]
bs) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m ()
checkOutput [FilePath]
ls) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map forall {m :: * -> *}.
(CollectErrorsM m, MonadIO m) =>
ObjectFile -> m ()
checkObject [ObjectFile]
os) forall a. [a] -> [a] -> [a]
++
(forall a b. (a -> b) -> [a] -> [b]
map CategoryIdentifier -> TrackedErrorsT IO ()
checkRequire [CategoryIdentifier]
rs)
where
checkHash :: TrackedErrorsT IO ()
checkHash =
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ VersionHash -> CompileMetadata -> Bool
checkModuleVersionHash VersionHash
h CompileMetadata
m) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Module \"" forall a. [a] -> [a] -> [a]
++ FilePath
p forall a. [a] -> [a] -> [a]
++ FilePath
"\" was compiled with a different compiler setup"
checkPresent :: FilePath -> m ()
checkPresent FilePath
f = do
Bool
exists <- forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m Bool
doesFileOrDirExist FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Required path \"" forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++ FilePath
"\" is missing"
checkInput :: UTCTime -> FilePath -> m ()
checkInput UTCTime
time FilePath
f = do
Bool
exists <- forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m Bool
doesFileOrDirExist FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Required path \"" forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++ FilePath
"\" is missing"
UTCTime
time2 <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO UTCTime
getModificationTime FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (UTCTime
time2 forall a. Ord a => a -> a -> Bool
> UTCTime
time) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Required path \"" forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++ FilePath
"\" is newer than cached data"
checkOutput :: FilePath -> m ()
checkOutput FilePath
f = do
Bool
exists <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
f
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
exists) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Output file \"" forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++ FilePath
"\" is missing"
checkDep :: UTCTime -> FilePath -> TrackedErrorsT IO ()
checkDep UTCTime
time FilePath
dep = do
CompileMetadata
cm <- MetadataMap -> FilePath -> TrackedErrorsIO CompileMetadata
loadMetadata MetadataMap
ca FilePath
dep
[FilePath]
files <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO FilePath
canonicalizePath forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CompileMetadata -> FilePath
cmRoot CompileMetadata
cm FilePath -> FilePath -> FilePath
</>)) (CompileMetadata -> [FilePath]
cmPublicFiles CompileMetadata
cm)
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ (forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
UTCTime -> FilePath -> m ()
checkInput UTCTime
time) [FilePath]
files
checkObject :: ObjectFile -> m ()
checkObject (CategoryObjectFile CategoryIdentifier
_ [CategoryIdentifier]
_ [FilePath]
fs) = forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m ()
checkOutput [FilePath]
fs
checkObject (OtherObjectFile FilePath
f) = forall {m :: * -> *}.
(MonadIO m, ErrorContextM m) =>
FilePath -> m ()
checkOutput FilePath
f
getRequires :: ObjectFile -> [CategoryIdentifier]
getRequires (CategoryObjectFile CategoryIdentifier
_ [CategoryIdentifier]
rs [FilePath]
_) = [CategoryIdentifier]
rs
getRequires ObjectFile
_ = []
checkRequire :: CategoryIdentifier -> TrackedErrorsT IO ()
checkRequire (CategoryIdentifier FilePath
d2 CategoryName
c Namespace
ns) = do
CompileMetadata
cm <- MetadataMap -> FilePath -> TrackedErrorsIO CompileMetadata
loadMetadata MetadataMap
ca FilePath
d2
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CompileMetadata -> FilePath
cmPath CompileMetadata
cm forall a. Eq a => a -> a -> Bool
/= FilePath
d Bool -> Bool -> Bool
&& Namespace
ns forall a. Eq a => a -> a -> Bool
/= CompileMetadata -> Namespace
cmPublicNamespace CompileMetadata
cm) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Required category " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show CategoryName
c forall a. [a] -> [a] -> [a]
++ FilePath
" is newer than cached data"
checkRequire (UnresolvedCategory CategoryName
c) =
forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Required category " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show CategoryName
c forall a. [a] -> [a] -> [a]
++ FilePath
" is unresolved"
checkMissing :: [FilePath] -> [FilePath] -> m ()
checkMissing [FilePath]
s0 [FilePath]
s1 = do
let missing :: [FilePath]
missing = forall a. Set a -> [a]
Set.toList forall a b. (a -> b) -> a -> b
$ forall a. Ord a => [a] -> Set a
Set.fromList [FilePath]
s1 forall a. Ord a => Set a -> Set a -> Set a
`Set.difference` forall a. Ord a => [a] -> Set a
Set.fromList [FilePath]
s0
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ (\FilePath
f -> forall (m :: * -> *) a. ErrorContextM m => FilePath -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ FilePath
"Input path \"" forall a. [a] -> [a] -> [a]
++ FilePath
f forall a. [a] -> [a] -> [a]
++ FilePath
"\" is not present in cached data") [FilePath]
missing
doesFileOrDirExist :: FilePath -> m Bool
doesFileOrDirExist FilePath
f2 = do
Bool
existF <- forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesFileExist FilePath
f2
if Bool
existF
then forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Bool
doesDirectoryExist FilePath
f2
getObjectFileResolver :: [ObjectFile] -> Set.Set Namespace -> Set.Set CategoryName -> [FilePath]
getObjectFileResolver :: [ObjectFile] -> Set Namespace -> Set CategoryName -> [FilePath]
getObjectFileResolver [ObjectFile]
os Set Namespace
ns Set CategoryName
ds = [FilePath]
resolved forall a. [a] -> [a] -> [a]
++ [FilePath]
nonCategories where
categories :: [ObjectFile]
categories = forall a. (a -> Bool) -> [a] -> [a]
filter ObjectFile -> Bool
isCategoryObjectFile [ObjectFile]
os
nonCategories :: [FilePath]
nonCategories = forall a b. (a -> b) -> [a] -> [b]
map ObjectFile -> FilePath
oofFile forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectFile -> Bool
isCategoryObjectFile) [ObjectFile]
os
categoryMap :: Map (CategoryName, Namespace) ObjectFile
categoryMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ObjectFile -> ((CategoryName, Namespace), ObjectFile)
keyByCategory2 [ObjectFile]
categories
keyByCategory2 :: ObjectFile -> ((CategoryName, Namespace), ObjectFile)
keyByCategory2 ObjectFile
o = ((CategoryIdentifier -> CategoryName
ciCategory forall a b. (a -> b) -> a -> b
$ ObjectFile -> CategoryIdentifier
cofCategory ObjectFile
o,CategoryIdentifier -> Namespace
ciNamespace forall a b. (a -> b) -> a -> b
$ ObjectFile -> CategoryIdentifier
cofCategory ObjectFile
o),ObjectFile
o)
objectMap :: Map CategoryIdentifier ObjectFile
objectMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ObjectFile -> (CategoryIdentifier, ObjectFile)
keyBySpec [ObjectFile]
categories
keyBySpec :: ObjectFile -> (CategoryIdentifier, ObjectFile)
keyBySpec ObjectFile
o = (ObjectFile -> CategoryIdentifier
cofCategory ObjectFile
o,ObjectFile
o)
directDeps :: [ObjectFile]
directDeps = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map CategoryName -> [ObjectFile]
resolveDep2 forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
Set.toList Set CategoryName
ds
directResolved :: [CategoryIdentifier]
directResolved = forall a b. (a -> b) -> [a] -> [b]
map ObjectFile -> CategoryIdentifier
cofCategory [ObjectFile]
directDeps
resolveDep2 :: CategoryName -> [ObjectFile]
resolveDep2 CategoryName
d = forall {a}. Maybe [a] -> [a]
unwrap forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>) forall a. Maybe a
Nothing [Maybe [ObjectFile]]
allChecks forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. a -> Maybe a
Just [] where
allChecks :: [Maybe [ObjectFile]]
allChecks = forall a b. (a -> b) -> [a] -> [b]
map (\Namespace
n -> (CategoryName
d,Namespace
n) forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map (CategoryName, Namespace) ObjectFile
categoryMap forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[])) (forall a. Set a -> [a]
Set.toList Set Namespace
ns forall a. [a] -> [a] -> [a]
++ [Namespace
NoNamespace])
unwrap :: Maybe [a] -> [a]
unwrap (Just [a]
xs) = [a]
xs
unwrap Maybe [a]
_ = []
(Set CategoryIdentifier
_,Set FilePath
_,[FilePath]
resolved) = Set CategoryIdentifier
-> Set FilePath
-> [CategoryIdentifier]
-> (Set CategoryIdentifier, Set FilePath, [FilePath])
collectAll forall a. Set a
Set.empty forall a. Set a
Set.empty [CategoryIdentifier]
directResolved
collectAll :: Set CategoryIdentifier
-> Set FilePath
-> [CategoryIdentifier]
-> (Set CategoryIdentifier, Set FilePath, [FilePath])
collectAll Set CategoryIdentifier
ca Set FilePath
fa [] = (Set CategoryIdentifier
ca,Set FilePath
fa,[])
collectAll Set CategoryIdentifier
ca Set FilePath
fa (CategoryIdentifier
c:[CategoryIdentifier]
cs)
| CategoryIdentifier
c forall a. Ord a => a -> Set a -> Bool
`Set.member` Set CategoryIdentifier
ca = Set CategoryIdentifier
-> Set FilePath
-> [CategoryIdentifier]
-> (Set CategoryIdentifier, Set FilePath, [FilePath])
collectAll Set CategoryIdentifier
ca Set FilePath
fa [CategoryIdentifier]
cs
| Bool
otherwise =
case CategoryIdentifier
c forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map CategoryIdentifier ObjectFile
objectMap of
Just (CategoryObjectFile CategoryIdentifier
_ [CategoryIdentifier]
ds2 [FilePath]
fs) -> (Set CategoryIdentifier
ca',Set FilePath
fa'',[FilePath]
fs') where
(Set CategoryIdentifier
ca',Set FilePath
fa',[FilePath]
fs0) = Set CategoryIdentifier
-> Set FilePath
-> [CategoryIdentifier]
-> (Set CategoryIdentifier, Set FilePath, [FilePath])
collectAll (CategoryIdentifier
c forall a. Ord a => a -> Set a -> Set a
`Set.insert` Set CategoryIdentifier
ca) Set FilePath
fa ([CategoryIdentifier]
ds2 forall a. [a] -> [a] -> [a]
++ [CategoryIdentifier]
cs)
fa'' :: Set FilePath
fa'' = Set FilePath
fa' forall a. Ord a => Set a -> Set a -> Set a
`Set.union` (forall a. Ord a => [a] -> Set a
Set.fromList [FilePath]
fs)
fs' :: [FilePath]
fs' = (forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Set FilePath
fa') [FilePath]
fs) forall a. [a] -> [a] -> [a]
++ [FilePath]
fs0
Maybe ObjectFile
_ -> Set CategoryIdentifier
-> Set FilePath
-> [CategoryIdentifier]
-> (Set CategoryIdentifier, Set FilePath, [FilePath])
collectAll Set CategoryIdentifier
ca Set FilePath
fa [CategoryIdentifier]
cs
resolveObjectDeps :: [CompileMetadata] -> FilePath -> FilePath -> [([FilePath],CxxOutput)] -> [ObjectFile]
resolveObjectDeps :: [CompileMetadata]
-> FilePath
-> FilePath
-> [([FilePath], CxxOutput)]
-> [ObjectFile]
resolveObjectDeps [CompileMetadata]
deps FilePath
p FilePath
d [([FilePath], CxxOutput)]
os = [ObjectFile]
resolvedCategories forall a. [a] -> [a] -> [a]
++ [ObjectFile]
nonCategories where
categories :: [([FilePath], CxxOutput)]
categories = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. CxxOutput -> Maybe CategoryName
coCategory forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [([FilePath], CxxOutput)]
os
publicNamespaces :: [Namespace]
publicNamespaces = [CompileMetadata] -> [Namespace]
getNamespacesForDeps [CompileMetadata]
deps
nonCategories :: [ObjectFile]
nonCategories = forall a b. (a -> b) -> [a] -> [b]
map FilePath -> ObjectFile
OtherObjectFile forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. CxxOutput -> Maybe CategoryName
coCategory forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd) [([FilePath], CxxOutput)]
os
resolvedCategories :: [ObjectFile]
resolvedCategories = forall k a. Map k a -> [a]
Map.elems forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith ObjectFile -> ObjectFile -> ObjectFile
mergeObjectFiles forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ([FilePath], CxxOutput) -> (CategoryIdentifier, ObjectFile)
resolveCategory [([FilePath], CxxOutput)]
categories
categoryMap :: Map (CategoryName, Namespace) CategoryIdentifier
categoryMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ [((CategoryName, Namespace), CategoryIdentifier)]
directCategories forall a. [a] -> [a] -> [a]
++ [((CategoryName, Namespace), CategoryIdentifier)]
depCategories
directCategories :: [((CategoryName, Namespace), CategoryIdentifier)]
directCategories = forall a b. (a -> b) -> [a] -> [b]
map (CategoryIdentifier
-> ((CategoryName, Namespace), CategoryIdentifier)
keyByCategory forall b c a. (b -> c) -> (a -> b) -> a -> c
. CxxOutput -> CategoryIdentifier
cxxToId) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [([FilePath], CxxOutput)]
categories
depCategories :: [((CategoryName, Namespace), CategoryIdentifier)]
depCategories = forall a b. (a -> b) -> [a] -> [b]
map CategoryIdentifier
-> ((CategoryName, Namespace), CategoryIdentifier)
keyByCategory forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> [CategoryIdentifier]
categoriesToIds [CompileMetadata]
deps)
getCats :: CompileMetadata -> [(CategoryName, Namespace)]
getCats CompileMetadata
dep = forall a b. [a] -> [b] -> [(a, b)]
zip (CompileMetadata -> [CategoryName]
cmPublicCategories CompileMetadata
dep) (forall a. a -> [a]
repeat forall a b. (a -> b) -> a -> b
$ CompileMetadata -> Namespace
cmPublicNamespace CompileMetadata
dep) forall a. [a] -> [a] -> [a]
++
(if CompileMetadata -> FilePath
cmPath CompileMetadata
dep forall a. Eq a => a -> a -> Bool
== FilePath
p then forall a b. [a] -> [b] -> [(a, b)]
zip (CompileMetadata -> [CategoryName]
cmPrivateCategories CompileMetadata
dep) (forall a. a -> [a]
repeat forall a b. (a -> b) -> a -> b
$ CompileMetadata -> Namespace
cmPrivateNamespace CompileMetadata
dep) else [])
categoriesToIds :: CompileMetadata -> [CategoryIdentifier]
categoriesToIds CompileMetadata
dep = forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. (a -> b) -> a -> b
$ FilePath -> CategoryName -> Namespace -> CategoryIdentifier
CategoryIdentifier forall a b. (a -> b) -> a -> b
$ CompileMetadata -> FilePath
cmPath CompileMetadata
dep) forall a b. (a -> b) -> a -> b
$ CompileMetadata -> [(CategoryName, Namespace)]
getCats CompileMetadata
dep
cxxToId :: CxxOutput -> CategoryIdentifier
cxxToId (CxxOutput (Just CategoryName
c) FilePath
_ Namespace
ns Set Namespace
_ Set CategoryName
_ Set FilePath
_ [FilePath]
_) = FilePath -> CategoryName -> Namespace -> CategoryIdentifier
CategoryIdentifier FilePath
d CategoryName
c Namespace
ns
cxxToId CxxOutput
_ = forall a. HasCallStack => a
undefined
resolveCategory :: ([FilePath], CxxOutput) -> (CategoryIdentifier, ObjectFile)
resolveCategory ([FilePath]
fs,ca :: CxxOutput
ca@(CxxOutput Maybe CategoryName
_ FilePath
_ Namespace
_ Set Namespace
ns2 Set CategoryName
ds Set FilePath
_ [FilePath]
_)) =
(CxxOutput -> CategoryIdentifier
cxxToId CxxOutput
ca,CategoryIdentifier
-> [CategoryIdentifier] -> [FilePath] -> ObjectFile
CategoryObjectFile (CxxOutput -> CategoryIdentifier
cxxToId CxxOutput
ca) (forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= CxxOutput -> CategoryIdentifier
cxxToId CxxOutput
ca) [CategoryIdentifier]
rs) [FilePath]
fs) where
rs :: [CategoryIdentifier]
rs = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (Map (CategoryName, Namespace) CategoryIdentifier
-> [Namespace] -> CategoryName -> [CategoryIdentifier]
resolveDep Map (CategoryName, Namespace) CategoryIdentifier
categoryMap (forall a. Set a -> [a]
Set.toList Set Namespace
ns2 forall a. [a] -> [a] -> [a]
++ [Namespace]
publicNamespaces)) forall a b. (a -> b) -> a -> b
$ forall a. Set a -> [a]
Set.toList Set CategoryName
ds
resolveCategoryDeps :: [CategoryName] -> [CompileMetadata] -> [CategoryIdentifier]
resolveCategoryDeps :: [CategoryName] -> [CompileMetadata] -> [CategoryIdentifier]
resolveCategoryDeps [CategoryName]
cs [CompileMetadata]
deps = [CategoryIdentifier]
resolvedCategories where
publicNamespaces :: [Namespace]
publicNamespaces = [CompileMetadata] -> [Namespace]
getNamespacesForDeps [CompileMetadata]
deps
resolvedCategories :: [CategoryIdentifier]
resolvedCategories = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (Map (CategoryName, Namespace) CategoryIdentifier
-> [Namespace] -> CategoryName -> [CategoryIdentifier]
resolveDep Map (CategoryName, Namespace) CategoryIdentifier
categoryMap [Namespace]
publicNamespaces) [CategoryName]
cs
categoryMap :: Map (CategoryName, Namespace) CategoryIdentifier
categoryMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [((CategoryName, Namespace), CategoryIdentifier)]
depCategories
depCategories :: [((CategoryName, Namespace), CategoryIdentifier)]
depCategories = forall a b. (a -> b) -> [a] -> [b]
map (CategoryIdentifier
-> ((CategoryName, Namespace), CategoryIdentifier)
keyByCategory forall b c a. (b -> c) -> (a -> b) -> a -> c
. ObjectFile -> CategoryIdentifier
cofCategory) forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter ObjectFile -> Bool
isCategoryObjectFile forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> [ObjectFile]
cmObjectFiles [CompileMetadata]
deps
keyByCategory :: CategoryIdentifier -> ((CategoryName,Namespace),CategoryIdentifier)
keyByCategory :: CategoryIdentifier
-> ((CategoryName, Namespace), CategoryIdentifier)
keyByCategory CategoryIdentifier
c = ((CategoryIdentifier -> CategoryName
ciCategory CategoryIdentifier
c,CategoryIdentifier -> Namespace
ciNamespace CategoryIdentifier
c),CategoryIdentifier
c)
resolveDep :: Map.Map (CategoryName,Namespace) CategoryIdentifier ->
[Namespace] -> CategoryName -> [CategoryIdentifier]
resolveDep :: Map (CategoryName, Namespace) CategoryIdentifier
-> [Namespace] -> CategoryName -> [CategoryIdentifier]
resolveDep Map (CategoryName, Namespace) CategoryIdentifier
cm (Namespace
n:[Namespace]
ns) CategoryName
d =
case (CategoryName
d,Namespace
n) forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map (CategoryName, Namespace) CategoryIdentifier
cm of
Just CategoryIdentifier
xs -> [CategoryIdentifier
xs]
Maybe CategoryIdentifier
Nothing -> Map (CategoryName, Namespace) CategoryIdentifier
-> [Namespace] -> CategoryName -> [CategoryIdentifier]
resolveDep Map (CategoryName, Namespace) CategoryIdentifier
cm [Namespace]
ns CategoryName
d
resolveDep Map (CategoryName, Namespace) CategoryIdentifier
_ [Namespace]
_ CategoryName
d = [CategoryName -> CategoryIdentifier
UnresolvedCategory CategoryName
d]
loadModuleGlobals :: PathIOHandler r => r -> FilePath -> (Namespace,Namespace) -> [FilePath] ->
Maybe CompileMetadata -> [CompileMetadata] -> [CompileMetadata] ->
TrackedErrorsIO ([WithVisibility (AnyCategory SourceContext)],Set.Set FilePath)
loadModuleGlobals :: forall r.
PathIOHandler r =>
r
-> FilePath
-> (Namespace, Namespace)
-> [FilePath]
-> Maybe CompileMetadata
-> [CompileMetadata]
-> [CompileMetadata]
-> TrackedErrorsIO
([WithVisibility (AnyCategory SourceContext)], Set FilePath)
loadModuleGlobals r
r FilePath
p (Namespace
ns0,Namespace
ns1) [FilePath]
fs Maybe CompileMetadata
m [CompileMetadata]
deps1 [CompileMetadata]
deps2 = do
let public :: Set FilePath
public = forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map CompileMetadata -> FilePath
cmPath [CompileMetadata]
deps1
let deps2' :: [CompileMetadata]
deps2' = forall a. (a -> Bool) -> [a] -> [a]
filter (\CompileMetadata
cm -> Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ CompileMetadata -> FilePath
cmPath CompileMetadata
cm forall a. Ord a => a -> Set a -> Bool
`Set.member` Set FilePath
public) [CompileMetadata]
deps2
[WithVisibility (AnyCategory SourceContext)]
cs0 <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall {m :: * -> *}.
(CollectErrorsM m, MonadIO m) =>
Bool
-> [CodeVisibility]
-> CompileMetadata
-> m [WithVisibility (AnyCategory SourceContext)]
processDeps Bool
False [CodeVisibility
FromDependency]) [CompileMetadata]
deps1
[WithVisibility (AnyCategory SourceContext)]
cs1 <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall {m :: * -> *}.
(CollectErrorsM m, MonadIO m) =>
Bool
-> [CodeVisibility]
-> CompileMetadata
-> m [WithVisibility (AnyCategory SourceContext)]
processDeps Bool
False [CodeVisibility
FromDependency,CodeVisibility
ModuleOnly]) [CompileMetadata]
deps2'
([WithVisibility (AnyCategory SourceContext)]
cs2,Set FilePath
xa) <- forall {m :: * -> *}.
(CollectErrorsM m, MonadIO m) =>
(Namespace, Namespace)
-> [(FilePath, [FilePath])]
-> m ([WithVisibility (AnyCategory SourceContext)], Set FilePath)
loadAllPublic (Namespace
ns0,Namespace
ns1) [(FilePath
p,[FilePath]
fs)]
[WithVisibility (AnyCategory SourceContext)]
cs3 <- case Maybe CompileMetadata
m of
Just CompileMetadata
m2 -> forall {m :: * -> *}.
(CollectErrorsM m, MonadIO m) =>
Bool
-> [CodeVisibility]
-> CompileMetadata
-> m [WithVisibility (AnyCategory SourceContext)]
processDeps Bool
True [CodeVisibility
FromDependency] CompileMetadata
m2
Maybe CompileMetadata
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return []
forall (m :: * -> *) a. Monad m => a -> m a
return ([WithVisibility (AnyCategory SourceContext)]
cs0forall a. [a] -> [a] -> [a]
++[WithVisibility (AnyCategory SourceContext)]
cs1forall a. [a] -> [a] -> [a]
++[WithVisibility (AnyCategory SourceContext)]
cs2forall a. [a] -> [a] -> [a]
++[WithVisibility (AnyCategory SourceContext)]
cs3,Set FilePath
xa) where
processDeps :: Bool
-> [CodeVisibility]
-> CompileMetadata
-> m [WithVisibility (AnyCategory SourceContext)]
processDeps Bool
same [CodeVisibility]
ss CompileMetadata
dep = do
let fs2 :: [(FilePath, [FilePath])]
fs2 = [CompileMetadata] -> [(FilePath, [FilePath])]
getSourceFilesForDeps [CompileMetadata
dep]
([WithVisibility (AnyCategory SourceContext)]
cs,Set FilePath
_) <- forall {m :: * -> *}.
(CollectErrorsM m, MonadIO m) =>
(Namespace, Namespace)
-> [(FilePath, [FilePath])]
-> m ([WithVisibility (AnyCategory SourceContext)], Set FilePath)
loadAllPublic (CompileMetadata -> Namespace
cmPublicNamespace CompileMetadata
dep,CompileMetadata -> Namespace
cmPrivateNamespace CompileMetadata
dep) [(FilePath, [FilePath])]
fs2
let cs' :: [WithVisibility (AnyCategory SourceContext)]
cs' = if Bool -> Bool
not Bool
same
then forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. CodeVisibility -> WithVisibility a -> Bool
hasCodeVisibility CodeVisibility
ModuleOnly) [WithVisibility (AnyCategory SourceContext)]
cs
else [WithVisibility (AnyCategory SourceContext)]
cs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a.
(Set CodeVisibility -> Set CodeVisibility)
-> WithVisibility a -> WithVisibility a
updateCodeVisibility (forall a. Ord a => Set a -> Set a -> Set a
Set.union (forall a. Ord a => [a] -> Set a
Set.fromList [CodeVisibility]
ss))) [WithVisibility (AnyCategory SourceContext)]
cs'
loadAllPublic :: (Namespace, Namespace)
-> [(FilePath, [FilePath])]
-> m ([WithVisibility (AnyCategory SourceContext)], Set FilePath)
loadAllPublic (Namespace
ns2,Namespace
ns3) [(FilePath, [FilePath])]
fs2 = do
[(FilePath, FilePath)]
fs2' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a b. (a -> b) -> a -> b
$ forall r (m :: * -> *).
(PathIOHandler r, MonadIO m, CollectErrorsM m) =>
r -> FilePath -> [FilePath] -> m [(FilePath, FilePath)]
zipWithContents r
r) [(FilePath, [FilePath])]
fs2
[([WithVisibility (AnyCategory SourceContext)], [FilePath])]
loaded <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM forall {m :: * -> *}.
(ErrorContextM m, MonadIO m) =>
(FilePath, FilePath)
-> m ([WithVisibility (AnyCategory SourceContext)], [FilePath])
loadPublic [(FilePath, FilePath)]
fs2'
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [([WithVisibility (AnyCategory SourceContext)], [FilePath])]
loaded,forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [([WithVisibility (AnyCategory SourceContext)], [FilePath])]
loaded)
where
loadPublic :: (FilePath, FilePath)
-> m ([WithVisibility (AnyCategory SourceContext)], [FilePath])
loadPublic (FilePath, FilePath)
p3 = do
([PragmaSource SourceContext]
pragmas,[AnyCategory SourceContext]
cs) <- forall (m :: * -> *).
ErrorContextM m =>
(FilePath, FilePath)
-> m ([PragmaSource SourceContext], [AnyCategory SourceContext])
parsePublicSource (FilePath, FilePath)
p3
[FilePath]
xs <- if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall c. PragmaSource c -> Bool
isModuleOnly [PragmaSource SourceContext]
pragmas
then forall (m :: * -> *) a. (MonadIO m, ErrorContextM m) => IO a -> m a
errorFromIO forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) forall a b. (a -> b) -> a -> b
$ FilePath -> IO FilePath
canonicalizePath forall a b. (a -> b) -> a -> b
$ FilePath
p FilePath -> FilePath -> FilePath
</> forall a b. (a, b) -> a
fst (FilePath, FilePath)
p3
else forall (m :: * -> *) a. Monad m => a -> m a
return []
let tags :: Set CodeVisibility
tags = forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$
(if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall c. PragmaSource c -> Bool
isTestsOnly [PragmaSource SourceContext]
pragmas then [CodeVisibility
TestsOnly] else []) forall a. [a] -> [a] -> [a]
++
(if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall c. PragmaSource c -> Bool
isModuleOnly [PragmaSource SourceContext]
pragmas then [CodeVisibility
ModuleOnly] else [])
let cs' :: [AnyCategory SourceContext]
cs' = if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall c. PragmaSource c -> Bool
isModuleOnly [PragmaSource SourceContext]
pragmas
then forall a b. (a -> b) -> [a] -> [b]
map (forall c. Namespace -> AnyCategory c -> AnyCategory c
setCategoryNamespace Namespace
ns3) [AnyCategory SourceContext]
cs
else forall a b. (a -> b) -> [a] -> [b]
map (forall c. Namespace -> AnyCategory c -> AnyCategory c
setCategoryNamespace Namespace
ns2) [AnyCategory SourceContext]
cs
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. (a -> b) -> [a] -> [b]
map (forall a. Set CodeVisibility -> a -> WithVisibility a
WithVisibility Set CodeVisibility
tags) [AnyCategory SourceContext]
cs',[FilePath]
xs)