]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Utils.hs
[Database] Refactor functions accessing the database
[gargantext.git] / src / Gargantext / Database / Utils.hs
1 {-|
2 Module : Gargantext.Database.Util
3 Description :
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 Here is a longer description of this module, containing some
11 commentary with @some markup@.
12 -}
13
14 {-# LANGUAGE ConstraintKinds #-}
15 {-# LANGUAGE FlexibleContexts #-}
16 {-# LANGUAGE NoImplicitPrelude #-}
17 {-# LANGUAGE OverloadedStrings #-}
18 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
19 {-# LANGUAGE RankNTypes #-}
20
21 module Gargantext.Database.Utils where
22
23 import Control.Lens (Getter, view)
24 import Control.Monad.Reader
25 import Control.Monad.Except
26 import Data.Aeson (Result(Error,Success), fromJSON, FromJSON)
27 import Data.Either.Extra (Either(Left, Right))
28 import Data.Ini (readIniFile, lookupValue)
29 import Data.Maybe (maybe)
30 import Data.Monoid ((<>))
31 import Data.Profunctor.Product.Default (Default)
32 import Data.Text (unpack, pack)
33 import Data.Typeable (Typeable)
34 import Data.Word (Word16)
35 import Database.PostgreSQL.Simple (Connection, connect)
36 import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
37 import Database.PostgreSQL.Simple.Internal (Field)
38 import Gargantext.Prelude
39 import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery)
40 import System.IO (FilePath)
41 import Text.Read (read)
42 import qualified Data.ByteString as DB
43 import qualified Database.PostgreSQL.Simple as PGS
44
45 class HasConnection env where
46 connection :: Getter env Connection
47
48 instance HasConnection Connection where
49 connection = identity
50
51 type CmdM env err m =
52 ( MonadReader env m
53 , HasConnection env
54 , MonadError err m
55 , MonadIO m
56 )
57
58 type Cmd err a = forall m env. CmdM env err m => m a
59
60 -- TODO: ideally there should be very few calls to this functions.
61 mkCmd :: (Connection -> IO a) -> Cmd err a
62 mkCmd k = do
63 conn <- view connection
64 liftIO $ k conn
65
66 runCmd :: Connection -> Cmd err a -> IO (Either err a)
67 runCmd conn m = runExceptT $ runReaderT m conn
68
69 -- Use only for dev
70 runCmdDev :: Show err => Cmd err a -> IO a
71 runCmdDev f = do
72 conn <- connectGargandb "gargantext.ini"
73 either (fail . show) pure =<< runCmd conn f
74
75 -- Use only for dev
76 runCmdDevNoErr :: Cmd () a -> IO a
77 runCmdDevNoErr = runCmdDev
78
79 runOpaQuery :: Default FromFields fields haskells => Select fields -> Cmd err [haskells]
80 runOpaQuery q = mkCmd $ \c -> runQuery c q
81
82 formatPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err DB.ByteString
83 formatPGSQuery q a = mkCmd $ \conn -> PGS.formatQuery conn q a
84
85 runPGSQuery :: (PGS.ToRow a, PGS.FromRow b) => PGS.Query -> a -> Cmd err [b]
86 runPGSQuery q a = mkCmd $ \conn -> PGS.query conn q a
87 ------------------------------------------------------------------------
88
89 databaseParameters :: FilePath -> IO PGS.ConnectInfo
90 databaseParameters fp = do
91 ini <- readIniFile fp
92 let ini'' = case ini of
93 Left e -> panic (pack $ "No ini file error" <> show e)
94 Right ini' -> ini'
95
96 let val x = case (lookupValue (pack "django") (pack x) ini'') of
97 Left _ -> panic (pack $ "no" <> x)
98 Right p' -> unpack p'
99
100 pure $ PGS.ConnectInfo { PGS.connectHost = val "DB_HOST"
101 , PGS.connectPort = read (val "DB_PORT") :: Word16
102 , PGS.connectUser = val "DB_USER"
103 , PGS.connectPassword = val "DB_PASS"
104 , PGS.connectDatabase = val "DB_NAME"
105 }
106
107 connectGargandb :: FilePath -> IO Connection
108 connectGargandb fp = databaseParameters fp >>= \params -> connect params
109
110 printSql :: Default Unpackspec a a => Query a -> IO ()
111 printSql = putStrLn . maybe "Empty query" identity . showSqlForPostgres
112
113 fromField' :: (Typeable b, FromJSON b) => Field -> Maybe DB.ByteString -> Conversion b
114 fromField' field mb = do
115 v <- fromField field mb
116 valueToHyperdata v
117 where
118 valueToHyperdata v = case fromJSON v of
119 Success a -> pure a
120 Error _err -> returnError ConversionFailed field "cannot parse hyperdata"
121
122 -- | Opaleye leftJoin* functions
123 -- TODO add here from Node.hs