module Taskell.UI.Draw.Main.StatusBar ( renderStatusBar ) where import ClassyPrelude import Control.Lens ((^.)) import Brick import Taskell.Data.Lists (count) import Taskell.Events.State.Types (current, lists, mode, path, searchTerm) import Taskell.Events.State.Types.Mode (ModalType (..), Mode (..)) import Taskell.IO.Config.Layout (columnPadding) import Taskell.Types (ListIndex (ListIndex), TaskIndex (TaskIndex)) import Taskell.UI.Draw.Field (Field) import Taskell.UI.Draw.Types (DSWidget, DrawState (..), ReaderDrawState) import Taskell.UI.Theme getPosition :: ReaderDrawState Text getPosition :: ReaderDrawState Text getPosition = do (ListIndex Int col, TaskIndex Int pos) <- (State -> Getting (ListIndex, TaskIndex) State (ListIndex, TaskIndex) -> (ListIndex, TaskIndex) forall s a. s -> Getting a s a -> a ^. Getting (ListIndex, TaskIndex) State (ListIndex, TaskIndex) Lens' State (ListIndex, TaskIndex) current) (State -> (ListIndex, TaskIndex)) -> ReaderT DrawState Identity State -> ReaderT DrawState Identity (ListIndex, TaskIndex) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (DrawState -> State) -> ReaderT DrawState Identity State forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a asks DrawState -> State dsState Int len <- Int -> Lists -> Int count Int col (Lists -> Int) -> (State -> Lists) -> State -> Int forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (State -> Getting Lists State Lists -> Lists forall s a. s -> Getting a s a -> a ^. Getting Lists State Lists Lens' State Lists lists) (State -> Int) -> ReaderT DrawState Identity State -> ReaderT DrawState Identity Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (DrawState -> State) -> ReaderT DrawState Identity State forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a asks DrawState -> State dsState let posNorm :: Int posNorm = if Int len Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 0 then Int pos Int -> Int -> Int forall a. Num a => a -> a -> a + Int 1 else Int 0 Text -> ReaderDrawState Text forall (f :: * -> *) a. Applicative f => a -> f a pure (Text -> ReaderDrawState Text) -> Text -> ReaderDrawState Text forall a b. (a -> b) -> a -> b $ Int -> Text forall a. Show a => a -> Text tshow Int posNorm Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "/" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Int -> Text forall a. Show a => a -> Text tshow Int len modeToText :: Maybe Field -> Mode -> ReaderDrawState Text modeToText :: Maybe Field -> Mode -> ReaderDrawState Text modeToText Maybe Field fld Mode md = do Bool debug <- (DrawState -> Bool) -> ReaderT DrawState Identity Bool forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a asks DrawState -> Bool dsDebug Text -> ReaderDrawState Text forall (f :: * -> *) a. Applicative f => a -> f a pure (Text -> ReaderDrawState Text) -> Text -> ReaderDrawState Text forall a b. (a -> b) -> a -> b $ if Bool debug then Mode -> Text forall a. Show a => a -> Text tshow Mode md else case Mode md of Mode Normal -> case Maybe Field fld of Maybe Field Nothing -> Text "NORMAL" Just Field _ -> Text "NORMAL + SEARCH" Insert {} -> Text "INSERT" Modal ModalType Help -> Text "HELP" Modal ModalType MoveTo -> Text "MOVE" Modal Detail {} -> Text "DETAIL" Modal Due {} -> Text "DUE" Search {} -> Text "SEARCH" Mode _ -> Text "" getMode :: ReaderDrawState Text getMode :: ReaderDrawState Text getMode = do State state <- (DrawState -> State) -> ReaderT DrawState Identity State forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a asks DrawState -> State dsState Maybe Field -> Mode -> ReaderDrawState Text modeToText (State state State -> Getting (Maybe Field) State (Maybe Field) -> Maybe Field forall s a. s -> Getting a s a -> a ^. Getting (Maybe Field) State (Maybe Field) Lens' State (Maybe Field) searchTerm) (State state State -> Getting Mode State Mode -> Mode forall s a. s -> Getting a s a -> a ^. Getting Mode State Mode Lens' State Mode mode) renderStatusBar :: DSWidget renderStatusBar :: DSWidget renderStatusBar = do Text topPath <- [Element Text] -> Text forall seq. IsSequence seq => [Element seq] -> seq pack ([Element Text] -> Text) -> (State -> [Element Text]) -> State -> Text forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (State -> Getting FilePath State FilePath -> FilePath forall s a. s -> Getting a s a -> a ^. Getting FilePath State FilePath Lens' State FilePath path) (State -> Text) -> ReaderT DrawState Identity State -> ReaderDrawState Text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (DrawState -> State) -> ReaderT DrawState Identity State forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a asks DrawState -> State dsState Int colPad <- Config -> Int columnPadding (Config -> Int) -> ReaderT DrawState Identity Config -> ReaderT DrawState Identity Int forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (DrawState -> Config) -> ReaderT DrawState Identity Config forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a asks DrawState -> Config dsLayout Text posTxt <- ReaderDrawState Text getPosition Text modeTxt <- ReaderDrawState Text getMode let titl :: Widget n titl = Int -> Widget n -> Widget n forall n. Int -> Widget n -> Widget n padLeftRight Int colPad (Widget n -> Widget n) -> Widget n -> Widget n forall a b. (a -> b) -> a -> b $ Text -> Widget n forall n. Text -> Widget n txt Text topPath let pos :: Widget n pos = Padding -> Widget n -> Widget n forall n. Padding -> Widget n -> Widget n padRight (Int -> Padding Pad Int colPad) (Widget n -> Widget n) -> Widget n -> Widget n forall a b. (a -> b) -> a -> b $ Text -> Widget n forall n. Text -> Widget n txt Text posTxt let md :: Widget n md = Text -> Widget n forall n. Text -> Widget n txt Text modeTxt let bar :: Widget n bar = Padding -> Widget n -> Widget n forall n. Padding -> Widget n -> Widget n padRight Padding Max (Widget n forall n. Widget n titl Widget n -> Widget n -> Widget n forall n. Widget n -> Widget n -> Widget n <+> Widget n forall n. Widget n md) Widget n -> Widget n -> Widget n forall n. Widget n -> Widget n -> Widget n <+> Widget n forall n. Widget n pos Widget ResourceName -> DSWidget forall (f :: * -> *) a. Applicative f => a -> f a pure (Widget ResourceName -> DSWidget) -> (Widget ResourceName -> Widget ResourceName) -> Widget ResourceName -> DSWidget forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Padding -> Widget ResourceName -> Widget ResourceName forall n. Padding -> Widget n -> Widget n padTop (Int -> Padding Pad Int 1) (Widget ResourceName -> DSWidget) -> Widget ResourceName -> DSWidget forall a b. (a -> b) -> a -> b $ AttrName -> Widget ResourceName -> Widget ResourceName forall n. AttrName -> Widget n -> Widget n withAttr AttrName statusBarAttr Widget ResourceName forall n. Widget n bar