1- module NOM.IO (interact , processTextStream , StreamParser , Stream ) where
1+ module NOM.IO (interact , processTextStream , StreamParser , Stream , Window , Output ) where
22
33import 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 )
66import Data.ByteString qualified as ByteString
77import Data.ByteString.Builder qualified as Builder
88import Data.ByteString.Char8 qualified as ByteString
@@ -11,6 +11,7 @@ import Data.Time (ZonedTime, getZonedTime)
1111import NOM.Error (NOMError )
1212import NOM.Print (Config (.. ))
1313import NOM.Print.Table as Table (bold , displayWidth , displayWidthBS , markup , red , truncate )
14+ import NOM.State (PrintNameStyle (.. ), PrintState (.. ), initPrintState )
1415import NOM.Update.Monad (UpdateMonad , getNow )
1516import Relude
1617import Streamly.Data.Fold qualified as Fold
@@ -28,7 +29,7 @@ type Output = Text
2829
2930type 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
3334type 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+
217226processTextStream ::
218227 forall update state .
219228 Config ->
@@ -227,6 +236,8 @@ processTextStream ::
227236 IO state
228237processTextStream 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
0 commit comments