Skip to content
Draft
Show file tree
Hide file tree
Changes from 7 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 5 additions & 1 deletion waspc/src/Wasp/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,11 @@ prettyShowSrcLinesOfErrorRgn
else line ++ stylingEnd
stylingStart = T.ansiEscapeCode ++ T.getAnsiCodeFor T.Red
stylingEnd = T.ansiEscapeCode ++ T.ansiResetCode
in (lineNum, if lineContainsError then lineWithStylingStartAndEnd else line)
in ( lineNum,
if lineContainsError && not T.isStylingDisabled
then lineWithStylingStartAndEnd
else line
)
)
srcLines
srcLinesWithMarkedErrorRgnAndLineNumber =
Expand Down
9 changes: 6 additions & 3 deletions waspc/src/Wasp/Generator/DbGenerator/Jobs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,14 +15,14 @@ where

import StrongPath (Abs, Dir, File', Path', (</>))
import qualified StrongPath as SP
import StrongPath.TH (relfile)
import Wasp.Generator.Common (ProjectRootDir)
import Wasp.Generator.DbGenerator.Common (MigrateArgs (..), dbSchemaFileInProjectRootDir)
import Wasp.Generator.ServerGenerator.Common (serverRootDirInProjectRootDir)
import Wasp.Generator.ServerGenerator.Db.Seed (dbSeedNameEnvVarName)
import qualified Wasp.Job as J
import Wasp.Job.Process (runNodeCommandAsJobWithExtraEnv)
import Wasp.Project.Common (WaspProjectDir, waspProjectDirFromProjectRootDir)
import Wasp.Node.NodeModules (getPathToExecutableInNodeModules)
import Wasp.Project.Common (WaspProjectDir, nodeModulesDirInWaspProjectDir, waspProjectDirFromProjectRootDir)

migrateDev :: Path' Abs (Dir ProjectRootDir) -> MigrateArgs -> J.Job
migrateDev projectRootDir migrateArgs =
Expand Down Expand Up @@ -178,4 +178,7 @@ absPrismaExecutableFp :: Path' Abs (Dir WaspProjectDir) -> FilePath
absPrismaExecutableFp waspProjectDir = SP.fromAbsFile prismaExecutableAbs
where
prismaExecutableAbs :: Path' Abs File'
prismaExecutableAbs = waspProjectDir </> [relfile|./node_modules/.bin/prisma|]
prismaExecutableAbs =
waspProjectDir
</> nodeModulesDirInWaspProjectDir
</> SP.castRel (getPathToExecutableInNodeModules "prisma")
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We are now being system-agnostic here, when figuring out abs path to prisma binary.

5 changes: 3 additions & 2 deletions waspc/src/Wasp/Generator/SdkGenerator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,6 +76,7 @@ import Wasp.Generator.WebAppGenerator.DepVersions
import qualified Wasp.Job as J
import Wasp.Job.IO (readJobMessagesAndPrintThemPrefixed)
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npmExec)
import qualified Wasp.Node.Version as NodeVersion
import Wasp.Project.Common (WaspProjectDir, waspProjectDirFromAppComponentDir)
import qualified Wasp.Project.Db as Db
Expand All @@ -90,7 +91,7 @@ buildSdk projectRootDir = do
(_, exitCode) <-
concurrently
(readJobMessagesAndPrintThemPrefixed chan)
(runNodeCommandAsJob dstDir "npm" ["run", "build"] J.Wasp chan)
(runNodeCommandAsJob dstDir npmExec ["run", "build"] J.Wasp chan)
case exitCode of
ExitSuccess -> return $ Right ()
ExitFailure code -> return $ Left $ "SDK build failed with exit code: " ++ show code
Expand Down Expand Up @@ -332,7 +333,7 @@ depsRequiredByTailwind spec =
-- Also, fix imports for wasp project.
installNpmDependencies :: Path' Abs (Dir WaspProjectDir) -> J.Job
installNpmDependencies projectDir =
runNodeCommandAsJob projectDir "npm" ["install"] J.Wasp
runNodeCommandAsJob projectDir npmExec ["install"] J.Wasp

-- todo(filip): consider reorganizing/splitting the file.

Expand Down
3 changes: 2 additions & 1 deletion waspc/src/Wasp/Generator/ServerGenerator/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,9 @@ import Wasp.Generator.Common (ProjectRootDir)
import qualified Wasp.Generator.ServerGenerator.Common as Common
import qualified Wasp.Job as J
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npmExec)

installNpmDependencies :: Path' Abs (Dir ProjectRootDir) -> J.Job
installNpmDependencies projectDir = do
let serverDir = projectDir </> Common.serverRootDirInProjectRootDir
runNodeCommandAsJob serverDir "npm" ["install"] J.Server
runNodeCommandAsJob serverDir npmExec ["install"] J.Server
3 changes: 2 additions & 1 deletion waspc/src/Wasp/Generator/ServerGenerator/Start.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,9 @@ import Wasp.Generator.Common (ProjectRootDir)
import qualified Wasp.Generator.ServerGenerator.Common as Common
import qualified Wasp.Job as J
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npmExec)

startServer :: Path' Abs (Dir ProjectRootDir) -> J.Job
startServer projectDir = do
let serverDir = projectDir </> Common.serverRootDirInProjectRootDir
runNodeCommandAsJob serverDir "npm" ["run", "watch"] J.Server
runNodeCommandAsJob serverDir npmExec ["run", "watch"] J.Server
3 changes: 2 additions & 1 deletion waspc/src/Wasp/Generator/WebAppGenerator/Setup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,9 @@ import Wasp.Generator.Common (ProjectRootDir)
import qualified Wasp.Generator.WebAppGenerator.Common as Common
import qualified Wasp.Job as J
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npmExec)

installNpmDependencies :: Path' Abs (Dir ProjectRootDir) -> J.Job
installNpmDependencies projectDir = do
let webAppDir = projectDir </> Common.webAppRootDirInProjectRootDir
runNodeCommandAsJob webAppDir "npm" ["install"] J.WebApp
runNodeCommandAsJob webAppDir npmExec ["install"] J.WebApp
3 changes: 2 additions & 1 deletion waspc/src/Wasp/Generator/WebAppGenerator/Start.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,9 @@ import Wasp.Generator.Common (ProjectRootDir)
import qualified Wasp.Generator.WebAppGenerator.Common as Common
import qualified Wasp.Job as J
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npmExec)

startWebApp :: Path' Abs (Dir ProjectRootDir) -> J.Job
startWebApp projectDir = do
let webAppDir = projectDir </> Common.webAppRootDirInProjectRootDir
runNodeCommandAsJob webAppDir "npm" ["start"] J.WebApp
runNodeCommandAsJob webAppDir npmExec ["start"] J.WebApp
3 changes: 2 additions & 1 deletion waspc/src/Wasp/Generator/WebAppGenerator/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,11 +8,12 @@ import qualified StrongPath as SP
import Wasp.Generator.WebAppGenerator.Common (webAppRootDirInProjectRootDir)
import qualified Wasp.Job as J
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npxExec)
import Wasp.Project.Common (WaspProjectDir, dotWaspDirInWaspProjectDir, generatedCodeDirInDotWaspDir)

testWebApp :: [String] -> Path' Abs (Dir WaspProjectDir) -> J.Job
testWebApp args projectDir = do
runNodeCommandAsJob projectDir "npx" (vitestCommand ++ args) J.WebApp
runNodeCommandAsJob projectDir npxExec (vitestCommand ++ args) J.WebApp
where
vitestCommand = ["vitest", "--config", SP.fromRelFile viteConfigPath]
viteConfigPath =
Expand Down
4 changes: 2 additions & 2 deletions waspc/src/Wasp/Job/Process.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,11 +18,11 @@ import StrongPath (Abs, Dir, Path')
import qualified StrongPath as SP
import System.Environment (getEnvironment)
import System.Exit (ExitCode (..))
import qualified System.Info
import qualified System.Process as P
import UnliftIO.Exception (bracket)
import qualified Wasp.Job as J
import qualified Wasp.Node.Version as NodeVersion
import Wasp.Util.System (isSystemWindows)

-- TODO:
-- Switch from Data.Conduit.Process to Data.Conduit.Process.Typed.
Expand Down Expand Up @@ -86,7 +86,7 @@ runProcessAsJob process jobType chan =
-- Ref: https://stackoverflow.com/questions/61856063/spawning-a-process-with-create-group-true-set-pgid-hangs-when-starting-docke
terminateStreamingProcess streamingProcessHandle = do
let processHandle = CP.streamingProcessHandleRaw streamingProcessHandle
if System.Info.os == "mingw32"
if isSystemWindows
then P.terminateProcess processHandle
else P.interruptProcessGroupOf processHandle
return $ ExitFailure 1
Expand Down
43 changes: 43 additions & 0 deletions waspc/src/Wasp/Node/Executables.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
module Wasp.Node.Executables
( nodeExec,
npmExec,
npxExec,
)
where

import GHC.IO (unsafePerformIO)
import StrongPath (fromAbsFile)
import Wasp.Util.System (ExecName, resolveExecNameIO)

-- | Node executable name to be passed to Haskell's "System.Process" functions.
--
-- This function being top level form in combo with NOINLINE guarantees that IO action will get
-- executed only once per lifetime of the Haskell program.
{-# NOINLINE nodeExec #-}
nodeExec :: ExecName
nodeExec =
-- NOTE: We are taking whole resolved absolute path here because just using the resolved exec name
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This I am not super happy with.
So basically just resolving npm to npm.cmd was not enough, we were still getting errors on Windows. Not the same ones, we moved forward, but different kind, I wish I wrote them down, something about not being able to find some .js files in node_modules.
But maybe it is for the best to have absolute paths to executables we use? Not 100% sure, I think if npm.cmd was working I woudl have stuck with it.

Interested in discussion here. Maybe I should try I again and write down the errors, that might help us make a decision.

-- was still flaky on Windows in some situations.
fromAbsFile $ snd $ unsafePerformIO $ resolveExecNameIO "node"
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Instead of doing unsaferPerformIO, we could have actually obtained these in real IO, somweher at the start of our app, and then propagated them through the code, likely via our monad stack.
While that would be the "best" way to do it, I didn't think it makes much sense to bother with such big refactoring at the moment, for no real gain. We can do it if it turns out it is needed.


-- | Npm executable name to be passed to Haskell's "System.Process" functions.
--
-- This function being top level form in combo with NOINLINE guarantees that IO action will get
-- executed only once per lifetime of the Haskell program.
{-# NOINLINE npmExec #-}
npmExec :: ExecName
npmExec =
-- NOTE: We are taking whole resolved absolute path here because just using the resolved exec name
-- was still flaky on Windows in some situations.
fromAbsFile $ snd $ unsafePerformIO $ resolveExecNameIO "npm"

-- | Node executable name to be passed to Haskell's "System.Process" functions.
--
-- This function being top level form in combo with NOINLINE guarantees that IO action will get
-- executed only once per lifetime of the Haskell program.
{-# NOINLINE npxExec #-}
npxExec :: ExecName
npxExec =
-- NOTE: We are taking whole resolved absolute path here because just using the resolved exec name
-- was still flaky on Windows in some situations.
fromAbsFile $ snd $ unsafePerformIO $ resolveExecNameIO "npx"
25 changes: 25 additions & 0 deletions waspc/src/Wasp/Node/NodeModules.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
module Wasp.Node.NodeModules
( getPathToExecutableInNodeModules,
)
where

import Data.Maybe (fromJust)
import StrongPath (File, Path', Rel, parseRelFile, reldir, (</>))
import Wasp.Util.System (isSystemWindows)

-- | Represents some node_modules dir.
data NodeModulesDir

-- | Node modules (node_modules) have a place where they put all the executables/binaries
-- produced by the packages/modules.
-- This function returns a path to such an executable with a given name, taking into account
-- details like current operating system.
--
-- Example: @getPathToExecutableInNodeModules "npm"@ -> @".bin/npm.cmd"@
getPathToExecutableInNodeModules :: String -> Path' (Rel NodeModulesDir) (File f)
getPathToExecutableInNodeModules execName =
[reldir|.bin|] </> fromJust (parseRelFile systemSpecificExecFilename)
where
systemSpecificExecFilename
| isSystemWindows = execName <> ".cmd"
| otherwise = execName
5 changes: 3 additions & 2 deletions waspc/src/Wasp/Node/Version.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ where
import Data.Conduit.Process.Typed (ExitCode (..))
import System.IO.Error (catchIOError, isDoesNotExistError)
import System.Process (readProcessWithExitCode)
import Wasp.Node.Executables (nodeExec, npmExec)
import Wasp.Node.Internal (parseVersionFromCommandOutput)
import qualified Wasp.SemanticVersion as SV
import qualified Wasp.SemanticVersion.VersionBound as SV
Expand Down Expand Up @@ -48,8 +49,8 @@ checkUserNodeAndNpmMeetWaspRequirements = do
(VersionCheckFail nodeError, _) -> VersionCheckFail nodeError
(_, VersionCheckFail npmError) -> VersionCheckFail npmError
where
checkUserNodeVersion = checkUserToolVersion "node" ["--version"] oldestWaspSupportedNodeVersion
checkUserNpmVersion = checkUserToolVersion "npm" ["--version"] oldestWaspSupportedNpmVersion
checkUserNodeVersion = checkUserToolVersion nodeExec ["--version"] oldestWaspSupportedNodeVersion
checkUserNpmVersion = checkUserToolVersion npmExec ["--version"] oldestWaspSupportedNpmVersion

checkUserToolVersion :: String -> [String] -> SV.Version -> IO VersionCheckResult
checkUserToolVersion commandName commandArgs oldestSupportedToolVersion = do
Expand Down
5 changes: 3 additions & 2 deletions waspc/src/Wasp/NodePackageFFI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ import System.IO (hPutStrLn, stderr)
import qualified System.Process as P
import Wasp.Data (DataDir)
import qualified Wasp.Data as Data
import Wasp.Node.Executables (nodeExec, npmExec)
import qualified Wasp.Node.Version as NodeVersion

-- | This are the globally installed packages waspc runs directly from
Expand Down Expand Up @@ -85,7 +86,7 @@ getPackageProcessOptions package args = do
packageDir <- getRunnablePackageDir package
let scriptFile = packageDir </> scriptInPackageDir
ensurePackageDependenciesAreInstalled packageDir
return $ packageCreateProcess packageDir "node" (fromAbsFile scriptFile : args)
return $ packageCreateProcess packageDir nodeExec (fromAbsFile scriptFile : args)

getPackageInstallationPath :: InstallablePackage -> IO String
getPackageInstallationPath package = do
Expand All @@ -103,7 +104,7 @@ getRunnablePackageDir package = do
ensurePackageDependenciesAreInstalled :: Path' Abs (Dir PackageDir) -> IO ()
ensurePackageDependenciesAreInstalled packageDir =
unlessM nodeModulesDirExists $ do
let npmInstallCreateProcess = packageCreateProcess packageDir "npm" ["install"]
let npmInstallCreateProcess = packageCreateProcess packageDir npmExec ["install"]
(exitCode, _out, err) <- P.readCreateProcessWithExitCode npmInstallCreateProcess ""
case exitCode of
ExitFailure _ -> do
Expand Down
5 changes: 3 additions & 2 deletions waspc/src/Wasp/Project/WaspFile/TypeScript.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ import Wasp.AppSpec.Core.Decl.JSON ()
import qualified Wasp.Job as J
import Wasp.Job.IO (readJobMessagesAndPrintThemPrefixed)
import Wasp.Job.Process (runNodeCommandAsJob)
import Wasp.Node.Executables (npxExec)
import Wasp.Project.Common
( CompileError,
WaspProjectDir,
Expand Down Expand Up @@ -71,7 +72,7 @@ compileWaspTsFile waspProjectDir tsconfigNodeFileInWaspProjectDir waspFilePath =
(readJobMessagesAndPrintThemPrefixed chan)
( runNodeCommandAsJob
waspProjectDir
"npx"
npxExec
-- We're using tsc to compile the *.wasp.ts file into a JS file.
--
-- The tsconfig.wasp.json is configured to give our users with the
Expand Down Expand Up @@ -125,7 +126,7 @@ executeMainWaspJsFileAndGetDeclsFile waspProjectDir prismaSchemaAst absCompiledM
(readJobMessagesAndPrintThemPrefixed chan)
( runNodeCommandAsJob
waspProjectDir
"npx"
npxExec
-- TODO: Figure out how to keep running instructions in a single
-- place (e.g., this is string the same as the package name, but it's
-- repeated in two places).
Expand Down
3 changes: 2 additions & 1 deletion waspc/src/Wasp/Util/Json.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ import Data.Aeson (FromJSON, Value (..), eitherDecode, encode)
import StrongPath (Abs, File, Path')
import System.Exit (ExitCode (..))
import qualified System.Process as P
import Wasp.Node.Executables (nodeExec)
import Wasp.Util.Aeson (decodeFromString)
import qualified Wasp.Util.IO as IOUtil

Expand All @@ -19,7 +20,7 @@ import qualified Wasp.Util.IO as IOUtil
parseJsonWithComments :: FromJSON a => String -> IO (Either String a)
parseJsonWithComments jsonStr = do
let evalScript = "const v = " ++ jsonStr ++ ";console.log(JSON.stringify(v));"
let cp = P.proc "node" ["-e", evalScript]
let cp = P.proc nodeExec ["-e", evalScript]
(exitCode, response, stderr) <- P.readCreateProcessWithExitCode cp ""
case exitCode of
ExitSuccess -> return $ decodeFromString response
Expand Down
66 changes: 66 additions & 0 deletions waspc/src/Wasp/Util/System.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,66 @@
{-# LANGUAGE TupleSections #-}

module Wasp.Util.System
( resolveExecNameIO,
isSystemWindows,
isSystemMacOS,
ExecName,
isEnvVarValueTruthy,
)
where

import Control.Exception (throwIO)
import Control.Monad.Extra (firstJustM)
import StrongPath (Abs, File', Path', parseAbsFile)
import System.Directory (findExecutable)
import qualified System.Info

-- | Executable name as expected by Haskell's "System.Process" and its 'System.Process.RawCommand',
-- therefore suited for passing to their functions for creating/executing processes.
-- It can be just "node", or "node.exe", or relative or full path, ... .
type ExecName = FilePath

-- | Resolve given executable name (e.g. "node") to the version of the name that resolves
-- successfully and the corresponding full path to which it resolves.
--
-- "Version of the name" because we might try a couple of different versions of the name till we
-- find one that resolves (e.g. for "node" we might also try "node.cmd" and "node.exe" on Windows).
--
-- The resolved path corresponds to the program that would be executed by
-- 'System.Process.createProcess' if exec name was provided as 'System.Process.RawCommand'. Check
-- 'System.Process.findExecutable' for more details since that is what we use internally.
--
-- Motivation for this function was mainly driven by how exec names are resolved when executing a
-- process on Windows.
-- On Linux/MacOS situation is simple, the system will normally do the name resolution for us, so
-- e.g. if we pass "npm" to 'System.Process.proc', that will work out of the box.
-- But on Windows, that will normally fail, since there is no "npm" really but instead "npm.cmd" or
-- "npm.exe". In that case, we want to figure out what exactly is the right exec name to use.
-- Note that we don't have to bother with this when using 'System.Process.shell' instead of
-- 'System.Process.proc', but at the price of abandoning any argument escaping.
--
-- Throws IOError if it failed to resolve the name.
--
-- Example: resolveExecNameIO "npm" -> ("npm.cmd", "C:\...\npm.cmd")
resolveExecNameIO :: ExecName -> IO (ExecName, Path' Abs File')
resolveExecNameIO execName = do
firstJustM (\name -> ((name,) <$>) <$> findExecutable name) execNamesToLookForByPriorityDesc >>= \case
Just (execName', execPath) -> (execName',) <$> parseAbsFile execPath
Nothing ->
(throwIO . userError . unlines)
[ "Could not find '" <> execName <> "' executable on your system.",
"Please ensure " <> execName <> " is installed and available in your PATH."
]
where
execNamesToLookForByPriorityDesc
| isSystemWindows = (execName <>) <$> ["", ".cmd", ".exe", ".ps1"]
| otherwise = [execName]

isSystemWindows :: Bool
isSystemWindows = System.Info.os == "mingw32"

isSystemMacOS :: Bool
isSystemMacOS = System.Info.os == "darwin"

isEnvVarValueTruthy :: String -> Bool
isEnvVarValueTruthy envVarValue = envVarValue `notElem` ["0", "false", "no", "off"]
Loading
Loading