Skip to content

Commit

Permalink
(chore): rename a few variables in IO.hs
Browse files Browse the repository at this point in the history
Kind of a Nit.
  • Loading branch information
picnoir committed Dec 4, 2024
1 parent bd7035e commit 99cbe13
Show file tree
Hide file tree
Showing 2 changed files with 15 additions and 14 deletions.
25 changes: 13 additions & 12 deletions lib/NOM/IO.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module NOM.IO (interact, processTextStream, StreamParser, Stream, Window, Output) where
module NOM.IO (interact, mainIOLoop, StreamParser, Stream, Window, Output) where

import Control.Concurrent (threadDelay)
import Control.Concurrent.Async (Concurrently (Concurrently, runConcurrently))
Expand Down Expand Up @@ -201,7 +201,7 @@ interact ::
state ->
IO state
interact config parser updater maintenance printer finalize input_stream output_handle initialState =
processTextStream config parser updater maintenance (Just (printer, output_handle)) finalize initialState input_stream
mainIOLoop config parser updater maintenance (Just (printer, output_handle)) finalize initialState input_stream

-- frame durations are passed to threadDelay and thus are given in microseconds

Expand All @@ -223,7 +223,7 @@ getKey = reverse <$> getKey' ""
more <- System.IO.hReady stdin
(if more then getKey' else return) (char : chars)

processTextStream ::
mainIOLoop ::
forall update state.
Config ->
StreamParser update ->
Expand All @@ -234,24 +234,23 @@ processTextStream ::
state ->
Stream (Either NOMError ByteString) ->
IO state
processTextStream config parser updater maintenance printerMay finalize initialState inputStream = do
mainIOLoop config parser updater maintenance printerMay finalize initialState inputStream = do
state_var <- newTMVarIO initialState
print_state_var <- newTMVarIO initPrintState
input_received <- newEmptyTMVarIO
new_user_input <- newEmptyTMVarIO
output_builder_var <- newTVarIO []
refresh_display_var <- newTVarIO False
let keepProcessing :: IO ()
keepProcessing =
let keepProcessingNixCmd :: IO ()
keepProcessingNixCmd =
inputStream
& Stream.tap (errorsToBuilderFold output_builder_var)
& Stream.mapMaybe rightToMaybe
& parser
& Stream.fold (Fold.drainMapM (runUpdate output_builder_var state_var refresh_display_var updater))
waitForInput :: IO ()
waitForInput = atomically $ check =<< readTVar refresh_display_var
printerMay & maybe keepProcessing \(printer, output_handle) -> do
linesVar <- newTVarIO 0
let keepProcessingStdin :: IO ()
printerMay & maybe keepProcessingNixCmd \(printer, output_handle) -> do
printedLinesVar <- newTVarIO 0
let toggleHelp :: IO () = atomically $ do
print_state <- readTMVar print_state_var
writeTMVar print_state_var $ print_state{printHelp = not print_state.printHelp}
Expand Down Expand Up @@ -285,13 +284,15 @@ processTextStream config parser updater maintenance printerMay finalize initialS
_ -> writeStateToScreen (not config.silent) printedLinesVar state_var print_state_var output_builder_var refresh_display_var maintenance printer output_handle
keepPrinting :: IO ()
keepPrinting = forever do
-- Wait for either a Nix new input, the max frame duration (to update the timestamp), or a new input from the user.
runConcurrently
$ (Concurrently (threadDelay minFrameDuration) *> Concurrently waitForInput)
<|> Concurrently (threadDelay maxFrameDuration)
<|> Concurrently (atomically $ takeTMVar input_received)
<|> Concurrently (atomically $ takeTMVar new_user_input)
writeToScreen
-- Actual main loop.
runConcurrently
$ Concurrently keepProcessing
$ Concurrently keepProcessingNixCmd
<|> Concurrently keepProcessingStdin
<|> Concurrently keepPrinting
atomically (takeTMVar state_var) >>= execStateT finalize >>= atomically . putTMVar state_var
Expand Down
4 changes: 2 additions & 2 deletions test/Golden.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import Data.ByteString.Char8 qualified as ByteString
import Data.Text qualified as Text
import NOM.Builds (parseStorePath)
import NOM.Error (NOMError)
import NOM.IO (processTextStream)
import NOM.IO (mainIOLoop)
import NOM.IO.Input (NOMInput (..), UpdateResult (..))
import NOM.IO.Input.JSON ()
import NOM.IO.Input.OldStyle (OldStyleInput)
Expand Down Expand Up @@ -100,7 +100,7 @@ testBuild name config asserts =
testProcess :: forall input. (NOMInput input) => Stream.Stream IO ByteString -> IO NOMV1State
testProcess input = withParser @input \streamParser -> do
first_state <- firstState @input <$> initalStateFromBuildPlatform (Just "x86_64-linux")
end_state <- processTextStream @input @(UpdaterState input) (MkConfig False False) streamParser stateUpdater (\now -> nomState @input %~ maintainState now) Nothing (finalizer @input) first_state (Right <$> input)
end_state <- mainIOLoop @input @(UpdaterState input) (MkConfig False False) streamParser stateUpdater (\now -> nomState @input %~ maintainState now) Nothing (finalizer @input) first_state (Right <$> input)
pure (end_state ^. nomState @input)

stateUpdater :: forall input m. (NOMInput input, UpdateMonad m) => input -> StateT (UpdaterState input) m ([NOMError], ByteString, Bool)
Expand Down

0 comments on commit 99cbe13

Please sign in to comment.