terminal-progress-bar-0.4.2: A progress bar in the terminal
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.ProgressBar

Description

A progress bar in the terminal.

A progress bar conveys the progress of a task. Use a progress bar to provide a visual cue that processing is underway.

Synopsis

Getting started

You want to perform some task which will take some time. You wish to show the progress of this task in the terminal.

  1. Determine the total amount of work
  2. Create a progress bar with newProgressBar
  3. For each unit of work:

    3a. Perform the work

    3b. Update the progress bar with incProgress

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

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.

Example

Write a function which represents a unit of work. This could be a file copy operation, a network operation or some other expensive calculation. This example simply waits 1 second.

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

And you define some work to be done. This could be a list of files to process or some jobs that need to be processed.

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

Now create the progress bar. 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 ())

Start performing the work 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 like this:

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

Progress bars

data ProgressBar s Source #

A terminal progress bar.

A ProgressBar value contains the state of a progress bar.

Create a progress bar with newProgressBar or hNewProgressBar. Update a progress bar with updateProgress or incProgress.

Instances

Instances details
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 progress bar.

The progress bar is drawn immediately. Update the progress bar with updateProgress or incProgress. Do not output anything to your terminal between updates. It will mess up the animation.

The progress bar is written to stderr. Write to another handle with hNewProgressBar.

hNewProgressBar Source #

Arguments

:: Handle

File handle on which the progress bar is drawn. Usually you 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 progress bar which outputs to the given handle.

See newProgressBar.

renderProgressBar Source #

Arguments

:: Style s 
-> Progress s

Current progress.

-> Timing

Timing information.

-> Text

Textual representation of the Progress in the given Style.

Renders a progress bar.

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

Note that this function can not use TerminalWidth because it doesn't use IO. Use newProgressBar or hNewProgressBar to get automatic width.

updateProgress Source #

Arguments

:: forall s. ProgressBar s

Progress bar to update.

-> (Progress s -> Progress s)

Function to change the progress.

-> IO () 

Change the progress of a progress bar.

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

There is a maximum refresh rate. This means that some updates might not be drawn.

incProgress Source #

Arguments

:: ProgressBar s

Progress bar which needs an update.

-> Int

Amount by which to increment the progress.

-> IO () 

Increment the progress of an existing progress bar.

See updateProgress for more information.

Options

data Style s Source #

Visual style of a progress bar.

The style determines how a progress bar is rendered to text.

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
, styleOnComplete = WriteNewline
}

Constructors

Style 

Fields

Instances

Instances details
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.2-BMlLa4E394S7aHr1iIEVHn" '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)) :*: S1 ('MetaSel ('Just "styleOnComplete") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OnComplete))))))

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.

data OnComplete Source #

What happens when a progress bar is finished.

Constructors

WriteNewline

Write a new line when the progress bar is finished. The completed progress bar will remain visible.

Clear

Clear the progress bar once it is finished.

Instances

Instances details
Generic OnComplete Source # 
Instance details

Defined in System.ProgressBar

Associated Types

type Rep OnComplete :: Type -> Type #

NFData OnComplete Source # 
Instance details

Defined in System.ProgressBar

Methods

rnf :: OnComplete -> () #

type Rep OnComplete Source # 
Instance details

Defined in System.ProgressBar

type Rep OnComplete = D1 ('MetaData "OnComplete" "System.ProgressBar" "terminal-progress-bar-0.4.2-BMlLa4E394S7aHr1iIEVHn" 'False) (C1 ('MetaCons "WriteNewline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Clear" 'PrefixI 'False) (U1 :: Type -> Type))

defStyle :: Style s Source #

The default style.

This style shows the progress as a percentage. It does not use any escape sequences.

Override some fields of the default instead of specifying all the fields of a Style record.

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

Instances details
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.2-BMlLa4E394S7aHr1iIEVHn" '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

  • progressDone :: !Int

    Amount of work completed.

  • progressTodo :: !Int

    Total amount of work.

  • progressCustom :: !s

    A value which is used by custom labels. The builtin labels do not care about this field. You can ignore it by using the unit value ().

Labels

newtype Label s Source #

A label is a part of a progress bar that changes based on the progress.

Labels can be at the front (prefix) or at the back (postfix) of a progress bar.

Labels can use both the current amount of progress and the timing information to generate some text.

Constructors

Label 

Fields

Instances

Instances details
IsString (Label s) Source #

Every string is a label which ignores its input and just outputs that string.

Instance details

Defined in System.ProgressBar

Methods

fromString :: String -> Label s #

Monoid (Label s) Source #

The mempty label always outputs an empty text.

Instance details

Defined in System.ProgressBar

Methods

mempty :: Label s #

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

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

Semigroup (Label s) Source #

Combining labels combines their output.

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 #

NFData (Label s) Source # 
Instance details

Defined in System.ProgressBar

Methods

rnf :: Label s -> () #

data Timing Source #

Timing information about a ProgressBar.

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

See elapsedTime, remainingTime and totalTime.

Constructors

Timing 

Fields

msg :: Text -> Label s Source #

Static text.

The output does not depend on the input.

>>> msg "foo" st
"foo"

percentage :: Label s Source #

Progress as a percentage.

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

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

exact :: Label s Source #

Progress as a fraction of the total amount of work.

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

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

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 

Estimated remaining time.

Tells you how much longer some task is expected to take.

This label uses a 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. Use renderDuration or formatTime from the time >= 1.9 package.

totalTime Source #

Arguments

:: (NominalDiffTime -> Text) 
-> Text

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

-> Label s 

Estimated total time.

This label uses a 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 the time >= 1.9 package.

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.