2 Module : Gargantext.Database.Prelude
3 Description : Specific Prelude for Database management
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE ConstraintKinds #-}
14 module Gargantext.Database.Prelude where
16 import Control.Exception
17 import Control.Lens (Getter, view)
18 import Control.Monad.Error.Class -- (MonadError(..), Error)
19 import Control.Monad.Except
20 import Control.Monad.Reader
21 import Control.Monad.Trans.Control (MonadBaseControl)
22 import Data.Aeson (Result(Error,Success), fromJSON, FromJSON)
23 import Data.ByteString.Char8 (hPutStrLn)
24 import Data.Either.Extra (Either(Left, Right))
25 import Data.Ini (readIniFile, lookupValue)
26 import Data.Pool (Pool, withResource)
27 import Data.Profunctor.Product.Default (Default)
28 import Data.Text (unpack, pack)
29 import Data.Word (Word16)
30 import Database.PostgreSQL.Simple (Connection, connect)
31 import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
32 import Database.PostgreSQL.Simple.Internal (Field)
33 import Gargantext.Prelude
34 import Gargantext.Prelude.Config (GargConfig())
35 import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery)
36 import Opaleye.Aggregate (countRows)
37 import System.IO (FilePath)
38 import System.IO (stderr)
39 import Text.Read (read)
40 import qualified Data.ByteString as DB
41 import qualified Data.List as DL
42 import qualified Database.PostgreSQL.Simple as PGS
44 -------------------------------------------------------
45 class HasConnectionPool env where
46 connPool :: Getter env (Pool Connection)
48 instance HasConnectionPool (Pool Connection) where
51 class HasConfig env where
52 hasConfig :: Getter env GargConfig
54 instance HasConfig GargConfig where
57 -------------------------------------------------------
58 type CmdM' env err m =
61 , MonadBaseControl IO m
66 , HasConnectionPool env
70 type Cmd' env err a = forall m. CmdM' env err m => m a
72 type Cmd err a = forall m env. CmdM env err m => m a
74 fromInt64ToInt :: Int64 -> Int
75 fromInt64ToInt = fromIntegral
77 -- TODO: ideally there should be very few calls to this functions.
78 mkCmd :: (Connection -> IO a) -> Cmd err a
81 withResource pool (liftBase . k)
83 runCmd :: (HasConnectionPool env)
87 runCmd env m = runExceptT $ runReaderT m env
89 runOpaQuery :: Default FromFields fields 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, HasConfig 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 "database") (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