mirror of
https://github.com/anoma/juvix.git
synced 2024-12-24 16:12:14 +03:00
Migrate all Juvix projects from juvix.yaml to Package.juvix in the repository (#2503)
This PR: * Modifies entry point `_entryPointBuildDir` to use the `BuildDir` type instead of `SomeBase Dir`. This allows delayed resolution of the default build directory which was useful for the Package -> Concrete translation point below. * Modifies `juvix dev root` to render the current package as a Package.juvix file. * Modifies the Package -> Concrete translation to recognise default arguments. So, for example, an empty `juvix.yaml` file will be translated into the following (instead of the `name`, `version`, and `dependencies` arguments being populated). module Package; import Stdlib.Prelude open; import PackageDescription.V1 open; package : Package := defaultPackage; * Adds a temporary command (removed when juvix.yaml support is removed) `juvix dev migrate-juvix-yaml` that translates `juvix.yaml` into an equivalent `Package.juvix` in the current project. * Adds a temporary script `migrate-juvix-yaml.sh` (removed when juvix.yaml support is removed) which can be run in the project to translate all Juvix projects in the repository. * Actually translate all of the `juvix.yaml` files to `Package.juvix` using the script. * Part of https://github.com/anoma/juvix/issues/2487
This commit is contained in:
parent
473ed259a5
commit
68d4314c78
@ -63,7 +63,7 @@ runAppIO args@RunAppIOArgs {..} =
|
||||
AskRoot -> return _runAppIOArgsRoot
|
||||
AskInvokeDir -> return invDir
|
||||
AskPkgDir -> return (_runAppIOArgsRoot ^. rootRootDir)
|
||||
AskBuildDir -> return (_runAppIOArgsRoot ^. rootBuildDir)
|
||||
AskBuildDir -> return (resolveAbsBuildDir (_runAppIOArgsRoot ^. rootRootDir) (_runAppIOArgsRoot ^. rootBuildDir))
|
||||
RunCorePipelineEither input -> do
|
||||
entry <- embed (getEntryPoint' args input)
|
||||
embed (corePipelineIOEither entry)
|
||||
|
@ -11,6 +11,7 @@ import Commands.Dev.DisplayRoot qualified as DisplayRoot
|
||||
import Commands.Dev.Geb qualified as Geb
|
||||
import Commands.Dev.Highlight qualified as Highlight
|
||||
import Commands.Dev.Internal qualified as Internal
|
||||
import Commands.Dev.MigrateJuvixYaml qualified as MigrateJuvixYaml
|
||||
import Commands.Dev.Options
|
||||
import Commands.Dev.Parse qualified as Parse
|
||||
import Commands.Dev.Runtime qualified as Runtime
|
||||
@ -31,3 +32,4 @@ runCommand = \case
|
||||
Runtime opts -> Runtime.runCommand opts
|
||||
DisplayRoot opts -> DisplayRoot.runCommand opts
|
||||
JuvixDevRepl opts -> Repl.runCommand opts
|
||||
MigrateJuvixYaml opts -> runFilesIO $ MigrateJuvixYaml.runCommand opts
|
||||
|
@ -2,7 +2,7 @@ module Commands.Dev.DisplayRoot where
|
||||
|
||||
import Commands.Base
|
||||
import Commands.Dev.DisplayRoot.Options
|
||||
import Data.Yaml
|
||||
import Commands.Extra.Package
|
||||
|
||||
runCommand :: forall r. (Members '[Embed IO, App] r) => RootOptions -> Sem r ()
|
||||
runCommand RootOptions {..} = do
|
||||
@ -12,4 +12,4 @@ runCommand RootOptions {..} = do
|
||||
printPackage :: Sem r ()
|
||||
printPackage = do
|
||||
say "+----------------------------+"
|
||||
askPackage >>= say . decodeUtf8 . encode . rawPackage
|
||||
askPackage >>= say . renderPackage
|
||||
|
@ -15,7 +15,7 @@ parseRoot = do
|
||||
_rootPrintPackage <-
|
||||
switch
|
||||
( long "print-package"
|
||||
<> help "print the juvix.yaml file as parsed"
|
||||
<> help "print the Package.juvix file as parsed"
|
||||
)
|
||||
|
||||
_rootMainFile <- optional (parseInputFile FileExtJuvix)
|
||||
|
20
app/Commands/Dev/MigrateJuvixYaml.hs
Normal file
20
app/Commands/Dev/MigrateJuvixYaml.hs
Normal file
@ -0,0 +1,20 @@
|
||||
module Commands.Dev.MigrateJuvixYaml where
|
||||
|
||||
import Commands.Base
|
||||
import Commands.Dev.MigrateJuvixYaml.Options
|
||||
import Commands.Extra.Package
|
||||
import Juvix.Extra.Paths
|
||||
|
||||
runCommand :: forall r. (Members '[Embed IO, Files, App] r) => MigrateJuvixYamlOptions -> Sem r ()
|
||||
runCommand MigrateJuvixYamlOptions {..} = do
|
||||
pkgDir <- askPkgDir
|
||||
isGlobalPackage <- askPackageGlobal
|
||||
let pkgFilePath = pkgDir <//> packageFilePath
|
||||
pkgFileExists <- fileExists' pkgFilePath
|
||||
pkg <- askPackage
|
||||
if
|
||||
| isGlobalPackage -> exitMsg (ExitFailure 1) "No Package file found"
|
||||
| not pkgFileExists || _migrateJuvixYamlOptionsForce -> do
|
||||
writePackageFile pkgDir pkg
|
||||
removeFile' (pkgDir <//> juvixYamlFile)
|
||||
| otherwise -> exitMsg (ExitFailure 1) (show pkgFilePath <> " already exists.")
|
20
app/Commands/Dev/MigrateJuvixYaml/Options.hs
Normal file
20
app/Commands/Dev/MigrateJuvixYaml/Options.hs
Normal file
@ -0,0 +1,20 @@
|
||||
module Commands.Dev.MigrateJuvixYaml.Options where
|
||||
|
||||
import CommonOptions
|
||||
|
||||
newtype MigrateJuvixYamlOptions = MigrateJuvixYamlOptions
|
||||
{ _migrateJuvixYamlOptionsForce :: Bool
|
||||
}
|
||||
deriving stock (Data)
|
||||
|
||||
makeLenses ''MigrateJuvixYamlOptions
|
||||
|
||||
parseMigrateJuvixYaml :: Parser MigrateJuvixYamlOptions
|
||||
parseMigrateJuvixYaml = do
|
||||
_migrateJuvixYamlOptionsForce <-
|
||||
switch
|
||||
( long "force"
|
||||
<> short 'f'
|
||||
<> help "Overwrite existing Package.juvix"
|
||||
)
|
||||
pure MigrateJuvixYamlOptions {..}
|
@ -18,6 +18,7 @@ import Commands.Dev.DisplayRoot.Options
|
||||
import Commands.Dev.Geb.Options
|
||||
import Commands.Dev.Highlight.Options
|
||||
import Commands.Dev.Internal.Options
|
||||
import Commands.Dev.MigrateJuvixYaml.Options
|
||||
import Commands.Dev.Parse.Options
|
||||
import Commands.Dev.Repl.Options
|
||||
import Commands.Dev.Runtime.Options
|
||||
@ -38,6 +39,7 @@ data DevCommand
|
||||
| Scope ScopeOptions
|
||||
| Termination TerminationCommand
|
||||
| JuvixDevRepl ReplOptions
|
||||
| MigrateJuvixYaml MigrateJuvixYamlOptions
|
||||
deriving stock (Data)
|
||||
|
||||
parseDevCommand :: Parser DevCommand
|
||||
@ -54,7 +56,8 @@ parseDevCommand =
|
||||
commandScope,
|
||||
commandShowRoot,
|
||||
commandTermination,
|
||||
commandJuvixDevRepl
|
||||
commandJuvixDevRepl,
|
||||
commandMigrateJuvixYaml
|
||||
]
|
||||
)
|
||||
|
||||
@ -136,3 +139,10 @@ commandJuvixDevRepl =
|
||||
(JuvixDevRepl <$> parseDevRepl)
|
||||
(progDesc "Run the Juvix dev REPL")
|
||||
)
|
||||
|
||||
commandMigrateJuvixYaml :: Mod CommandFields DevCommand
|
||||
commandMigrateJuvixYaml =
|
||||
command "migrate-juvix-yaml" $
|
||||
info
|
||||
(MigrateJuvixYaml <$> parseMigrateJuvixYaml)
|
||||
(progDesc "Migrate juvix.yaml to Package.juvix in the current project")
|
||||
|
18
app/Commands/Extra/Package.hs
Normal file
18
app/Commands/Extra/Package.hs
Normal file
@ -0,0 +1,18 @@
|
||||
module Commands.Extra.Package where
|
||||
|
||||
import Data.Text.IO.Utf8 qualified as Utf8
|
||||
import Juvix.Compiler.Pipeline.Package.Base
|
||||
import Juvix.Compiler.Pipeline.Package.Loader
|
||||
import Juvix.Extra.Paths
|
||||
import Juvix.Prelude
|
||||
|
||||
renderPackage :: Package -> Text
|
||||
renderPackage = renderPackageVersion PackageVersion1
|
||||
|
||||
writePackageFile :: (Member (Embed IO) r) => Path Abs Dir -> Package -> Sem r ()
|
||||
writePackageFile root pkg =
|
||||
embed
|
||||
( Utf8.writeFile @IO
|
||||
(toFilePath (root <//> packageFilePath))
|
||||
(renderPackage pkg)
|
||||
)
|
@ -1,11 +1,10 @@
|
||||
module Commands.Init where
|
||||
|
||||
import Commands.Extra.Package
|
||||
import Commands.Init.Options
|
||||
import Data.Text qualified as Text
|
||||
import Data.Text.IO.Utf8 qualified as Utf8
|
||||
import Data.Versions
|
||||
import Juvix.Compiler.Pipeline.Package
|
||||
import Juvix.Compiler.Pipeline.Package.Loader
|
||||
import Juvix.Data.Effect.Fail.Extra qualified as Fail
|
||||
import Juvix.Extra.Paths
|
||||
import Juvix.Prelude
|
||||
@ -39,13 +38,11 @@ init opts = do
|
||||
Nothing -> emptyPkg
|
||||
Just n -> emptyPkg {_packageName = n}
|
||||
when isInteractive (say ("creating " <> pack (toFilePath packageFilePath)))
|
||||
writePackage pkg
|
||||
cwd <- getCurrentDir
|
||||
writePackageFile cwd pkg
|
||||
checkPackage
|
||||
when isInteractive (say "you are all set")
|
||||
where
|
||||
writePackage :: Package -> Sem r ()
|
||||
writePackage pkg = embed (Utf8.writeFile @IO (toFilePath packageFilePath) (renderPackageVersion PackageVersion1 pkg))
|
||||
|
||||
isInteractive :: Bool
|
||||
isInteractive = not (opts ^. initOptionsNonInteractive)
|
||||
|
||||
|
@ -535,8 +535,8 @@ runCommand opts = do
|
||||
defaultPreludeEntryPoint :: Repl (Maybe EntryPoint)
|
||||
defaultPreludeEntryPoint = do
|
||||
root <- State.gets (^. replStateRoot)
|
||||
let buildDir = root ^. rootBuildDir
|
||||
buildRoot = root ^. rootRootDir
|
||||
let buildRoot = root ^. rootRootDir
|
||||
buildDir = resolveAbsBuildDir buildRoot (root ^. rootBuildDir)
|
||||
pkg = root ^. rootPackage
|
||||
mstdlibPath <- liftIO (runM (runFilesIO (packageStdlib buildRoot buildDir (pkg ^. packageDependencies))))
|
||||
case mstdlibPath of
|
||||
|
@ -157,7 +157,7 @@ entryPointFromGlobalOptions root mainFile opts = do
|
||||
_entryPointNoStdlib = opts ^. globalNoStdlib,
|
||||
_entryPointUnrollLimit = opts ^. globalUnrollLimit,
|
||||
_entryPointGenericOptions = project opts,
|
||||
_entryPointBuildDir = maybe (def ^. entryPointBuildDir) Abs mabsBuildDir,
|
||||
_entryPointBuildDir = maybe (def ^. entryPointBuildDir) (CustomBuildDir . Abs) mabsBuildDir,
|
||||
_entryPointOffline = opts ^. globalOffline
|
||||
}
|
||||
where
|
||||
@ -178,7 +178,7 @@ entryPointFromGlobalOptionsNoFile root opts = do
|
||||
_entryPointNoStdlib = opts ^. globalNoStdlib,
|
||||
_entryPointUnrollLimit = opts ^. globalUnrollLimit,
|
||||
_entryPointGenericOptions = project opts,
|
||||
_entryPointBuildDir = maybe (def ^. entryPointBuildDir) Abs mabsBuildDir,
|
||||
_entryPointBuildDir = maybe (def ^. entryPointBuildDir) (CustomBuildDir . Abs) mabsBuildDir,
|
||||
_entryPointOffline = opts ^. globalOffline
|
||||
}
|
||||
where
|
||||
|
7
examples/demo/Package.juvix
Normal file
7
examples/demo/Package.juvix
Normal file
@ -0,0 +1,7 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "Demo"; version := mkVersion 0 1 0};
|
@ -1,2 +0,0 @@
|
||||
name: Demo
|
||||
version: 0.1.0
|
7
examples/midsquare/Package.juvix
Normal file
7
examples/midsquare/Package.juvix
Normal file
@ -0,0 +1,7 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "midsquare"; version := mkVersion 0 1 0};
|
@ -1,2 +0,0 @@
|
||||
name: midsquare
|
||||
version: 0.1.0
|
5
examples/milestone/Bank/Package.juvix
Normal file
5
examples/milestone/Bank/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage {name := "bank"};
|
@ -1,4 +0,0 @@
|
||||
dependencies:
|
||||
- .juvix-build/stdlib/
|
||||
name: bank
|
||||
version: 0.0.0
|
10
examples/milestone/Collatz/Package.juvix
Normal file
10
examples/milestone/Collatz/Package.juvix
Normal file
@ -0,0 +1,10 @@
|
||||
module Package;
|
||||
|
||||
import Stdlib.Prelude open;
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "Collatz";
|
||||
version := mkVersion 0 1 0;
|
||||
main := just "Collatz.juvix"};
|
@ -1,3 +0,0 @@
|
||||
name: Collatz
|
||||
main: Collatz.juvix
|
||||
version: 0.1.0
|
10
examples/milestone/Fibonacci/Package.juvix
Normal file
10
examples/milestone/Fibonacci/Package.juvix
Normal file
@ -0,0 +1,10 @@
|
||||
module Package;
|
||||
|
||||
import Stdlib.Prelude open;
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "Fibonacci";
|
||||
version := mkVersion 0 1 0;
|
||||
main := just "Fibonacci.juvix"};
|
@ -1,3 +0,0 @@
|
||||
name: Fibonacci
|
||||
main: Fibonacci.juvix
|
||||
version: 0.1.0
|
10
examples/milestone/Hanoi/Package.juvix
Normal file
10
examples/milestone/Hanoi/Package.juvix
Normal file
@ -0,0 +1,10 @@
|
||||
module Package;
|
||||
|
||||
import Stdlib.Prelude open;
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "Hanoi";
|
||||
version := mkVersion 0 1 0;
|
||||
main := just "Hanoi.juvix"};
|
@ -1,3 +0,0 @@
|
||||
name: Hanoi
|
||||
main: Hanoi.juvix
|
||||
version: 0.1.0
|
10
examples/milestone/HelloWorld/Package.juvix
Normal file
10
examples/milestone/HelloWorld/Package.juvix
Normal file
@ -0,0 +1,10 @@
|
||||
module Package;
|
||||
|
||||
import Stdlib.Prelude open;
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "HelloWorld";
|
||||
version := mkVersion 0 1 0;
|
||||
main := just "HelloWorld.juvix"};
|
@ -1,3 +0,0 @@
|
||||
name: HelloWorld
|
||||
main: HelloWorld.juvix
|
||||
version: 0.1.0
|
10
examples/milestone/PascalsTriangle/Package.juvix
Normal file
10
examples/milestone/PascalsTriangle/Package.juvix
Normal file
@ -0,0 +1,10 @@
|
||||
module Package;
|
||||
|
||||
import Stdlib.Prelude open;
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "PascalsTriangle";
|
||||
version := mkVersion 0 1 0;
|
||||
main := just "PascalsTriangle.juvix"};
|
@ -1,3 +0,0 @@
|
||||
name: PascalsTriangle
|
||||
main: PascalsTriangle.juvix
|
||||
version: 0.1.0
|
10
examples/milestone/TicTacToe/Package.juvix
Normal file
10
examples/milestone/TicTacToe/Package.juvix
Normal file
@ -0,0 +1,10 @@
|
||||
module Package;
|
||||
|
||||
import Stdlib.Prelude open;
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "TicTacToe";
|
||||
version := mkVersion 0 1 0;
|
||||
main := just "CLI/TicTacToe.juvix"};
|
@ -1,3 +0,0 @@
|
||||
name: TicTacToe
|
||||
main: CLI/TicTacToe.juvix
|
||||
version: 0.1.0
|
7
examples/milestone/Tutorial/Package.juvix
Normal file
7
examples/milestone/Tutorial/Package.juvix
Normal file
@ -0,0 +1,7 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage
|
||||
{name := "Tutorial"; version := mkVersion 0 1 0};
|
@ -1,2 +0,0 @@
|
||||
name: Tutorial
|
||||
version: 0.1.0
|
9
migrate-juvix-yaml.sh
Executable file
9
migrate-juvix-yaml.sh
Executable file
@ -0,0 +1,9 @@
|
||||
#!/usr/bin/env bash
|
||||
|
||||
# Projects must be migrated depth-first because Package.juvix is searched before juvix.yaml
|
||||
# (so Package.juvix in parent directories are used before juvix.yaml in the current directory)
|
||||
find . -type f -name "juvix.yaml" | awk -F'/' '{print NF-1 " " $0}' | sort -nr | cut -d' ' -f2- | while IFS= read -r file; do
|
||||
dir=$(dirname "$file")
|
||||
echo "migrating: $dir"
|
||||
(cd "$dir" && juvix dev migrate-juvix-yaml)
|
||||
done
|
@ -36,10 +36,9 @@ mkPackage ::
|
||||
Path Abs Dir ->
|
||||
Sem r Package
|
||||
mkPackage mpackageEntry _packageRoot = do
|
||||
let buildDir :: Path Abs Dir = maybe (rootBuildDir _packageRoot) (someBaseToAbs _packageRoot . (^. entryPointBuildDir)) mpackageEntry
|
||||
buildDirDep :: BuildDir
|
||||
| isJust mpackageEntry = CustomBuildDir (Abs buildDir)
|
||||
| otherwise = DefaultBuildDir
|
||||
let buildDirDep = case mpackageEntry of
|
||||
Just packageEntry -> rootedBuildDir _packageRoot (packageEntry ^. entryPointBuildDir)
|
||||
Nothing -> DefaultBuildDir
|
||||
maybe (readPackage _packageRoot buildDirDep) (return . (^. entryPointPackage)) mpackageEntry
|
||||
|
||||
mkPackageInfo ::
|
||||
@ -50,7 +49,7 @@ mkPackageInfo ::
|
||||
Package ->
|
||||
Sem r PackageInfo
|
||||
mkPackageInfo mpackageEntry _packageRoot pkg = do
|
||||
let buildDir :: Path Abs Dir = maybe (rootBuildDir _packageRoot) (someBaseToAbs _packageRoot . (^. entryPointBuildDir)) mpackageEntry
|
||||
let buildDir :: Path Abs Dir = maybe (rootBuildDir _packageRoot) (someBaseToAbs _packageRoot . resolveBuildDir . (^. entryPointBuildDir)) mpackageEntry
|
||||
deps <- getDependencies
|
||||
let _packagePackage = set packageDependencies deps pkg
|
||||
depsPaths <- mapM (fmap (^. resolvedDependencyPath) . resolveDependency . mkPackageDependencyInfo pkgFile) deps
|
||||
|
@ -7,7 +7,6 @@ where
|
||||
import Juvix.Compiler.Backend
|
||||
import Juvix.Compiler.Pipeline.Package.Base
|
||||
import Juvix.Compiler.Pipeline.Root.Base
|
||||
import Juvix.Extra.Paths
|
||||
import Juvix.Prelude
|
||||
|
||||
-- | An option specifiying how symbols should be pruned in the Internal to Core translation
|
||||
@ -22,7 +21,7 @@ data EntryPoint = EntryPoint
|
||||
-- | initial root for the path resolver. Usually it should be equal to
|
||||
-- _entryPointRoot. It only differs for `juvix repl`.
|
||||
_entryPointResolverRoot :: Path Abs Dir,
|
||||
_entryPointBuildDir :: SomeBase Dir,
|
||||
_entryPointBuildDir :: BuildDir,
|
||||
_entryPointNoTermination :: Bool,
|
||||
_entryPointNoPositivity :: Bool,
|
||||
_entryPointNoCoverage :: Bool,
|
||||
@ -56,7 +55,7 @@ defaultEntryPointNoFile root =
|
||||
EntryPoint
|
||||
{ _entryPointRoot = root ^. rootRootDir,
|
||||
_entryPointResolverRoot = root ^. rootRootDir,
|
||||
_entryPointBuildDir = Rel relBuildDir,
|
||||
_entryPointBuildDir = DefaultBuildDir,
|
||||
_entryPointNoTermination = False,
|
||||
_entryPointNoPositivity = False,
|
||||
_entryPointNoCoverage = False,
|
||||
|
@ -17,6 +17,7 @@ import Lens.Micro.Platform qualified as Lens
|
||||
data BuildDir
|
||||
= DefaultBuildDir
|
||||
| CustomBuildDir (SomeBase Dir)
|
||||
deriving stock (Eq, Show)
|
||||
|
||||
type NameType :: IsProcessed -> GHC.Type
|
||||
type family NameType s = res | res -> s where
|
||||
@ -99,6 +100,17 @@ resolveBuildDir = \case
|
||||
DefaultBuildDir -> Rel (relBuildDir)
|
||||
CustomBuildDir d -> d
|
||||
|
||||
resolveAbsBuildDir :: Path Abs Dir -> BuildDir -> Path Abs Dir
|
||||
resolveAbsBuildDir root = someBaseToAbs root . resolveBuildDir
|
||||
|
||||
mapCustomBuildDir :: (SomeBase Dir -> SomeBase Dir) -> BuildDir -> BuildDir
|
||||
mapCustomBuildDir f = \case
|
||||
DefaultBuildDir -> DefaultBuildDir
|
||||
CustomBuildDir d -> CustomBuildDir (f d)
|
||||
|
||||
rootedBuildDir :: Path Abs Dir -> BuildDir -> BuildDir
|
||||
rootedBuildDir root = mapCustomBuildDir (Abs . someBaseToAbs root)
|
||||
|
||||
-- | This is used when juvix.yaml exists but it is empty
|
||||
emptyPackage :: BuildDir -> Path Abs File -> Package
|
||||
emptyPackage buildDir yamlPath =
|
||||
|
@ -18,7 +18,6 @@ import Juvix.Compiler.Pipeline.Package.Loader.EvalEff
|
||||
import Juvix.Compiler.Pipeline.Package.Loader.PathResolver
|
||||
import Juvix.Data.Effect.Git
|
||||
import Juvix.Data.Effect.Process
|
||||
import Juvix.Extra.Paths qualified as Paths
|
||||
|
||||
data LoaderResource = LoaderResource
|
||||
{ _loaderResourceResult :: CoreResult,
|
||||
@ -152,7 +151,7 @@ loadPackage' packagePath = do
|
||||
_rootPackageGlobal = False,
|
||||
_rootPackage = rootPkg,
|
||||
_rootInvokeDir = rootPath,
|
||||
_rootBuildDir = Paths.rootBuildDir rootPath
|
||||
_rootBuildDir = DefaultBuildDir
|
||||
}
|
||||
|
||||
rootPkg :: Package
|
||||
|
@ -34,49 +34,73 @@ v1PackageDescriptionType = PackageDescriptionType v1PackageDescriptionFile "Pack
|
||||
|
||||
fromPackage :: Package -> FunctionDefBody 'Parsed
|
||||
fromPackage p = run . runReader l $ do
|
||||
defaultPackageName' <- NameUnqualified <$> symbol "defaultPackage"
|
||||
argBlock <- argumentBlock Implicit =<< mkNamedArgs
|
||||
let defaultPackageArg = namedApplication defaultPackageName' (argBlock :| [])
|
||||
functionDefExpression (defaultPackageArg :| [])
|
||||
bodyExpression <-
|
||||
maybeM
|
||||
defaultPackageNoArgs
|
||||
defaultPackageWithArgs
|
||||
(nonEmpty <$> mkNamedArgs)
|
||||
functionDefExpression bodyExpression
|
||||
where
|
||||
defaultPackageStr :: Text
|
||||
defaultPackageStr = "defaultPackage"
|
||||
|
||||
defaultPackageNoArgs :: (Member (Reader Interval) r) => Sem r (NonEmpty (ExpressionAtom 'Parsed))
|
||||
defaultPackageNoArgs = NEL.singleton <$> identifier defaultPackageStr
|
||||
|
||||
defaultPackageWithArgs :: (Member (Reader Interval) r) => NonEmpty (NamedArgument 'Parsed) -> Sem r (NonEmpty (ExpressionAtom 'Parsed))
|
||||
defaultPackageWithArgs as = do
|
||||
defaultPackageName' <- NameUnqualified <$> symbol defaultPackageStr
|
||||
argBlock <- argumentBlock Implicit as
|
||||
let defaultPackageArg = namedApplication defaultPackageName' (argBlock :| [])
|
||||
return (defaultPackageArg :| [])
|
||||
|
||||
l :: Interval
|
||||
l = singletonInterval (mkInitialLoc (p ^. packageFile))
|
||||
|
||||
mkNamedArgs :: forall r. (Member (Reader Interval) r) => Sem r (NonEmpty (NamedArgument 'Parsed))
|
||||
mkNamedArgs :: forall r. (Member (Reader Interval) r) => Sem r [NamedArgument 'Parsed]
|
||||
mkNamedArgs = do
|
||||
args <- sequence (mkNameArg :| [mkVersionArg, mkDependenciesArg])
|
||||
optionalArgs <- catMaybes <$> sequence [mkMainArg, mkBuildDirArg]
|
||||
return (appendList args optionalArgs)
|
||||
catMaybes <$> sequence [mkNameArg, mkVersionArg, mkDependenciesArg, mkMainArg, mkBuildDirArg]
|
||||
where
|
||||
mkNameArg :: Sem r (NamedArgument 'Parsed)
|
||||
mkNameArg = do
|
||||
n <- literalString (p ^. packageName)
|
||||
namedArgument "name" (n :| [])
|
||||
mkNameArg :: Sem r (Maybe (NamedArgument 'Parsed))
|
||||
mkNameArg
|
||||
| defaultPackageName == p ^. packageName = return Nothing
|
||||
| otherwise = do
|
||||
n <- literalString (p ^. packageName)
|
||||
Just <$> namedArgument "name" (n :| [])
|
||||
|
||||
mkDependenciesArg :: Sem r (NamedArgument 'Parsed)
|
||||
mkDependenciesArg :: Sem r (Maybe (NamedArgument 'Parsed))
|
||||
mkDependenciesArg = do
|
||||
deps <- mkList =<< mapM mkDependencyArg (p ^. packageDependencies)
|
||||
namedArgument "dependencies" (deps :| [])
|
||||
let deps = p ^. packageDependencies
|
||||
dependenciesArg = Just <$> mkDependenciesArg' (p ^. packageDependencies)
|
||||
case deps of
|
||||
[d] ->
|
||||
if
|
||||
| d == defaultStdlibDep DefaultBuildDir -> return Nothing
|
||||
| otherwise -> dependenciesArg
|
||||
_ -> dependenciesArg
|
||||
where
|
||||
mkDependenciesArg' :: [Dependency] -> Sem r (NamedArgument 'Parsed)
|
||||
mkDependenciesArg' ds = do
|
||||
deps <- mkList =<< mapM mkDependencyArg ds
|
||||
namedArgument "dependencies" (deps :| [])
|
||||
|
||||
mkDependencyArg :: Dependency -> Sem r (NonEmpty (ExpressionAtom 'Parsed))
|
||||
mkDependencyArg d
|
||||
| d == defaultStdlibDep DefaultBuildDir = NEL.singleton <$> identifier "defaultStdlib"
|
||||
| otherwise = case d of
|
||||
DependencyPath x ->
|
||||
sequence
|
||||
( identifier "path"
|
||||
:| [literalString (pack (unsafePrepathToFilePath (x ^. pathDependencyPath)))]
|
||||
)
|
||||
DependencyGit x ->
|
||||
sequence
|
||||
( identifier "git"
|
||||
:| ( literalString
|
||||
<$> [ x ^. gitDependencyName,
|
||||
x ^. gitDependencyUrl,
|
||||
x ^. gitDependencyRef
|
||||
]
|
||||
)
|
||||
)
|
||||
mkDependencyArg = \case
|
||||
DependencyPath x ->
|
||||
sequence
|
||||
( identifier "path"
|
||||
:| [literalString (pack (unsafePrepathToFilePath (x ^. pathDependencyPath)))]
|
||||
)
|
||||
DependencyGit x ->
|
||||
sequence
|
||||
( identifier "git"
|
||||
:| ( literalString
|
||||
<$> [ x ^. gitDependencyName,
|
||||
x ^. gitDependencyUrl,
|
||||
x ^. gitDependencyRef
|
||||
]
|
||||
)
|
||||
)
|
||||
|
||||
mkMainArg :: Sem r (Maybe (NamedArgument 'Parsed))
|
||||
mkMainArg = do
|
||||
@ -94,12 +118,17 @@ v1PackageDescriptionType = PackageDescriptionType v1PackageDescriptionFile "Pack
|
||||
buildDirArg :: SomeBase Dir -> Sem r (NonEmpty (ExpressionAtom 'Parsed))
|
||||
buildDirArg d = mkJust =<< literalString (pack (fromSomeDir d))
|
||||
|
||||
mkVersionArg :: Sem r (NamedArgument 'Parsed)
|
||||
mkVersionArg = do
|
||||
mkVersionArgs <- liftM2 (++) explicitArgs implicitArgs
|
||||
mkVersionName <- identifier "mkVersion"
|
||||
namedArgument "version" (mkVersionName :| mkVersionArgs)
|
||||
mkVersionArg :: Sem r (Maybe (NamedArgument 'Parsed))
|
||||
mkVersionArg
|
||||
| p ^. packageVersion == defaultVersion = return Nothing
|
||||
| otherwise = Just <$> mkVersionArg'
|
||||
where
|
||||
mkVersionArg' :: Sem r (NamedArgument 'Parsed)
|
||||
mkVersionArg' = do
|
||||
mkVersionArgs <- liftM2 (++) explicitArgs implicitArgs
|
||||
mkVersionName <- identifier "mkVersion"
|
||||
namedArgument "version" (mkVersionName :| mkVersionArgs)
|
||||
|
||||
explicitArgs :: Sem r [ExpressionAtom 'Parsed]
|
||||
explicitArgs =
|
||||
let SemVer {..} = p ^. packageVersion
|
||||
|
@ -44,16 +44,16 @@ findRootAndChangeDir minputFileDir mbuildDir _rootInvokeDir = do
|
||||
_rootPackage <- readGlobalPackageIO
|
||||
_rootRootDir <- runM (runFilesIO globalRoot)
|
||||
let _rootPackageGlobal = True
|
||||
_rootBuildDir = getBuildDir mbuildDir _rootRootDir
|
||||
_rootBuildDir = getBuildDir mbuildDir
|
||||
return Root {..}
|
||||
Just yamlPath -> do
|
||||
let _rootRootDir = parent yamlPath
|
||||
_rootPackageGlobal = False
|
||||
_rootBuildDir = getBuildDir mbuildDir _rootRootDir
|
||||
_rootPackage <- readPackageIO _rootRootDir (CustomBuildDir (Abs _rootBuildDir))
|
||||
_rootBuildDir = getBuildDir mbuildDir
|
||||
_rootPackage <- readPackageIO _rootRootDir _rootBuildDir
|
||||
return Root {..}
|
||||
|
||||
getBuildDir :: Maybe (Path Abs Dir) -> Path Abs Dir -> Path Abs Dir
|
||||
getBuildDir mbuildDirOpt pkgDir = case mbuildDirOpt of
|
||||
Nothing -> Paths.rootBuildDir pkgDir
|
||||
Just p -> p
|
||||
getBuildDir :: Maybe (Path Abs Dir) -> BuildDir
|
||||
getBuildDir mbuildDirOpt = case mbuildDirOpt of
|
||||
Nothing -> DefaultBuildDir
|
||||
Just p -> CustomBuildDir (Abs p)
|
||||
|
@ -7,7 +7,7 @@ data Root = Root
|
||||
{ _rootRootDir :: Path Abs Dir,
|
||||
_rootPackage :: Package,
|
||||
_rootPackageGlobal :: Bool,
|
||||
_rootBuildDir :: Path Abs Dir,
|
||||
_rootBuildDir :: BuildDir,
|
||||
_rootInvokeDir :: Path Abs Dir
|
||||
}
|
||||
deriving stock (Show)
|
||||
|
5
tests/Compilation/negative/Package.juvix
Normal file
5
tests/Compilation/negative/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/Compilation/positive/Package.juvix
Normal file
5
tests/Compilation/positive/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage {name := "tests"};
|
@ -1,4 +0,0 @@
|
||||
dependencies:
|
||||
- .juvix-build/stdlib/
|
||||
name: tests
|
||||
version: 0.0.0
|
5
tests/Compilation/positive/test066/Package.juvix
Normal file
5
tests/Compilation/positive/test066/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/Geb/positive/Compilation/Package.juvix
Normal file
5
tests/Geb/positive/Compilation/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/Internal/Core/positive/Package.juvix
Normal file
5
tests/Internal/Core/positive/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
6
tests/Internal/positive/Dependencies/Dep1/Package.juvix
Normal file
6
tests/Internal/positive/Dependencies/Dep1/Package.juvix
Normal file
@ -0,0 +1,6 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage {name := "dep1"; dependencies := []};
|
@ -1,3 +0,0 @@
|
||||
dependencies: []
|
||||
name: dep1
|
||||
version: 0.0.0
|
6
tests/Internal/positive/Dependencies/Dep2/Package.juvix
Normal file
6
tests/Internal/positive/Dependencies/Dep2/Package.juvix
Normal file
@ -0,0 +1,6 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package :=
|
||||
defaultPackage {name := "dep2"; dependencies := []};
|
@ -1,3 +0,0 @@
|
||||
dependencies: []
|
||||
name: dep2
|
||||
version: 0.0.0
|
5
tests/Internal/positive/Import/Package.juvix
Normal file
5
tests/Internal/positive/Import/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/Internal/positive/NestedModuleScope/Package.juvix
Normal file
5
tests/Internal/positive/NestedModuleScope/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/Internal/positive/Package.juvix
Normal file
5
tests/Internal/positive/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/VampIR/negative/Package.juvix
Normal file
5
tests/VampIR/negative/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/VampIR/positive/Compilation/Package.juvix
Normal file
5
tests/VampIR/positive/Compilation/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/230/Package.juvix
Normal file
5
tests/negative/230/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/258/Package.juvix
Normal file
5
tests/negative/258/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/265/Package.juvix
Normal file
5
tests/negative/265/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/BindGroupConflict/Package.juvix
Normal file
5
tests/negative/BindGroupConflict/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/Dependencies/Package.juvix
Normal file
5
tests/negative/Dependencies/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/ImportCycle/Package.juvix
Normal file
5
tests/negative/ImportCycle/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/Internal/Package.juvix
Normal file
5
tests/negative/Internal/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/Internal/Positivity/Package.juvix
Normal file
5
tests/negative/Internal/Positivity/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/NoDependencies/Package.juvix
Normal file
5
tests/negative/NoDependencies/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage {dependencies := []};
|
@ -1 +0,0 @@
|
||||
dependencies: []
|
5
tests/negative/Package.juvix
Normal file
5
tests/negative/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/StdlibConflict/Package.juvix
Normal file
5
tests/negative/StdlibConflict/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/Termination/Package.juvix
Normal file
5
tests/negative/Termination/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/UsingHiding/Package.juvix
Normal file
5
tests/negative/UsingHiding/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/issue1337/Package.juvix
Normal file
5
tests/negative/issue1337/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/issue1344/Package.juvix
Normal file
5
tests/negative/issue1344/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/negative/issue1700/Package.juvix
Normal file
5
tests/negative/issue1700/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/positive/265/Package.juvix
Normal file
5
tests/positive/265/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/positive/272/Package.juvix
Normal file
5
tests/positive/272/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
5
tests/positive/BuiltinsMultiImport/Package.juvix
Normal file
5
tests/positive/BuiltinsMultiImport/Package.juvix
Normal file
@ -0,0 +1,5 @@
|
||||
module Package;
|
||||
|
||||
import PackageDescription.V1 open;
|
||||
|
||||
package : Package := defaultPackage;
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user