mirror of
https://github.com/wasp-lang/wasp.git
synced 2024-12-28 11:34:41 +03:00
'wasp start' now reloads on file change.
This commit is contained in:
parent
e95fae7f06
commit
32bb439c53
@ -8,13 +8,13 @@ import Control.Monad.IO.Class (liftIO)
|
||||
|
||||
import qualified StrongPath as SP
|
||||
import Command (Command)
|
||||
import Command.Common (findWaspProjectRootFromCwd)
|
||||
import Command.Common (findWaspProjectRootDirFromCwd)
|
||||
import qualified Common
|
||||
|
||||
clean :: Command ()
|
||||
clean = do
|
||||
waspRoot <- findWaspProjectRootFromCwd
|
||||
let dotWaspDirFp = SP.toFilePath $ waspRoot SP.</> Common.dotWaspDirInWaspProjectDir
|
||||
waspProjectDir <- findWaspProjectRootDirFromCwd
|
||||
let dotWaspDirFp = SP.toFilePath $ waspProjectDir SP.</> Common.dotWaspDirInWaspProjectDir
|
||||
liftIO $ putStrLn "Deleting .wasp/ directory..." >> hFlush stdout
|
||||
doesDotWaspDirExist <- liftIO $ doesDirectoryExist dotWaspDirFp
|
||||
if doesDotWaspDirExist
|
||||
|
@ -1,7 +1,7 @@
|
||||
module Command.Common
|
||||
( findWaspProjectRootFromCwd
|
||||
( findWaspProjectRootDirFromCwd
|
||||
, findWaspProjectRoot
|
||||
, waspSays
|
||||
, waspSaysC
|
||||
) where
|
||||
|
||||
import System.Directory (getCurrentDirectory, doesPathExist, doesFileExist)
|
||||
@ -14,7 +14,7 @@ import Control.Monad (when, unless)
|
||||
import StrongPath (Path, Abs, Dir)
|
||||
import qualified StrongPath as SP
|
||||
import Command (Command, CommandError(..))
|
||||
import Common (WaspProjectDir, dotWaspRootFileInWaspProjectDir)
|
||||
import Common (WaspProjectDir, dotWaspRootFileInWaspProjectDir, waspSays)
|
||||
|
||||
|
||||
findWaspProjectRoot :: Path Abs (Dir ()) -> Command (Path Abs (Dir WaspProjectDir))
|
||||
@ -33,10 +33,10 @@ findWaspProjectRoot currentDir = do
|
||||
notFoundError = CommandError ("Couldn't find wasp project root - make sure"
|
||||
++ " you are running this command from Wasp project.")
|
||||
|
||||
findWaspProjectRootFromCwd :: Command (Path Abs (Dir WaspProjectDir))
|
||||
findWaspProjectRootFromCwd = do
|
||||
findWaspProjectRootDirFromCwd :: Command (Path Abs (Dir WaspProjectDir))
|
||||
findWaspProjectRootDirFromCwd = do
|
||||
absCurrentDir <- liftIO getCurrentDirectory
|
||||
findWaspProjectRoot (fromJust $ SP.parseAbsDir absCurrentDir)
|
||||
|
||||
waspSays :: String -> Command ()
|
||||
waspSays what = liftIO $ putStrLn $ "\ESC[33m{= Wasp =}\ESC[0m " ++ what -- Yellow
|
||||
waspSaysC :: String -> Command ()
|
||||
waspSaysC = liftIO . waspSays
|
||||
|
38
waspc/cli/Command/Compile.hs
Normal file
38
waspc/cli/Command/Compile.hs
Normal file
@ -0,0 +1,38 @@
|
||||
module Command.Compile
|
||||
( compile
|
||||
) where
|
||||
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.List (find, isSuffixOf)
|
||||
import qualified Path as P
|
||||
|
||||
import qualified Common
|
||||
import CompileOptions (CompileOptions (..))
|
||||
import qualified Lib
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified Util.IO
|
||||
|
||||
|
||||
-- | Compiles Wasp source code in waspProjectDir directory and generates a project
|
||||
-- in given outDir directory.
|
||||
compile :: Path Abs (Dir Common.WaspProjectDir)
|
||||
-> Path Abs (Dir Lib.ProjectRootDir)
|
||||
-> IO (Either String ())
|
||||
compile waspProjectDir outDir = do
|
||||
maybeWaspFile <- findWaspFile waspProjectDir
|
||||
case maybeWaspFile of
|
||||
Nothing -> return $ Left "No *.wasp file present in the root of Wasp project."
|
||||
Just waspFile -> Lib.compile waspFile outDir options
|
||||
where
|
||||
options = CompileOptions
|
||||
{ externalCodeDirPath = waspProjectDir </> Common.extCodeDirInWaspProjectDir }
|
||||
|
||||
findWaspFile :: Path Abs (Dir d) -> IO (Maybe (Path Abs SP.File))
|
||||
findWaspFile dir = do
|
||||
(files, _) <- liftIO $ Util.IO.listDirectory (SP.toPathAbsDir dir)
|
||||
return $ (dir SP.</>) . SP.fromPathRelFile <$> find isWaspFile files
|
||||
|
||||
isWaspFile :: P.Path P.Rel P.File -> Bool
|
||||
isWaspFile path = ".wasp" `isSuffixOf` P.toFilePath path
|
||||
&& (length (P.toFilePath path) > length (".wasp" :: String))
|
@ -2,69 +2,51 @@ module Command.Start
|
||||
( start
|
||||
) where
|
||||
|
||||
import qualified Path as P
|
||||
import Control.Monad.Except (throwError)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
import Data.List (find, isSuffixOf)
|
||||
import Control.Concurrent.Async (race)
|
||||
import Control.Monad.Except (throwError)
|
||||
import Control.Monad.IO.Class (liftIO)
|
||||
|
||||
import CompileOptions (CompileOptions (..))
|
||||
import StrongPath (Path, Abs, Dir, (</>))
|
||||
import qualified StrongPath as SP
|
||||
import qualified Lib
|
||||
import qualified Util.IO
|
||||
import Command (Command, CommandError(..))
|
||||
import Command.Common (findWaspProjectRootFromCwd, waspSays)
|
||||
import Command (Command, CommandError (..))
|
||||
import Command.Common (findWaspProjectRootDirFromCwd,
|
||||
waspSaysC)
|
||||
import Command.Compile (compile)
|
||||
import Command.Watch (watch)
|
||||
import qualified Common
|
||||
import qualified Lib
|
||||
import StrongPath ((</>))
|
||||
|
||||
|
||||
-- | Does initial compile of wasp code and then runs the generated project.
|
||||
-- It also listens for any file changes and recompiles and restarts generated project accordingly.
|
||||
start :: Command ()
|
||||
start = do
|
||||
waspRoot <- findWaspProjectRootFromCwd
|
||||
waspFile <- findWaspFile waspRoot
|
||||
waspRoot <- findWaspProjectRootDirFromCwd
|
||||
let outDir = waspRoot </> Common.dotWaspDirInWaspProjectDir </> Common.generatedCodeDirInDotWaspDir
|
||||
let options = CompileOptions
|
||||
{ externalCodeDirPath = waspRoot </> Common.extCodeDirInWaspProjectDir }
|
||||
|
||||
-- TODO: This just compiles once. We need `wasp start` to do much more.
|
||||
waspSays "Compiling wasp code..."
|
||||
errorOrResult <- liftIO $ Lib.compile waspFile outDir options
|
||||
case errorOrResult of
|
||||
waspSaysC "Compiling wasp code..."
|
||||
compilationResult <- liftIO $ compile waspRoot outDir
|
||||
case compilationResult of
|
||||
Left compileError -> throwError $ CommandError $ "Compilation failed: " ++ compileError
|
||||
Right () -> waspSays "Code has been successfully compiled.\n"
|
||||
Right () -> waspSaysC "Code has been successfully compiled, project has been generated.\n"
|
||||
|
||||
-- TODO: Do smart install -> if we need to install stuff, install it.
|
||||
-- TODO: Do smart install -> if we need to install stuff, install it, otherwise don't.
|
||||
-- This should be responsibility of Generator, it should tell us how to install stuff.
|
||||
-- But who checks out if stuff needs to be installed at all? That should probably be
|
||||
-- Generator again. After installation, it should return some kind of data that describes that installation.
|
||||
-- Then, next time, we give it data we have about last installation, and it uses that
|
||||
-- to decide if installation needs to happen or not. If it happens, it returnes new data again.
|
||||
-- Right now we have setup/installation being called, but it has not support for being "smart" yet.
|
||||
waspSays "Setting up generated project..."
|
||||
waspSaysC "Setting up generated project..."
|
||||
setupResult <- liftIO $ Lib.setup outDir
|
||||
case setupResult of
|
||||
Left setupError -> throwError $ CommandError $ "Setup failed: " ++ setupError
|
||||
Right () -> waspSays "Setup successful.\n"
|
||||
|
||||
-- TODO: Check node version and then run `npm start` on both web and server.
|
||||
-- Again, this is something that Generator should be responsible for, since it knows how the code is generated.
|
||||
-- It should tell us how to start stuff and we just start it. It should even do composing of the outputs,
|
||||
-- since it knows more than us about that.
|
||||
waspSays "Starting up generated project..."
|
||||
startResult <- liftIO $ Lib.start outDir
|
||||
case startResult of
|
||||
Left startError -> throwError $ CommandError $ "Start failed: " ++ startError
|
||||
Right () -> error "This should never happen, start should never end."
|
||||
|
||||
-- TODO: Listen for changes, if they happen, re-generate the code.
|
||||
where
|
||||
findWaspFile :: Path Abs (Dir d) -> Command (Path Abs SP.File)
|
||||
findWaspFile dir = do
|
||||
(files, _) <- liftIO $ Util.IO.listDirectory (SP.toPathAbsDir dir)
|
||||
case find isWaspFile files of
|
||||
Just file -> return $ dir SP.</> SP.fromPathRelFile file
|
||||
Nothing -> throwError $ CommandError "No .wasp file present in the root of Wasp project."
|
||||
|
||||
isWaspFile :: P.Path P.Rel P.File -> Bool
|
||||
isWaspFile path = ".wasp" `isSuffixOf` P.toFilePath path
|
||||
&& (length (P.toFilePath path) > length (".wasp" :: String))
|
||||
Right () -> waspSaysC "Setup successful.\n"
|
||||
|
||||
waspSaysC "Listening for file changes..."
|
||||
waspSaysC "Starting up generated project..."
|
||||
watchOrStartResult <- liftIO $ race (watch waspRoot outDir) (Lib.start outDir)
|
||||
case watchOrStartResult of
|
||||
Left () -> error "This should never happen, listening for file changes should never end but it did."
|
||||
Right startResult -> case startResult of
|
||||
Left startError -> throwError $ CommandError $ "Start failed: " ++ startError
|
||||
Right () -> error "This should never happen, start should never end but it did."
|
||||
|
73
waspc/cli/Command/Watch.hs
Normal file
73
waspc/cli/Command/Watch.hs
Normal file
@ -0,0 +1,73 @@
|
||||
module Command.Watch
|
||||
( watch
|
||||
) where
|
||||
|
||||
import Control.Concurrent.Chan (Chan, newChan, readChan)
|
||||
import Data.List (isSuffixOf)
|
||||
import Data.Time.Clock (UTCTime, getCurrentTime)
|
||||
import qualified System.FilePath as FP
|
||||
import qualified System.FSNotify as FSN
|
||||
|
||||
import Command.Compile (compile)
|
||||
import Common (waspSays)
|
||||
import qualified Common
|
||||
import qualified Lib
|
||||
import StrongPath (Abs, Dir, Path, (</>))
|
||||
import qualified StrongPath as SP
|
||||
|
||||
|
||||
-- TODO: Another possible problem: on re-generation, wasp re-generates a lot of files, even those that should not
|
||||
-- be generated again, since it is not smart enough yet to know which files do not need to be regenerated.
|
||||
-- This can trigger `npm start` processes to reload multiple times, once for each file!
|
||||
-- `nodemon` specifically has --delay option which says how long it should wait before restarting,
|
||||
-- and it's default value is 1 second, so it will restart only once if all file changes happen in one second interval.
|
||||
-- We could play in the future with increasing this delay. Nodemon can also be manually restarted with `rs` so
|
||||
-- that could also be useful -> if we could do only manual restarting and not have it restart on its own, we could
|
||||
-- have tigther control over it. But do we need nodemon at all then hm :)?
|
||||
-- TODO: Idea: Read .gitignore file, and ignore everything from it. This will then also cover the
|
||||
-- .wasp dir, and users can easily add any custom stuff they want ignored. But, we also have to
|
||||
-- be ready for the case when there is no .gitignore, that could be possible.
|
||||
-- | Forever listens for any file changes in waspProjectDir, and if there is a change,
|
||||
-- compiles Wasp source files in waspProjectDir and regenerates files in outDir.
|
||||
watch :: Path Abs (Dir Common.WaspProjectDir) -> Path Abs (Dir Lib.ProjectRootDir) -> IO ()
|
||||
watch waspProjectDir outDir = FSN.withManager $ \mgr -> do
|
||||
currentTime <- getCurrentTime
|
||||
chan <- newChan
|
||||
_ <- FSN.watchDirChan mgr (SP.toFilePath waspProjectDir) eventFilter chan
|
||||
_ <- FSN.watchTreeChan mgr (SP.toFilePath $ waspProjectDir </> Common.extCodeDirInWaspProjectDir) eventFilter chan
|
||||
listenForEvents chan currentTime
|
||||
where
|
||||
listenForEvents :: Chan FSN.Event -> UTCTime -> IO ()
|
||||
listenForEvents chan lastCompileTime = do
|
||||
event <- readChan chan
|
||||
let eventTime = FSN.eventTime event
|
||||
if eventTime < lastCompileTime
|
||||
-- | If event happened before last compilation started, skip it.
|
||||
then listenForEvents chan lastCompileTime
|
||||
else do
|
||||
currentTime <- getCurrentTime
|
||||
recompile
|
||||
listenForEvents chan currentTime
|
||||
|
||||
recompile :: IO ()
|
||||
recompile = do
|
||||
waspSays "Recompiling on file change..."
|
||||
compilationResult <- compile waspProjectDir outDir
|
||||
case compilationResult of
|
||||
Left err -> waspSays $ "Recompilation on file change failed: " ++ err
|
||||
Right () -> waspSays "Recompilation on file change succeeded."
|
||||
return ()
|
||||
|
||||
-- TODO: This is a hardcoded approach to ignoring most of the common tmp files that editors
|
||||
-- create next to the source code. Bad thing here is that users can't modify this,
|
||||
-- so better approach would be probably to use information from .gitignore instead, or
|
||||
-- maybe combining the two somehow.
|
||||
eventFilter :: FSN.Event -> Bool
|
||||
eventFilter event =
|
||||
let filename = FP.takeFileName $ FSN.eventPath event
|
||||
in not (null filename)
|
||||
&& not (take 2 filename == ".#") -- Ignore emacs lock files.
|
||||
&& not (head filename == '#' && last filename == '#') -- Ignore emacs auto-save files.
|
||||
&& not (last filename == '~') -- Ignore emacs and vim backup files.
|
||||
&& not (head filename == '.' && ".swp" `isSuffixOf` filename) -- Ignore vim swp files.
|
||||
&& not (head filename == '.' && ".un~" `isSuffixOf` filename) -- Ignore vim undo files.
|
@ -5,6 +5,7 @@ module Common
|
||||
, dotWaspRootFileInWaspProjectDir
|
||||
, extCodeDirInWaspProjectDir
|
||||
, generatedCodeDirInDotWaspDir
|
||||
, waspSays
|
||||
) where
|
||||
|
||||
import qualified Path as P
|
||||
@ -31,3 +32,6 @@ dotWaspRootFileInWaspProjectDir = SP.fromPathRelFile [P.relfile|.wasproot|]
|
||||
|
||||
extCodeDirInWaspProjectDir :: Path (Rel WaspProjectDir) (Dir SourceExternalCodeDir)
|
||||
extCodeDirInWaspProjectDir = SP.fromPathRelDir [P.reldir|ext|]
|
||||
|
||||
waspSays :: String -> IO ()
|
||||
waspSays what = putStrLn $ "\ESC[33m{= Wasp =}\ESC[0m " ++ what -- Yellow
|
||||
|
@ -74,6 +74,9 @@ executables:
|
||||
- directory
|
||||
- mtl
|
||||
- exceptions
|
||||
- fsnotify
|
||||
- async
|
||||
- time
|
||||
|
||||
benchmarks:
|
||||
waspc-benchmarks:
|
||||
|
Loading…
Reference in New Issue
Block a user