Skip to content

Commit 7f7bbf4

Browse files
committed
Toggle between drvname/name when pressing n
TODO - help screen - freeze print when pressing f
1 parent c528570 commit 7f7bbf4

File tree

5 files changed

+85
-22
lines changed

5 files changed

+85
-22
lines changed

exe/Main.hs

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -10,23 +10,24 @@ import Data.Time (ZonedTime)
1010
import Data.Version (showVersion)
1111
import GHC.IO.Exception (ExitCode (ExitFailure))
1212
import NOM.Error (NOMError)
13-
import NOM.IO (interact)
13+
import NOM.IO (Window, interact)
14+
import NOM.IO qualified as Nom.IO
1415
import NOM.IO.Input (NOMInput (..), UpdateResult (..))
1516
import NOM.IO.Input.JSON ()
1617
import NOM.IO.Input.OldStyle (OldStyleInput)
1718
import NOM.NixMessage.JSON (NixJSONMessage)
1819
import NOM.Print (Config (..), stateToText)
1920
import NOM.Print.Table (markup, red)
20-
import NOM.State (NOMV1State (..), ProgressState (..), failedBuilds, fullSummary, initalStateFromBuildPlatform)
21+
import NOM.State (NOMV1State (..), PrintState, ProgressState (..), failedBuilds, fullSummary, initalStateFromBuildPlatform)
2122
import NOM.State.CacheId.Map qualified as CMap
2223
import NOM.Update (detectLocalFinishedBuilds, maintainState)
2324
import NOM.Update.Monad (UpdateMonad)
2425
import Optics (gfield, (%), (%~), (.~), (^.))
2526
import Paths_nix_output_monitor (version)
2627
import Relude
2728
import System.Console.ANSI qualified as Terminal
28-
import System.Console.Terminal.Size (Window)
2929
import System.Environment qualified as Environment
30+
import System.IO qualified
3031
import System.IO.Error qualified as IOError
3132
import System.Posix.Signals qualified as Signals
3233
import System.Process.Typed (proc, runProcess)
@@ -160,7 +161,8 @@ runMonitoredCommand config process_config = do
160161

161162
data ProcessState a = MkProcessState
162163
{ updaterState :: UpdaterState a
163-
, printFunction :: Maybe (Window Int) -> (ZonedTime, Double) -> Text
164+
, printFunction :: PrintState -> Maybe NOM.IO.Window -> (ZonedTime, Double) -> Nom.IO.Output
165+
-- ^ That print function is 'NOM.IO.OutputFunc' without the nom state.
164166
}
165167
deriving stock (Generic)
166168

@@ -170,6 +172,8 @@ monitorHandle config input_handle = withParser @a \streamParser -> do
170172
do
171173
Terminal.hHideCursor outputHandle
172174
hSetBuffering stdout (BlockBuffering (Just 1_000_000))
175+
System.IO.hSetBuffering stdin NoBuffering
176+
System.IO.hSetEcho stdin False
173177

174178
current_system <- Exception.handle ((Nothing <$) . printIOException) $ Just . decodeUtf8 <$> Process.readProcessStdout_ (Process.proc "nix" ["eval", "--extra-experimental-features", "nix-command", "--impure", "--raw", "--expr", "builtins.currentSystem"])
175179
first_state <- initalStateFromBuildPlatform current_system

flake.nix

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -102,6 +102,7 @@
102102
pkgs.haskell.packages.ghc92.weeder
103103
pkgs.haskellPackages.cabal-install
104104
pkgs.pv
105+
pkgs.haskellPackages.fourmolu
105106
];
106107
withHoogle = true;
107108
inherit (self.checks.${system}.pre-commit-check) shellHook;

lib/NOM/IO.hs

Lines changed: 45 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,8 @@
1-
module NOM.IO (interact, processTextStream, StreamParser, Stream) where
1+
module NOM.IO (interact, processTextStream, StreamParser, Stream, Window, Output) where
22

33
import Control.Concurrent (threadDelay)
4-
import Control.Concurrent.Async (concurrently_, race_)
5-
import Control.Concurrent.STM (check, swapTVar)
4+
import Control.Concurrent.Async (Concurrently (Concurrently, runConcurrently))
5+
import Control.Concurrent.STM (check, swapTVar, writeTMVar)
66
import Data.ByteString qualified as ByteString
77
import Data.ByteString.Builder qualified as Builder
88
import Data.ByteString.Char8 qualified as ByteString
@@ -11,6 +11,7 @@ import Data.Time (ZonedTime, getZonedTime)
1111
import NOM.Error (NOMError)
1212
import NOM.Print (Config (..))
1313
import NOM.Print.Table as Table (bold, displayWidth, displayWidthBS, markup, red, truncate)
14+
import NOM.State (PrintNameStyle (..), PrintState (..), initPrintState)
1415
import NOM.Update.Monad (UpdateMonad, getNow)
1516
import Relude
1617
import Streamly.Data.Fold qualified as Fold
@@ -28,7 +29,7 @@ type Output = Text
2829

2930
type UpdateFunc update state = forall m. (UpdateMonad m) => update -> StateT state m ([NOMError], ByteString, Bool)
3031

31-
type OutputFunc state = state -> Maybe Window -> (ZonedTime, Double) -> Output
32+
type OutputFunc state = state -> PrintState -> Maybe Window -> (ZonedTime, Double) -> Output
3233

3334
type Finalizer state = forall m. (UpdateMonad m) => StateT state m ()
3435

@@ -59,13 +60,14 @@ writeStateToScreen ::
5960
Bool ->
6061
TVar Int ->
6162
TMVar state ->
63+
TMVar PrintState ->
6264
TVar [ByteString] ->
6365
TVar Bool ->
6466
(Double -> state -> state) ->
6567
OutputFunc state ->
6668
Handle ->
6769
IO ()
68-
writeStateToScreen pad printed_lines_var nom_state_var nix_output_buffer_var refresh_display_var maintenance printer output_handle = do
70+
writeStateToScreen pad printed_lines_var nom_state_var print_state_var nix_output_buffer_var refresh_display_var maintenance printer output_handle = do
6971
nowClock <- getZonedTime
7072
now <- getNow
7173
terminalSize <-
@@ -88,11 +90,10 @@ writeStateToScreen pad printed_lines_var nom_state_var nix_output_buffer_var ref
8890
nix_output_raw <- swapTVar nix_output_buffer_var []
8991
pure (nom_state, nix_output_raw)
9092
-- ====
91-
93+
print_state <- atomically $ readTMVar print_state_var
9294
let nix_output = ByteString.lines $ ByteString.concat $ reverse nix_output_raw
9395
nix_output_length = length nix_output
94-
95-
nom_output = ByteString.lines $ encodeUtf8 $ truncateOutput terminalSize (printer nom_state terminalSize (nowClock, now))
96+
nom_output = ByteString.lines $ encodeUtf8 $ truncateOutput terminalSize (printer nom_state print_state terminalSize (nowClock, now))
9697
nom_output_length = length nom_output
9798

9899
-- We will try to calculate how many lines we can draw without reaching the end
@@ -214,6 +215,14 @@ minFrameDuration =
214215
-- feel to sluggish for the eye, for me.
215216
60_000 -- ~17 times per second
216217

218+
getKey :: IO [Char]
219+
getKey = reverse <$> getKey' ""
220+
where
221+
getKey' chars = do
222+
char <- System.IO.getChar
223+
more <- System.IO.hReady stdin
224+
(if more then getKey' else return) (char : chars)
225+
217226
processTextStream ::
218227
forall update state.
219228
Config ->
@@ -227,6 +236,8 @@ processTextStream ::
227236
IO state
228237
processTextStream config parser updater maintenance printerMay finalize initialState inputStream = do
229238
state_var <- newTMVarIO initialState
239+
print_state_var <- newTMVarIO initPrintState
240+
input_received <- newEmptyTMVarIO
230241
output_builder_var <- newTVarIO []
231242
refresh_display_var <- newTVarIO False
232243
let keepProcessing :: IO ()
@@ -240,13 +251,35 @@ processTextStream config parser updater maintenance printerMay finalize initialS
240251
waitForInput = atomically $ check =<< readTVar refresh_display_var
241252
printerMay & maybe keepProcessing \(printer, output_handle) -> do
242253
linesVar <- newTVarIO 0
243-
let writeToScreen :: IO ()
244-
writeToScreen = writeStateToScreen (not config.silent) linesVar state_var output_builder_var refresh_display_var maintenance printer output_handle
254+
let keepProcessingStdin :: IO ()
255+
keepProcessingStdin = forever $ do
256+
key <- getKey
257+
case key of
258+
"n" -> do
259+
atomically $ do
260+
print_state <- readTMVar print_state_var
261+
let print_state_style = if print_state.printName == PrintName then PrintDerivationPath else PrintName
262+
writeTMVar print_state_var $ print_state{printName = print_state_style}
263+
writeTMVar input_received ()
264+
"?" -> do
265+
atomically $ do
266+
print_state <- takeTMVar print_state_var
267+
putTMVar print_state_var $ print_state{printHelp = True}
268+
writeTMVar input_received ()
269+
_ -> pure ()
270+
writeToScreen :: IO ()
271+
writeToScreen = writeStateToScreen (not config.silent) linesVar state_var print_state_var output_builder_var refresh_display_var maintenance printer output_handle
245272
keepPrinting :: IO ()
246273
keepPrinting = forever do
247-
race_ (concurrently_ (threadDelay minFrameDuration) waitForInput) (threadDelay maxFrameDuration)
274+
runConcurrently
275+
$ (Concurrently (threadDelay minFrameDuration) *> Concurrently waitForInput)
276+
<|> Concurrently (threadDelay maxFrameDuration)
277+
<|> Concurrently (atomically $ takeTMVar input_received)
248278
writeToScreen
249-
race_ keepProcessing keepPrinting
279+
runConcurrently
280+
$ Concurrently keepProcessing
281+
<|> Concurrently keepProcessingStdin
282+
<|> Concurrently keepPrinting
250283
atomically (takeTMVar state_var) >>= execStateT finalize >>= atomically . putTMVar state_var
251284
writeToScreen
252285
(if isNothing printerMay then (>>= execStateT finalize) else id) $ atomically $ takeTMVar state_var

lib/NOM/Print.hs

Lines changed: 13 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,8 @@ import NOM.State (
2929
InputDerivation (..),
3030
NOMState,
3131
NOMV1State (..),
32+
PrintNameStyle (..),
33+
PrintState (..),
3234
ProgressState (..),
3335
StorePathId,
3436
StorePathInfo (..),
@@ -151,8 +153,8 @@ printErrors errors maxHeight =
151153
compactError :: Text -> Text
152154
compactError = fst . Text.breakOn "\n last 10 log lines:"
153155

154-
stateToText :: Config -> NOMV1State -> Maybe (Window Int) -> (ZonedTime, Double) -> Text
155-
stateToText config buildState@MkNOMV1State{..} = memo printWithSize . fmap Window.height
156+
stateToText :: Config -> NOMV1State -> PrintState -> Maybe (Window Int) -> (ZonedTime, Double) -> Text
157+
stateToText config buildState@MkNOMV1State{..} printState = memo printWithSize . fmap Window.height
156158
where
157159
printWithSize :: Maybe Int -> (ZonedTime, Double) -> Text
158160
printWithSize maybeWindow = printWithTime
@@ -182,7 +184,7 @@ stateToText config buildState@MkNOMV1State{..} = memo printWithSize . fmap Windo
182184
horizontal
183185
(vertical <> " ")
184186
(vertical <> " ")
185-
(printBuilds buildState hostNums maxHeight now)
187+
(printBuilds buildState printState hostNums maxHeight now)
186188
errorDisplay = printErrors nixErrors maxHeight
187189
traceDisplay = printTraces nixTraces maxHeight
188190
-- evalMessage = case evaluationState.lastFileName of
@@ -303,11 +305,12 @@ ifTimeDurRelevant dur mod' = memptyIfFalse (dur > 1) (mod' [clock, printDuration
303305

304306
printBuilds ::
305307
NOMV1State ->
308+
PrintState ->
306309
[(Host, Int)] ->
307310
Int ->
308311
Double ->
309312
NonEmpty Text
310-
printBuilds nomState@MkNOMV1State{..} hostNums maxHeight = printBuildsWithTime
313+
printBuilds nomState@MkNOMV1State{..} print_state hostNums maxHeight = printBuildsWithTime
311314
where
312315
hostLabel :: Bool -> Host -> Text
313316
hostLabel color host = (if color then markup magenta else id) $ maybe (toText host) (("[" <>) . (<> "]") . show) (List.lookup host hostNums)
@@ -453,8 +456,12 @@ printBuilds nomState@MkNOMV1State{..} hostNums maxHeight = printBuildsWithTime
453456
phaseMay activityId' = do
454457
activityId <- Strict.toLazy activityId'
455458
activity_status <- IntMap.lookup activityId.value nomState.activities
456-
Strict.toLazy $ activity_status.phase
457-
drvName = appendDifferingPlatform nomState drvInfo drvInfo.name.storePath.name
459+
Strict.toLazy activity_status.phase
460+
printStyle = print_state.printName
461+
storePathName = case printStyle of
462+
PrintName -> drvInfo.name.storePath.name
463+
PrintDerivationPath -> "/nix/store/" <> drvInfo.name.storePath.hash <> "-" <> drvInfo.name.storePath.name <> ".drv"
464+
drvName = appendDifferingPlatform nomState drvInfo storePathName
458465
downloadingOutputs = store_paths_in_map drvInfo.dependencySummary.runningDownloads
459466
uploadingOutputs = store_paths_in_map drvInfo.dependencySummary.runningUploads
460467
plannedDownloads = store_paths_in drvInfo.dependencySummary.plannedDownloads

lib/NOM/State.hs

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,9 @@ module NOM.State (
2424
InterestingActivity (..),
2525
InputDerivation (..),
2626
EvalInfo (..),
27+
PrintState (..),
28+
PrintNameStyle (..),
29+
initPrintState,
2730
getDerivationInfos,
2831
initalStateFromBuildPlatform,
2932
updateSummaryForStorePath,
@@ -194,6 +197,21 @@ data EvalInfo = MkEvalInfo
194197
}
195198
deriving stock (Show, Eq, Ord, Generic)
196199

200+
data PrintNameStyle = PrintName | PrintDerivationPath deriving stock (Show, Eq, Ord, Generic)
201+
202+
data PrintState = MkPrintState
203+
{ printName :: PrintNameStyle
204+
, printHelp :: Bool
205+
}
206+
deriving stock (Show, Eq, Ord, Generic)
207+
208+
initPrintState :: PrintState
209+
initPrintState =
210+
MkPrintState
211+
{ printName = PrintName
212+
, printHelp = False
213+
}
214+
197215
data NOMV1State = MkNOMV1State
198216
{ derivationInfos :: DerivationMap DerivationInfo
199217
, storePathInfos :: StorePathMap StorePathInfo

0 commit comments

Comments
 (0)