-- | Buffers.hs -- A module which contain buffer structures (structures which contain -- text and info about opened rooms and privates). module Buffers where import Network.XMPP (TCPConnection) import Network.XMPP.Roster (RosterItem(..)) import Network.XMPP.Presence (Status(..), StatusType(..)) import Control.Concurrent (ThreadId) import Graphics.Vty (Event) import qualified Data.Map as M import Data.List type Buffers = M.Map Key Buffer type Key = String data Buffer = BufHelp [Content] | BufAccount Account | BufChat Chat | BufGroupchat Groupchat -- Show instances instance Show Buffer where show (BufHelp _) = "[help]" show (BufAccount acc) = case connection acc of OK _ _ -> c:" [o] "++accName acc NoConnection -> c:" [_] "++accName acc Trying -> c:" [c] "++accName acc where c = if accCollapsed acc then '+' else '-' show (BufChat chat) = " "++(show $ status chat)++ " "++(itemJid $ item chat) show (BufGroupchat _) = "" instance Show Status where show (Status StatusOnline _) = "[o]" show (Status StatusAway _) = "[a]" show (Status StatusChat _) = "[c]" show (Status StatusDND _) = "[d]" show (Status StatusXA _) = "[n]" show (Status StatusOffline _) = "[_]" data Account = Account { accName :: String , username :: String , server :: String , password :: String , resource :: String , defaultNick :: String , connection :: Connection , accCollapsed :: Bool } data Connection = OK TCPConnection ThreadId | NoConnection | Trying data Chat = Chat { item :: RosterItem , status :: Status , chatName :: String , chatConn :: TCPConnection , chatContents :: [Content] } data Groupchat = Groupchat { groupchatContents :: [Content] , groupchatNick :: String } -- | New contents goes at top for more eaiser insert. data Content = Msg String | MyMsg String | HistoryMsg String | InfoMsg String data MEvent = VtyEvent Event | InsBuffer Key Buffer | NewMsg Key Content | NewStatus Key Status insElem :: Key -> Buffer -> Buffers -> Buffers insElem k = M.insert k getAccount :: Key -> Buffers -> Maybe Account getAccount cur buffers = case M.lookup cur buffers of Just (BufAccount account) -> Just account _ -> Nothing getBuf :: Key -> Buffers -> Buffer getBuf cur buffers = case M.lookup cur buffers of Just buf -> buf _ -> BufHelp [] killBuffers :: String -> Buffers -> Buffers killBuffers startswith = M.filterWithKey (\k _ -> not $ startswith `isPrefixOf` k)