module Taskell.UI.Draw.Main ( renderMain ) where import ClassyPrelude import Brick import Control.Lens ((^.)) import Data.Sequence (mapWithIndex) import Taskell.Events.State.Types (lists) import Taskell.IO.Config.Layout (padding, statusBar) import Taskell.UI.Draw.Main.List (renderList) import Taskell.UI.Draw.Main.Search (renderSearch) import Taskell.UI.Draw.Main.StatusBar (renderStatusBar) import Taskell.UI.Draw.Types (DSWidget, DrawState (..)) import Taskell.UI.Types (ResourceName (..)) renderMain :: DSWidget renderMain :: DSWidget renderMain = do Lists ls <- (State -> Getting Lists State Lists -> Lists forall s a. s -> Getting a s a -> a ^. Getting Lists State Lists Lens' State Lists lists) (State -> Lists) -> ReaderT DrawState Identity State -> ReaderT DrawState Identity Lists 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 [Widget ResourceName] listWidgets <- Seq (Widget ResourceName) -> [Widget ResourceName] forall mono. MonoFoldable mono => mono -> [Element mono] toList (Seq (Widget ResourceName) -> [Widget ResourceName]) -> ReaderT DrawState Identity (Seq (Widget ResourceName)) -> ReaderT DrawState Identity [Widget ResourceName] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Seq DSWidget -> ReaderT DrawState Identity (Seq (Widget ResourceName)) forall (t :: * -> *) (m :: * -> *) a. (Traversable t, Monad m) => t (m a) -> m (t a) sequence (Int -> List -> DSWidget renderList (Int -> List -> DSWidget) -> Lists -> Seq DSWidget forall a b. (Int -> a -> b) -> Seq a -> Seq b `mapWithIndex` Lists ls) Int pad <- Config -> Int padding (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 let mainWidget :: Widget ResourceName mainWidget = ResourceName -> ViewportType -> Widget ResourceName -> Widget ResourceName forall n. (Ord n, Show n) => n -> ViewportType -> Widget n -> Widget n viewport ResourceName RNLists ViewportType Horizontal (Widget ResourceName -> Widget ResourceName) -> (Widget ResourceName -> Widget ResourceName) -> Widget ResourceName -> Widget ResourceName forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Int -> Widget ResourceName -> Widget ResourceName forall n. Int -> Widget n -> Widget n padTopBottom Int pad (Widget ResourceName -> Widget ResourceName) -> Widget ResourceName -> Widget ResourceName forall a b. (a -> b) -> a -> b $ [Widget ResourceName] -> Widget ResourceName forall n. [Widget n] -> Widget n hBox [Widget ResourceName] listWidgets Widget ResourceName sb <- Widget ResourceName -> Widget ResourceName -> Bool -> Widget ResourceName forall a. a -> a -> Bool -> a bool Widget ResourceName forall n. Widget n emptyWidget (Widget ResourceName -> Bool -> Widget ResourceName) -> DSWidget -> ReaderT DrawState Identity (Bool -> Widget ResourceName) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> DSWidget renderStatusBar ReaderT DrawState Identity (Bool -> Widget ResourceName) -> ReaderT DrawState Identity Bool -> DSWidget forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (Config -> Bool statusBar (Config -> Bool) -> ReaderT DrawState Identity Config -> ReaderT DrawState Identity Bool 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) Widget ResourceName -> DSWidget renderSearch (Widget ResourceName mainWidget Widget ResourceName -> Widget ResourceName -> Widget ResourceName forall n. Widget n -> Widget n -> Widget n <=> Widget ResourceName sb)