concurrent-output-1.1.0: Ungarble output from several threads

Copyright2013 Joey Hess <id@joeyh.name>
LicenseBSD-2-clause
Safe HaskellNone
LanguageHaskell98

System.Console.Regions

Contents

Description

Console regions are displayed near the bottom of the console, and can be updated concurrently by threads. Any other output displayed using outputConcurrent and createProcessConcurrent will scroll up above the open console regions.

For example, this program:

 import Control.Concurrent.Async
 import Control.Concurrent
 import System.Console.Concurrent
 import System.Console.Regions
 
 main = displayConsoleRegions $ do
 	mapConcurrently download [1..5] `concurrently` mapM_ message [1..10]
 
 message :: Int -> IO ()
 message n = do
 	threadDelay 500000
 	outputConcurrent ("Message " ++ show n ++ "\n")
 
 download :: Int -> IO ()
 download n = withConsoleRegion Linear $ \r -> do
 	setConsoleRegion r basemsg
 	go n r
   where
 	basemsg = "Download " ++ show n
	go c r
		| c < 1 = finishConsoleRegion r (basemsg ++ " done!")
 		| otherwise = do
 			threadDelay 1000000
 			appendConsoleRegion r " ... "
 			go (c-1) r

Will display like this:

Message 1
Message 2
Download 1 ...
Download 2 ...
Download 3 ...

Once the 1st download has finished, and another message has displayed, the console will update like this:

Message 1
Message 2
Download 1 done!
Message 3
Download 2 ... ...
Download 3 ... ...

Synopsis

Initialization

displayConsoleRegions :: (MonadIO m, MonadMask m) => m a -> m a Source

Handles all display for the other functions in this module.

Note that this uses lockOutput, so it takes over all output to the console while the passed IO action is running. As well as displaying the console regions, this handles display of anything buffered by outputConcurrent and createProcessConcurrent.

When standard output is not an ANSI capable terminal, console regions are not displayed.

data RegionLayout Source

Controls how a region is laid out in the console.

Here's an annotated example of how the console layout works.

scrolling......
scrolling......
scrolling......
aaaaaa......... -- Linear
bbbbbbbbbbbbbbb -- Linear
bbb............       (expanded to multiple lines)
ccccccccc...... -- Linear
ddd eee fffffff -- [InLine]
ffff ggggg.....       (expanded to multiple lines)

withConsoleRegion :: (MonadIO m, MonadMask m) => RegionLayout -> (ConsoleRegionHandle -> m a) -> m a Source

Runs the action with a new console region, closing the region when the action finishes or on exception.

openConsoleRegion :: RegionLayout -> IO ConsoleRegionHandle Source

Opens a new console region for output.

closeConsoleRegion :: ConsoleRegionHandle -> IO () Source

Closes a console region. Once closed, the region is removed from the display.

Output

setConsoleRegion :: Outputable v => ConsoleRegionHandle -> v -> IO () Source

Sets the value to display within a console region.

appendConsoleRegion :: Outputable v => ConsoleRegionHandle -> v -> IO () Source

Appends the value to whatever was already on display within a console region.

finishConsoleRegion :: Outputable v => ConsoleRegionHandle -> v -> IO () Source

Closes the console region and displays the passed value in the scrolling area above the active console regions.

STM interface

These actions can be composed into a STM transaction; once the transaction completes the console will be updated a single time to reflect all the changes made.

openConsoleRegionSTM :: RegionLayout -> STM ConsoleRegionHandle Source

STM version of openConsoleRegion. Allows atomically opening multiple regions at the same time, which guarantees they are on adjacent lines.

 [r1, r2, r3] <- atomically $
	replicateM 3 (openConsoleRegionSTM Linear)

updateRegionListSTM :: ([ConsoleRegionHandle] -> [ConsoleRegionHandle]) -> STM () Source

Updates the list of regions. The list is ordered from the bottom of the screen up. Reordering it will change the order in which regions are displayed. It's also fine to remove, duplicate, or add new regions to the list.