Support second-level headers

master
Lennart Spitzner 2022-12-12 18:48:28 +01:00
parent 8956098913
commit ca93157c6e
1 changed files with 38 additions and 30 deletions

View File

@ -98,13 +98,14 @@ data JoinMode
| JoinAllKeep -- join with any other JoinAll-tagged lines/patterns, override headers | JoinAllKeep -- join with any other JoinAll-tagged lines/patterns, override headers
| JoinAllDrop -- join with any other JoinAll-tagged lines/patterns, drop before headers, dont output | JoinAllDrop -- join with any other JoinAll-tagged lines/patterns, drop before headers, dont output
| JoinSpecific -- join with this pattern only | JoinSpecific -- join with this pattern only
| JoinHeader -- join with nothing, stays, only gets replaced by next yield/header | JoinHeader1 -- join with nothing, stays, only gets replaced by next yield/header
| JoinHeader2
| JoinErrorStart | JoinErrorStart
| JoinErrorStop | JoinErrorStop
data JoinedInfo data JoinedInfo
= JoinedNot Bool -- yield or drop, not to be merged. bool determines whether to forward = JoinedNot Bool -- yield or drop, not to be merged. bool determines whether to forward
| JoinedHeader Bool Int Int -- header, not to be merged. bool determines whether to forward. Int is count stdout/stderr | JoinedHeader Bool (Maybe Text) Int Int -- header, not to be merged. bool determines whether to forward. Int is count stdout/stderr
| JoinedAll Bool Int -- bool determines whether to forward | JoinedAll Bool Int -- bool determines whether to forward
| Joined Int Text [Text] -- pattern, prefix | Joined Int Text [Text] -- pattern, prefix
@ -237,9 +238,10 @@ dispatchPat oldKind i pat prefix = do
StdOut -> when (c_keepStdout conf /= Drop) $ outputConcurrent prettyPat StdOut -> when (c_keepStdout conf /= Drop) $ outputConcurrent prettyPat
StdErr -> when (c_keepStderr conf /= Drop) $ errorConcurrent prettyPat StdErr -> when (c_keepStderr conf /= Drop) $ errorConcurrent prettyPat
showHeader :: Text -> Int -> Int -> Text showHeader :: Text -> Maybe Text -> Int -> Int -> Text
showHeader header countOut countErr = showHeader header mLevel2 countOut countErr =
header header
<> (maybe (t "") (\l2 -> t " " <> l2) mLevel2)
<> fGrey <> fGrey
<> t " (" <> t " ("
<> t (show countOut) <> t (show countOut)
@ -250,7 +252,7 @@ showHeader header countOut countErr =
dispatchHeader :: StreamKind -> Int -> Int -> Text -> StateT State IO () dispatchHeader :: StreamKind -> Int -> Int -> Text -> StateT State IO ()
dispatchHeader oldKind countOut countErr header = do dispatchHeader oldKind countOut countErr header = do
let prettyPat = showHeader header countOut countErr <> t "\n" let prettyPat = showHeader header Nothing countOut countErr <> t "\n"
conf <- gets s_config conf <- gets s_config
liftIO $ case oldKind of liftIO $ case oldKind of
StdOut -> when (c_keepStdout conf /= Drop) $ outputConcurrent prettyPat StdOut -> when (c_keepStdout conf /= Drop) $ outputConcurrent prettyPat
@ -281,7 +283,7 @@ dispatchSummary = \case
SummaryNone -> pure () SummaryNone -> pure ()
SummaryNorm kind line (JoinedNot keep) -> SummaryNorm kind line (JoinedNot keep) ->
when keep $ dispatchYielded (kind, line) when keep $ dispatchYielded (kind, line)
SummaryNorm kind line (JoinedHeader keep iOut iErr) -> SummaryNorm kind line (JoinedHeader keep _mLevel2 iOut iErr) ->
when keep $ dispatchHeader kind iOut iErr line when keep $ dispatchHeader kind iOut iErr line
SummaryNorm kind _ (JoinedAll keep i ) -> when keep $ dispatchSkipped kind i SummaryNorm kind _ (JoinedAll keep i ) -> when keep $ dispatchSkipped kind i
SummaryNorm kind _ (Joined i pat prefix) -> dispatchPat kind i pat prefix SummaryNorm kind _ (Joined i pat prefix) -> dispatchPat kind i pat prefix
@ -319,7 +321,9 @@ summarizeLines (kind, line, _linetime) = do
(JoinAllDrop, _) -> SummaryNorm kind line (JoinedAll False 1) (JoinAllDrop, _) -> SummaryNorm kind line (JoinedAll False 1)
(JoinSpecific, pat) -> (JoinSpecific, pat) ->
SummaryNorm kind line (Joined 1 pat (Text.words line)) SummaryNorm kind line (Joined 1 pat (Text.words line))
(JoinHeader , _) -> SummaryNorm kind line (JoinedHeader False 0 0) (JoinHeader1, _) ->
SummaryNorm kind line (JoinedHeader False Nothing 0 0)
(JoinHeader2 , _) -> SummaryNorm kind line (JoinedNot False)
(JoinDrop , _) -> SummaryNorm kind line (JoinedNot False) (JoinDrop , _) -> SummaryNorm kind line (JoinedNot False)
(JoinErrorStart, _) -> SummaryErr kind line (JoinErrorStart, _) -> SummaryErr kind line
(JoinErrorStop, _) -> (JoinErrorStop, _) ->
@ -361,14 +365,15 @@ summarizeLines (kind, line, _linetime) = do
(SummaryNorm oldKind oldLine (JoinedNot keep), _joiner) -> do (SummaryNorm oldKind oldLine (JoinedNot keep), _joiner) -> do
when keep $ dispatchYielded (oldKind, oldLine) when keep $ dispatchYielded (oldKind, oldLine)
defaultReplace defaultReplace
(SummaryNorm oldKind oldLine (JoinedHeader keep countOut countErr), joiner) (SummaryNorm oldKind oldLine (JoinedHeader keep mLevel2 countOut countErr), joiner)
-> do -> do
let replaceMay = case joiner of let replaceMay = case joiner of
(JoinYield , _pat) -> Just (JoinedNot True) (JoinYield , _pat) -> Just (JoinedNot True)
(JoinAllKeep , _ ) -> Just (JoinedAll True 1) (JoinAllKeep , _ ) -> Just (JoinedAll True 1)
(JoinAllDrop , _ ) -> Nothing (JoinAllDrop , _ ) -> Nothing
(JoinSpecific , pat ) -> Just (Joined 1 pat (Text.words line)) (JoinSpecific , pat ) -> Just (Joined 1 pat (Text.words line))
(JoinHeader , _ ) -> Just (JoinedHeader False 0 0) (JoinHeader1 , _ ) -> Just (JoinedHeader False Nothing 0 0)
(JoinHeader2 , _ ) -> Nothing
(JoinDrop , _ ) -> Nothing (JoinDrop , _ ) -> Nothing
(JoinErrorStart, _ ) -> Nothing (JoinErrorStart, _ ) -> Nothing
(JoinErrorStop , _ ) -> Nothing (JoinErrorStop , _ ) -> Nothing
@ -377,23 +382,22 @@ summarizeLines (kind, line, _linetime) = do
when keep $ dispatchHeader oldKind countOut countErr oldLine when keep $ dispatchHeader oldKind countOut countErr oldLine
put s { s_summary = SummaryNorm kind line replace } put s { s_summary = SummaryNorm kind line replace }
Nothing -> do Nothing -> do
let newLevel2 = case joiner of
(JoinHeader2, _) -> Just line
_ -> mLevel2
put s put s
{ s_summary = SummaryNorm { s_summary = SummaryNorm
oldKind oldKind
oldLine oldLine
(case kind of (case kind of
StdOut -> StdOut -> JoinedHeader keep newLevel2 (countOut + 1) countErr
JoinedHeader keep (countOut + 1) countErr StdErr -> JoinedHeader keep newLevel2 countOut (countErr + 1)
StdErr ->
JoinedHeader keep countOut (countErr + 1)
) )
} }
(SummaryNorm oldKind _ (JoinedAll keep i), joiner) -> case joiner of (SummaryNorm oldKind _ (JoinedAll keep i), joiner) -> case joiner of
(JoinAllKeep, _) (JoinAllKeep, _) | kind == oldKind -> do
| kind == oldKind -> do
put s { s_summary = SummaryNorm kind line (JoinedAll True (i + 1)) } put s { s_summary = SummaryNorm kind line (JoinedAll True (i + 1)) }
(JoinAllDrop, _) (JoinAllDrop, _) | kind == oldKind -> do
| kind == oldKind -> do
put s { s_summary = SummaryNorm kind line (JoinedAll False (i + 1)) } put s { s_summary = SummaryNorm kind line (JoinedAll False (i + 1)) }
_ -> do _ -> do
when keep $ dispatchSkipped oldKind i when keep $ dispatchSkipped oldKind i
@ -461,10 +465,10 @@ processLine newKind newLine = execStateT $ do
SummaryNone -> prettyLines SummaryNone -> prettyLines
SummaryNorm StdOut line (JoinedNot _) -> SummaryNorm StdOut line (JoinedNot _) ->
(fWhiteDis <> t "" <> fReset <> ellipse conf line) : prettyLines (fWhiteDis <> t "" <> fReset <> ellipse conf line) : prettyLines
SummaryNorm StdOut line (JoinedHeader _ countOut countErr) -> SummaryNorm StdOut line (JoinedHeader _ mLevel2 countOut countErr) ->
(fWhiteDis <> t "" <> fReset <> ellipse (fWhiteDis <> t "" <> fReset <> ellipse
conf conf
(showHeader line countOut countErr) (showHeader line mLevel2 countOut countErr)
) )
: prettyLines : prettyLines
SummaryNorm StdOut line (JoinedAll _ 1) -> SummaryNorm StdOut line (JoinedAll _ 1) ->
@ -497,10 +501,10 @@ processLine newKind newLine = execStateT $ do
(fWhiteDis <> t "" <> fReset <> ellipse conf line) : prettyLines (fWhiteDis <> t "" <> fReset <> ellipse conf line) : prettyLines
SummaryNorm StdErr line (JoinedNot _) -> SummaryNorm StdErr line (JoinedNot _) ->
(fRedDis <> t "" <> fReset <> ellipse conf line) : prettyLines (fRedDis <> t "" <> fReset <> ellipse conf line) : prettyLines
SummaryNorm StdErr line (JoinedHeader _ countOut countErr) -> SummaryNorm StdErr line (JoinedHeader _ mLevel2 countOut countErr) ->
(fRedDis <> t "" <> fReset <> ellipse (fRedDis <> t "" <> fReset <> ellipse
conf conf
(showHeader line countOut countErr) (showHeader line mLevel2 countOut countErr)
) )
: prettyLines : prettyLines
SummaryNorm StdErr line (JoinedAll _ 1) -> SummaryNorm StdErr line (JoinedAll _ 1) ->
@ -648,6 +652,8 @@ main = B.mainFromCmdParser $ do
yieldFull <- B.addFlagStringParams "" ["yield-any"] "REGEX" (B.flagHelpStr "always fully retain lines containing this pattern, disregarding skip/summarize") yieldFull <- B.addFlagStringParams "" ["yield-any"] "REGEX" (B.flagHelpStr "always fully retain lines containing this pattern, disregarding skip/summarize")
header <- B.addFlagStringParams "h" ["header"] "REGEX" (B.flagHelpStr "starting with this pattern: always replaces summary, then gets dropped") header <- B.addFlagStringParams "h" ["header"] "REGEX" (B.flagHelpStr "starting with this pattern: always replaces summary, then gets dropped")
headerFull <- B.addFlagStringParams "" ["header-any"] "REGEX" (B.flagHelpStr "containing this pattern: always replaces summary, then gets dropped") headerFull <- B.addFlagStringParams "" ["header-any"] "REGEX" (B.flagHelpStr "containing this pattern: always replaces summary, then gets dropped")
header2 <- B.addFlagStringParams "" ["header2"] "REGEX" (B.flagHelpStr "starting with this pattern: always replaces summary, then gets dropped")
header2Full <- B.addFlagStringParams "" ["header2-any"] "REGEX" (B.flagHelpStr "containing this pattern: always replaces summary, then gets dropped")
errorStart <- B.addFlagStringParams "" ["error-start"] "REGEX" mempty errorStart <- B.addFlagStringParams "" ["error-start"] "REGEX" mempty
errorStartFull <- B.addFlagStringParams "" ["error-start-any"] "REGEX" mempty errorStartFull <- B.addFlagStringParams "" ["error-start-any"] "REGEX" mempty
errorStop <- B.addFlagStringParams "" ["error-stop"] "REGEX" mempty errorStop <- B.addFlagStringParams "" ["error-stop"] "REGEX" mempty
@ -739,8 +745,10 @@ main = B.mainFromCmdParser $ do
, yieldFull <&> compiler JoinYield , yieldFull <&> compiler JoinYield
, summarize <&> compiler JoinSpecific . (\x -> "^(" ++ x ++ ")") , summarize <&> compiler JoinSpecific . (\x -> "^(" ++ x ++ ")")
, summarizeFull <&> compiler JoinSpecific , summarizeFull <&> compiler JoinSpecific
, header <&> compiler JoinHeader . (\x -> "^(" ++ x ++ ")") , header <&> compiler JoinHeader1 . (\x -> "^(" ++ x ++ ")")
, headerFull <&> compiler JoinHeader , headerFull <&> compiler JoinHeader1
, header2 <&> compiler JoinHeader2 . (\x -> "^(" ++ x ++ ")")
, header2Full <&> compiler JoinHeader2
, dropArg <&> compiler JoinAllDrop . (\x -> "^(" ++ x ++ ")") , dropArg <&> compiler JoinAllDrop . (\x -> "^(" ++ x ++ ")")
, dropFull <&> compiler JoinAllDrop , dropFull <&> compiler JoinAllDrop
, errorStart <&> compiler JoinErrorStart . (\x -> "^(" ++ x ++ ")") , errorStart <&> compiler JoinErrorStart . (\x -> "^(" ++ x ++ ")")