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.Except
19 import Control.Monad.Random
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)
25 import Data.Pool (Pool, withResource)
26 import Data.Profunctor.Product.Default (Default)
27 import Data.Text (unpack, Text)
28 import Data.Word (Word16)
29 import Database.PostgreSQL.Simple (Connection, connect)
30 import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
31 import Database.PostgreSQL.Simple.Internal (Field)
32 import Gargantext.Core.Mail.Types (HasMail)
33 import Gargantext.Prelude
34 import Gargantext.Prelude.Config (readIniFile', val)
35 import Opaleye (Query, Unpackspec, showSql, FromFields, Select, runSelect, PGJsonb, DefaultFromField)
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 import Gargantext.Prelude.Config (GargConfig())
46 -------------------------------------------------------
47 class HasConnectionPool env where
48 connPool :: Getter env (Pool Connection)
50 instance HasConnectionPool (Pool Connection) where
53 class HasConfig env where
54 hasConfig :: Getter env GargConfig
56 instance HasConfig GargConfig where
59 -------------------------------------------------------
60 type JSONB = DefaultFromField PGJsonb
61 -------------------------------------------------------
63 type CmdM'' env err m =
66 , MonadBaseControl IO m
70 type CmdM' env err m =
73 , MonadBaseControl IO m
79 , HasConnectionPool env
84 type CmdRandom env err m =
86 , HasConnectionPool env
92 type Cmd'' env err a = forall m. CmdM'' env err m => m a
93 type Cmd' env err a = forall m. CmdM' env err m => m a
94 type Cmd err a = forall m env. CmdM env err m => m a
95 type CmdR err a = forall m env. CmdRandom env err m => m a
99 fromInt64ToInt :: Int64 -> Int
100 fromInt64ToInt = fromIntegral
102 -- TODO: ideally there should be very few calls to this functions.
103 mkCmd :: (Connection -> IO a) -> Cmd err a
105 pool <- view connPool
106 withResource pool (liftBase . k)
108 runCmd :: (HasConnectionPool env)
112 runCmd env m = runExceptT $ runReaderT m env
114 runOpaQuery :: Default FromFields fields haskells
116 -> Cmd err [haskells]
117 runOpaQuery q = mkCmd $ \c -> runSelect c q
119 runCountOpaQuery :: Select a -> Cmd err Int
120 runCountOpaQuery q = do
121 counts <- mkCmd $ \c -> runSelect c $ countRows q
122 -- countRows is guaranteed to return a list with exactly one row so DL.head is safe here
123 pure $ fromInt64ToInt $ DL.head counts
125 formatPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err DB.ByteString
126 formatPGSQuery q a = mkCmd $ \conn -> PGS.formatQuery conn q a
128 -- TODO use runPGSQueryDebug everywhere
129 runPGSQuery' :: (PGS.ToRow a, PGS.FromRow b) => PGS.Query -> a -> Cmd err [b]
130 runPGSQuery' q a = mkCmd $ \conn -> PGS.query conn q a
132 runPGSQuery :: ( CmdM env err m
133 , PGS.FromRow r, PGS.ToRow q
135 => PGS.Query -> q -> m [r]
136 runPGSQuery q a = mkCmd $ \conn -> catch (PGS.query conn q a) (printError conn)
138 printError c (SomeException e) = do
139 q' <- PGS.formatQuery c q a
141 throw (SomeException e)
143 -- | TODO catch error
144 runPGSQuery_ :: ( CmdM env err m
147 => PGS.Query -> m [r]
148 runPGSQuery_ q = mkCmd $ \conn -> catch (PGS.query_ conn q) printError
150 printError (SomeException e) = do
151 printDebug "[G.D.P.runPGSQuery_]" ("TODO: format query error query" :: Text)
152 throw (SomeException e)
156 execPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err Int64
157 execPGSQuery q a = mkCmd $ \conn -> PGS.execute conn q a
159 ------------------------------------------------------------------------
161 databaseParameters :: FilePath -> IO PGS.ConnectInfo
162 databaseParameters fp = do
163 ini <- readIniFile' fp
164 let val' key = unpack $ val ini "database" key
166 pure $ PGS.ConnectInfo { PGS.connectHost = val' "DB_HOST"
167 , PGS.connectPort = read (val' "DB_PORT") :: Word16
168 , PGS.connectUser = val' "DB_USER"
169 , PGS.connectPassword = val' "DB_PASS"
170 , PGS.connectDatabase = val' "DB_NAME"
173 connectGargandb :: FilePath -> IO Connection
174 connectGargandb fp = databaseParameters fp >>= \params -> connect params
176 fromField' :: (Typeable b, FromJSON b) => Field -> Maybe DB.ByteString -> Conversion b
177 fromField' field mb = do
178 v <- fromField field mb
181 valueToHyperdata v = case fromJSON v of
183 Error _err -> returnError ConversionFailed field
184 $ DL.intercalate " " [ "cannot parse hyperdata for JSON: "
188 printSqlOpa :: Default Unpackspec a a => Query a -> IO ()
189 printSqlOpa = putStrLn . maybe "Empty query" identity . showSql