2 Module : Gargantext.Database.Util
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Here is a longer description of this module, containing some
11 commentary with @some markup@.
14 {-# LANGUAGE ConstraintKinds #-}
15 {-# LANGUAGE FlexibleContexts #-}
16 {-# LANGUAGE FlexibleInstances #-}
17 {-# LANGUAGE NoImplicitPrelude #-}
18 {-# LANGUAGE OverloadedStrings #-}
19 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
20 {-# LANGUAGE RankNTypes #-}
22 module Gargantext.Database.Utils where
24 import Data.ByteString.Char8 (hPutStrLn)
25 import System.IO (stderr)
26 import Control.Exception
27 import Control.Monad.Error.Class -- (MonadError(..), Error)
28 import Control.Lens (Getter, view)
29 import Control.Monad.Reader
30 import Control.Monad.Trans.Control (MonadBaseControl)
31 import Control.Monad.Except
32 import Data.Aeson (Result(Error,Success), fromJSON, FromJSON)
33 import Data.Either.Extra (Either(Left, Right))
34 import Data.Ini (readIniFile, lookupValue)
35 import qualified Data.List as DL
36 import Data.Maybe (maybe)
37 import Data.Monoid ((<>))
38 import Data.Pool (Pool, withResource)
39 import Data.Profunctor.Product.Default (Default)
40 import Data.Text (unpack, pack)
41 import Data.Typeable (Typeable)
42 import Data.Word (Word16)
43 --import Database.PostgreSQL.Simple (Connection, Pool, connect, withPoolConnection)
44 import Database.PostgreSQL.Simple (Connection, connect)
45 import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
46 import Database.PostgreSQL.Simple.Internal (Field)
47 import Gargantext.Prelude
48 import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery)
49 import Opaleye.Aggregate (countRows)
50 import System.IO (FilePath)
51 import Text.Read (read)
52 import qualified Data.ByteString as DB
53 import qualified Database.PostgreSQL.Simple as PGS
55 class HasConnectionPool env where
56 connPool :: Getter env (Pool Connection)
58 instance HasConnectionPool (Pool Connection) where
61 type CmdM' env err m =
64 , MonadBaseControl IO m
69 , HasConnectionPool env
72 type Cmd' env err a = forall m. CmdM' env err m => m a
74 type Cmd err a = forall m env. CmdM env err m => m a
76 fromInt64ToInt :: Int64 -> Int
77 fromInt64ToInt = fromIntegral
79 -- TODO: ideally there should be very few calls to this functions.
80 mkCmd :: (Connection -> IO a) -> Cmd err a
83 withResource pool (liftBase . k)
85 runCmd :: (HasConnectionPool env)
86 => env -> Cmd' env err a
88 runCmd env m = runExceptT $ runReaderT m env
90 runOpaQuery :: Default FromFields fields haskells
91 => Select fields -> Cmd err [haskells]
92 runOpaQuery q = mkCmd $ \c -> runQuery c q
94 runCountOpaQuery :: Select a -> Cmd err Int
95 runCountOpaQuery q = do
96 counts <- mkCmd $ \c -> runQuery c $ countRows q
97 -- countRows is guaranteed to return a list with exactly one row so DL.head is safe here
98 pure $ fromInt64ToInt $ DL.head counts
100 formatPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err DB.ByteString
101 formatPGSQuery q a = mkCmd $ \conn -> PGS.formatQuery conn q a
103 -- TODO use runPGSQueryDebug everywhere
104 runPGSQuery' :: (PGS.ToRow a, PGS.FromRow b) => PGS.Query -> a -> Cmd err [b]
105 runPGSQuery' q a = mkCmd $ \conn -> PGS.query conn q a
107 runPGSQuery :: (MonadError err m, MonadReader env m, MonadBaseControl IO m,
108 PGS.FromRow r, PGS.ToRow q, HasConnectionPool env)
109 => PGS.Query -> q -> m [r]
110 runPGSQuery q a = mkCmd $ \conn -> catch (PGS.query conn q a) (printError conn)
112 printError c (SomeException e) = do
113 q' <- PGS.formatQuery c q a
115 throw (SomeException e)
118 execPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err Int64
119 execPGSQuery q a = mkCmd $ \conn -> PGS.execute conn q a
121 ------------------------------------------------------------------------
123 databaseParameters :: FilePath -> IO PGS.ConnectInfo
124 databaseParameters fp = do
125 ini <- readIniFile fp
126 let ini'' = case ini of
127 Left e -> panic (pack $ "No ini file error" <> show e)
130 let val x = case (lookupValue (pack "django") (pack x) ini'') of
131 Left _ -> panic (pack $ "no" <> x)
132 Right p' -> unpack p'
134 pure $ PGS.ConnectInfo { PGS.connectHost = val "DB_HOST"
135 , PGS.connectPort = read (val "DB_PORT") :: Word16
136 , PGS.connectUser = val "DB_USER"
137 , PGS.connectPassword = val "DB_PASS"
138 , PGS.connectDatabase = val "DB_NAME"
141 connectGargandb :: FilePath -> IO Connection
142 connectGargandb fp = databaseParameters fp >>= \params -> connect params
144 fromField' :: (Typeable b, FromJSON b) => Field -> Maybe DB.ByteString -> Conversion b
145 fromField' field mb = do
146 v <- fromField field mb
149 valueToHyperdata v = case fromJSON v of
151 Error _err -> returnError ConversionFailed field
152 $ DL.intercalate " " [ "cannot parse hyperdata for JSON: "
156 printSqlOpa :: Default Unpackspec a a => Query a -> IO ()
157 printSqlOpa = putStrLn . maybe "Empty query" identity . showSqlForPostgres