Skip to content

Commit

Permalink
display package name in dependency log
Browse files Browse the repository at this point in the history
  • Loading branch information
janmasrovira committed Aug 28, 2024
1 parent 438a09f commit 6702abe
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 3 deletions.
16 changes: 16 additions & 0 deletions src/Juvix/Compiler/Pipeline/Loader/PathResolver/PackageInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,10 @@ module Juvix.Compiler.Pipeline.Loader.PathResolver.PackageInfo
where

import Data.HashSet qualified as HashSet
import Data.Versions
import Juvix.Compiler.Concrete.Translation.ImportScanner.Base
import Juvix.Compiler.Pipeline.EntryPoint
import Juvix.Data.CodeAnn
import Juvix.Prelude

data PackageLike
Expand Down Expand Up @@ -48,6 +50,20 @@ packageLikeName = to $ \case
PackageType -> "package-type"
PackageDotJuvix -> "package-dot-juvix"

-- | TODO perhaps we could versions for the non-real packages
packageLikeVersion :: SimpleGetter PackageLike (Maybe SemVer)
packageLikeVersion = to $ \case
PackageReal pkg -> Just (pkg ^. packageVersion)
PackageGlobalStdlib {} -> Nothing
PackageBase {} -> Nothing
PackageType {} -> Nothing
PackageDotJuvix {} -> Nothing

packageLikeNameAndVersion :: SimpleGetter PackageLike (Doc CodeAnn)
packageLikeNameAndVersion = to $ \n ->
annotate AnnImportant (pretty (n ^. packageLikeName))
<+?> (pretty . prettySemVer <$> n ^. packageLikeVersion)

packageLikeDependencies :: SimpleGetter PackageLike [Dependency]
packageLikeDependencies = to $ \case
PackageReal r -> r ^. packageDependencies
Expand Down
14 changes: 11 additions & 3 deletions src/Parallel/ProgressLog.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ import Juvix.Compiler.Concrete.Print.Base
import Juvix.Compiler.Pipeline.Driver.Data
import Juvix.Compiler.Pipeline.Loader.PathResolver.Base
import Juvix.Compiler.Pipeline.Loader.PathResolver.ImportTree.Base
import Juvix.Compiler.Pipeline.Loader.PathResolver.PackageInfo
import Juvix.Compiler.Pipeline.Options
import Juvix.Data.CodeAnn
import Juvix.Data.Logger
Expand All @@ -18,6 +19,7 @@ data ProgressLog :: Effect where
data ProgressLogOptions = ProgressLogOptions
{ _progressLogOptionsShowThreadId :: Bool,
_progressLogOptionsPackageRoot :: Path Abs Dir,
_progressLogOptionsPackages :: HashMap (Path Abs Dir) PackageInfo,
_progressLogOptionsImportTree :: ImportTree
}

Expand All @@ -41,7 +43,7 @@ type LogQueue = TQueue LogQueueItem

data LogKind
= LogMainPackage
| LogDependency
| LogDependency (Doc CodeAnn)

data LogItemDetails = LogItemDetails
{ _logItemDetailsNumber :: Natural,
Expand Down Expand Up @@ -76,11 +78,13 @@ runProgressLog ::
runProgressLog m = do
tree <- ask
root <- resolverInitialRoot
pkgs <- getPackageInfos
popts :: PipelineOptions <- ask
let opts :: ProgressLogOptions =
ProgressLogOptions
{ _progressLogOptionsImportTree = tree,
_progressLogOptionsPackageRoot = root,
_progressLogOptionsPackages = pkgs,
_progressLogOptionsShowThreadId = popts ^. pipelineShowThreadId
}
runProgressLogOptions opts m
Expand All @@ -100,6 +104,9 @@ runProgressLogOptions opts m = do
wait logHandler
return x
where
getPackageTag :: Path Abs Dir -> Doc CodeAnn
getPackageTag pkgRoot = opts ^. progressLogOptionsPackages . at pkgRoot . _Just . packagePackage . packageLikeNameAndVersion

tree :: ImportTree
tree = opts ^. progressLogOptionsImportTree

Expand All @@ -124,9 +131,10 @@ runProgressLogOptions opts m = do
node :: ImportNode
node = l ^. logItemModule

dependencyTag :: Maybe (Doc CodeAnn)
dependencyTag = case d ^. logItemDetailsKind of
LogMainPackage -> Nothing
LogDependency -> Just (annotate AnnKeyword "Dependency" <+> pretty (node ^. importNodePackageRoot))
LogDependency pkgName -> Just (annotate AnnComment "Dependency" <+> pkgName)

num =
annotate AnnLiteralInteger (pretty (d ^. logItemDetailsNumber))
Expand Down Expand Up @@ -157,7 +165,7 @@ runProgressLogOptions opts m = do
n <- getNextNumber
let k
| fromMainPackage = LogMainPackage
| otherwise = LogDependency
| otherwise = LogDependency (getPackageTag fromPackage)
d =
LogItemDetails
{ _logItemDetailsKind = k,
Expand Down

0 comments on commit 6702abe

Please sign in to comment.