Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Append unique hash to the pre-release tag in the Package.juvix version #3215

Merged
merged 28 commits into from
Dec 6, 2024
Merged
Show file tree
Hide file tree
Changes from 24 commits
Commits
Show all changes
28 commits
Select commit Hold shift + click to select a range
3be1946
hash global package
janmasrovira Dec 1, 2024
df62ccd
fix loop
janmasrovira Dec 1, 2024
389c56f
rename _moduleIdPackageName
janmasrovira Dec 1, 2024
1243fa3
derive Ord
janmasrovira Dec 1, 2024
1b98a36
importNodePackageId
janmasrovira Dec 1, 2024
76f9c24
mkEntryIndex changes packageId
janmasrovira Dec 1, 2024
f9856fa
groupSortOnWith
janmasrovira Dec 1, 2024
e816821
use PackageId in ModuleId instead of Text for name and version
janmasrovira Dec 2, 2024
6b99284
remove GlobalVersions
janmasrovira Dec 2, 2024
27afe0a
packageId with hash
janmasrovira Dec 2, 2024
05531e6
remove Package from global stdlib
janmasrovira Dec 2, 2024
b9c9a37
fill pre-release with hash only when it is not there
janmasrovira Dec 2, 2024
90d98cf
clean
janmasrovira Dec 2, 2024
e26aa46
add test
janmasrovira Dec 2, 2024
0286f5f
error message
janmasrovira Dec 2, 2024
ff8f660
disable check
janmasrovira Dec 2, 2024
500af3f
Revert "update stdlib TEMPORARY"
janmasrovira Dec 3, 2024
95d39c5
disable test
janmasrovira Dec 3, 2024
69eb03f
preserve order of inductive type declarations in Core
lukaszcz Dec 3, 2024
822b4fe
use juvix/main stdlib
janmasrovira Dec 3, 2024
3076c8d
remove commented out test
janmasrovira Dec 3, 2024
a7ec169
append hash including Package.juvix
janmasrovira Dec 3, 2024
5dacf3e
Merge remote-tracking branch 'origin/main' into hash-globalpkg
janmasrovira Dec 4, 2024
95b4183
add comment
janmasrovira Dec 5, 2024
7c3c402
Squashed commit of the following:
janmasrovira Dec 5, 2024
6931aa5
Merge remote-tracking branch 'origin/main' into hash-globalpkg
janmasrovira Dec 5, 2024
37f3004
deterministicly digest the files to create the hash
janmasrovira Dec 5, 2024
f2b8cfc
Merge branch 'main' into hash-globalpkg
janmasrovira Dec 5, 2024
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 5 additions & 1 deletion src/Juvix/Compiler/Concrete/Data/Name.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,12 @@
module Juvix.Compiler.Concrete.Data.Name where

import Data.List.NonEmpty.Extra qualified as NonEmpty
import Juvix.Data.Fixity
import Juvix.Data.Loc
import Juvix.Data.TopModulePathKey
import Juvix.Data.WithLoc
import Juvix.Extra.Serialize
import Juvix.Prelude
import Juvix.Prelude.Base
import Juvix.Prelude.Pretty as Pretty

type Symbol = WithLoc Text
Expand Down
1 change: 0 additions & 1 deletion src/Juvix/Compiler/Concrete/Translation/FromParsed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,6 @@ import Juvix.Compiler.Concrete.Language
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping.Data.Context
import Juvix.Compiler.Concrete.Translation.FromSource.Data.Context qualified as Parsed
import Juvix.Compiler.Pipeline.EntryPoint
import Juvix.Compiler.Store.Extra
import Juvix.Compiler.Store.Language
import Juvix.Prelude
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ import Juvix.Compiler.Concrete.Pretty (ppTrace)
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping.Data.Context
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping.Error
import Juvix.Compiler.Concrete.Translation.FromSource.Data.Context qualified as Parser
import Juvix.Compiler.Pipeline.EntryPoint
import Juvix.Compiler.Store.Scoped.Language as Store
import Juvix.Data.FixityInfo qualified as FI
import Juvix.Prelude
Expand Down Expand Up @@ -956,12 +955,11 @@ checkFixityInfo ParsedFixityInfo {..} = do

getModuleId :: forall r. (Member (Reader PackageId) r) => TopModulePathKey -> Sem r ModuleId
getModuleId path = do
pkg <- ask
pkgId <- ask
return
ModuleId
{ _moduleIdPath = path,
_moduleIdPackage = pkg ^. packageIdName,
_moduleIdPackageVersion = show (pkg ^. packageIdVersion)
_moduleIdPackageId = pkgId
}

checkFixitySyntaxDef ::
Expand Down
1 change: 0 additions & 1 deletion src/Juvix/Compiler/Core/Data/InfoTable/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@ module Juvix.Compiler.Core.Data.InfoTable.Base where

import Juvix.Compiler.Concrete.Data.Builtins
import Juvix.Compiler.Core.Language.Base
import Juvix.Extra.Serialize

data InfoTable' n = InfoTable
{ _identContext :: HashMap Symbol n,
Expand Down
12 changes: 8 additions & 4 deletions src/Juvix/Compiler/Core/Data/Module.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ where

import Juvix.Compiler.Core.Data.InfoTable
import Juvix.Compiler.Core.Language
import Juvix.Compiler.Core.Pretty

data Module = Module
{ _moduleId :: ModuleId,
Expand Down Expand Up @@ -64,17 +65,20 @@ lookupSpecialisationInfo Module {..} sym =
lookupTabSpecialisationInfo' _moduleInfoTable sym
<|> lookupTabSpecialisationInfo' _moduleImportsTable sym

impossibleSymbolNotFound :: Symbol -> a
impossibleSymbolNotFound sym = impossibleError ("Could not find symbol " <> ppTrace sym)

lookupInductiveInfo :: Module -> Symbol -> InductiveInfo
lookupInductiveInfo m sym = fromJust $ lookupInductiveInfo' m sym
lookupInductiveInfo m sym = fromMaybe (impossibleSymbolNotFound sym) (lookupInductiveInfo' m sym)

lookupConstructorInfo :: Module -> Tag -> ConstructorInfo
lookupConstructorInfo m tag = fromJust $ lookupConstructorInfo' m tag
lookupConstructorInfo m tag = fromJust (lookupConstructorInfo' m tag)

lookupIdentifierInfo :: Module -> Symbol -> IdentifierInfo
lookupIdentifierInfo m sym = fromJust $ lookupIdentifierInfo' m sym
lookupIdentifierInfo m sym = fromMaybe (impossibleSymbolNotFound sym) (lookupIdentifierInfo' m sym)

lookupIdentifierNode :: Module -> Symbol -> Node
lookupIdentifierNode m sym = fromJust $ lookupIdentifierNode' m sym
lookupIdentifierNode m sym = fromMaybe (impossibleSymbolNotFound sym) (lookupIdentifierNode' m sym)

lookupBuiltinInductive :: Module -> BuiltinInductive -> Maybe InductiveInfo
lookupBuiltinInductive Module {..} b =
Expand Down
1 change: 0 additions & 1 deletion src/Juvix/Compiler/Core/Language/Primitives.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,6 @@ represented by booleans, any type isomorphic to unary natural numbers may be
represented by integers with minimum value 0. -}

import Juvix.Compiler.Core.Language.Base
import Juvix.Extra.Serialize

-- | Primitive type representation.
data Primitive
Expand Down
8 changes: 7 additions & 1 deletion src/Juvix/Compiler/Core/Pretty/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,12 @@ instance PrettyCode Tag where
BuiltinTag tag -> ppCode tag
UserTag (TagUser mid tag) -> return $ kwUnnamedConstr <> pretty tag <> "@" <> pretty mid

instance PrettyCode ModuleId where
ppCode = return . pretty

instance PrettyCode Symbol where
ppCode = return . pretty

instance PrettyCode Primitive where
ppCode = \case
p@(PrimInteger _) | p == primitiveUInt8 -> return $ annotate (AnnKind KNameInductive) (pretty ("UInt8" :: String))
Expand Down Expand Up @@ -568,7 +574,7 @@ instance PrettyCode InfoTable where
ppCode :: forall r. (Member (Reader Options) r) => InfoTable -> Sem r (Doc Ann)
ppCode tbl = do
let header x = annotate AnnImportant (Str.commentLineStart <+> x) <> line
tys <- ppInductives (toList (tbl ^. infoInductives))
tys <- ppInductives (sortOn (^. inductiveSymbol) $ toList (tbl ^. infoInductives))
sigs <- ppSigs (sortOn (^. identifierSymbol) $ toList (tbl ^. infoIdentifiers))
ctx' <- ppContext (tbl ^. identContext)
axioms <- vsep <$> mapM ppCode (tbl ^. infoAxioms)
Expand Down
5 changes: 4 additions & 1 deletion src/Juvix/Compiler/Pipeline/Driver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -274,7 +274,7 @@ processModuleCacheMiss entryIx = do
return r
ProcessModuleRecompile recomp -> recomp ^. recompileDo

processProject :: (Members '[ModuleInfoCache, Reader EntryPoint, Reader ImportTree] r) => Sem r [(ImportNode, PipelineResult ModuleInfo)]
processProject :: (Members '[PathResolver, ModuleInfoCache, Reader EntryPoint, Reader ImportTree] r) => Sem r [(ImportNode, PipelineResult ModuleInfo)]
processProject = do
rootDir <- asks (^. entryPointRoot)
nodes <- toList <$> asks (importTreeProjectNodes rootDir)
Expand Down Expand Up @@ -312,10 +312,13 @@ processRecursiveUpToTyped = do
where
goImport :: ImportNode -> Sem r InternalTypedResult
goImport node = do
pkgInfo <- fromJust . HashMap.lookup (node ^. importNodePackageRoot) <$> getPackageInfos
let pid = pkgInfo ^. packageInfoPackageId
entry <- ask
let entry' =
entry
{ _entryPointStdin = Nothing,
_entryPointPackageId = pid,
_entryPointModulePath = Just (node ^. importNodeAbsFile)
}
(^. pipelineResult) <$> runReader entry' (processFileUpTo upToInternalTyped)
Expand Down
2 changes: 1 addition & 1 deletion src/Juvix/Compiler/Pipeline/DriverParallel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ type Node = EntryIndex

mkNodesIndex ::
forall r.
(Members '[Reader EntryPoint] r) =>
(Members '[PathResolver, Reader EntryPoint] r) =>
ImportTree ->
Sem r (NodesIndex ImportNode Node)
mkNodesIndex tree =
Expand Down
130 changes: 97 additions & 33 deletions src/Juvix/Compiler/Pipeline/Loader/PathResolver.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,16 @@ module Juvix.Compiler.Pipeline.Loader.PathResolver
runPathResolverPipe',
evalPathResolverPipe,
findPackageJuvixFiles,
importNodePackageId,
mkPackageInfoPackageId,
checkConflicts,
)
where

import Data.HashMap.Strict qualified as HashMap
import Data.HashSet qualified as HashSet
import Data.List.NonEmpty.Extra qualified as NonEmpty
import Data.Versions qualified as Ver
import Juvix.Compiler.Concrete.Data.Name
import Juvix.Compiler.Concrete.Translation.FromParsed.Analysis.Scoping.Error
import Juvix.Compiler.Concrete.Translation.ImportScanner
Expand All @@ -36,6 +41,23 @@ import Juvix.Extra.Paths
import Juvix.Extra.Stdlib (ensureStdlib)
import Juvix.Prelude

checkConflicts :: forall r'. (Members '[Error JuvixError] r') => [PackageInfo] -> Sem r' ()
checkConflicts pkgs = do
let reps = findRepeatedOn (^. packageInfoPackageId) pkgs
case nonEmpty reps of
Just (rep :| _) -> errRep rep
Nothing -> return ()
where
errRep :: (NonEmpty PackageInfo, PackageId) -> Sem r' ()
errRep (l, pid) =
throw
. JuvixError
$ ErrAmbiguousPackageId
AmbiguousPackageId
{ _ambiguousPackageId = pid,
_ambiguousPackageIdPackages = l
}

mkPackage ::
forall r.
(Members '[Files, Error JuvixError, Reader ResolverEnv, DependencyResolver, EvalFileEff] r) =>
Expand All @@ -55,6 +77,35 @@ findPackageJuvixFiles pkgRoot = map (fromJust . stripProperPrefix pkgRoot) <$> w
newJuvixFiles :: [Path Abs File]
newJuvixFiles = [cd <//> f | f <- files, isJuvixOrJuvixMdFile f, not (isPackageFile f)]

-- | Append the hash of all files in the project to the pre-release
mkPackageInfoPackageId :: (Members '[Files] r) => Path Abs Dir -> [Path Rel File] -> PackageLike -> Sem r PackageId
mkPackageInfoPackageId root pkgRelFiles pkgLike = do
let pkgDotJuvix = mkPackageFilePath root
pkgDotJuvixExists <- fileExists' pkgDotJuvix
let pkgJuvixFiles = [root <//> rFile | rFile <- pkgRelFiles]
let baseVersion = packageLikeVersion pkgLike
allFiles
| pkgDotJuvixExists = pkgDotJuvix : pkgJuvixFiles
| otherwise = pkgJuvixFiles
filesHash <- SHA256.digestFiles allFiles
let version = case Ver._svPreRel baseVersion of
Nothing ->
baseVersion {_svPreRel = Just (Ver.Release (pure (Ver.Alphanum filesHash)))}
Just (Ver.Release r) -> baseVersion {_svPreRel = Just (Ver.Release (NonEmpty.snoc r (Ver.Alphanum filesHash)))}
return
PackageId
{ _packageIdName = pkgLike ^. packageLikeName,
_packageIdVersion = version
}
where
packageLikeVersion :: PackageLike -> SemVer
packageLikeVersion = \case
PackageReal pkg -> pkg ^. packageVersion
PackageStdlibInGlobalPackage -> defaultVersion
PackageBase {} -> defaultVersion
PackageType {} -> defaultVersion
PackageDotJuvix {} -> defaultVersion

mkPackageInfo ::
forall r.
(Members '[TaggedLock, Files, Error JuvixError, Error DependencyError, Reader ResolverEnv, DependencyResolver] r) =>
Expand All @@ -78,6 +129,7 @@ mkPackageInfo mpackageEntry _packageRoot pkg = do
: globalPackageBaseAbsDir
: _packageRoot
: depsPaths
_packageInfoPackageId <- mkPackageInfoPackageId _packageRoot (toList _packageJuvixRelativeFiles) _packagePackage
return PackageInfo {..}
where
pkgFile :: Path Abs File
Expand Down Expand Up @@ -117,17 +169,16 @@ mkPackageInfo mpackageEntry _packageRoot pkg = do
checkDep d =
unless
(mkName d `HashSet.member` lockfileDepNames)
( throw
DependencyError
{ _dependencyErrorPackageFile = pkgFile,
_dependencyErrorCause =
MissingLockfileDependencyError
MissingLockfileDependency
{ _missingLockfileDependencyDependency = d,
_missingLockfileDependencyPath = lf ^. lockfileInfoPath
}
}
)
$ throw
DependencyError
{ _dependencyErrorPackageFile = pkgFile,
_dependencyErrorCause =
MissingLockfileDependencyError
MissingLockfileDependency
{ _missingLockfileDependencyDependency = d,
_missingLockfileDependencyPath = lf ^. lockfileInfoPath
}
}

lookupCachedDependency :: (Members '[State ResolverState, Reader ResolverEnv, Files, DependencyResolver] r) => Path Abs Dir -> Sem r (Maybe LockfileDependency)
lookupCachedDependency p = fmap (^. resolverCacheItemDependency) . HashMap.lookup p <$> gets (^. resolverCache)
Expand All @@ -140,12 +191,14 @@ registerPackageBase = do
packageBaseAbsDir <- globalPackageBaseRoot
runReader packageBaseAbsDir updatePackageBaseFiles
packageBaseRelFiles <- relFiles packageBaseAbsDir
_packageInfoPackageId <- mkPackageInfoPackageId packageBaseAbsDir (toList packageBaseRelFiles) PackageBase
let pkgInfo =
PackageInfo
{ _packageRoot = packageBaseAbsDir,
_packageJuvixRelativeFiles = packageBaseRelFiles,
_packagePackage = PackageBase,
_packageAvailableRoots = HashSet.singleton packageBaseAbsDir
_packageAvailableRoots = HashSet.singleton packageBaseAbsDir,
_packageInfoPackageId
}
dep =
LockfileDependency
Expand All @@ -169,27 +222,30 @@ registerDependencies' conf = do
initialized <- gets (^. resolverInitialized)
unless initialized $ do
modify (set resolverInitialized True)
e <- ask @EntryPoint
registerDepsFromRoot
mapError (JuvixError @ParserError) registerPackageBase
case e ^. entryPointPackageType of
GlobalStdlib -> do
glob <- globalRoot
void (addRootDependency conf e glob)
GlobalPackageBase -> return ()
GlobalPackageDescription -> void (addRootDependency conf e (e ^. entryPointRoot))
LocalPackage -> do
lockfile <- addRootDependency conf e (e ^. entryPointRoot)
whenM shouldWriteLockfile $ do
let root :: Path Abs Dir = e ^. entryPointSomeRoot . someRootDir
packagePath :: Path Abs File <- do
let packageDotJuvix = mkPackagePath root
juvixDotYaml = mkPackageFilePath root
x <- findM fileExists' [packageDotJuvix, juvixDotYaml]
return (fromMaybe (error ("No package file found in " <> show root)) x)
packageFileChecksum <- SHA256.digestFile packagePath
lockfilePath' <- lockfilePath
writeLockfile lockfilePath' packageFileChecksum lockfile
where
registerDepsFromRoot = do
e <- ask
case e ^. entryPointPackageType of
GlobalStdlib -> do
glob <- globalRoot
void (addRootDependency conf e glob)
GlobalPackageBase -> return ()
GlobalPackageDescription -> void (addRootDependency conf e (e ^. entryPointRoot))
LocalPackage -> do
lockfile <- addRootDependency conf e (e ^. entryPointRoot)
whenM shouldWriteLockfile $ do
let root :: Path Abs Dir = e ^. entryPointSomeRoot . someRootDir
packagePath :: Path Abs File <- do
let packageDotJuvix = mkPackagePath root
juvixDotYaml = mkPackageFilePath root
x <- findM fileExists' [packageDotJuvix, juvixDotYaml]
return (fromMaybe (error ("No package file found in " <> show root)) x)
packageFileChecksum <- SHA256.digestFile packagePath
lockfilePath' <- lockfilePath
writeLockfile lockfilePath' packageFileChecksum lockfile

shouldWriteLockfile :: Sem r Bool
shouldWriteLockfile = do
lockfileExists <- lockfilePath >>= fileExists'
Expand Down Expand Up @@ -268,7 +324,7 @@ addDependency' pkg me resolvedDependency = do
selectPackageLockfile pkg $ do
pkgInfo <- mkPackageInfo me (resolvedDependency ^. resolvedDependencyPath) pkg
addPackageRelativeFiles pkgInfo
let packagePath = pkgInfo ^. packagePackage . packageLikeFile
let packagePath = packageLikeFile (pkgInfo ^. packagePackage)
subDeps <-
forM
(pkgInfo ^. packagePackage . packageLikeDependencies)
Expand Down Expand Up @@ -365,6 +421,10 @@ isModuleOrphan topJuvixPath = do
&& not (pathPackageBase `isProperPrefixOf` actualPath)
)

importNodePackageId :: (Members '[PathResolver] r) => ImportNode -> Sem r PackageId
importNodePackageId n =
(^?! at (n ^. importNodePackageRoot) . _Just . packageInfoPackageId) <$> getPackageInfos

expectedPath' ::
(Members '[Reader ResolverEnv, Files] r) =>
TopModulePath ->
Expand Down Expand Up @@ -409,7 +469,11 @@ runPathResolver2 st topEnv arg = do
)
handler
)
arg
$ do
_pkgs <- toList <$> getPackageInfos
-- I think we should not check for conflicts
-- checkConflicts pkgs
arg
where
handler ::
forall t localEs x.
Expand Down
Loading
Loading