{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Brick.Widgets.ProgressBar
  ( progressBar
  
  , 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
progressCompleteAttr :: AttrName
progressCompleteAttr = "progressComplete"
progressIncompleteAttr :: AttrName
progressIncompleteAttr = "progressIncomplete"
progressBar :: Maybe String
            
            
            -> Float
            
            -> Widget n
progressBar mLabel progress =
    Widget Greedy Fixed $ do
        c <- getContext
        let barWidth = c^.availWidthL
            label = fromMaybe "" mLabel
            labelWidth = safeWcswidth label
            spacesWidth = barWidth - labelWidth
            leftPart = replicate (spacesWidth `div` 2) ' '
            rightPart = replicate (barWidth - (labelWidth + length leftPart)) ' '
            fullBar = leftPart <> label <> rightPart
            completeWidth = round $ progress * toEnum (length fullBar)
            completePart = take completeWidth fullBar
            incompletePart = drop completeWidth fullBar
        render $ (withAttr progressCompleteAttr $ str completePart) <+>
                 (withAttr progressIncompleteAttr $ str incompletePart)