{-# LANGUAGE RecordWildCards #-} -- | UI.hs -- User interface. module UI ( UIState(..), mkUI, mkTree, defaultUI ) where import Buffers import Config import qualified Widgets.Tree as T import qualified Widgets.EditBox as E import Widgets.PrettyBorders import Widgets.TextBox import Graphics.Vty import Graphics.Vty.Widgets.All import Data.Tree import qualified Data.Map as M import Data.List data UIState = UIState { roster :: T.Tree , textBox :: TextBox , edit :: E.EditBox } mkUI :: UIState -> Config -> Buffers -> Box mkUI (UIState {..}) config buffers = (if null $ getCF "show_roster" config then tb <--> text def_attr "" else roster <++> pVBorder def_attr <++> tb) <--> text (back blue) "info" <--> edit where tb = case getBuf (T.cur roster) buffers of BufHelp cnts -> mkTextBox cnts config BufChat chat -> mkTextBox (chatContents chat) config _ -> mkTextBox [] config mkTextBox :: [Content] -> Config -> TextBox mkTextBox cnts config = TextBox $ map cnt2line cnts where -- todo: read colors from config cnt2line (Msg msg) = (def_attr, msg) cnt2line (MyMsg msg) = (fore yellow, msg) cnt2line (HistoryMsg msg) = (fore cyan, msg) cnt2line (InfoMsg msg) = (fore cyan, msg) mkTree :: T.Tree -> Buffers -> T.Tree mkTree roster buffers = roster { T.nodes = ns } where -- all nodes ns = (Node (T.NodeData False ("[help]", "help")) []):(map mkAcc accs) -- accounts accs = [ buf | buf@(BufAccount _) <- M.elems buffers ] --- mkAcc buf@(BufAccount acc) = Node (T.NodeData (accCollapsed acc) (show buf, accName acc)) $ map (mkChat (accCollapsed acc)) (chats acc) mkChat coll buf@(BufChat chat) = Node (T.NodeData coll (show buf, chatName chat)) [] -- get all chats account chats acc = M.elems $ M.filterWithKey (filt (accName acc++"|")) buffers filt prefix k _ = prefix `isPrefixOf` k defaultUI :: Buffers -> UIState defaultUI buffers = UIState { roster = mkTree (T.defaultTree []) buffers , textBox = TextBox [] , edit = E.empty } --- fore = (def_attr `with_fore_color`) back = (def_attr `with_back_color`)