Improve verbosity
This commit is contained in:
parent
30b4d399b9
commit
1a64527e14
@ -179,7 +179,7 @@ validateTarballs dls = do
|
|||||||
|
|
||||||
where
|
where
|
||||||
downloadAll dli = do
|
downloadAll dli = do
|
||||||
let settings = Settings True False Never Curl
|
let settings = Settings True False Never Curl False
|
||||||
let runLogger = myLoggerT LoggerConfig { lcPrintDebug = True
|
let runLogger = myLoggerT LoggerConfig { lcPrintDebug = True
|
||||||
, colorOutter = B.hPut stderr
|
, colorOutter = B.hPut stderr
|
||||||
, rawOutter = (\_ -> pure ())
|
, rawOutter = (\_ -> pure ())
|
||||||
|
@ -299,6 +299,7 @@ settings' = unsafePerformIO
|
|||||||
, noVerify = False
|
, noVerify = False
|
||||||
, keepDirs = Never
|
, keepDirs = Never
|
||||||
, downloader = Curl
|
, downloader = Curl
|
||||||
|
, verbose = False
|
||||||
}
|
}
|
||||||
)
|
)
|
||||||
|
|
||||||
|
@ -808,6 +808,7 @@ toSettings Options {..} =
|
|||||||
noVerify = optNoVerify
|
noVerify = optNoVerify
|
||||||
keepDirs = optKeepDirs
|
keepDirs = optKeepDirs
|
||||||
downloader = optsDownloader
|
downloader = optsDownloader
|
||||||
|
verbose = optVerbose
|
||||||
in Settings { .. }
|
in Settings { .. }
|
||||||
|
|
||||||
|
|
||||||
|
20
lib/GHCup.hs
20
lib/GHCup.hs
@ -133,19 +133,19 @@ installGHCBin bDls ver mpfReq = do
|
|||||||
|
|
||||||
where
|
where
|
||||||
-- | Install an unpacked GHC distribution. This only deals with the GHC build system and nothing else.
|
-- | Install an unpacked GHC distribution. This only deals with the GHC build system and nothing else.
|
||||||
installGHC' :: (MonadLogger m, MonadIO m)
|
installGHC' :: (MonadReader Settings m, MonadThrow m, MonadLogger m, MonadIO m)
|
||||||
=> Path Abs -- ^ Path to the unpacked GHC bindist (where the configure script resides)
|
=> Path Abs -- ^ Path to the unpacked GHC bindist (where the configure script resides)
|
||||||
-> Path Abs -- ^ Path to install to
|
-> Path Abs -- ^ Path to install to
|
||||||
-> Excepts '[ProcessError] m ()
|
-> Excepts '[ProcessError] m ()
|
||||||
installGHC' path inst = do
|
installGHC' path inst = do
|
||||||
lift $ $(logInfo) "Installing GHC (this may take a while)"
|
lift $ $(logInfo) "Installing GHC (this may take a while)"
|
||||||
lEM $ liftIO $ execLogged "./configure"
|
lEM $ execLogged "./configure"
|
||||||
False
|
False
|
||||||
["--prefix=" <> toFilePath inst]
|
["--prefix=" <> toFilePath inst]
|
||||||
[rel|ghc-configure|]
|
[rel|ghc-configure|]
|
||||||
(Just path)
|
(Just path)
|
||||||
Nothing
|
Nothing
|
||||||
lEM $ liftIO $ make ["install"] (Just path)
|
lEM $ make ["install"] (Just path)
|
||||||
pure ()
|
pure ()
|
||||||
|
|
||||||
|
|
||||||
@ -672,7 +672,7 @@ BUILD_SPHINX_PDF = NO
|
|||||||
HADDOCK_DOCS = NO
|
HADDOCK_DOCS = NO
|
||||||
Stage1Only = YES|]
|
Stage1Only = YES|]
|
||||||
|
|
||||||
compile :: (MonadCatch m, MonadLogger m, MonadIO m)
|
compile :: (MonadReader Settings m, MonadThrow m, MonadCatch m, MonadLogger m, MonadIO m)
|
||||||
=> Either (Path Rel) (Path Abs)
|
=> Either (Path Rel) (Path Abs)
|
||||||
-> Path Abs
|
-> Path Abs
|
||||||
-> Path Abs
|
-> Path Abs
|
||||||
@ -700,7 +700,7 @@ Stage1Only = YES|]
|
|||||||
Left bver -> do
|
Left bver -> do
|
||||||
spaths <- catMaybes . fmap parseAbs <$> liftIO getSearchPath
|
spaths <- catMaybes . fmap parseAbs <$> liftIO getSearchPath
|
||||||
(liftIO $ searchPath spaths bver) !? NotFoundInPATH bver
|
(liftIO $ searchPath spaths bver) !? NotFoundInPATH bver
|
||||||
lEM $ liftIO $ execLogged
|
lEM $ execLogged
|
||||||
"./configure"
|
"./configure"
|
||||||
False
|
False
|
||||||
( ["--prefix=" <> toFilePath ghcdir]
|
( ["--prefix=" <> toFilePath ghcdir]
|
||||||
@ -714,7 +714,7 @@ Stage1Only = YES|]
|
|||||||
(Just workdir)
|
(Just workdir)
|
||||||
(Just (("GHC", toFilePath bghcPath) : cEnv))
|
(Just (("GHC", toFilePath bghcPath) : cEnv))
|
||||||
| otherwise -> do
|
| otherwise -> do
|
||||||
lEM $ liftIO $ execLogged
|
lEM $ execLogged
|
||||||
"./configure"
|
"./configure"
|
||||||
False
|
False
|
||||||
( [ "--prefix=" <> toFilePath ghcdir
|
( [ "--prefix=" <> toFilePath ghcdir
|
||||||
@ -739,11 +739,11 @@ Stage1Only = YES|]
|
|||||||
liftIO $ writeFile (build_mk workdir) (Just newFilePerms) defaultConf
|
liftIO $ writeFile (build_mk workdir) (Just newFilePerms) defaultConf
|
||||||
|
|
||||||
lift $ $(logInfo) [i|Building (this may take a while)...|]
|
lift $ $(logInfo) [i|Building (this may take a while)...|]
|
||||||
lEM $ liftIO $ make (maybe [] (\j -> ["-j" <> fS (show j)]) jobs)
|
lEM $ make (maybe [] (\j -> ["-j" <> fS (show j)]) jobs)
|
||||||
(Just workdir)
|
(Just workdir)
|
||||||
|
|
||||||
lift $ $(logInfo) [i|Installing...|]
|
lift $ $(logInfo) [i|Installing...|]
|
||||||
lEM $ liftIO $ make ["install"] (Just workdir)
|
lEM $ make ["install"] (Just workdir)
|
||||||
|
|
||||||
markSrcBuilt ghcdir workdir = do
|
markSrcBuilt ghcdir workdir = do
|
||||||
let dest = (ghcdir </> ghcUpSrcBuiltFile)
|
let dest = (ghcdir </> ghcUpSrcBuiltFile)
|
||||||
@ -848,7 +848,7 @@ compileCabal dls tver bghc jobs patchdir = do
|
|||||||
pure ()
|
pure ()
|
||||||
|
|
||||||
where
|
where
|
||||||
compile :: (MonadThrow m, MonadLogger m, MonadIO m, MonadResource m)
|
compile :: (MonadReader Settings m, MonadThrow m, MonadLogger m, MonadIO m, MonadResource m)
|
||||||
=> Path Abs
|
=> Path Abs
|
||||||
-> Excepts '[ProcessError , PatchFailed] m (Path Abs)
|
-> Excepts '[ProcessError , PatchFailed] m (Path Abs)
|
||||||
compile workdir = do
|
compile workdir = do
|
||||||
@ -881,7 +881,7 @@ compileCabal dls tver bghc jobs patchdir = do
|
|||||||
newEnv <- lift $ addToCurrentEnv (("PREFIX", toFilePath tmp) : ghcEnv)
|
newEnv <- lift $ addToCurrentEnv (("PREFIX", toFilePath tmp) : ghcEnv)
|
||||||
lift $ $(logDebug) [i|Environment: #{newEnv}|]
|
lift $ $(logDebug) [i|Environment: #{newEnv}|]
|
||||||
|
|
||||||
lEM $ liftIO $ execLogged "./bootstrap.sh"
|
lEM $ execLogged "./bootstrap.sh"
|
||||||
False
|
False
|
||||||
(maybe [] (\j -> ["-j", fS (show j)]) jobs)
|
(maybe [] (\j -> ["-j", fS (show j)]) jobs)
|
||||||
[rel|cabal-bootstrap|]
|
[rel|cabal-bootstrap|]
|
||||||
|
@ -152,6 +152,7 @@ data Settings = Settings
|
|||||||
, noVerify :: Bool
|
, noVerify :: Bool
|
||||||
, keepDirs :: KeepDirs
|
, keepDirs :: KeepDirs
|
||||||
, downloader :: Downloader
|
, downloader :: Downloader
|
||||||
|
, verbose :: Bool
|
||||||
}
|
}
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
||||||
|
@ -473,10 +473,13 @@ ghcUpSrcBuiltFile = [rel|.ghcup_src_built|]
|
|||||||
|
|
||||||
|
|
||||||
-- | Calls gmake if it exists in PATH, otherwise make.
|
-- | Calls gmake if it exists in PATH, otherwise make.
|
||||||
make :: [ByteString] -> Maybe (Path Abs) -> IO (Either ProcessError ())
|
make :: (MonadThrow m, MonadIO m, MonadReader Settings m)
|
||||||
|
=> [ByteString]
|
||||||
|
-> Maybe (Path Abs)
|
||||||
|
-> m (Either ProcessError ())
|
||||||
make args workdir = do
|
make args workdir = do
|
||||||
spaths <- catMaybes . fmap parseAbs <$> getSearchPath
|
spaths <- catMaybes . fmap parseAbs <$> (liftIO getSearchPath)
|
||||||
has_gmake <- isJust <$> searchPath spaths [rel|gmake|]
|
has_gmake <- isJust <$> (liftIO $ searchPath spaths [rel|gmake|])
|
||||||
let mymake = if has_gmake then "gmake" else "make"
|
let mymake = if has_gmake then "gmake" else "make"
|
||||||
execLogged mymake True args [rel|ghc-make|] workdir Nothing
|
execLogged mymake True args [rel|ghc-make|] workdir Nothing
|
||||||
|
|
||||||
|
@ -1,16 +1,19 @@
|
|||||||
{-# LANGUAGE QuasiQuotes #-}
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module GHCup.Utils.File where
|
module GHCup.Utils.File where
|
||||||
|
|
||||||
import GHCup.Utils.Dirs
|
import GHCup.Utils.Dirs
|
||||||
import GHCup.Utils.Prelude
|
import GHCup.Utils.Prelude
|
||||||
|
import GHCup.Types
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
import Control.Exception ( evaluate )
|
import Control.Exception ( evaluate )
|
||||||
import Control.Exception.Safe
|
import Control.Exception.Safe
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
import Control.Monad.Reader
|
||||||
import Data.ByteString ( ByteString )
|
import Data.ByteString ( ByteString )
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
import Data.Functor
|
import Data.Functor
|
||||||
@ -101,19 +104,21 @@ executeOut path args chdir = captureOutStreams $ do
|
|||||||
SPPB.executeFile (toFilePath path) True args Nothing
|
SPPB.executeFile (toFilePath path) True args Nothing
|
||||||
|
|
||||||
|
|
||||||
execLogged :: ByteString -- ^ thing to execute
|
execLogged :: (MonadReader Settings m, MonadIO m, MonadThrow m)
|
||||||
|
=> ByteString -- ^ thing to execute
|
||||||
-> Bool -- ^ whether to search PATH for the thing
|
-> Bool -- ^ whether to search PATH for the thing
|
||||||
-> [ByteString] -- ^ args for the thing
|
-> [ByteString] -- ^ args for the thing
|
||||||
-> Path Rel -- ^ log filename
|
-> Path Rel -- ^ log filename
|
||||||
-> Maybe (Path Abs) -- ^ optionally chdir into this
|
-> Maybe (Path Abs) -- ^ optionally chdir into this
|
||||||
-> Maybe [(ByteString, ByteString)] -- ^ optional environment
|
-> Maybe [(ByteString, ByteString)] -- ^ optional environment
|
||||||
-> IO (Either ProcessError ())
|
-> m (Either ProcessError ())
|
||||||
execLogged exe spath args lfile chdir env = do
|
execLogged exe spath args lfile chdir env = do
|
||||||
ldir <- ghcupLogsDir
|
Settings{..} <- ask
|
||||||
|
ldir <- liftIO ghcupLogsDir
|
||||||
logfile <- (ldir </>) <$> parseRel (toFilePath lfile <> ".log")
|
logfile <- (ldir </>) <$> parseRel (toFilePath lfile <> ".log")
|
||||||
bracket (createFile (toFilePath logfile) newFilePerms) closeFd action
|
liftIO $ bracket (createFile (toFilePath logfile) newFilePerms) closeFd (action verbose)
|
||||||
where
|
where
|
||||||
action fd = do
|
action verbose fd = do
|
||||||
actionWithPipes $ \(stdoutRead, stdoutWrite) -> do
|
actionWithPipes $ \(stdoutRead, stdoutWrite) -> do
|
||||||
-- start the thread that logs to stdout in a region
|
-- start the thread that logs to stdout in a region
|
||||||
done <- newEmptyMVar
|
done <- newEmptyMVar
|
||||||
@ -122,7 +127,7 @@ execLogged exe spath args lfile chdir env = do
|
|||||||
$ EX.handle (\(_ :: StopThread) -> pure ())
|
$ EX.handle (\(_ :: StopThread) -> pure ())
|
||||||
$ EX.handle (\(_ :: IOException) -> pure ())
|
$ EX.handle (\(_ :: IOException) -> pure ())
|
||||||
$ flip finally (putMVar done ())
|
$ flip finally (putMVar done ())
|
||||||
$ printToRegion fd stdoutRead 6
|
$ (if verbose then tee fd stdoutRead else printToRegion fd stdoutRead 6)
|
||||||
|
|
||||||
-- fork our subprocess
|
-- fork our subprocess
|
||||||
pid <- SPPB.forkProcess $ do
|
pid <- SPPB.forkProcess $ do
|
||||||
@ -151,6 +156,17 @@ execLogged exe spath args lfile chdir env = do
|
|||||||
closeFd stdoutRead
|
closeFd stdoutRead
|
||||||
pure e
|
pure e
|
||||||
|
|
||||||
|
tee fileFd fdIn = do
|
||||||
|
flip finally (readTilEOF lineAction fdIn) -- make sure the last few lines don't get cut off
|
||||||
|
$ do
|
||||||
|
hideError eofErrorType $ readTilEOF lineAction fdIn
|
||||||
|
forever (threadDelay 5000)
|
||||||
|
|
||||||
|
where
|
||||||
|
lineAction bs' = do
|
||||||
|
void $ SPIB.fdWrite fileFd (bs' <> "\n")
|
||||||
|
void $ SPIB.fdWrite stdOutput (bs' <> "\n")
|
||||||
|
|
||||||
-- Reads fdIn and logs the output in a continous scrolling area
|
-- Reads fdIn and logs the output in a continous scrolling area
|
||||||
-- of 'size' terminal lines. Also writes to a log file.
|
-- of 'size' terminal lines. Also writes to a log file.
|
||||||
printToRegion fileFd fdIn size = do
|
printToRegion fileFd fdIn size = do
|
||||||
@ -170,6 +186,7 @@ execLogged exe spath args lfile chdir env = do
|
|||||||
|
|
||||||
where
|
where
|
||||||
-- action to perform line by line
|
-- action to perform line by line
|
||||||
|
-- TODO: do this with vty for efficiency
|
||||||
lineAction ref rs bs' = do
|
lineAction ref rs bs' = do
|
||||||
modifyIORef' ref (swapRegs bs')
|
modifyIORef' ref (swapRegs bs')
|
||||||
regs <- readIORef ref
|
regs <- readIORef ref
|
||||||
|
Loading…
Reference in New Issue
Block a user