concurrent-output-1.10.6: Ungarble output from several threads or commands

Copyright2015 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 lines 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
 import System.Process
 
 main = displayConsoleRegions $ do
 	mapConcurrently download [1..5]
		`concurrently` mapM_ message [1..10]
		`concurrently` createProcessConcurrent (proc "echo" ["hello world"])
 
 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
hello world
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
hello world
Message 2
Download 1 done!
Message 3
Download 2 ... ...
Download 3 ... ...
Synopsis

Types

data ConsoleRegion Source #

A handle allowing access to a region of the console.

Instances
Eq ConsoleRegion Source # 
Instance details

Defined in System.Console.Regions

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
ddddeeeefffffff -- [InLine]
fffffggggg.....       (expanded to multiple lines)

Constructors

Linear 
InLine ConsoleRegion 
Instances
Eq RegionLayout Source # 
Instance details

Defined in System.Console.Regions

class ToRegionContent v where Source #

Values that can be displayed in a region.

Minimal complete definition

toRegionContent

Instances
ToRegionContent String Source # 
Instance details

Defined in System.Console.Regions

ToRegionContent Text Source #

Note that using a lazy Text in a region will buffer it all in memory.

Instance details

Defined in System.Console.Regions

ToRegionContent Text Source # 
Instance details

Defined in System.Console.Regions

ToRegionContent (STM Text) Source #

Makes a STM action be run to get the content of a region.

Any change to the values that action reads will result in an immediate refresh of the display.

Instance details

Defined in System.Console.Regions

newtype RegionContent Source #

Constructors

RegionContent (STM Text) 

class LiftRegion m where Source #

Many actions in this module can be run in either the IO monad or the STM monad. Using STM allows making several changes to the displayed regions atomically, with the display updated a single time.

Minimal complete definition

liftRegion

Methods

liftRegion :: STM a -> m a Source #

Instances
LiftRegion IO Source # 
Instance details

Defined in System.Console.Regions

Methods

liftRegion :: STM a -> IO a Source #

LiftRegion STM Source # 
Instance details

Defined in System.Console.Regions

Methods

liftRegion :: STM a -> STM a Source #

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.

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

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

openConsoleRegion :: LiftRegion m => RegionLayout -> m ConsoleRegion Source #

Opens a new console region.

newConsoleRegion :: LiftRegion m => ToRegionContent v => RegionLayout -> v -> m ConsoleRegion Source #

Makes a new region, but does not add it to the display.

closeConsoleRegion :: LiftRegion m => ConsoleRegion -> m () Source #

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

Region content and display

setConsoleRegion :: (ToRegionContent v, LiftRegion m) => ConsoleRegion -> v -> m () Source #

Sets the value of a console region. This will cause the console to be updated to display the new value.

It's fine for the value to be longer than the terminal is wide, or to include newlines ('\n'). Regions expand to multiple lines as necessary.

The value can include ANSI SGR escape sequences for changing the colors etc of all or part of a region.

Other ANSI escape sequences, especially those doing cursor movement, will mess up the layouts of regions. Caveat emptor.

appendConsoleRegion :: (Outputable v, LiftRegion m) => ConsoleRegion -> v -> m () Source #

Appends a value to the current value of a console region.

appendConsoleRegion progress "." -- add another dot to progress display

finishConsoleRegion :: (Outputable v, LiftRegion m) => ConsoleRegion -> v -> m () Source #

Closes the console region, and displays the passed value in the scrolling area above the active console regions. When Nothing is passed, displays the current value of the console region.

getConsoleRegion :: LiftRegion m => ConsoleRegion -> m Text Source #

Gets the current content of a console region.

tuneDisplay :: LiftRegion m => ConsoleRegion -> (Text -> STM Text) -> m () Source #

Changes how a console region displays.

Each time the region's value changes, the STM action is provided with the current value of the region, and returns the value to display.

For example, this will prevent a region from ever displaying more than 10 characters wide, and will make it display text reversed:

tuneDisplay myregion $ pure . T.take 10
tuneDisplay myregion $ pure . T.reverse

Note that repeated calls to tuneDisplay are cumulative.

Normally, the STM action should avoid retrying, as that would block all display updates.

STM region contents

The ToRegionContent instance for STM Text can be used to make regions that automatically update whenever there's a change to any of the STM values that they use.

For example, a region that displays the screen size, and automatically refreshes it:

import qualified Data.Text as T
 r <- openConsoleRegion Linear s
 setConsoleRegion r $ do
 	w <- readTVar consoleWidth
 	h <- readTVar consoleHeight
 	return $ T.pack $ unwords
 		[ "size:"
		, show w
 		, "x"
		, show h
 		]

consoleWidth :: STM Int Source #

Gets the width of the console.

On Unix, this is automatically updated when the terminal is resized. On Windows, it is only initialized on program start.

consoleHeight :: STM Int Source #

Get the height of the console.

regionList :: TMVar [ConsoleRegion] Source #

All the regions that are currently displayed on the screen.

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.

waitDisplayChange :: STM a -> IO a Source #

Runs a STM action, and waits for the display to be fully updated before returning.