Commit 9179315e authored by Alexandre Delanoë's avatar Alexandre Delanoë

[DEBUG] message for SQL.

parent 33cee927
...@@ -253,7 +253,7 @@ SELECT nng.node_id, ng.id, ng.terms FROM nodes_ngrams nng ...@@ -253,7 +253,7 @@ SELECT nng.node_id, ng.id, ng.terms FROM nodes_ngrams nng
AND nng.ngrams_type = ? -- NgramsTypeId AND nng.ngrams_type = ? -- NgramsTypeId
GROUP BY nng.node_id, ng.id, ng.terms) GROUP BY nng.node_id, ng.id, ng.terms)
SELECT m.node_id, m.terms FROM nodesByNgramsMaster m SELECTx m.node_id, m.terms FROM nodesByNgramsMaster m
RIGHT JOIN nodesByNgramsUser u ON u.id = m.id RIGHT JOIN nodesByNgramsUser u ON u.id = m.id
|] |]
......
...@@ -20,10 +20,9 @@ commentary with @some markup@. ...@@ -20,10 +20,9 @@ commentary with @some markup@.
module Gargantext.Database.Utils where module Gargantext.Database.Utils where
import Prelude (String) import Control.Exception
import Control.Monad ((>>)) import Data.Text (Text)
--import Data.Text (Text) import Control.Monad.Error.Class -- (MonadError(..), Error)
import Control.Monad.Error.Class (MonadError(..))
import Control.Lens (Getter, view) import Control.Lens (Getter, view)
import Control.Monad.Reader import Control.Monad.Reader
import Control.Monad.Except import Control.Monad.Except
...@@ -84,17 +83,26 @@ runOpaQuery q = mkCmd $ \c -> runQuery c q ...@@ -84,17 +83,26 @@ runOpaQuery q = mkCmd $ \c -> runQuery c q
formatPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err DB.ByteString formatPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err DB.ByteString
formatPGSQuery q a = mkCmd $ \conn -> PGS.formatQuery conn q a formatPGSQuery q a = mkCmd $ \conn -> PGS.formatQuery conn q a
runPGSQuery' :: (PGS.ToRow a, PGS.FromRow b) => PGS.Query -> a -> Cmd err [b] runPGSQuery :: (PGS.ToRow a, PGS.FromRow b) => PGS.Query -> a -> Cmd err [b]
runPGSQuery' q a = mkCmd $ \conn -> PGS.query conn q a runPGSQuery q a = mkCmd $ \conn -> PGS.query conn q a
runPGSQuery :: (MonadError err m, MonadReader env m,
data SqlErrorX = SqlErrorX
deriving (Eq, Show)
instance Exception SqlErrorX
runPGSQuery' :: (MonadError (SqlErrorX) m, MonadReader env m,
PGS.FromRow r, PGS.ToRow q, MonadIO m, HasConnection env) PGS.FromRow r, PGS.ToRow q, MonadIO m, HasConnection env)
=> PGS.Query -> q -> m [r] => PGS.Query -> q -> m [r]
runPGSQuery q a = mkCmd $ \conn -> catchError (PGS.query conn q a) runPGSQuery' q a = mkCmd $ \conn -> catchError (PGS.query conn q a) (printError conn)
(\e -> putStrLn ("Text xxxxxxxxxxxxxxxxxxx" :: String) where
--(\e -> putStrLn ((cs $ formatPGSQuery q a):: Text) printError c e = do
>> throwError e q' <- (PGS.formatQuery c q a :: IO DB.ByteString)
) putStrLn (cs q':: Text)
throwError e
execPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err Int64 execPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err Int64
execPGSQuery q a = mkCmd $ \conn -> PGS.execute conn q a execPGSQuery q a = mkCmd $ \conn -> PGS.execute conn q a
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment