terminal-progress-bar-0.4.0.1: A simple progress bar in the terminal

Safe HaskellNone
LanguageHaskell2010

System.ProgressBar

Contents

Description

A simple progress bar in the terminal.

A progress bar is used to convey the progress of a task. This module implements a very simple textual progress bar.

Synopsis

How to use this library

We want to perform some task which we expect to take some time. We wish to show the progress of this task in the terminal.

First we write a dummy function which represents a unit of work. This could be a file copy operation, a network operation or some other expensive calculation. In this example we simply wait 1 second.

  work :: IO ()
  work = threadDelay 1000000 -- 1 second

And we define some work to be done.

  toBeDone :: [()]
  toBeDone = replicate 20 ()

Now we create a progress bar in the terminal. We use the default style and choose a maximum refresh rate of 10 Hz. The initial progress is 0 work done out of 20.

  pb <- newProgressBar defStyle 10 (Progress 0 20 ())

Let's start working while keeping the user informed of the progress:

  for_ toBeDone $ () -> do
    work             -- perform 1 unit of work
    incProgress pb 1 -- increment progress by 1

That's it! You get a nice animated progress bar in your terminal. It will look something like this:

[==========>................................]  25%

Explore the Style and the Label types to see various ways in which you can customize the way the progress bar looks.

You do not have to close the progress bar, or even finish the task. It is perfectly fine to stop half way (maybe your task throws an exception).

Just remember to avoid outputting text to the terminal while a progress bar is active. It will mess up the output a bit.

Progress bars

data ProgressBar s Source #

A terminal progress bar.

A ProgressBar value contains the state of a progress bar.

It is produced by newProgressBar and hNewProgressBar. It is updated by updateProgress and incProgress.

Instances
NFData s => NFData (ProgressBar s) Source # 
Instance details

Defined in System.ProgressBar

Methods

rnf :: ProgressBar s -> () #

newProgressBar Source #

Arguments

:: Style s

Visual style of the progress bar.

-> Double

Maximum refresh rate in Hertz.

-> Progress s

Initial progress.

-> IO (ProgressBar s) 

Creates a new progress bar.

The progress bar is drawn immediately. You can update the progress bar using updateProgress or incProgress. You shouldn't output anything to your terminal between updates. It will mess up the animation.

The progress bar is written to stderr. Use hNewProgressBar if you would like the progress bar output send to another handle.

hNewProgressBar Source #

Arguments

:: Handle

File handle on which the progress bar is drawn. Usually you would select a standard stream like stderr or stdout.

-> Style s

Visual style of the progress bar.

-> Double

Maximum refresh rate in Hertz.

-> Progress s

Initial progress.

-> IO (ProgressBar s) 

Creates a new progress bar on a given handle.

See newProgressBar for more information.

renderProgressBar :: Style s -> Progress s -> Timing -> Text Source #

Renders a progress bar.

>>> let t = UTCTime (ModifiedJulianDay 0) 0
>>> renderProgressBar defStyle (Progress 30 100 ()) (Timing t t)
"[============>..............................]  30%"

Not that this function can not use TerminalWidth because it doesn't use IO. Use progressBar or hProgressBar to get automatic width.

updateProgress Source #

Arguments

:: ProgressBar s

Progress bar which needs an update.

-> (Progress s -> Progress s)

Function to change the progress.

-> IO () 

Change the progress of an existing progress bar.

This will cause the progress bar to be redrawn. If updates occur to fast some updates will not be drawn.

This function is thread safe, but blocking. Multiple threads may update a single progress bar at the same time.

incProgress Source #

Arguments

:: ProgressBar s

Progress bar which needs an update.

-> Int

Amount by which the increment the progress.

-> IO () 

Increment the progress of an existing progress bar.

See updateProgress for more information.

Options

data Style s Source #

Options that determine the textual representation of a progress bar.

The textual representation of a progress bar follows the following template:

<prefix><open><done><current><todo><close><postfix>

Where <done> and <todo> are repeated as often as necessary.

Consider the following progress bar

"Working [=======>.................]  30%"

This bar can be specified using the following style:

Style
{ styleOpen    = "["
, styleClose   = "]"
, styleDone    = '='
, styleCurrent = '>'
, styleTodo    = '.'
, stylePrefix  = msg "Working"
, stylePostfix = percentage
, styleWidth   = ConstantWidth 40
, styleEscapeOpen    = const empty
, styleEscapeClose   = const empty
, styleEscapeDone    = const empty
, styleEscapeCurrent = const empty
, styleEscapeTodo    = const empty
, styleEscapePrefix  = const empty
, styleEscapePostfix = const empty
}

Constructors

Style 

Fields

Instances
Generic (Style s) Source # 
Instance details

Defined in System.ProgressBar

Associated Types

type Rep (Style s) :: Type -> Type #

Methods

from :: Style s -> Rep (Style s) x #

to :: Rep (Style s) x -> Style s #

NFData s => NFData (Style s) Source # 
Instance details

Defined in System.ProgressBar

Methods

rnf :: Style s -> () #

type Rep (Style s) Source # 
Instance details

Defined in System.ProgressBar

type Rep (Style s) = D1 (MetaData "Style" "System.ProgressBar" "terminal-progress-bar-0.4.0.1-GP7WacvU9SLabrqXY70gz" False) (C1 (MetaCons "Style" PrefixI True) (((S1 (MetaSel (Just "styleOpen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "styleClose") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "styleDone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char))) :*: ((S1 (MetaSel (Just "styleCurrent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char) :*: S1 (MetaSel (Just "styleTodo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char)) :*: (S1 (MetaSel (Just "stylePrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Label s)) :*: S1 (MetaSel (Just "stylePostfix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Label s))))) :*: (((S1 (MetaSel (Just "styleWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProgressBarWidth) :*: S1 (MetaSel (Just "styleEscapeOpen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s))) :*: (S1 (MetaSel (Just "styleEscapeClose") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s)) :*: S1 (MetaSel (Just "styleEscapeDone") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s)))) :*: ((S1 (MetaSel (Just "styleEscapeCurrent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s)) :*: S1 (MetaSel (Just "styleEscapeTodo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s))) :*: (S1 (MetaSel (Just "styleEscapePrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s)) :*: S1 (MetaSel (Just "styleEscapePostfix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EscapeCode s)))))))

type EscapeCode s Source #

Arguments

 = Progress s

Current progress bar state.

-> Text

Resulting escape code. Must be non-printable.

An escape code is a sequence of bytes which the terminal looks for and interprets as commands, not as character codes.

It is vital that the output of this function, when send to the terminal, does not result in characters being drawn.

defStyle :: Style s Source #

A default style.

You can override some fields of the default instead of specifying all the fields of a Style record.

The default does not use any escape sequences.

data ProgressBarWidth Source #

Width of progress bar in characters.

Constructors

ConstantWidth !Int

A constant width.

TerminalWidth !Int

Use the entire width of the terminal.

Identical to ConstantWidth if the width of the terminal can not be determined.

Instances
Generic ProgressBarWidth Source # 
Instance details

Defined in System.ProgressBar

Associated Types

type Rep ProgressBarWidth :: Type -> Type #

NFData ProgressBarWidth Source # 
Instance details

Defined in System.ProgressBar

Methods

rnf :: ProgressBarWidth -> () #

type Rep ProgressBarWidth Source # 
Instance details

Defined in System.ProgressBar

type Rep ProgressBarWidth = D1 (MetaData "ProgressBarWidth" "System.ProgressBar" "terminal-progress-bar-0.4.0.1-GP7WacvU9SLabrqXY70gz" False) (C1 (MetaCons "ConstantWidth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: C1 (MetaCons "TerminalWidth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

Progress

data Progress s Source #

An amount of progress.

Constructors

Progress 

Fields

Labels

newtype Label s Source #

A label that can be pre- or postfixed to a progress bar.

Constructors

Label 

Fields

Instances
IsString (Label s) Source # 
Instance details

Defined in System.ProgressBar

Methods

fromString :: String -> Label s #

Semigroup (Label s) Source # 
Instance details

Defined in System.ProgressBar

Methods

(<>) :: Label s -> Label s -> Label s #

sconcat :: NonEmpty (Label s) -> Label s #

stimes :: Integral b => b -> Label s -> Label s #

Monoid (Label s) Source # 
Instance details

Defined in System.ProgressBar

Methods

mempty :: Label s #

mappend :: Label s -> Label s -> Label s #

mconcat :: [Label s] -> Label s #

NFData (Label s) Source # 
Instance details

Defined in System.ProgressBar

Methods

rnf :: Label s -> () #

data Timing Source #

Timing information related to a ProgressBar.

This information is used by Labels to calculate elapsed time, remaining time, total time, etc.

Constructors

Timing 

Fields

msg :: Text -> Label s Source #

A label consisting of a static string.

>>> msg "foo" st
"foo"

percentage :: Label s Source #

A label which displays the progress as a percentage.

>>> runLabel $ percentage (Progress 30 100 ()) someTiming
" 30%"

Note: if no work is to be done (todo == 0) the percentage will always be 100%.

exact :: Label s Source #

A label which displays the progress as a fraction of the total amount of work.

Equal width property - the length of the resulting label is a function of the total amount of work:

>>> runLabel $ exact (Progress 30 100 ()) someTiming
" 30/100"

elapsedTime :: (NominalDiffTime -> Text) -> Label s Source #

A label which displays the amount of time that has elapsed.

Time starts when a progress bar is created.

The user must supply a function which actually renders the amount of time that has elapsed. You can use renderDuration or formatTime from time >= 1.9.

remainingTime Source #

Arguments

:: (NominalDiffTime -> Text) 
-> Text

Alternative message when remaining time can't be calculated (yet).

-> Label s 

Displays the estimated remaining time until all work is done.

Tells you how much longer some task will take.

This label uses a really simple estimation algorithm. It assumes progress is linear. To prevent nonsense results it won't estimate remaining time until at least 1 second of work has been done.

When it refuses to estimate the remaining time it will show an alternative message instead.

The user must supply a function which actually renders the amount of time that has elapsed. You can use renderDuration or formatTime from time >= 1.9.

totalTime Source #

Arguments

:: (NominalDiffTime -> Text) 
-> Text

Alternative message when total time can't be calculated (yet).

-> Label s 

Displays the estimated total time a task will take.

This label uses a really simple estimation algorithm. It assumes progress is linear. To prevent nonsense results it won't estimate the total time until at least 1 second of work has been done.

When it refuses to estimate the total time it will show an alternative message instead.

The user must supply a function which actually renders the total amount of time that a task will take. You can use renderDuration or formatTime from time >= 1.9.

renderDuration :: NominalDiffTime -> Text Source #

Show amount of time.

renderDuration (fromInteger 42)

42

renderDuration (fromInteger $ 5 * 60 + 42)

05:42

renderDuration (fromInteger $ 8 * 60 * 60 + 5 * 60 + 42)

08:05:42

Use the time >= 1.9 package to get a formatTime function which accepts NominalDiffTime.