Skip to content

Commit

Permalink
Added label functions and auto-padding
Browse files Browse the repository at this point in the history
  • Loading branch information
roelvandijk committed Jan 30, 2012
1 parent d8cb71d commit bb9bed1
Showing 1 changed file with 58 additions and 14 deletions.
72 changes: 58 additions & 14 deletions src/System/ProgressBar.hs
@@ -1,15 +1,28 @@
{-# LANGUAGE NoImplicitPrelude, PackageImports, UnicodeSyntax #-}

module System.ProgressBar ( progressBar ) where
module System.ProgressBar
( -- * Progress bars
progressBar
, mkProgressBar
-- * Labels
, Label
, noLabel
, percentage
, exact
) where

import "base" Control.Monad ( when )
import "base" Data.Bool ( otherwise )
import "base" Data.Function ( ($) )
import "base" Data.List ( genericReplicate )
import "base" Data.Int ( Int )
import "base" Data.List ( (++), null, genericLength, genericReplicate )
import "base" Data.Ord ( max )
import "base" Data.Ratio ( (%) )
import "base" Data.String ( String )
import "base" Prelude ( (-), round )
import "base" System.IO ( IO, putStr, putChar )
import "base" Text.Printf ( printf )
import "base" Text.Show ( show )
import "base-unicode-symbols" Data.Eq.Unicode ( (≢) )
import "base-unicode-symbols" Prelude.Unicode ( , , (⋅) )

Expand All @@ -19,22 +32,53 @@ import "base-unicode-symbols" Prelude.Unicode ( ℤ, ℚ, (⋅) )
-- Erases the current line! (by outputting '\r') Does not print a
-- newline '\n'. Subsequent invocations will overwrite the previous
-- output.
progressBar -- ^ Width in characters.
-- ^ Current progress.
progressBar Label -- ^ Prefixed label.
Label -- ^ Postfixed label.
-- ^ Total progress bar width in characters.
-- ^ Amount of work completed.
-- ^ Total amount of work.
IO ()
progressBar width fraction = do
progressBar mkPreLabel mkPostLabel width todo done = do
putChar '\r'
putStr $ progressBarString width fraction
putStr $ mkProgressBar mkPreLabel mkPostLabel width todo done

progressBarString String
progressBarString width fraction =
printf "%3i%% [%s%s]"
percentage
mkProgressBar Label
Label
String
mkProgressBar mkPreLabel mkPostLabel width todo done =
printf "%s%s[%s%s]%s%s"
preLabel
(pad preLabel)
(genericReplicate completed '=')
(genericReplicate remaining '.')
(pad postLabel)
postLabel
where
percentage
percentage = round $ fraction 100
completed = round $ fraction (width % 1)
remaining = width - completed
fraction = todo % done

effectiveWidth = max 0 $ width - 2 - genericLength preLabel - genericLength postLabel

completed = min effectiveWidth $ round $ fraction (effectiveWidth % 1)
remaining = effectiveWidth - completed

preLabel = mkPreLabel todo done
postLabel = mkPostLabel todo done

pad String String
pad s | null s = ""
| otherwise = " "


type Label = String

noLabel Label
noLabel _ _ = ""

percentage Label
percentage done todo = printf "%3i%%" (round (done % todo 100) )

exact Label
exact done todo = show done ++ "/" ++ show todo

0 comments on commit bb9bed1

Please sign in to comment.