diff --git a/CHANGELOG.md b/CHANGELOG.md index 82e513f55..363aa3eb0 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -43,6 +43,8 @@ Other improvements: - When the `publish.location` field is missing, `spago publish` will attempt to figure out the location from Git remotes and write it back to `spago.yaml`. - Internally Spago uses stricter-typed file paths. +- Spago can now be launched from a directory nested within the workspace, not + just from workspace root. ## [0.21.0] - 2023-05-04 diff --git a/bin/src/Main.purs b/bin/src/Main.purs index 4056387d3..93fed2a45 100644 --- a/bin/src/Main.purs +++ b/bin/src/Main.purs @@ -536,8 +536,7 @@ main = do \c -> Aff.launchAff_ case c of Cmd'SpagoCmd (SpagoCmd globalArgs@{ offline, migrateConfig } command) -> do logOptions <- mkLogOptions startingTime globalArgs - rootPath <- Path.mkRoot =<< Paths.cwd - runSpago { logOptions, rootPath } case command of + runSpago { logOptions } case command of Sources args -> do { env } <- mkFetchEnv { packages: mempty @@ -552,6 +551,7 @@ main = do void $ runSpago env (Sources.run { json: args.json }) Init args@{ useSolver } -> do -- Fetch the registry here so we can select the right package set later + rootPath <- Path.mkRoot =<< Paths.cwd env <- mkRegistryEnv offline <#> Record.union { rootPath } setVersion <- parseSetVersion args.setVersion void $ runSpago env $ Init.run { mode: args.mode, setVersion, useSolver } @@ -599,7 +599,8 @@ main = do void $ runSpago publishEnv (Publish.publish {}) Repl args@{ selectedPackage } -> do - packages <- FS.exists (rootPath "spago.yaml") >>= case _ of + cwd <- Paths.cwd + packages <- FS.exists (cwd "spago.yaml") >>= case _ of true -> do -- if we have a config then we assume it's a workspace, and we can run a repl in the project pure mempty -- TODO newPackages @@ -661,13 +662,14 @@ main = do testEnv <- runSpago env (mkTestEnv args buildEnv) runSpago testEnv Test.run LsPaths args -> do - runSpago { logOptions, rootPath } $ Ls.listPaths args + let fetchArgs = { packages: mempty, selectedPackage: Nothing, pure: false, ensureRanges: false, testDeps: false, isRepl: false, migrateConfig, offline } + { env } <- mkFetchEnv fetchArgs + runSpago env $ Ls.listPaths args LsPackages args@{ pure } -> do let fetchArgs = { packages: mempty, selectedPackage: Nothing, pure, ensureRanges: false, testDeps: false, isRepl: false, migrateConfig, offline } - { env: env@{ workspace }, fetchOpts } <- mkFetchEnv fetchArgs + { env, fetchOpts } <- mkFetchEnv fetchArgs dependencies <- runSpago env (Fetch.run fetchOpts) - let lsEnv = { workspace, dependencies, logOptions, rootPath } - runSpago lsEnv (Ls.listPackageSet args) + runSpago (Record.union env { dependencies }) (Ls.listPackageSet args) LsDeps { selectedPackage, json, transitive, pure } -> do let fetchArgs = { packages: mempty, selectedPackage, pure, ensureRanges: false, testDeps: false, isRepl: false, migrateConfig, offline } { env, fetchOpts } <- mkFetchEnv fetchArgs @@ -690,13 +692,11 @@ main = do GraphModules args -> do { env, fetchOpts } <- mkFetchEnv { packages: mempty, selectedPackage: Nothing, pure: false, ensureRanges: false, testDeps: false, isRepl: false, migrateConfig, offline } dependencies <- runSpago env (Fetch.run fetchOpts) - purs <- Purs.getPurs - runSpago { dependencies, logOptions, rootPath, purs, workspace: env.workspace } (Graph.graphModules args) + runSpago (Record.union env { dependencies }) (Graph.graphModules args) GraphPackages args -> do { env, fetchOpts } <- mkFetchEnv { packages: mempty, selectedPackage: Nothing, pure: false, ensureRanges: false, testDeps: false, isRepl: false, migrateConfig, offline } dependencies <- runSpago env (Fetch.run fetchOpts) - purs <- Purs.getPurs - runSpago { dependencies, logOptions, rootPath, purs, workspace: env.workspace } (Graph.graphPackages args) + runSpago (Record.union env { dependencies }) (Graph.graphPackages args) Cmd'VersionCmd v -> when v do output (OutputLines [ BuildInfo.packages."spago-bin" ]) @@ -951,7 +951,14 @@ mkReplEnv replArgs dependencies supportPackage = do , selected } -mkFetchEnv :: forall a b. { offline :: OnlineStatus, migrateConfig :: Boolean, isRepl :: Boolean | FetchArgsRow b } -> Spago (SpagoBaseEnv a) { env :: Fetch.FetchEnv (), fetchOpts :: Fetch.FetchOpts } +mkFetchEnv + :: ∀ a b + . { offline :: OnlineStatus + , migrateConfig :: Boolean + , isRepl :: Boolean + | FetchArgsRow b + } + -> Spago { logOptions :: LogOptions | a } { env :: Fetch.FetchEnv (), fetchOpts :: Fetch.FetchOpts } mkFetchEnv args@{ migrateConfig, offline } = do let parsePackageName p = @@ -966,24 +973,26 @@ mkFetchEnv args@{ migrateConfig, offline } = do Left _err -> die $ "Failed to parse selected package name, was: " <> show args.selectedPackage env <- mkRegistryEnv offline - { rootPath } <- ask - workspace <- - runSpago (Record.union env { rootPath }) - (Config.readWorkspace { maybeSelectedPackage, pureBuild: args.pure, migrateConfig }) + cwd <- Paths.cwd + { workspace, rootPath } <- + runSpago env + (Config.discoverWorkspace { maybeSelectedPackage, pureBuild: args.pure, migrateConfig } cwd) + + FS.mkdirp $ rootPath Paths.localCachePath + FS.mkdirp $ rootPath Paths.localCachePackagesPath + logDebug $ "Workspace root path: " <> Path.quote rootPath + logDebug $ "Local cache: " <> Paths.localCachePath + let fetchOpts = { packages: packageNames, ensureRanges: args.ensureRanges, isTest: args.testDeps, isRepl: args.isRepl } pure { fetchOpts, env: Record.union { workspace, rootPath } env } mkRegistryEnv :: forall a. OnlineStatus -> Spago (SpagoBaseEnv a) (Registry.RegistryEnv ()) mkRegistryEnv offline = do - { logOptions, rootPath } <- ask + { logOptions } <- ask -- Take care of the caches FS.mkdirp Paths.globalCachePath - FS.mkdirp $ rootPath Paths.localCachePath - FS.mkdirp $ rootPath Paths.localCachePackagesPath - logDebug $ "Workspace root path: " <> Path.quote rootPath logDebug $ "Global cache: " <> Path.quote Paths.globalCachePath - logDebug $ "Local cache: " <> Paths.localCachePath -- Make sure we have git and purs git <- Git.getGit @@ -1004,7 +1013,7 @@ mkRegistryEnv offline = do , db } -mkLsEnv :: forall a. Fetch.PackageTransitiveDeps -> Spago (Fetch.FetchEnv a) Ls.LsEnv +mkLsEnv :: ∀ a. Fetch.PackageTransitiveDeps -> Spago (Fetch.FetchEnv a) (Ls.LsEnv ()) mkLsEnv dependencies = do { logOptions, workspace, rootPath } <- ask selected <- case workspace.selected of diff --git a/core/src/Log.purs b/core/src/Log.purs index ea7eb4694..046fa6b26 100644 --- a/core/src/Log.purs +++ b/core/src/Log.purs @@ -22,7 +22,6 @@ module Spago.Log , rightOrDie , rightOrDie_ , rightOrDieWith - , rightOrDieWith' , toDoc ) where @@ -183,25 +182,18 @@ justOrDieWith' value msg = case value of die' msg rightOrDie :: ∀ b m err x. MonadEffect m => MonadAsk (LogEnv b) m => Loggable err => Either err x -> m x -rightOrDie value = rightOrDieWith value identity +rightOrDie = rightOrDieWith identity rightOrDie_ :: ∀ b m err x. MonadEffect m => MonadAsk (LogEnv b) m => Loggable err => Either err x -> m Unit rightOrDie_ = void <<< rightOrDie -rightOrDieWith :: ∀ a b m err x. MonadEffect m => MonadAsk (LogEnv b) m => Loggable a => Either err x -> (err -> a) -> m x -rightOrDieWith value toMsg = case value of +rightOrDieWith :: ∀ a b m err x. MonadEffect m => MonadAsk (LogEnv b) m => Loggable a => (err -> a) -> Either err x -> m x +rightOrDieWith toMsg value = case value of Right a -> pure a Left err -> die $ toMsg err -rightOrDieWith' :: ∀ a b m err x. MonadEffect m => MonadAsk (LogEnv b) m => Loggable a => Either err x -> (err -> Array a) -> m x -rightOrDieWith' value toMsg = case value of - Right a -> - pure a - Left err -> - die' $ toMsg err - data OutputFormat a = OutputJson (CJ.Codec a) a | OutputYaml (CJ.Codec a) a diff --git a/core/src/Prelude.purs b/core/src/Prelude.purs index 585724c71..f6ca91459 100644 --- a/core/src/Prelude.purs +++ b/core/src/Prelude.purs @@ -21,6 +21,7 @@ import Data.DateTime.Instant (Instant) as Extra import Data.Either (Either(..), isLeft, isRight, either, hush) as Extra import Data.Filterable (partition, partitionMap) as Extra import Data.Foldable (foldMap, for_, foldl, and, or) as Extra +import Data.FoldableWithIndex (forWithIndex_) as Extra import Data.Function (on) as Extra import Data.Generic.Rep (class Generic) as Extra import Data.Identity (Identity(..)) as Extra @@ -47,7 +48,7 @@ import Partial.Unsafe (unsafeCrashWith) import Registry.ManifestIndex (ManifestIndex) as Extra import Registry.Types (PackageName, Version, Range, Location, License, Manifest(..), Metadata(..), Sha256) as Extra import Spago.Json (printJson, parseJson) as Extra -import Spago.Log (logDebug, logError, logInfo, Docc, logSuccess, logWarn, die, die', justOrDieWith, justOrDieWith', rightOrDie, rightOrDie_, rightOrDieWith, rightOrDieWith', toDoc, indent, indent2, output, LogEnv, LogOptions, OutputFormat(..)) as Extra +import Spago.Log (logDebug, logError, logInfo, Docc, logSuccess, logWarn, die, die', justOrDieWith, justOrDieWith', rightOrDie, rightOrDie_, rightOrDieWith, toDoc, indent, indent2, output, LogEnv, LogOptions, OutputFormat(..)) as Extra import Spago.Path (RawFilePath, GlobalPath, LocalPath, RootPath, class AppendPath, appendPath, ()) as Extra import Spago.Yaml (YamlDoc, printYaml, parseYaml) as Extra diff --git a/src/Spago/Command/Ls.purs b/src/Spago/Command/Ls.purs index 8f0b15056..3a01144ff 100644 --- a/src/Spago/Command/Ls.purs +++ b/src/Spago/Command/Ls.purs @@ -50,22 +50,24 @@ type LsPathsArgs = { json :: Boolean } -type LsSetEnv = +type LsSetEnv r = { dependencies :: Fetch.PackageTransitiveDeps , logOptions :: LogOptions , workspace :: Workspace , rootPath :: RootPath + | r } -type LsEnv = +type LsEnv r = { dependencies :: Fetch.PackageTransitiveDeps , logOptions :: LogOptions , workspace :: Workspace , selected :: WorkspacePackage , rootPath :: RootPath + | r } -listPaths :: LsPathsArgs -> Spago { logOptions :: LogOptions, rootPath :: RootPath } Unit +listPaths :: ∀ r. LsPathsArgs -> Spago { logOptions :: LogOptions, rootPath :: RootPath | r } Unit listPaths { json } = do logDebug "Running `listPaths`" { rootPath } <- ask @@ -90,7 +92,7 @@ listPaths { json } = do -- TODO: add LICENSE field -listPackageSet :: LsPackagesArgs -> Spago LsSetEnv Unit +listPackageSet :: ∀ r. LsPackagesArgs -> Spago (LsSetEnv r) Unit listPackageSet { json } = do logDebug "Running `listPackageSet`" { workspace, rootPath } <- ask @@ -102,7 +104,7 @@ listPackageSet { json } = do true -> formatPackagesJson rootPath packages false -> formatPackagesTable packages -listPackages :: LsDepsOpts -> Spago LsEnv Unit +listPackages :: ∀ r. LsDepsOpts -> Spago (LsEnv r) Unit listPackages { transitive, json } = do logDebug "Running `listPackages`" { dependencies, selected, rootPath } <- ask diff --git a/src/Spago/Config.purs b/src/Spago/Config.purs index 5c2885f7b..60b381b2f 100644 --- a/src/Spago/Config.purs +++ b/src/Spago/Config.purs @@ -19,9 +19,8 @@ module Spago.Config , isRootPackage , module Core , readConfig - , readWorkspace + , discoverWorkspace , removePackagesFromConfig - , rootPackageToWorkspacePackage , setPackageSetVersionInConfig , sourceGlob , workspacePackageToLockfilePackage @@ -33,12 +32,14 @@ import Affjax.Node as Http import Affjax.ResponseFormat as Response import Affjax.StatusCode (StatusCode(..)) import Codec.JSON.DecodeError as CJ.DecodeError +import Control.Monad.State as State import Data.Array as Array import Data.Array.NonEmpty as NEA import Data.CodePoint.Unicode as Unicode import Data.Codec.JSON as CJ import Data.Codec.JSON.Record as CJ.Record import Data.Enum as Enum +import Data.Foldable (traverse_) import Data.Graph as Graph import Data.HTTP.Method as Method import Data.Int as Int @@ -174,119 +175,196 @@ type ReadWorkspaceOptions = isRootPackage :: WorkspacePackage -> Boolean isRootPackage p = Path.localPart p.path == "" --- | Reads all the configurations in the tree and builds up the Map of local --- | packages to be integrated in the package set -readWorkspace :: ∀ a. ReadWorkspaceOptions -> Spago (Registry.RegistryEnv (rootPath :: RootPath | a)) Workspace -readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do - { rootPath } <- ask +spagoYaml = "spago.yaml" :: String + +discoverWorkspace :: ∀ a. ReadWorkspaceOptions -> GlobalPath -> Spago (Registry.RegistryEnv a) { workspace :: Workspace, rootPath :: RootPath } +discoverWorkspace options cwd = do logInfo "Reading Spago workspace configuration..." + logDebug $ "Discovering nearest workspace " <> spagoYaml <> " starting at " <> Path.quote cwd + + { workspace, rootPath } /\ { loadedPackages, closestPackage } <- + State.runStateT (walkDirectoriesUpFrom cwd) + { loadedPackages: Map.empty, otherWorkspaceRoots: [], misnamedConfigs: [], closestPackage: Nothing } + + migrateConfigsWhereNeeded rootPath loadedPackages + + packagesByName <- + Map.fromFoldable <$> + for (Map.toUnfoldable loadedPackages :: Array _) \(path /\ { package, config }) -> do + hasTests <- FS.exists (path "test") + let + wsp :: WorkspacePackage + wsp = { package, path: path `Path.relativeTo` rootPath, doc: Just config.doc, hasTests } + pure (package.name /\ wsp) + + selected <- + determineSelectedPackage + { explicitlySelected: options.maybeSelectedPackage + , inferredFromCwd: closestPackage + , rootPackage: workspace.rootPackage <#> _.name + , loadedPackages: packagesByName + } - let - doMigrateConfig :: ∀ path. Path.IsPath path => path -> _ -> Spago (Registry.RegistryEnv _) Unit - doMigrateConfig path config = do - case migrateConfig, config.wasMigrated of - true, true -> do - logInfo $ "Migrating your " <> Path.quote path <> " to the latest version..." - liftAff $ FS.writeYamlDocFile path config.doc - false, true -> logWarn $ "Your " <> Path.quote path <> " is using an outdated format. Run Spago with the --migrate flag to update it to the latest version." - _, false -> pure unit - - rootConfigPath = rootPath "spago.yaml" - - -- First try to read the config in the root. It _has_ to contain a workspace - -- configuration, or we fail early. - { workspace, package: maybePackage, workspaceDoc } <- readConfig rootConfigPath >>= case _ of - Left errLines -> - die - [ toDoc "Couldn't parse Spago config, error:" - , Log.break - , indent $ toDoc errLines - , Log.break - , toDoc "The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file" - ] - Right { yaml: { workspace: Nothing } } -> die - [ "Your spago.yaml doesn't contain a workspace section." - , "See the relevant documentation here: https://github.com/purescript/spago#the-workspace" - ] - Right config@{ yaml: { workspace: Just workspace, package }, doc } -> do - logDebug "Read the root config" - doMigrateConfig (rootPath "spago.yaml") config - pure { workspace, package, workspaceDoc: doc } - - logDebug "Gathering all the spago configs in the tree..." - otherConfigPaths <- liftAff $ Array.delete rootConfigPath <$> Glob.gitignoringGlob - { root: rootPath - , includePatterns: [ "**/spago.yaml" ] - , ignorePatterns: [ "**/node_modules/**", "**/.spago/**" ] + lockfile <- + loadLockfile { pureBuild: options.pureBuild, workspaceConfig: workspace.config, loadedPackages: packagesByName, rootPath } + + { packageSet, compiler } <- + loadPackageSet { workspaceConfig: workspace.config, loadedPackages: packagesByName, rootPath, lockfile } + + pure + { rootPath + , workspace: + { selected + , packageSet + , compatibleCompiler: compiler + , backend: workspace.config.backend + , buildOptions: + { output: workspace.config.buildOpts >>= _.output <#> \o -> withForwardSlashes $ rootPath o + , censorLibWarnings: _.censorLibraryWarnings =<< workspace.config.buildOpts + , statVerbosity: _.statVerbosity =<< workspace.config.buildOpts + } + , doc: Just workspace.doc + , workspaceConfig: workspace.config + , rootPackage: workspace.rootPackage + } } + where + readConfig' = State.lift <<< readConfig - unless (Array.null otherConfigPaths) do - logDebug $ [ toDoc "Found packages at these paths:", Log.indent $ Log.lines (map (toDoc <<< Path.quote) otherConfigPaths) ] + walkDirectoriesUpFrom dir = do + maybeConfig <- tryReadConfigAt configFile - -- We read all of them in, and only read the package section, if any. - let - readWorkspaceConfig :: LocalPath -> Spago (Registry.RegistryEnv _) (Either Docc ReadWorkspaceConfigResult) - readWorkspaceConfig path = do - maybeConfig <- readConfig path - -- We try to figure out if this package has tests - look for test sources - hasTests <- FS.exists (Path.dirname path "test") - pure $ case maybeConfig of - Left eLines -> Left $ toDoc - [ toDoc $ "Could not read config at path " <> Path.quote path - , toDoc "Error was: " - , indent $ toDoc eLines - ] - Right config -> Right - { config - , hasTests - , configPath: path - , packagePath: Path.dirname path `Path.relativeTo` rootPath + for_ maybeConfig \config -> + for_ config.yaml.package \package -> + -- If there is a package in this directory, remember it + State.modify_ \s -> s + { loadedPackages = Map.insert dir { package, config } s.loadedPackages + , closestPackage = s.closestPackage <|> Just package.name } - { right: otherPackages, left: failedPackages } <- partitionMap identity <$> traverse readWorkspaceConfig otherConfigPaths - unless (Array.null failedPackages) do - logWarn $ [ toDoc "Failed to read some configs:" ] <> failedPackages + whenM (FS.exists $ dir "spago.yml") $ + State.modify_ \s -> s { misnamedConfigs = Array.cons dir s.misnamedConfigs } + + case maybeConfig of + Just { doc, yaml: { workspace: Just workspace, package } } -> do + -- Finally, found the "workspace" config! + rootPath <- Path.mkRoot dir + loadSubprojectConfigs rootPath + pure { workspace: { config: workspace, doc, rootPackage: package }, rootPath } + _ -> do + -- No workspace in this directory => recur to parent directory (unless it's already root) + when (parentDir == dir) $ + dieForLackOfSpagoYaml + walkDirectoriesUpFrom parentDir + + where + configFile = dir spagoYaml + parentDir = Path.dirname dir + + loadSubprojectConfigs rootPath = do + candidates <- liftAff $ Glob.gitignoringGlob + { root: rootPath + , includePatterns: [ "**/" <> spagoYaml ] + , ignorePatterns: [ "**/node_modules/**", "**/.spago/**" ] + } - -- We prune any configs that use a different workspace. - -- For reasoning, see https://github.com/purescript/spago/issues/951 - let configPathsWithWorkspaces = otherPackages # Array.mapMaybe \readResult -> readResult.packagePath <$ readResult.config.yaml.workspace - unless (Array.null configPathsWithWorkspaces) do - logDebug $ "Found these paths with workspaces: " <> String.joinWith ", " (Path.quote <$> configPathsWithWorkspaces) + -- Traversing directories (not files) and doing it in sorted order ensures + -- that parent directories come before their subdirectories. That way we + -- can remember workspaces that we find along the way and avoid trying to + -- load their subprojects that come later. + candidates <#> Path.toGlobal <#> Path.dirname # Array.sort # traverse_ \dir -> do + st <- State.get + let + configFile = dir spagoYaml + alreadyLoaded = st.loadedPackages # Map.member configFile + anotherParentWorkspace = st.otherWorkspaceRoots # Array.find (_ `Path.isPrefixOf` dir) + case alreadyLoaded, anotherParentWorkspace of + true, _ -> + pure unit + _, Just ws -> do + logDebug $ "Not trying to load " <> Path.quote configFile <> " because it belongs to a different workspace at " <> Path.quote ws + pure unit + false, Nothing -> + readConfig' configFile >>= case _ of + Left _ -> + logWarn $ "Failed to read config at " <> Path.quote configFile + Right { yaml: { workspace: Just _ } } -> + State.modify_ \s -> s { otherWorkspaceRoots = Array.cons dir s.otherWorkspaceRoots } + Right config@{ yaml: { package: Just package } } -> do + logDebug $ "Loaded a subproject config at " <> Path.quote configFile + State.modify_ \s -> s { loadedPackages = Map.insert dir { package, config } s.loadedPackages } + Right _ -> do + logWarn $ "Neither workspace nor package found in " <> Path.quote configFile + + tryReadConfigAt path = do + exists <- FS.exists path + if exists then + Just <$> do + logDebug $ "Loading spago.yaml at " <> Path.quote path + readConfig' path >>= rightOrDieWith \errLines -> + [ toDoc $ "Couldn't parse Spago config file at: " <> Path.quote path + , indent $ toDoc errLines + , Log.break + , toDoc "The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file" + ] + else + pure Nothing - { right: configsNoWorkspaces, left: prunedConfigs } <- + migrateConfigsWhereNeeded rootPath loadedConfigs = do + forWithIndex_ loadedConfigs \path' { config } -> do + let path = (path' spagoYaml) `Path.relativeTo` rootPath + case options.migrateConfig, config.wasMigrated of + true, true -> do + logInfo $ "Migrating your " <> Path.quote path <> " to the latest version..." + liftAff $ FS.writeYamlDocFile path config.doc + false, true -> + logWarn $ "Your " <> Path.quote path <> " is using an outdated format. Run Spago with the --migrate flag to update it to the latest version." + _, false -> + pure unit + + dieForLackOfSpagoYaml = do + root <- Path.mkRoot cwd + misnamedConfigs <- State.gets _.misnamedConfigs let - fn { left, right } readResult@{ configPath, packagePath, hasTests, config } = do - if Array.any (_ `Path.isPrefixOf` packagePath) configPathsWithWorkspaces then - pure { right, left: Array.cons packagePath left } + misnamedConfigsList = + case misnamedConfigs <#> \c -> Path.quote $ (c "spago.yml") `Path.relativeTo` root of + [] -> [] + [ one ] -> [ toDoc $ "Instead found " <> one ] + many -> [ toDoc "Instead found these:", indent $ toDoc many ] + die + [ toDoc $ "No " <> spagoYaml <> " found in the current directory or any of its parents." + , if Array.null misnamedConfigsList then + toDoc "" else - case readResult.config.yaml.package of - Nothing -> - pure { right, left: Array.cons packagePath left } - Just package -> do - -- Note: we migrate configs only at this point - this is because we read a whole lot of them but we are - -- supposed to ignore any subtrees that contain a different workspace, and those we don't want to migrate - doMigrateConfig configPath config - -- We store the path of the package, so we can treat it basically as a LocalPackage - pure { left, right: Array.cons (Tuple package.name { package, hasTests, path: packagePath, doc: Just config.doc }) right } - in - Array.foldM fn { right: [], left: [] } otherPackages - - unless (Array.null prunedConfigs) do - logDebug - $ [ "Excluding configs that use a different workspace (directly or implicitly via parent directory's config):" ] - <> Array.sort (Path.quote <$> prunedConfigs) - - rootPackage <- case maybePackage of - Nothing -> pure [] - Just rootPackage -> do - rootPackage' <- rootPackageToWorkspacePackage rootPath { rootPackage, workspaceDoc } - pure [ Tuple rootPackage.name rootPackage' ] - - let workspacePackages = Map.fromFoldable $ configsNoWorkspaces <> rootPackage + toDoc + [ Log.break + , indent $ toDoc $ misnamedConfigsList + , indent $ toDoc $ "Note that Spago config files should be named " <> spagoYaml <> ", not spago.yml." + , Log.break + , toDoc "The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file" + ] + ] + +determineSelectedPackage + :: ∀ a + . { explicitlySelected :: Maybe PackageName + , inferredFromCwd :: Maybe PackageName + , rootPackage :: Maybe PackageName + , loadedPackages :: Map PackageName WorkspacePackage + } + -> Spago (Registry.RegistryEnv a) (Maybe WorkspacePackage) +determineSelectedPackage { explicitlySelected, inferredFromCwd, rootPackage, loadedPackages } = do + let + inferredFromCwd' = + -- Do not auto-select the root package if Spago is being run from the root directory. + if inferredFromCwd == rootPackage then Nothing else inferredFromCwd + + selectedName = + explicitlySelected <|> inferredFromCwd' -- Select the package for spago to handle during the rest of the execution - maybeSelected <- case maybeSelectedPackage of - Nothing -> case Array.uncons (Map.toUnfoldable workspacePackages) of + maybeSelected <- case selectedName of + Nothing -> case Array.uncons (Map.toUnfoldable loadedPackages) of Nothing -> die "No valid packages found in the current project, halting." -- If there's only one package and it's not in the root we still select that Just { head: (Tuple packageName package), tail: [] } -> do @@ -294,10 +372,10 @@ readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do pure (Just package) -- If no package has been selected and we have many packages, then we build all of them but select none _ -> pure Nothing - Just name -> case Map.lookup name workspacePackages of + Just name -> case Map.lookup name loadedPackages of Nothing -> die $ [ toDoc $ "Selected package " <> PackageName.print name <> " was not found in the local packages." ] - <> case (Array.fromFoldable $ Map.keys workspacePackages) of + <> case (Array.fromFoldable $ Map.keys loadedPackages) of [] -> [ toDoc "No available packages." ] pkgs -> @@ -307,9 +385,31 @@ readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do Just p -> pure (Just p) + -- Figure out if we are selecting a single package or not + case maybeSelected of + Just selected -> do + logSuccess $ "Selecting package to build: " <> PackageName.print selected.package.name + logDebug $ "Package path: " <> Path.quote selected.path + Nothing -> do + logSuccess + [ toDoc $ "Selecting " <> show (Map.size loadedPackages) <> " packages to build:" + , indent2 (toDoc (Set.toUnfoldable $ Map.keys loadedPackages :: Array PackageName)) + ] + + pure maybeSelected + +loadLockfile + :: ∀ a + . { pureBuild :: Boolean + , workspaceConfig :: Core.WorkspaceConfig + , loadedPackages :: Map PackageName WorkspacePackage + , rootPath :: RootPath + } + -> Spago (Registry.RegistryEnv a) (Either String Lockfile) +loadLockfile { pureBuild, workspaceConfig, loadedPackages, rootPath } = do logDebug "Parsing the lockfile..." let lockFilePath = rootPath "spago.lock" - maybeLockfileContents <- FS.exists lockFilePath >>= case _ of + FS.exists lockFilePath >>= case _ of false -> pure (Left "No lockfile found") true -> liftAff (FS.readJsonFile Lock.lockfileCodec lockFilePath) >>= case _ of Left error -> do @@ -323,7 +423,7 @@ readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do -- Unless! the user is passing the --pure flag, in which case we just use the lockfile Right contents -> do logDebug "Parsed the lockfile" - case pureBuild, shouldComputeNewLockfile { workspace, workspacePackages } contents.workspace of + case pureBuild, shouldComputeNewLockfile { workspace: workspaceConfig, workspacePackages: loadedPackages } contents.workspace of true, _ -> do logDebug "Using lockfile because of --pure flag" pure (Right contents) @@ -334,18 +434,26 @@ readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do logDebug "Lockfile is up to date, using it" pure (Right contents) - -- Read in the package database +loadPackageSet + :: ∀ a + . { workspaceConfig :: Core.WorkspaceConfig + , loadedPackages :: Map PackageName WorkspacePackage + , rootPath :: RootPath + , lockfile :: Either String Lockfile + } + -> Spago (Registry.RegistryEnv a) { packageSet :: PackageSet, compiler :: Range } +loadPackageSet { lockfile, workspaceConfig, loadedPackages, rootPath } = do { offline } <- ask - packageSetInfo <- case maybeLockfileContents, workspace.packageSet of + packageSetInfo <- case lockfile, workspaceConfig.packageSet of _, Nothing -> do logDebug "Did not find a package set in your config, using Registry solver" pure Nothing -- If there's a lockfile we don't attempt to fetch the package set from the registry -- repo nor from the internet, since we already have the whole set right there - Right lockfile, _ -> do + Right lf, _ -> do logDebug "Found the lockfile, using the package set from there" - pure lockfile.workspace.package_set + pure lf.workspace.package_set Left reason, Just address@(Core.SetFromRegistry { registry: v }) -> do logDebug reason @@ -416,16 +524,12 @@ readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do -- This is to (1) easily allow overriding packages, (2) easily allow "private registries" -- and (3) prevent the security hole where people can register new names and take precedence in your build. let - extraPackages = map fromExtraPackage (fromMaybe Map.empty workspace.extraPackages) - localPackagesOverlap = Set.intersection (Map.keys workspacePackages) (Map.keys extraPackages) - buildType = - let - localPackages = Map.union (map WorkspacePackage workspacePackages) extraPackages - in - case packageSetInfo of - Nothing -> RegistrySolverBuild localPackages - Just info -> PackageSetBuild info $ Map.union localPackages (map fromRemotePackage info.content) - packageSet = { buildType, lockfile: maybeLockfileContents } + extraPackages = map fromExtraPackage (fromMaybe Map.empty workspaceConfig.extraPackages) + localPackagesOverlap = Set.intersection (Map.keys loadedPackages) (Map.keys extraPackages) + localPackages = Map.union (map WorkspacePackage loadedPackages) extraPackages + buildType = case packageSetInfo of + Nothing -> RegistrySolverBuild localPackages + Just info -> PackageSetBuild info $ Map.union localPackages (map fromRemotePackage info.content) -- Note again: we only try to prevent collisions between workspace packages and local overrides. -- We otherwise want local packages to override _remote_ ones, e.g. in the case where you are @@ -438,46 +542,11 @@ readWorkspace { maybeSelectedPackage, pureBuild, migrateConfig } = do ] <> map (\p -> indent $ toDoc $ "- " <> PackageName.print p) (Array.fromFoldable localPackagesOverlap) - -- Figure out if we are selecting a single package or not - case maybeSelected of - Just selected -> do - logSuccess $ "Selecting package to build: " <> PackageName.print selected.package.name - logDebug $ "Package path: " <> Path.quote selected.path - Nothing -> do - logSuccess - [ toDoc $ "Selecting " <> show (Map.size workspacePackages) <> " packages to build:" - , indent2 (toDoc (Set.toUnfoldable $ Map.keys workspacePackages :: Array PackageName)) - ] - - let - buildOptions :: WorkspaceBuildOptions - buildOptions = - { output: workspace.buildOpts >>= _.output <#> \o -> withForwardSlashes $ rootPath o - , censorLibWarnings: _.censorLibraryWarnings =<< workspace.buildOpts - , statVerbosity: _.statVerbosity =<< workspace.buildOpts - } - pure - { selected: maybeSelected - , packageSet - , compatibleCompiler: fromMaybe Core.widestRange $ map _.compiler packageSetInfo - , backend: workspace.backend - , buildOptions - , doc: Just workspaceDoc - , workspaceConfig: workspace - , rootPackage: maybePackage + { packageSet: { buildType, lockfile } + , compiler: packageSetInfo <#> _.compiler # fromMaybe Core.widestRange } -rootPackageToWorkspacePackage - :: forall m - . MonadEffect m - => RootPath - -> { rootPackage :: Core.PackageConfig, workspaceDoc :: YamlDoc Core.Config } - -> m WorkspacePackage -rootPackageToWorkspacePackage rootPath { rootPackage, workspaceDoc } = do - hasTests <- liftEffect $ FS.exists (rootPath "test") - pure { path: rootPath "", doc: Just workspaceDoc, package: rootPackage, hasTests } - workspacePackageToLockfilePackage :: WorkspacePackage -> Tuple PackageName Lock.WorkspaceLockPackage workspacePackageToLockfilePackage { path, package } = Tuple package.name { path: case Path.localPart (withForwardSlashes path) of @@ -622,19 +691,15 @@ readConfig path = do Just yml else Nothing - pure $ Left $ case Path.basename path, yml of - "spago.yaml", Nothing -> - [ "Did not find " <> Path.quote path <> ". Run `spago init` to initialize a new project." ] - "spago.yaml", Just y -> + pure $ Left $ case yml of + Just y -> [ "Did not find " <> Path.quote path <> ". Spago's configuration files must end with `.yaml`, not `.yml`." - , "Try renaming " <> Path.quote y <> " to " <> Path.quote path <> " or run `spago init` to initialize a new project." + , "Try renaming " <> Path.basename y <> " to " <> Path.basename path <> " or run `spago init` to initialize a new project." ] - _, Nothing -> + Nothing | Path.basename path == spagoYaml -> + [ "Did not find " <> Path.quote path <> ". Run `spago init` to initialize a new project." ] + Nothing -> [ "Did not find " <> Path.quote path <> "." ] - _, Just y -> - [ "Did not find " <> Path.quote path <> ". Spago's configuration files must end with `.yaml`, not `.yml`." - , "Try renaming " <> Path.quote y <> " to " <> Path.quote path <> "." - ] Right yamlString -> do case lmap (\err -> CJ.DecodeError.basic ("YAML: " <> err)) (Yaml.parser yamlString) of Left err -> pure $ Left [ CJ.DecodeError.print err ] @@ -658,7 +723,7 @@ readConfig path = do setPackageSetVersionInConfig :: forall m. MonadAff m => MonadEffect m => RootPath -> YamlDoc Core.Config -> Version -> m Unit setPackageSetVersionInConfig root doc version = do liftEffect $ runEffectFn2 setPackageSetVersionInConfigImpl doc (Version.print version) - liftAff $ FS.writeYamlDocFile (root "spago.yaml") doc + liftAff $ FS.writeYamlDocFile (root spagoYaml) doc addPackagesToConfig :: forall m path. Path.IsPath path => MonadAff m => path -> YamlDoc Core.Config -> Boolean -> Array PackageName -> m Unit addPackagesToConfig configPath doc isTest pkgs = do diff --git a/src/Spago/Prelude.purs b/src/Spago/Prelude.purs index 04df4e7ed..9fa336f7a 100644 --- a/src/Spago/Prelude.purs +++ b/src/Spago/Prelude.purs @@ -51,8 +51,7 @@ data OnlineStatus = Offline | Online | OnlineBypassCache derive instance Eq OnlineStatus type SpagoBaseEnv a = - { rootPath :: Path.RootPath - , logOptions :: LogOptions + { logOptions :: LogOptions | a } diff --git a/test-fixtures/config/discovery/a/spago.yaml b/test-fixtures/config/discovery/a/spago.yaml new file mode 100644 index 000000000..069d839a5 --- /dev/null +++ b/test-fixtures/config/discovery/a/spago.yaml @@ -0,0 +1,4 @@ +package: + name: a + dependencies: + - prelude diff --git a/test-fixtures/config/discovery/b/spago.yaml b/test-fixtures/config/discovery/b/spago.yaml new file mode 100644 index 000000000..d33f67709 --- /dev/null +++ b/test-fixtures/config/discovery/b/spago.yaml @@ -0,0 +1,4 @@ +package: + name: b + dependencies: + - prelude diff --git a/test-fixtures/config/discovery/from-a.txt b/test-fixtures/config/discovery/from-a.txt new file mode 100644 index 000000000..24796559e --- /dev/null +++ b/test-fixtures/config/discovery/from-a.txt @@ -0,0 +1,12 @@ +Reading Spago workspace configuration... + +✓ Selecting package to build: a + +Downloading dependencies... +Building... +purs compile: No files found using pattern: a/src/**/*.purs + Src Lib All +Warnings 0 0 0 +Errors 0 0 0 + +✓ Build succeeded. diff --git a/test-fixtures/config/discovery/from-d.txt b/test-fixtures/config/discovery/from-d.txt new file mode 100644 index 000000000..2a1953635 --- /dev/null +++ b/test-fixtures/config/discovery/from-d.txt @@ -0,0 +1,12 @@ +Reading Spago workspace configuration... + +✓ Selecting package to build: d + +Downloading dependencies... +Building... +purs compile: No files found using pattern: d/src/**/*.purs + Src Lib All +Warnings 0 0 0 +Errors 0 0 0 + +✓ Build succeeded. diff --git a/test-fixtures/config/discovery/from-nested.txt b/test-fixtures/config/discovery/from-nested.txt new file mode 100644 index 000000000..d72721f17 --- /dev/null +++ b/test-fixtures/config/discovery/from-nested.txt @@ -0,0 +1,17 @@ +Reading Spago workspace configuration... + +✓ Selecting 3 packages to build: + c + d + nested-workspace + +Downloading dependencies... +Building... +purs compile: No files found using pattern: c/src/**/*.purs +purs compile: No files found using pattern: d/src/**/*.purs +purs compile: No files found using pattern: src/**/*.purs + Src Lib All +Warnings 0 0 0 +Errors 0 0 0 + +✓ Build succeeded. diff --git a/test-fixtures/config/discovery/from-root.txt b/test-fixtures/config/discovery/from-root.txt new file mode 100644 index 000000000..285b01001 --- /dev/null +++ b/test-fixtures/config/discovery/from-root.txt @@ -0,0 +1,17 @@ +Reading Spago workspace configuration... + +✓ Selecting 3 packages to build: + a + b + foo + +Downloading dependencies... +Building... +purs compile: No files found using pattern: a/src/**/*.purs +purs compile: No files found using pattern: b/src/**/*.purs +purs compile: No files found using pattern: src/**/*.purs + Src Lib All +Warnings 0 0 0 +Errors 0 0 0 + +✓ Build succeeded. diff --git a/test-fixtures/config/discovery/nested-workspace/c/spago.yaml b/test-fixtures/config/discovery/nested-workspace/c/spago.yaml new file mode 100644 index 000000000..a9c44e0f0 --- /dev/null +++ b/test-fixtures/config/discovery/nested-workspace/c/spago.yaml @@ -0,0 +1,4 @@ +package: + name: c + dependencies: + - prelude diff --git a/test-fixtures/config/discovery/nested-workspace/d/spago.yaml b/test-fixtures/config/discovery/nested-workspace/d/spago.yaml new file mode 100644 index 000000000..77ee1ae44 --- /dev/null +++ b/test-fixtures/config/discovery/nested-workspace/d/spago.yaml @@ -0,0 +1,4 @@ +package: + name: d + dependencies: + - prelude diff --git a/test-fixtures/config/discovery/nested-workspace/spago.yaml b/test-fixtures/config/discovery/nested-workspace/spago.yaml new file mode 100644 index 000000000..3277c1e9b --- /dev/null +++ b/test-fixtures/config/discovery/nested-workspace/spago.yaml @@ -0,0 +1,8 @@ +package: + name: nested-workspace + dependencies: + - prelude + +workspace: + packageSet: + registry: 41.5.0 diff --git a/test-fixtures/config/discovery/spago.yaml b/test-fixtures/config/discovery/spago.yaml new file mode 100644 index 000000000..164648573 --- /dev/null +++ b/test-fixtures/config/discovery/spago.yaml @@ -0,0 +1,10 @@ +package: + name: foo + dependencies: + - console + - effect + - prelude + +workspace: + packageSet: + registry: 41.5.0 diff --git a/test-fixtures/config/misnamed-configs/a/b/c/spago.yml b/test-fixtures/config/misnamed-configs/a/b/c/spago.yml new file mode 100644 index 000000000..e69de29bb diff --git a/test-fixtures/config/misnamed-configs/a/b/d/.keep b/test-fixtures/config/misnamed-configs/a/b/d/.keep new file mode 100644 index 000000000..e69de29bb diff --git a/test-fixtures/config/misnamed-configs/a/b/spago.yml b/test-fixtures/config/misnamed-configs/a/b/spago.yml new file mode 100644 index 000000000..e69de29bb diff --git a/test-fixtures/config/misnamed-configs/from-a.txt b/test-fixtures/config/misnamed-configs/from-a.txt new file mode 100644 index 000000000..ac2cb95de --- /dev/null +++ b/test-fixtures/config/misnamed-configs/from-a.txt @@ -0,0 +1,10 @@ +Reading Spago workspace configuration... + +✘ No spago.yaml found in the current directory or any of its parents. + + + Instead found "../spago.yml" + Note that Spago config files should be named spago.yaml, not spago.yml. + + +The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file diff --git a/test-fixtures/config/misnamed-configs/from-b.txt b/test-fixtures/config/misnamed-configs/from-b.txt new file mode 100644 index 000000000..136d1f2b2 --- /dev/null +++ b/test-fixtures/config/misnamed-configs/from-b.txt @@ -0,0 +1,12 @@ +Reading Spago workspace configuration... + +✘ No spago.yaml found in the current directory or any of its parents. + + + Instead found these: + "../../spago.yml" + "spago.yml" + Note that Spago config files should be named spago.yaml, not spago.yml. + + +The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file diff --git a/test-fixtures/config/misnamed-configs/from-c.txt b/test-fixtures/config/misnamed-configs/from-c.txt new file mode 100644 index 000000000..eab873467 --- /dev/null +++ b/test-fixtures/config/misnamed-configs/from-c.txt @@ -0,0 +1,13 @@ +Reading Spago workspace configuration... + +✘ No spago.yaml found in the current directory or any of its parents. + + + Instead found these: + "../../../spago.yml" + "../spago.yml" + "spago.yml" + Note that Spago config files should be named spago.yaml, not spago.yml. + + +The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file diff --git a/test-fixtures/config/misnamed-configs/from-d.txt b/test-fixtures/config/misnamed-configs/from-d.txt new file mode 100644 index 000000000..61e6ff5aa --- /dev/null +++ b/test-fixtures/config/misnamed-configs/from-d.txt @@ -0,0 +1,12 @@ +Reading Spago workspace configuration... + +✘ No spago.yaml found in the current directory or any of its parents. + + + Instead found these: + "../../../spago.yml" + "../spago.yml" + Note that Spago config files should be named spago.yaml, not spago.yml. + + +The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file diff --git a/test-fixtures/config/misnamed-configs/from-root.txt b/test-fixtures/config/misnamed-configs/from-root.txt new file mode 100644 index 000000000..349bf5548 --- /dev/null +++ b/test-fixtures/config/misnamed-configs/from-root.txt @@ -0,0 +1,10 @@ +Reading Spago workspace configuration... + +✘ No spago.yaml found in the current directory or any of its parents. + + + Instead found "spago.yml" + Note that Spago config files should be named spago.yaml, not spago.yml. + + +The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file diff --git a/test-fixtures/config/misnamed-configs/spago.yml b/test-fixtures/config/misnamed-configs/spago.yml new file mode 100644 index 000000000..e69de29bb diff --git a/test-fixtures/config/no-workspace-anywhere.txt b/test-fixtures/config/no-workspace-anywhere.txt new file mode 100644 index 000000000..5fd21e84a --- /dev/null +++ b/test-fixtures/config/no-workspace-anywhere.txt @@ -0,0 +1,3 @@ +Reading Spago workspace configuration... + +✘ No spago.yaml found in the current directory or any of its parents. diff --git a/test-fixtures/spago-yml-check-stderr.txt b/test-fixtures/spago-yml-check-stderr.txt index ccd6509e4..349bf5548 100644 --- a/test-fixtures/spago-yml-check-stderr.txt +++ b/test-fixtures/spago-yml-check-stderr.txt @@ -1,10 +1,10 @@ Reading Spago workspace configuration... -✘ Couldn't parse Spago config, error: +✘ No spago.yaml found in the current directory or any of its parents. - Did not find "spago.yaml". Spago's configuration files must end with `.yaml`, not `.yml`. - Try renaming "spago.yml" to "spago.yaml" or run `spago init` to initialize a new project. + Instead found "spago.yml" + Note that Spago config files should be named spago.yaml, not spago.yml. The configuration file help can be found here https://github.com/purescript/spago#the-configuration-file diff --git a/test/Spago/Config.purs b/test/Spago/Config.purs index 89a0f138f..62cd1240b 100644 --- a/test/Spago/Config.purs +++ b/test/Spago/Config.purs @@ -3,12 +3,15 @@ module Test.Spago.Config where import Test.Prelude import Codec.JSON.DecodeError as CJ +import Data.String as String import Registry.License as License import Registry.Location (Location(..)) import Registry.PackageName as PackageName import Registry.Version as Version import Spago.Core.Config (SetAddress(..)) import Spago.Core.Config as C +import Spago.FS as FS +import Spago.Paths as Paths import Spago.Yaml as Yaml import Test.Spec (Spec) import Test.Spec as Spec @@ -64,11 +67,75 @@ spec = <> "\n - Could not decode GitHub:" <> "\n Unknown field(s): bogus_field" ) - where - shouldFailWith result expectedError = - case result of - Right _ -> Assert.fail "Expected an error, but parsed successfully" - Left err -> CJ.print err `shouldEqual` expectedError + + Spec.around withTempDir $ + Spec.describe "spago.yaml discovery" do + Spec.it "discovers config up the directory tree" \{ testCwd, fixture, spago } -> do + FS.copyTree { src: fixture "config/discovery", dst: testCwd } + spago [ "build" ] >>= shouldBeSuccess + spago [ "build" ] >>= shouldBeSuccessErr' (fixture "config/discovery/from-root.txt") + + -- Running from `./a`, Spago should discover the workspace root at + -- './' and select package 'a' + Paths.chdir $ testCwd "a" + spago [ "build" ] >>= shouldBeSuccessErr' (fixture "config/discovery/from-a.txt") + + -- Running from `./nested-workspace`, Spago should use the workspace + -- root at './nested-workspace' and not the one at './' + Paths.chdir $ testCwd "nested-workspace" + spago [ "build" ] >>= shouldBeSuccess + spago [ "build" ] >>= shouldBeSuccessErr' (fixture "config/discovery/from-nested.txt") + + -- Running from `./nested-workspace/d`, Spago should use the workspace + -- root at './nested-workspace', because that's the closest one, and + -- select package 'd' + Paths.chdir $ testCwd "nested-workspace" "d" + spago [ "build" ] >>= shouldBeSuccessErr' (fixture "config/discovery/from-d.txt") + + -- At workspace roots, a ".spago" directory should be created for + -- local cache, but not in subdirs + FS.exists (testCwd ".spago") `Assert.shouldReturn` true + FS.exists (testCwd "a" ".spago") `Assert.shouldReturn` false + FS.exists (testCwd "nested-workspace" ".spago") `Assert.shouldReturn` true + FS.exists (testCwd "nested-workspace" "d" ".spago") `Assert.shouldReturn` false + + Spec.it "reports no config in any parent directories" \{ spago, fixture } -> + spago [ "build" ] >>= shouldBeFailureErr' (fixture "config/no-workspace-anywhere.txt") + + Spec.it "reports possible misnamed configs up the directory tree" \{ testCwd, spago, fixture } -> do + FS.copyTree { src: fixture "config/misnamed-configs", dst: testCwd } + spago [ "build" ] >>= shouldBeFailureErr' (fixture "config/misnamed-configs/from-root.txt") + + Paths.chdir $ testCwd "a" + spago [ "build" ] >>= shouldBeFailureErr' (fixture "config/misnamed-configs/from-a.txt") + + Paths.chdir $ testCwd "a" "b" + spago [ "build" ] >>= shouldBeFailureErr' (fixture "config/misnamed-configs/from-b.txt") + + Paths.chdir $ testCwd "a" "b" "c" + spago [ "build" ] >>= shouldBeFailureErr' (fixture "config/misnamed-configs/from-c.txt") + + Paths.chdir $ testCwd "a" "b" "d" + spago [ "build" ] >>= shouldBeFailureErr' (fixture "config/misnamed-configs/from-d.txt") + + where + shouldFailWith result expectedError = + case result of + Right _ -> Assert.fail "Expected an error, but parsed successfully" + Left err -> CJ.print err `shouldEqual` expectedError + + shouldBeSuccessErr' = shouldBeErr isRight + shouldBeFailureErr' = shouldBeErr isLeft + + shouldBeErr result file = checkOutputs' + { stdoutFile: Nothing + , stderrFile: Just file + , result + , sanitize: + String.trim + >>> String.replaceAll (String.Pattern "\\") (String.Replacement "/") + >>> String.replaceAll (String.Pattern "\r\n") (String.Replacement "\n") + } validSpagoYaml :: { serialized :: String, parsed :: C.Config } validSpagoYaml =