module EVM.TTYCenteredList where
import Control.Lens
import Data.Maybe (fromMaybe)
import Brick.Types
import Brick.Widgets.Core
import Brick.Widgets.List
import qualified Data.Vector as V
renderList :: (Ord n, Show n)
           => (Bool -> e -> Widget n)
           
           -> Bool
           
           -> List n e
           
           -> Widget n
           
renderList drawElem foc l =
    withDefAttr listAttr $
    drawListElements foc l drawElem
drawListElements :: (Ord n, Show n) => Bool -> List n e -> (Bool -> e -> Widget n) -> Widget n
drawListElements foc l drawElem =
    Widget Greedy Greedy $ do
        c <- getContext
        let es = V.slice start num (l^.listElementsL)
            idx = fromMaybe 0 (l^.listSelectedL)
            start = max 0 $ idx - (initialNumPerHeight `div` 2)
            num = min (numPerHeight * 2) (V.length (l^.listElementsL) - start)
            
            
            initialNumPerHeight = (c^.availHeightL) `div` (l^.listItemHeightL)
            
            
            
            
            
            
            
            
            numPerHeight = initialNumPerHeight +
                           if initialNumPerHeight * (l^.listItemHeightL) == c^.availHeightL
                           then 0
                           else 1
            
            drawnElements = flip V.imap es $ \i e ->
                let isSelected = i == (if start == 0 then idx else div initialNumPerHeight 2)
                    elemWidget = drawElem isSelected e
                    selItemAttr = if foc
                                  then withDefAttr listSelectedFocusedAttr
                                  else withDefAttr listSelectedAttr
                    makeVisible = if isSelected
                                  then visible . selItemAttr
                                  else id
                in makeVisible elemWidget
        render $ viewport (l^.listNameL) Vertical $
                 
                 vBox $ V.toList drawnElements