wip, console logs

This commit is contained in:
voidlizard 2025-02-13 10:41:54 +03:00
parent 4c33ffbe8c
commit 9e2257f9ef
3 changed files with 66 additions and 24 deletions

View File

@ -15,6 +15,8 @@ import HBS2.Git3.Logger
import Data.Config.Suckless import Data.Config.Suckless
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Data.Time.Format (formatTime, defaultTimeLocale)
import System.Posix.Signals import System.Posix.Signals
import System.IO qualified as IO import System.IO qualified as IO
import System.Posix.IO import System.Posix.IO
@ -31,6 +33,10 @@ import System.Exit hiding (die)
import System.Console.ANSI import System.Console.ANSI
formatTs :: Int -> String
formatTs ts =
formatTime defaultTimeLocale "%Y-%m-%d %H:%M:%S" (posixSecondsToUTCTime (fromIntegral ts))
{- HLINT ignore "Use isEOF" -} {- HLINT ignore "Use isEOF" -}
{- HLINT ignore "Use putStrLn" -} {- HLINT ignore "Use putStrLn" -}
@ -132,6 +138,7 @@ localDict DeferredOps{..} = makeDict @C do
runTop :: (ParseSExp what, MonadUnliftIO m) => Dict C m -> what -> m () runTop :: (ParseSExp what, MonadUnliftIO m) => Dict C m -> what -> m ()
runTop dict s = parseTop s & either (const none) (void . run dict) runTop dict s = parseTop s & either (const none) (void . run dict)
{- HLINT ignore "Functor law" -} {- HLINT ignore "Functor law" -}
main :: IO () main :: IO ()
main = flip runContT pure do main = flip runContT pure do
@ -150,23 +157,53 @@ main = flip runContT pure do
liftIO $ hSetBuffering origHandle NoBuffering liftIO $ hSetBuffering origHandle NoBuffering
liftIO $ IO.hPutStr origHandle "\n" lift $ void $ installHandler sigPIPE Ignore Nothing
ContT $ withAsync $ liftIO $ forever do
pause @'Seconds 0.25
wut <- IO.hGetContents rStderr <&> lines
for_ wut $ \s -> do
hClearLine origHandle cp_ <- newTVarIO Nothing
hSetCursorColumn origHandle 0
IO.hPutStr origHandle s ContT $ withAsync $ liftIO $ flip runContT pure do
hSetCursorColumn origHandle 0 callCC \finished -> do
-- pause @'Seconds 0.05 forever do
pause @'Seconds 0.1
wut <- liftIO $ IO.hGetContents rStderr <&> lines
for_ wut $ \s -> do
let what = parseTop s & fromRight mempty
case what of
[ListVal [SymbolVal "checkpoint", TextLike w, LitIntVal r]] -> do
atomically $ writeTVar cp_ (Just (w,r))
[ListVal [SymbolVal "status", TextLike "FLUSH"]] -> do
finished ()
_ -> none
liftIO do
hClearLine origHandle
hSetCursorColumn origHandle 0
IO.hPutStr origHandle s
hSetCursorColumn origHandle 0
ContT $ bracket none $ const do ContT $ bracket none $ const do
cp <- readTVarIO cp_
let cpHash = fst <$> cp
let ts = maybe 0 (fromIntegral . snd) cp & formatTs
hClearLine origHandle hClearLine origHandle
hSetCursorColumn origHandle 0 hSetCursorColumn origHandle 0
lift $ void $ installHandler sigPIPE Ignore Nothing when (isJust cp) do
hPutDoc origHandle $ "fetched from checkpoint" <+> pretty ts <+> pretty cpHash <> line
hPutDoc origHandle $ "use" <+> yellow "git fetch" <+> "to get latest versions" <> line
hFlush origHandle
env <- nullGit3Env env <- nullGit3Env
ops <- DeferredOps <$> newTQueueIO ops <- DeferredOps <$> newTQueueIO
@ -198,7 +235,7 @@ main = flip runContT pure do
waitRepo Nothing =<< getGitRepoKeyThrow waitRepo Nothing =<< getGitRepoKeyThrow
notice "WAIT-FOR-REPO-DONE" notice "wait-for-repo-done"
void $ run dict conf void $ run dict conf
@ -207,6 +244,10 @@ main = flip runContT pure do
flip fix Plain $ \next -> \case flip fix Plain $ \next -> \case
Plain -> do Plain -> do
closed <- hIsEOF stdin
when closed $ next End
inp <- try @_ @IOError getLine <&> fromRight mempty inp <- try @_ @IOError getLine <&> fromRight mempty
when (null (words inp)) $ next End when (null (words inp)) $ next End
@ -222,10 +263,9 @@ main = flip runContT pure do
End -> do End -> do
sendLine "" sendLine ""
liftIO exitSuccess notice "status FLUSH"
_ -> do _ -> do
sendLine "" sendLine ""
next Plain next Plain
-- liftIO exitSuccess

View File

@ -191,7 +191,7 @@ importGitRefLog = do
ProbeSnapshotElement "Download.wip" n -> Just n ProbeSnapshotElement "Download.wip" n -> Just n
_ -> Nothing _ -> Nothing
notice $ "wait some time..." <+> parens (pretty down) notice $ "wait-for-download" <+> parens (pretty down)
case d of case d of
Just n | down /= n || down == 0 -> again next Just n | down /= n || down == 0 -> again next
@ -227,7 +227,7 @@ importGitRefLog = do
hxs <- txList ( pure . not . flip HS.member excl ) rv hxs <- txList ( pure . not . flip HS.member excl ) rv
cp' <- flip fix (fmap snd hxs, Nothing) $ \next -> \case cp' <- flip fix (fmap snd hxs, Nothing) $ \next -> \case
([], r) -> pure (gitTxTree <$> r) ([], r) -> pure r
(TxSegment{}:xs, l) -> next (xs, l) (TxSegment{}:xs, l) -> next (xs, l)
(cp@(TxCheckpoint n tree) : xs, l) -> do (cp@(TxCheckpoint n tree) : xs, l) -> do
@ -241,14 +241,10 @@ importGitRefLog = do
next (xs, l) next (xs, l)
case cp' of case cp' of
Nothing -> do Just TxCheckpoint{..} -> do
notice "no checkpoints found"
pure Nothing
Just cp -> do notice $ "checkpoint" <+> pretty gitTxTree <+> pretty gitTxRank
txs <- txList ( pure . not . flip HS.member excl ) (Just gitTxTree)
notice $ "found checkpoint" <+> pretty cp
txs <- txList ( pure . not . flip HS.member excl ) (Just cp)
forConcurrently_ txs $ \case forConcurrently_ txs $ \case
(_, TxCheckpoint{}) -> none (_, TxCheckpoint{}) -> none
@ -265,7 +261,11 @@ importGitRefLog = do
atomically $ modifyTVar already_ (HS.insert tree) atomically $ modifyTVar already_ (HS.insert tree)
notice $ "imported" <+> pretty h notice $ "imported" <+> pretty h
pure (Just cp) pure (Just gitTxTree)
_ -> do
notice "no checkpoints found"
pure Nothing
case r of case r of
Right cp -> again $ ImportDone cp Right cp -> again $ ImportDone cp

View File

@ -16,6 +16,7 @@ setupLogger = do
setLogging @ERROR $ toStderr . logPrefix "[error] " setLogging @ERROR $ toStderr . logPrefix "[error] "
setLogging @WARN $ toStderr . logPrefix "[warn] " setLogging @WARN $ toStderr . logPrefix "[warn] "
setLogging @NOTICE $ toStderr . logPrefix "" setLogging @NOTICE $ toStderr . logPrefix ""
setLogging @INFO $ toStderr . logPrefix ""
pure () pure ()
flushLoggers :: MonadIO m => m () flushLoggers :: MonadIO m => m ()
@ -28,5 +29,6 @@ silence = do
setLoggingOff @ERROR setLoggingOff @ERROR
setLoggingOff @WARN setLoggingOff @WARN
setLoggingOff @NOTICE setLoggingOff @NOTICE
setLoggingOff @INFO