{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
-- | This module provides a progress bar widget.
module Brick.Widgets.ProgressBar
  ( progressBar
  -- * Attributes
  , progressCompleteAttr
  , progressIncompleteAttr
  )
where

import Lens.Micro ((^.))
import Data.Maybe (fromMaybe)
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid
#endif
import Graphics.Vty (safeWcswidth)

import Brick.Types
import Brick.AttrMap
import Brick.Widgets.Core

-- | The attribute of the completed portion of the progress bar.
progressCompleteAttr :: AttrName
progressCompleteAttr :: AttrName
progressCompleteAttr = "progressComplete"

-- | The attribute of the incomplete portion of the progress bar.
progressIncompleteAttr :: AttrName
progressIncompleteAttr :: AttrName
progressIncompleteAttr = "progressIncomplete"

-- | Draw a progress bar with the specified (optional) label and
-- progress value. This fills available horizontal space and is one row
-- high.
progressBar :: Maybe String
            -- ^ The label. If specified, this is shown in the center of
            -- the progress bar.
            -> Float
            -- ^ The progress value. Should be between 0 and 1 inclusive.
            -> Widget n
progressBar :: Maybe String -> Float -> Widget n
progressBar mLabel :: Maybe String
mLabel progress :: Float
progress =
    Size -> Size -> RenderM n (Result n) -> Widget n
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy Size
Fixed (RenderM n (Result n) -> Widget n)
-> RenderM n (Result n) -> Widget n
forall a b. (a -> b) -> a -> b
$ do
        Context
c <- RenderM n Context
forall n. RenderM n Context
getContext
        let barWidth :: Int
barWidth = Context
cContext -> Getting Int Context Int -> Int
forall s a. s -> Getting a s a -> a
^.Getting Int Context Int
Lens' Context Int
availWidthL
            label :: String
label = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe "" Maybe String
mLabel
            labelWidth :: Int
labelWidth = String -> Int
safeWcswidth String
label
            spacesWidth :: Int
spacesWidth = Int
barWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
labelWidth
            leftPart :: String
leftPart = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
spacesWidth Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` 2) ' '
            rightPart :: String
rightPart = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
barWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
labelWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
+ String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
leftPart)) ' '
            fullBar :: String
fullBar = String
leftPart String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
label String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
rightPart
            completeWidth :: Int
completeWidth = Float -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Float -> Int) -> Float -> Int
forall a b. (a -> b) -> a -> b
$ Float
progress Float -> Float -> Float
forall a. Num a => a -> a -> a
* Int -> Float
forall a. Enum a => Int -> a
toEnum (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
fullBar)
            completePart :: String
completePart = Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
completeWidth String
fullBar
            incompletePart :: String
incompletePart = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
completeWidth String
fullBar
        Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render (Widget n -> RenderM n (Result n))
-> Widget n -> RenderM n (Result n)
forall a b. (a -> b) -> a -> b
$ (AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
progressCompleteAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
completePart) Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+>
                 (AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
progressIncompleteAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ String -> Widget n
forall n. String -> Widget n
str String
incompletePart)