Skip to content

Commit

Permalink
Fix output truncation with json-errors and build failure. Fix purescr…
Browse files Browse the repository at this point in the history
…ipt#1160 (purescript#1199)

Problematic situation is when --json-errors is passed (output is one very long line printed out all at once),
there are many warnings (json > 65536 bytes) and there is an error (spago should exit with an error code).
Set the error code and allow control flow to naturally exit to allow output to be flushed.
  • Loading branch information
nwolverson authored Mar 12, 2024
1 parent ebb99a0 commit 10657ca
Show file tree
Hide file tree
Showing 13 changed files with 206 additions and 55 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ and this project adheres to [Semantic Versioning](https://semver.org/spec/v2.0.0
Other improvements:
- builds with Cabal successfully
- update to latest `versions` dependency: https://hackage.haskell.org/package/versions-6.0.1/changelog
- Fix output truncation with `--json-errors`, many warnings and build failure (#1199)

## [0.21.0] - 2023-05-04

Expand Down
25 changes: 14 additions & 11 deletions bin/src/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -570,7 +570,7 @@ main = do
}
env' <- runSpago env (mkBuildEnv buildArgs dependencies)
let options = { depsOnly: true, pursArgs: List.toUnfoldable args.pursArgs, jsonErrors: false }
runSpago env' (Build.run options)
void $ runSpago env' (Build.run options)
Uninstall { packagesToRemove, selectedPackage, testDeps } -> do
{ env, fetchOpts } <- mkFetchEnv offline { packages: packagesToRemove, selectedPackage, ensureRanges: false, testDeps: false, isRepl: false, pure: false }
let options = { testDeps, dependenciesToRemove: Set.fromFoldable fetchOpts.packages }
Expand All @@ -580,7 +580,7 @@ main = do
dependencies <- runSpago env (Fetch.run fetchOpts)
buildEnv <- runSpago env (mkBuildEnv args dependencies)
let options = { depsOnly: false, pursArgs: List.toUnfoldable args.pursArgs, jsonErrors }
runSpago buildEnv (Build.run options)
void $ runSpago buildEnv (Build.run options)
Publish { selectedPackage } -> do
{ env, fetchOpts } <- mkFetchEnv offline { packages: mempty, selectedPackage, ensureRanges: false, testDeps: false, isRepl: false, pure: false }
dependencies <- runSpago env (Fetch.run fetchOpts)
Expand Down Expand Up @@ -625,25 +625,28 @@ main = do
dependencies <- runSpago env (Fetch.run fetchOpts)
buildEnv <- runSpago env (mkBuildEnv args dependencies)
let options = { depsOnly: false, pursArgs: List.toUnfoldable args.pursArgs, jsonErrors: false }
runSpago buildEnv (Build.run options)
bundleEnv <- runSpago env (mkBundleEnv args)
runSpago bundleEnv Bundle.run
built <- runSpago buildEnv (Build.run options)
when built do
bundleEnv <- runSpago env (mkBundleEnv args)
runSpago bundleEnv Bundle.run
Run args@{ selectedPackage, ensureRanges, pure } -> do
{ env, fetchOpts } <- mkFetchEnv offline { packages: mempty, selectedPackage, ensureRanges, pure, testDeps: false, isRepl: false }
dependencies <- runSpago env (Fetch.run fetchOpts)
buildEnv <- runSpago env (mkBuildEnv args dependencies)
let options = { depsOnly: false, pursArgs: List.toUnfoldable args.pursArgs, jsonErrors: false }
runSpago buildEnv (Build.run options)
runEnv <- runSpago env (mkRunEnv args buildEnv)
runSpago runEnv Run.run
built <- runSpago buildEnv (Build.run options)
when built do
runEnv <- runSpago env (mkRunEnv args buildEnv)
runSpago runEnv Run.run
Test args@{ selectedPackage, pure } -> do
{ env, fetchOpts } <- mkFetchEnv offline { packages: mempty, selectedPackage, pure, ensureRanges: false, testDeps: false, isRepl: false }
dependencies <- runSpago env (Fetch.run fetchOpts)
buildEnv <- runSpago env (mkBuildEnv (Record.union args { ensureRanges: false }) dependencies)
let options = { depsOnly: false, pursArgs: List.toUnfoldable args.pursArgs, jsonErrors: false }
runSpago buildEnv (Build.run options)
testEnv <- runSpago env (mkTestEnv args buildEnv)
runSpago testEnv Test.run
built <- runSpago buildEnv (Build.run options)
when built do
testEnv <- runSpago env (mkTestEnv args buildEnv)
runSpago testEnv Test.run
LsPaths args -> do
runSpago { logOptions } $ Ls.listPaths args
LsPackages args@{ pure } -> do
Expand Down
12 changes: 9 additions & 3 deletions core/src/Log.purs
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,9 @@ module Spago.Log
, class Loggable
, die
, die'
, indent2
, justOrDieWith
, justOrDieWith'
, rightOrDieWith
, rightOrDieWith'
, indent2
, logDebug
, logError
, logFailure
Expand All @@ -20,6 +18,9 @@ module Spago.Log
, logWarn
, module DodoExport
, output
, prepareToDie
, rightOrDieWith
, rightOrDieWith'
, toDoc
) where

Expand Down Expand Up @@ -154,6 +155,11 @@ die msg = do
logFailure msg
Effect.liftEffect $ Process.exit' 1

prepareToDie :: forall a b m. MonadEffect m => MonadAsk (LogEnv b) m => Loggable a => a -> m Unit
prepareToDie msg = do
logFailure msg
Effect.liftEffect $ Process.setExitCode 1

-- | Same as `die`, but with multiple failures
die' :: forall a b m u. MonadEffect m => MonadAsk (LogEnv b) m => Loggable a => Array a -> m u
die' msgs = do
Expand Down
12 changes: 0 additions & 12 deletions shell.nix

This file was deleted.

56 changes: 32 additions & 24 deletions src/Spago/Command/Build.purs
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,7 @@ import Spago.Command.Fetch as Fetch
import Spago.Config (Package(..), PackageMap, WithTestGlobs(..), Workspace, WorkspacePackage)
import Spago.Config as Config
import Spago.Git (Git)
import Spago.Log (prepareToDie)
import Spago.Psa as Psa
import Spago.Psa.Types as PsaTypes
import Spago.Purs (Purs)
Expand All @@ -42,7 +43,7 @@ type BuildOptions =
, jsonErrors :: Boolean
}

run :: BuildOptions -> Spago (BuildEnv _) Unit
run :: BuildOptions -> Spago (BuildEnv _) Boolean
run opts = do
logInfo "Building..."
{ dependencies
Expand Down Expand Up @@ -123,10 +124,10 @@ run opts = do
, statVerbosity: fromMaybe Psa.defaultStatVerbosity workspace.buildOptions.statVerbosity
}

Psa.psaCompile globs args psaArgs

case workspace.backend of
Nothing -> pure unit
built <- Psa.psaCompile globs args psaArgs
backendBuilt <- case workspace.backend of
_ | not built -> pure false
Nothing -> pure true
Just backend -> do
logInfo $ "Compiling with backend \"" <> backend.cmd <> "\""
logDebug $ "Running command `" <> backend.cmd <> "`"
Expand All @@ -137,26 +138,33 @@ run opts = do
Cmd.exec backend.cmd (addOutputArgs moreBackendArgs) Cmd.defaultExecOptions >>= case _ of
Left r -> do
logDebug $ Cmd.printExecResult r
die [ "Failed to build with backend " <> backend.cmd ]
prepareToDie [ "Failed to build with backend " <> backend.cmd ] $> false
Right _ ->
logSuccess "Backend build succeeded."

let
pedanticPkgs = NEA.toArray selectedPackages # Array.mapMaybe \p -> do
let reportSrc = pedanticPackages || (fromMaybe false $ p.package.build >>= _.pedantic_packages)
let reportTest = pedanticPackages || (fromMaybe false $ p.package.test >>= _.pedantic_packages)
Alternative.guard (reportSrc || reportTest)
pure $ Tuple p { reportSrc, reportTest }
unless (Array.null pedanticPkgs || opts.depsOnly) do
logInfo $ "Looking for unused and undeclared transitive dependencies..."
eitherGraph <- Graph.runGraph globs opts.pursArgs
graph <- either die pure eitherGraph
env <- ask
checkResults <- map Array.fold $ for pedanticPkgs \(Tuple selected options) -> do
Graph.toImportErrors selected options
<$> runSpago (Record.union { selected, workspacePackages: selectedPackages } env) (Graph.checkImports graph)
unless (Array.null checkResults) do
die $ Graph.formatImportErrors checkResults
logSuccess "Backend build succeeded." $> true

if not backendBuilt then
pure false
else do
let
pedanticPkgs = NEA.toArray selectedPackages # Array.mapMaybe \p -> do
let reportSrc = pedanticPackages || (fromMaybe false $ p.package.build >>= _.pedantic_packages)
let reportTest = pedanticPackages || (fromMaybe false $ p.package.test >>= _.pedantic_packages)
Alternative.guard (reportSrc || reportTest)
pure $ Tuple p { reportSrc, reportTest }
if Array.null pedanticPkgs || opts.depsOnly then
pure true
else do
logInfo $ "Looking for unused and undeclared transitive dependencies..."
eitherGraph <- Graph.runGraph globs opts.pursArgs
eitherGraph # either (prepareToDie >>> (_ $> false)) \graph -> do
env <- ask
checkResults <- map Array.fold $ for pedanticPkgs \(Tuple selected options) -> do
Graph.toImportErrors selected options
<$> runSpago (Record.union { selected, workspacePackages: selectedPackages } env) (Graph.checkImports graph)
if Array.null checkResults then
pure true
else
prepareToDie (Graph.formatImportErrors checkResults) $> false

-- TODO: if we are building with all the packages (i.e. selected = Nothing),
-- then we could use the graph to remove outdated modules from `output`!
Expand Down
13 changes: 11 additions & 2 deletions src/Spago/Command/Publish.purs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ import Effect.Aff (Milliseconds(..))
import Effect.Aff as Aff
import Effect.Ref as Ref
import Node.Path as Path
import Node.Process as Process
import Record as Record
import Registry.API.V1 as V1
import Registry.Internal.Format as Internal.Format
Expand All @@ -41,6 +42,7 @@ import Spago.Git as Git
import Spago.Json as Json
import Spago.Log (LogVerbosity(..))
import Spago.Log as Log
import Spago.Prelude as Effect
import Spago.Purs (Purs)
import Spago.Purs.Graph as Graph
import Spago.Registry (PreRegistryEnv)
Expand Down Expand Up @@ -99,13 +101,16 @@ publish _args = do
logDebug $ "Publishing package " <> strName

-- As first thing we run a build to make sure the package compiles at all
runBuild { selected, dependencies: env.dependencies }
built <- runBuild { selected, dependencies: env.dependencies }
( Build.run
{ depsOnly: false
, pursArgs: []
, jsonErrors: false
}
)
-- There's a pending failure exit and its' easier to just abort here
when (not built) $
Effect.liftEffect Process.exit

-- We then need to check that the dependency graph is accurate. If not, queue the errors
let allDependencies = Fetch.toAllDependencies dependencies
Expand Down Expand Up @@ -338,14 +343,18 @@ publish _args = do
-- from the solver (this is because the build might terminate the process, and we shall output the errors first)
logInfo "Building again with the build plan from the solver..."
let buildPlanDependencies = map Config.RegistryVersion resolutions
runBuild { selected, dependencies: Map.singleton selected.package.name buildPlanDependencies }
builtAgain <- runBuild { selected, dependencies: Map.singleton selected.package.name buildPlanDependencies }
( Build.run
{ depsOnly: false
, pursArgs: []
, jsonErrors: false
}
)

-- As above: there's a pending failure exit and its' easier to just abort here
when (not builtAgain) $
Effect.liftEffect Process.exit

logDebug $ unsafeStringify publishingData
logSuccess "Ready for publishing. Calling the registry.."

Expand Down
7 changes: 5 additions & 2 deletions src/Spago/Psa.purs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Spago.Config (Package(..), PackageMap, WorkspacePackage)
import Spago.Config as Config
import Spago.Core.Config (CensorBuildWarnings(..), WarningCensorTest(..))
import Spago.Core.Config as Core
import Spago.Log (prepareToDie)
import Spago.Psa.Output (buildOutput)
import Spago.Psa.Printer (printDefaultOutputToErr, printJsonOutputToOut)
import Spago.Psa.Types (ErrorCode, PathDecision, PsaArgs, PsaOutputOptions, PsaPathType(..), psaResultCodec)
Expand All @@ -36,7 +37,7 @@ import Spago.Purs as Purs
defaultStatVerbosity :: Core.StatVerbosity
defaultStatVerbosity = Core.CompactStats

psaCompile :: forall a. Set.Set FilePath -> Array String -> PsaArgs -> Spago (Purs.PursEnv a) Unit
psaCompile :: forall a. Set.Set FilePath -> Array String -> PsaArgs -> Spago (Purs.PursEnv a) Boolean
psaCompile globs pursArgs psaArgs = do
result <- Purs.compile globs (Array.snoc pursArgs "--json-errors")
let resultStdout = Cmd.getStdout result
Expand All @@ -60,11 +61,13 @@ psaCompile globs pursArgs psaArgs = do

if Array.all identity arrErrorsIsEmpty then do
logSuccess "Build succeeded."
pure true
else do
case result of
Left r -> logDebug $ Cmd.printExecResult r
_ -> pure unit
die [ "Failed to build." ]
prepareToDie [ "Failed to build." ]
pure false

where
isEmptySpan filename pos =
Expand Down
9 changes: 9 additions & 0 deletions test-fixtures/build/json-truncated-many-warnings/spago.yaml
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
package:
name: spago-bug
dependencies:
- effect
- prelude
workspace:
package_set:
registry: 50.1.2
extra_packages: {}
10 changes: 10 additions & 0 deletions test-fixtures/build/json-truncated-many-warnings/src/Main.purs
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
module Main where

import Prelude

import Effect (Effect)
import Warn (test)

main :: Effect Unit
main = do
test 1
Loading

0 comments on commit 10657ca

Please sign in to comment.