| Copyright | 2015 Joey Hess <id@joeyh.name> | 
|---|---|
| License | BSD-2-clause | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
System.Console.Regions
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) rWill 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
- data ConsoleRegion
- data RegionLayout
- class ToRegionContent v where- toRegionContent :: v -> RegionContent
 
- newtype RegionContent = RegionContent (STM Text)
- class LiftRegion m where- liftRegion :: STM a -> m a
 
- displayConsoleRegions :: (MonadIO m, MonadMask m) => m a -> m a
- withConsoleRegion :: (MonadIO m, MonadMask m) => RegionLayout -> (ConsoleRegion -> m a) -> m a
- openConsoleRegion :: LiftRegion m => RegionLayout -> m ConsoleRegion
- newConsoleRegion :: LiftRegion m => ToRegionContent v => RegionLayout -> v -> m ConsoleRegion
- closeConsoleRegion :: LiftRegion m => ConsoleRegion -> m ()
- setConsoleRegion :: (ToRegionContent v, LiftRegion m) => ConsoleRegion -> v -> m ()
- appendConsoleRegion :: (Outputable v, LiftRegion m) => ConsoleRegion -> v -> m ()
- finishConsoleRegion :: (Outputable v, LiftRegion m) => ConsoleRegion -> v -> m ()
- getConsoleRegion :: LiftRegion m => ConsoleRegion -> m Text
- tuneDisplay :: LiftRegion m => ConsoleRegion -> (Text -> STM Text) -> m ()
- consoleWidth :: STM Int
- consoleHeight :: STM Int
- regionList :: TMVar [ConsoleRegion]
- waitDisplayChange :: STM a -> IO a
Types
data ConsoleRegion Source #
A handle allowing access to a region of the console.
Instances
| Eq ConsoleRegion Source # | |
| Defined in System.Console.Regions Methods (==) :: ConsoleRegion -> ConsoleRegion -> Bool # (/=) :: ConsoleRegion -> ConsoleRegion -> Bool # | |
data RegionLayout Source #
Controls how a region is laid out in the console.
Here's an annotated example of how the console layout works. Each sequence of the same letter represents a distinct region.
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 # | |
| Defined in System.Console.Regions | |
class ToRegionContent v where Source #
Values that can be displayed in a region.
Methods
toRegionContent :: v -> RegionContent Source #
Instances
| ToRegionContent Text Source # | |
| Defined in System.Console.Regions Methods toRegionContent :: Text -> RegionContent Source # | |
| ToRegionContent Text Source # | Note that using a lazy Text in a region will buffer it all in memory. | 
| Defined in System.Console.Regions Methods toRegionContent :: Text -> RegionContent Source # | |
| ToRegionContent String Source # | |
| Defined in System.Console.Regions Methods | |
| 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. | 
| Defined in System.Console.Regions Methods toRegionContent :: STM Text -> RegionContent Source # | |
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.
Methods
liftRegion :: STM a -> m a Source #
Instances
| LiftRegion STM Source # | |
| Defined in System.Console.Regions Methods liftRegion :: STM a -> STM a Source # | |
| LiftRegion IO Source # | |
| Defined in System.Console.Regions Methods liftRegion :: STM a -> IO 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. So,
 withConcurrentOutput and flushConcurrentOutput should not be run
 while this is in use, and will block.
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 of all or part of a region. For this to display properly, a reset escape sequence must be included to get the color back to default. System.Console.ANSI makes it easy to construct such values. For example:
import System.Console.ANSI setConsoleRegion region ( "hello " <> setSGRCode [SetColor Foreground Vivid Red] <> "Mars" <> setSGRCode [Reset] <> "!" )
Other ANSI escape sequences, especially those doing cursor movement, will mess up the layouts of regions. Caveat emptor.
ANSI SGR escape sequences that span multiple lines do not currently display as you might hope. (Patches would be accepted.)
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 determined at start. On WASM, the console width is hard coded to 80 since WASI does not provide a way to determine it.
consoleHeight :: STM Int Source #
Get the height of the console.
On Unix, this is automatically updated when the terminal is resized. On Windows, it is determined at start. On WASM, the console heigth is hard coded to 25 since WASI does not provide a way to determine it.
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 with any changes that action makes to the displayed regions.