{- * Programmer: Piotr Borek * E-mail: piotrborek@op.pl * Copyright 2016 Piotr Borek * * Distributed under the terms of the GPL (GNU Public License) * * This program is free software; you can redistribute it and/or modify * it under the terms of the GNU General Public License as published by * the Free Software Foundation; either version 2 of the License, or * (at your option) any later version. * * This program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program; if not, write to the Free Software * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -} {-#LANGUAGE FlexibleContexts #-} module Coin.UI.HistoryView ( HistoryViewWidget, historyViewNew, historyViewGetSelected, historyViewUpdate ) where import qualified System.Glib.Types as Gtk import qualified Graphics.UI.Gtk as Gtk import Graphics.UI.Gtk ( AttrOp(..) ) import Database.Persist import Control.Monad import Coin.DB.Tables import Coin.DB.Functions import Coin.UI.MainState import Coin.UI.Utils.CalendarUtils import Coin.Locale.Translate import Coin.Utils.ValueParser import Coin.Utils.TableView type HistoryData = (Entity OperationsTable, String, String, String, String, String, String, String, String) data HistoryViewWidget = HistoryViewWidget { historyViewContainer :: Gtk.TreeView, historyViewStore :: Gtk.ListStore HistoryData } instance Gtk.GObjectClass HistoryViewWidget where toGObject = Gtk.toGObject . historyViewContainer unsafeCastGObject = undefined instance Gtk.WidgetClass HistoryViewWidget instance Gtk.ContainerClass HistoryViewWidget instance Gtk.TreeViewClass HistoryViewWidget historyViewNew :: Bool -> Bool -> Bool -> IO HistoryViewWidget historyViewNew incomeVisible outcomeVisible transferVisible = do store <- Gtk.listStoreNew [] treeView <- Gtk.treeViewNewWithModel store col1 <- tableTextColumnNew (__"Date") store $ \(_, x, _, _, _, _, _, _, _ ) -> [ Gtk.cellText := x ] col2 <- tableTextColumnNew (__"From") store $ \(_, _, x, _, _, _, _, _, _ ) -> [ Gtk.cellText := x ] col3 <- tableTextColumnNew (__"To") store $ \(_, _, _, x, _, _, _, _, _ ) -> [ Gtk.cellText := x ] col4 <- tableTextColumnNew (__"Income") store $ \(_, _, _, _, x, _, _, _, _ ) -> [ Gtk.cellText := x ] col5 <- tableTextColumnNew (__"Outcome") store $ \(_, _, _, _, _, x, _, _, _ ) -> [ Gtk.cellText := x ] col6 <- tableTextColumnNew (__"Transfer") store $ \(_, _, _, _, _, _, x, _, _ ) -> [ Gtk.cellText := x ] col7 <- tableTextColumnNew (__"Tag") store $ \(_, _, _, _, _, _, _, x, _ ) -> [ Gtk.cellText := x ] col8 <- tableTextColumnNew (__"Description") store $ \(_, _, _, _, _, _, _, _, x ) -> [ Gtk.cellText := x ] forM_ [col1, col2, col3, col4, col5, col6, col7, col8] $ Gtk.treeViewAppendColumn treeView Gtk.treeViewColumnSetVisible col4 incomeVisible Gtk.treeViewColumnSetVisible col5 outcomeVisible Gtk.treeViewColumnSetVisible col6 transferVisible Gtk.treeViewColumnSetVisible col2 transferVisible Gtk.treeViewColumnSetVisible col3 transferVisible Gtk.treeViewSetHeadersVisible treeView True return $ HistoryViewWidget treeView store historyViewGetSelected :: HistoryViewWidget -> IO (Maybe (Entity OperationsTable)) historyViewGetSelected view = do (path, _) <- Gtk.treeViewGetCursor $ historyViewContainer view if path == [] then return Nothing else do (entity, _, _, _, _, _, _, _, _ ) <- Gtk.listStoreGetValue (historyViewStore view) (head path) return $ Just entity historyViewUpdate :: MainState -> HistoryViewWidget -> [Entity OperationsTable] -> IO () historyViewUpdate mainState view entities = do list <- historyViewUpdate' mainState entities Gtk.listStoreClear $ historyViewStore view forM_ list $ Gtk.listStoreAppend (historyViewStore view) historyViewUpdate' :: MainState -> [Entity OperationsTable] -> IO [HistoryData] historyViewUpdate' mainState entities = do let incomeID = mainStateIncomeID mainState let outcomeID = mainStateOutcomeID mainState list <- runDB $ forM entities $ \entity@(Entity _ op) -> do let date = calendarShow $ operationsTableDate op (Just (Entity fromID from)) <- rawSqlFirstCached $ "SELECT ?? FROM AccountsTable WHERE id = " ++ showSqlKey (operationsTableFrom op) (Just (Entity toID to)) <- rawSqlFirstCached $ "SELECT ?? FROM AccountsTable WHERE id = " ++ showSqlKey (operationsTableTo op) let value = valueShow $ operationsTableValue op (Just (Entity _ tag)) <- rawSqlFirstCached $ "SELECT ?? FROM TagsTable WHERE id = " ++ showSqlKey (operationsTableTag op) let desc = operationsTableDescription op if | fromID == incomeID -> return (entity, date, "", "", value, "", "", tagsTableName tag, desc) | toID == outcomeID -> return (entity, date, "", "", "", value, "", tagsTableName tag, desc) | otherwise -> return (entity, date, accountsTableName from, accountsTableName to, "", "", value, tagsTableName tag, desc) return list