Rework printing/tee
This should be faster to draw, use less syscalls and generally use EOF and pipes correctly.
This commit is contained in:
parent
e348de8dc4
commit
0f69c73e0e
@ -50,7 +50,7 @@ import Data.Versions
|
|||||||
import Data.Word8
|
import Data.Word8
|
||||||
import GHC.IO.Exception
|
import GHC.IO.Exception
|
||||||
import HPath
|
import HPath
|
||||||
import HPath.IO
|
import HPath.IO hiding ( hideError )
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import Optics
|
import Optics
|
||||||
import Prelude hiding ( abs
|
import Prelude hiding ( abs
|
||||||
|
@ -50,7 +50,7 @@ import Data.Versions
|
|||||||
import Data.Word8
|
import Data.Word8
|
||||||
import GHC.IO.Exception
|
import GHC.IO.Exception
|
||||||
import HPath
|
import HPath
|
||||||
import HPath.IO as HIO
|
import HPath.IO as HIO hiding ( hideError )
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import Optics
|
import Optics
|
||||||
import Prelude hiding ( abs
|
import Prelude hiding ( abs
|
||||||
|
@ -45,7 +45,7 @@ import Data.Versions
|
|||||||
import Data.Word8
|
import Data.Word8
|
||||||
import GHC.IO.Exception
|
import GHC.IO.Exception
|
||||||
import HPath
|
import HPath
|
||||||
import HPath.IO
|
import HPath.IO hiding ( hideError )
|
||||||
import Haskus.Utils.Variant.Excepts
|
import Haskus.Utils.Variant.Excepts
|
||||||
import Optics
|
import Optics
|
||||||
import Prelude hiding ( abs
|
import Prelude hiding ( abs
|
||||||
|
@ -14,17 +14,20 @@ import Control.Exception ( evaluate )
|
|||||||
import Control.Exception.Safe
|
import Control.Exception.Safe
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Reader
|
import Control.Monad.Reader
|
||||||
|
import Control.Monad.Trans.State.Strict
|
||||||
import Data.ByteString ( ByteString )
|
import Data.ByteString ( ByteString )
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
import Data.Functor
|
import Data.Functor
|
||||||
import Data.IORef
|
import Data.IORef
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
import Data.Sequence ( Seq, (|>) )
|
||||||
import Data.Text ( Text )
|
import Data.Text ( Text )
|
||||||
import Data.Void
|
import Data.Void
|
||||||
|
import Data.Word8
|
||||||
import GHC.IO.Exception
|
import GHC.IO.Exception
|
||||||
import HPath
|
import HPath
|
||||||
import HPath.IO
|
import HPath.IO hiding ( hideError )
|
||||||
import Optics
|
import Optics hiding ((<|), (|>))
|
||||||
import System.Console.Pretty
|
import System.Console.Pretty
|
||||||
import System.Console.Regions
|
import System.Console.Regions
|
||||||
import System.IO.Error
|
import System.IO.Error
|
||||||
@ -40,6 +43,7 @@ import Text.Regex.Posix
|
|||||||
|
|
||||||
|
|
||||||
import qualified Control.Exception as EX
|
import qualified Control.Exception as EX
|
||||||
|
import qualified Data.Sequence as Sq
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as E
|
import qualified Data.Text.Encoding as E
|
||||||
import qualified System.Posix.Process.ByteString
|
import qualified System.Posix.Process.ByteString
|
||||||
@ -53,6 +57,7 @@ import qualified "unix-bytestring" System.Posix.IO.ByteString
|
|||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
-- | Bool signals whether the regions should be cleaned.
|
-- | Bool signals whether the regions should be cleaned.
|
||||||
data StopThread = StopThread Bool
|
data StopThread = StopThread Bool
|
||||||
deriving Show
|
deriving Show
|
||||||
@ -113,86 +118,92 @@ execLogged :: (MonadReader Settings m, MonadIO m, MonadThrow m)
|
|||||||
-> Maybe [(ByteString, ByteString)] -- ^ optional environment
|
-> Maybe [(ByteString, ByteString)] -- ^ optional environment
|
||||||
-> m (Either ProcessError ())
|
-> m (Either ProcessError ())
|
||||||
execLogged exe spath args lfile chdir env = do
|
execLogged exe spath args lfile chdir env = do
|
||||||
Settings{..} <- ask
|
Settings {..} <- ask
|
||||||
ldir <- liftIO ghcupLogsDir
|
ldir <- liftIO ghcupLogsDir
|
||||||
logfile <- (ldir </>) <$> parseRel (toFilePath lfile <> ".log")
|
logfile <- (ldir </>) <$> parseRel (toFilePath lfile <> ".log")
|
||||||
liftIO $ bracket (createFile (toFilePath logfile) newFilePerms) closeFd (action verbose)
|
liftIO $ bracket (createFile (toFilePath logfile) newFilePerms)
|
||||||
|
closeFd
|
||||||
|
(action verbose)
|
||||||
where
|
where
|
||||||
action verbose 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
|
||||||
|
pState <- newEmptyMVar
|
||||||
done <- newEmptyMVar
|
done <- newEmptyMVar
|
||||||
tid <-
|
void
|
||||||
forkIO
|
$ forkOS
|
||||||
$ EX.handle (\(_ :: StopThread) -> pure ())
|
$ EX.handle (\(_ :: StopThread) -> pure ())
|
||||||
$ EX.handle (\(_ :: IOException) -> pure ())
|
$ EX.handle (\(_ :: IOException) -> pure ())
|
||||||
$ flip finally (putMVar done ())
|
$ flip finally (putMVar done ())
|
||||||
$ (if verbose then tee fd stdoutRead else printToRegion fd stdoutRead 6)
|
$ (if verbose
|
||||||
|
then tee fd stdoutRead
|
||||||
|
else printToRegion fd stdoutRead 6 pState
|
||||||
|
)
|
||||||
|
|
||||||
-- fork our subprocess
|
-- fork the subprocess
|
||||||
pid <- SPPB.forkProcess $ do
|
pid <- SPPB.forkProcess $ do
|
||||||
void $ dupTo stdoutWrite stdOutput
|
void $ dupTo stdoutWrite stdOutput
|
||||||
void $ dupTo stdoutWrite stdError
|
void $ dupTo stdoutWrite stdError
|
||||||
closeFd stdoutWrite
|
|
||||||
closeFd stdoutRead
|
closeFd stdoutRead
|
||||||
|
closeFd stdoutWrite
|
||||||
|
|
||||||
-- execute the action
|
-- execute the action
|
||||||
maybe (pure ()) (changeWorkingDirectory . toFilePath) chdir
|
maybe (pure ()) (changeWorkingDirectory . toFilePath) chdir
|
||||||
SPPB.executeFile exe spath args env
|
void $ SPPB.executeFile exe spath args env
|
||||||
|
|
||||||
closeFd stdoutWrite
|
closeFd stdoutWrite
|
||||||
|
|
||||||
-- wait for the subprocess to finish
|
-- wait for the subprocess to finish
|
||||||
e <- SPPB.getProcessStatus True True pid >>= \case
|
e <- toProcessError exe args <$!> SPPB.getProcessStatus True True pid
|
||||||
i@(Just (SPPB.Exited _)) -> pure $ toProcessError exe args i
|
putMVar pState (either (const False) (const True) e)
|
||||||
i -> pure $ toProcessError exe args i
|
|
||||||
|
|
||||||
-- make sure the logging thread stops
|
|
||||||
case e of
|
|
||||||
Left _ -> EX.throwTo tid (StopThread False)
|
|
||||||
Right _ -> EX.throwTo tid (StopThread True)
|
|
||||||
takeMVar done
|
takeMVar done
|
||||||
|
|
||||||
closeFd stdoutRead
|
closeFd stdoutRead
|
||||||
|
|
||||||
pure e
|
pure e
|
||||||
|
|
||||||
tee fileFd fdIn = do
|
tee :: Fd -> Fd -> IO ()
|
||||||
flip finally (readTilEOF lineAction fdIn) -- make sure the last few lines don't get cut off
|
tee fileFd fdIn = readTilEOF lineAction fdIn
|
||||||
$ do
|
|
||||||
hideError eofErrorType $ readTilEOF lineAction fdIn
|
|
||||||
forever (threadDelay 5000)
|
|
||||||
|
|
||||||
where
|
where
|
||||||
|
lineAction :: ByteString -> IO ()
|
||||||
lineAction bs' = do
|
lineAction bs' = do
|
||||||
void $ SPIB.fdWrite fileFd (bs' <> "\n")
|
void $ SPIB.fdWrite fileFd (bs' <> "\n")
|
||||||
void $ SPIB.fdWrite stdOutput (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 :: Fd -> Fd -> Int -> MVar Bool -> IO ()
|
||||||
ref <- newIORef ([] :: [ByteString])
|
printToRegion fileFd fdIn size pState = do
|
||||||
displayConsoleRegions $ do
|
void $ displayConsoleRegions $ do
|
||||||
rs <- sequence . replicate size . openConsoleRegion $ Linear
|
rs <-
|
||||||
flip finally (readTilEOF (lineAction ref rs) fdIn) -- make sure the last few lines don't get cut off
|
liftIO
|
||||||
|
. fmap Sq.fromList
|
||||||
|
. sequence
|
||||||
|
. replicate size
|
||||||
|
. openConsoleRegion
|
||||||
|
$ Linear
|
||||||
|
flip runStateT mempty
|
||||||
$ handle
|
$ handle
|
||||||
(\(StopThread b) -> do
|
(\(ex :: SomeException) -> do
|
||||||
when b (forM_ rs closeConsoleRegion)
|
ps <- liftIO $ takeMVar pState
|
||||||
EX.throw (StopThread b)
|
when (ps == True) (forM_ rs (liftIO . closeConsoleRegion))
|
||||||
|
throw ex
|
||||||
)
|
)
|
||||||
$ do
|
$ readTilEOF (lineAction rs) fdIn
|
||||||
hideError eofErrorType $ readTilEOF (lineAction ref rs) fdIn
|
|
||||||
-- wait for explicit stop from the parent to signal what cleanup to run
|
|
||||||
forever (threadDelay 5000)
|
|
||||||
|
|
||||||
where
|
where
|
||||||
-- action to perform line by line
|
-- action to perform line by line
|
||||||
-- TODO: do this with vty for efficiency
|
-- TODO: do this with vty for efficiency
|
||||||
lineAction ref rs bs' = do
|
lineAction :: (MonadMask m, MonadIO m)
|
||||||
modifyIORef' ref (swapRegs bs')
|
=> Seq ConsoleRegion
|
||||||
regs <- readIORef ref
|
-> ByteString
|
||||||
void $ SPIB.fdWrite fileFd (bs' <> "\n")
|
-> StateT (Seq ByteString) m ()
|
||||||
forM (zip regs rs) $ \(bs, r) -> do
|
lineAction rs = \bs' -> do
|
||||||
setConsoleRegion r $ do
|
void $ liftIO $ SPIB.fdWrite fileFd (bs' <> "\n")
|
||||||
|
modify (swapRegs bs')
|
||||||
|
regs <- get
|
||||||
|
liftIO $ forM_ (Sq.zip regs rs) $ \(bs, r) -> setConsoleRegion r $ do
|
||||||
w <- consoleWidth
|
w <- consoleWidth
|
||||||
return
|
return
|
||||||
. T.pack
|
. T.pack
|
||||||
@ -203,25 +214,44 @@ execLogged exe spath args lfile chdir env = do
|
|||||||
. (\b -> "[ " <> toFilePath lfile <> " ] " <> b)
|
. (\b -> "[ " <> toFilePath lfile <> " ] " <> b)
|
||||||
$ bs
|
$ bs
|
||||||
|
|
||||||
swapRegs bs regs | length regs < size = regs ++ [bs]
|
swapRegs :: a -> Seq a -> Seq a
|
||||||
| otherwise = tail regs ++ [bs]
|
swapRegs bs = \regs -> if
|
||||||
|
| Sq.length regs < size -> regs |> bs
|
||||||
|
| otherwise -> Sq.drop 1 regs |> bs
|
||||||
|
|
||||||
-- trim output line to terminal width
|
-- trim output line to terminal width
|
||||||
trim w bs | BS.length bs > w && w > 5 = BS.take (w - 4) bs <> "..."
|
trim :: Int -> ByteString -> ByteString
|
||||||
| otherwise = bs
|
trim w = \bs -> if
|
||||||
|
| BS.length bs > w && w > 5 -> BS.take (w - 4) bs <> "..."
|
||||||
|
| otherwise -> bs
|
||||||
|
|
||||||
-- read an entire line from the file descriptor (removes the newline char)
|
-- read an entire line from the file descriptor (removes the newline char)
|
||||||
readLine fd' = do
|
readLine :: MonadIO m => Fd -> ByteString -> m (ByteString, ByteString)
|
||||||
bs <- SPIB.fdRead fd' 1
|
readLine fd = go
|
||||||
|
where
|
||||||
|
go inBs = do
|
||||||
|
bs <-
|
||||||
|
liftIO
|
||||||
|
$ handleIO (\e -> if isEOFError e then pure "" else ioError e)
|
||||||
|
$ SPIB.fdRead fd 512
|
||||||
|
let nbs = BS.append inBs bs
|
||||||
|
(line, rest) = BS.span (/= _lf) nbs
|
||||||
if
|
if
|
||||||
| bs == "\n" -> pure ""
|
| BS.length rest /= 0 -> pure (line, BS.tail rest)
|
||||||
| bs == "" -> pure ""
|
| BS.length line == 0 -> pure (mempty, mempty)
|
||||||
| otherwise -> fmap (bs <>) $ readLine fd'
|
| otherwise -> (\(l, r) -> (line <> l, r)) <$!> go mempty
|
||||||
|
|
||||||
readTilEOF action' fd' = do
|
readTilEOF :: MonadIO m => (ByteString -> m a) -> Fd -> m ()
|
||||||
bs <- readLine fd'
|
readTilEOF ~action' fd' = go mempty
|
||||||
|
where
|
||||||
|
go bs' = do
|
||||||
|
(bs, rest) <- readLine fd' bs'
|
||||||
|
if
|
||||||
|
| BS.length bs == 0 -> liftIO
|
||||||
|
$ ioError (mkIOError eofErrorType "" Nothing Nothing)
|
||||||
|
| otherwise -> do
|
||||||
void $ action' bs
|
void $ action' bs
|
||||||
readTilEOF action' fd'
|
go rest
|
||||||
|
|
||||||
|
|
||||||
-- | Capture the stdout and stderr of the given action, which
|
-- | Capture the stdout and stderr of the given action, which
|
||||||
|
@ -165,6 +165,11 @@ liftIOException errType ex =
|
|||||||
. lift
|
. lift
|
||||||
|
|
||||||
|
|
||||||
|
-- | Uses safe-exceptions.
|
||||||
|
hideError :: (MonadIO m, MonadCatch m) => IOErrorType -> m () -> m ()
|
||||||
|
hideError err = handleIO (\e -> if err == ioeGetErrorType e then pure () else liftIO . ioError $ e)
|
||||||
|
|
||||||
|
|
||||||
hideErrorDef :: [IOErrorType] -> a -> IO a -> IO a
|
hideErrorDef :: [IOErrorType] -> a -> IO a -> IO a
|
||||||
hideErrorDef errs def =
|
hideErrorDef errs def =
|
||||||
handleIO (\e -> if ioeGetErrorType e `elem` errs then pure def else ioError e)
|
handleIO (\e -> if ioeGetErrorType e `elem` errs then pure def else ioError e)
|
||||||
|
Loading…
Reference in New Issue
Block a user