]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Database/Prelude.hs
[FIX] undefined lacking functions
[gargantext.git] / src / Gargantext / Database / Prelude.hs
1 {-|
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
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE ConstraintKinds #-}
13
14 module Gargantext.Database.Prelude where
15
16 -- import Control.Monad.Error.Class -- (MonadError(..), Error)
17 import Control.Exception
18 import Control.Lens (Getter, view)
19 import Control.Monad.Except
20 import Control.Monad.Random
21 import Control.Monad.Reader
22 import Control.Monad.Trans.Control (MonadBaseControl)
23 import Data.Aeson (Result(Error,Success), fromJSON, FromJSON)
24 import Data.ByteString.Char8 (hPutStrLn)
25 import Data.Either.Extra (Either(Left, Right))
26 import Data.Ini (readIniFile, lookupValue)
27 import Data.Pool (Pool, withResource)
28 import Data.Profunctor.Product.Default (Default)
29 import Data.Text (unpack, pack)
30 import Data.Word (Word16)
31 import Database.PostgreSQL.Simple (Connection, connect)
32 import Database.PostgreSQL.Simple.FromField ( Conversion, ResultError(ConversionFailed), fromField, returnError)
33 import Database.PostgreSQL.Simple.Internal (Field)
34 import Gargantext.Prelude
35 import Gargantext.Prelude.Config (GargConfig())
36 import Opaleye (Query, Unpackspec, showSqlForPostgres, FromFields, Select, runQuery, PGJsonb, QueryRunnerColumnDefault)
37 import Opaleye.Aggregate (countRows)
38 import System.IO (FilePath)
39 import System.IO (stderr)
40 import Text.Read (read)
41 import qualified Data.ByteString as DB
42 import qualified Data.List as DL
43 import qualified Database.PostgreSQL.Simple as PGS
44
45 -------------------------------------------------------
46 class HasConnectionPool env where
47 connPool :: Getter env (Pool Connection)
48
49 instance HasConnectionPool (Pool Connection) where
50 connPool = identity
51
52 class HasConfig env where
53 hasConfig :: Getter env GargConfig
54
55 instance HasConfig GargConfig where
56 hasConfig = identity
57
58 -------------------------------------------------------
59 type JSONB = QueryRunnerColumnDefault PGJsonb
60 -------------------------------------------------------
61
62 type CmdM'' env err m =
63 ( MonadReader env m
64 , MonadError err m
65 , MonadBaseControl IO m
66 , MonadRandom m
67 )
68
69 type CmdM' env err m =
70 ( MonadReader env m
71 , MonadError err m
72 , MonadBaseControl IO m
73 -- , MonadRandom m
74 )
75
76 type CmdM env err m =
77 ( CmdM' env err m
78 , HasConnectionPool env
79 , HasConfig env
80 )
81
82 type CmdRandom env err m =
83 ( CmdM' env err m
84 , HasConnectionPool env
85 , HasConfig env
86 , MonadRandom m
87 )
88
89 type Cmd'' env err a = forall m. CmdM'' env err m => m a
90 type Cmd' env err a = forall m. CmdM' env err m => m a
91 type Cmd err a = forall m env. CmdM env err m => m a
92 type CmdR err a = forall m env. CmdRandom env err m => m a
93
94
95
96 fromInt64ToInt :: Int64 -> Int
97 fromInt64ToInt = fromIntegral
98
99 -- TODO: ideally there should be very few calls to this functions.
100 mkCmd :: (Connection -> IO a) -> Cmd err a
101 mkCmd k = do
102 pool <- view connPool
103 withResource pool (liftBase . k)
104
105 runCmd :: (HasConnectionPool env)
106 => env
107 -> Cmd'' env err a
108 -> IO (Either err a)
109 runCmd env m = runExceptT $ runReaderT m env
110
111 runOpaQuery :: Default FromFields fields haskells
112 => Select fields
113 -> Cmd err [haskells]
114 runOpaQuery q = mkCmd $ \c -> runQuery c q
115
116 runCountOpaQuery :: Select a -> Cmd err Int
117 runCountOpaQuery q = do
118 counts <- mkCmd $ \c -> runQuery c $ countRows q
119 -- countRows is guaranteed to return a list with exactly one row so DL.head is safe here
120 pure $ fromInt64ToInt $ DL.head counts
121
122 formatPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err DB.ByteString
123 formatPGSQuery q a = mkCmd $ \conn -> PGS.formatQuery conn q a
124
125 -- TODO use runPGSQueryDebug everywhere
126 runPGSQuery' :: (PGS.ToRow a, PGS.FromRow b) => PGS.Query -> a -> Cmd err [b]
127 runPGSQuery' q a = mkCmd $ \conn -> PGS.query conn q a
128
129 runPGSQuery :: ( CmdM env err m
130 , PGS.FromRow r, PGS.ToRow q
131 )
132 => PGS.Query -> q -> m [r]
133 runPGSQuery q a = mkCmd $ \conn -> catch (PGS.query conn q a) (printError conn)
134 where
135 printError c (SomeException e) = do
136 q' <- PGS.formatQuery c q a
137 hPutStrLn stderr q'
138 throw (SomeException e)
139
140
141 execPGSQuery :: PGS.ToRow a => PGS.Query -> a -> Cmd err Int64
142 execPGSQuery q a = mkCmd $ \conn -> PGS.execute conn q a
143
144 ------------------------------------------------------------------------
145
146 databaseParameters :: FilePath -> IO PGS.ConnectInfo
147 databaseParameters fp = do
148 ini <- readIniFile fp
149 let ini'' = case ini of
150 Left e -> panic (pack $ "No ini file error" <> show e)
151 Right ini' -> ini'
152
153 let val x = case (lookupValue (pack "database") (pack x) ini'') of
154 Left _ -> panic (pack $ "no" <> x)
155 Right p' -> unpack p'
156
157 pure $ PGS.ConnectInfo { PGS.connectHost = val "DB_HOST"
158 , PGS.connectPort = read (val "DB_PORT") :: Word16
159 , PGS.connectUser = val "DB_USER"
160 , PGS.connectPassword = val "DB_PASS"
161 , PGS.connectDatabase = val "DB_NAME"
162 }
163
164 connectGargandb :: FilePath -> IO Connection
165 connectGargandb fp = databaseParameters fp >>= \params -> connect params
166
167 fromField' :: (Typeable b, FromJSON b) => Field -> Maybe DB.ByteString -> Conversion b
168 fromField' field mb = do
169 v <- fromField field mb
170 valueToHyperdata v
171 where
172 valueToHyperdata v = case fromJSON v of
173 Success a -> pure a
174 Error _err -> returnError ConversionFailed field
175 $ DL.intercalate " " [ "cannot parse hyperdata for JSON: "
176 , show v
177 ]
178
179 printSqlOpa :: Default Unpackspec a a => Query a -> IO ()
180 printSqlOpa = putStrLn . maybe "Empty query" identity . showSqlForPostgres
181