File: test.hs

package info (click to toggle)
haskell-terminal-progress-bar 0.0.1.4-1
  • links: PTS, VCS
  • area: main
  • in suites: jessie, jessie-kfreebsd
  • size: 68 kB
  • ctags: 1
  • sloc: haskell: 196; makefile: 3
file content (69 lines) | stat: -rw-r--r-- 2,798 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
{-# LANGUAGE NoImplicitPrelude, PackageImports, UnicodeSyntax #-}

module Main where


--------------------------------------------------------------------------------
-- Imports
--------------------------------------------------------------------------------

import "base" Control.Monad      ( (=<<) )
import "base" Data.Function      ( ($) )
import "base" Prelude            ( String )
import "base" System.Environment ( getArgs )
import "base" System.IO          ( IO )
import "base-unicode-symbols" Prelude.Unicode ( ℤ )
import "HUnit" Test.HUnit.Base ( assertEqual )
import "test-framework" Test.Framework
    ( defaultMainWithOpts, interpretArgsOrExit, Test, testGroup )
import "test-framework-hunit" Test.Framework.Providers.HUnit ( testCase )
import "terminal-progress-bar" System.ProgressBar
    ( mkProgressBar, Label, noLabel, msg, percentage, exact )

--------------------------------------------------------------------------------
-- Test suite
--------------------------------------------------------------------------------

main ∷ IO ()
main = do opts ← interpretArgsOrExit =<< getArgs
          defaultMainWithOpts tests opts

tests ∷ [Test]
tests =
  [ testGroup "Label padding"
    [ eqTest "no labels"  "[]"          noLabel     noLabel      0 0 0
    , eqTest "pre"        "pre []"      (msg "pre") noLabel      0 0 0
    , eqTest "post"       "[] post"     noLabel     (msg "post") 0 0 0
    , eqTest "pre & post" "pre [] post" (msg "pre") (msg "post") 0 0 0
    ]
  , testGroup "Bar fill"
    [ eqTest "empty"       "[....]" noLabel noLabel 6  0   1
    , eqTest "almost half" "[=>..]" noLabel noLabel 6 49 100
    , eqTest "half"        "[==>.]" noLabel noLabel 6  1   2
    , eqTest "almost full" "[===>]" noLabel noLabel 6 99 100
    , eqTest "full"        "[====]" noLabel noLabel 6  1   1
    , eqTest "overfull"    "[====]" noLabel noLabel 6  2   1
    ]
  , testGroup "Labels"
    [ testGroup "Percentage"
      [ eqTest "  0%" "  0% [....]" percentage noLabel 11 0 1
      , eqTest "100%" "100% [====]" percentage noLabel 11 1 1
      , eqTest " 50%" " 50% [==>.]" percentage noLabel 11 1 2
      , eqTest "200%" "200% [====]" percentage noLabel 11 2 1
      ]
    , testGroup "Exact"
      [ eqTest "0/0" "0/0 [....]" exact noLabel 10 0 0
      , eqTest "1/1" "1/1 [====]" exact noLabel 10 1 1
      , eqTest "1/2" "1/2 [==>.]" exact noLabel 10 1 2
      , eqTest "2/1" "2/1 [====]" exact noLabel 10 2 1
      ]
    ]
  ]

eqTest ∷ String → String → Label → Label → ℤ → ℤ → ℤ → Test
eqTest name expected mkPreLabel mkPostLabel width todo done =
    testCase name $ assertEqual errMsg expected actual
  where
    actual = mkProgressBar mkPreLabel mkPostLabel width todo done
    errMsg = "Expected result doesn't match actual result"