{- * Programmer: Piotr Borek * E-mail: piotrborek@op.pl * Copyright 2015 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 #-} {-#LANGUAGE TypeFamilies #-} {-#LANGUAGE GADTs #-} module Coin.DB.Functions ( EntityCache, runDB, rawSqlCached, rawSqlFirstCached, showSqlKey ) where import qualified Data.Map as Map import qualified Data.Text as T import qualified Control.Monad.State.Strict as State import qualified Data.Aeson as JSON import Control.Monad.Reader import Control.Monad.Trans.Control import Control.Monad.Logger import Control.Monad.Trans.Resource import Database.Persist.Sqlite import Data.Maybe import Coin.Config.Dirs type EntityCache = Map.Map T.Text JSON.Value #ifdef DEBUG_DB runDB :: (MonadBaseControl IO m, MonadIO m) => SqlPersistT (LoggingT (ResourceT (State.StateT EntityCache m))) a -> m a runDB action = do dir <- liftIO configGetDirectory State.evalStateT (runResourceT $ runStdoutLoggingT $ withSqliteConn (T.pack $ dir ++ "/coin.db") . runSqlConn $ action) Map.empty #else runDB :: (MonadBaseControl IO m, MonadIO m) => SqlPersistT (NoLoggingT (ResourceT (State.StateT EntityCache m))) a -> m a runDB action = do dir <- liftIO configGetDirectory State.evalStateT (runResourceT $ runNoLoggingT $ withSqliteConn (T.pack $ dir ++ "/coin.db") . runSqlConn $ action) Map.empty #endif rawSqlFirstCached :: (MonadLogger m, MonadIO m, State.MonadState EntityCache m, JSON.ToJSON a, JSON.FromJSON a, RawSql a) => String -> ReaderT SqlBackend m (Maybe a) rawSqlFirstCached stmt = listToMaybe <$> rawSqlCached stmt rawSqlCached :: (MonadLogger m, MonadIO m, State.MonadState EntityCache m, JSON.ToJSON a, JSON.FromJSON a, RawSql a) => String -> ReaderT SqlBackend m [a] rawSqlCached stmt = do let text = T.pack stmt cache <- State.get case Map.lookup text cache of Just val -> case JSON.fromJSON val of JSON.Success entities -> do logDebugNS (T.pack "CACHED") $ T.append text $ T.pack ";" return entities JSON.Error _ -> rawSql text [] Nothing -> do entities <- rawSql text [] State.put $ Map.insert text (JSON.toJSON entities) cache return entities showSqlKey :: ToBackendKey SqlBackend record => Key record -> String showSqlKey = show . fromSqlKey