Dev.hs 2.41 KB
Newer Older
Alexandre Delanoë's avatar
Alexandre Delanoë committed
1 2
{-|
Module      : Gargantext.API.Dev
3
Description :
Alexandre Delanoë's avatar
Alexandre Delanoë committed
4 5 6 7 8 9 10
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}
11

12
-- Use only for dev/repl
13 14
module Gargantext.API.Dev where

15 16 17 18
import Control.Exception (finally)
import Control.Monad (fail)
import Control.Monad.Reader (runReaderT)
import Gargantext.API.Admin.EnvTypes
19
import Gargantext.API.Admin.Settings
20
import Gargantext.API.Ngrams (saveNodeStoryImmediate)
21 22
import Gargantext.API.Prelude
import Gargantext.Core.NodeStory
23 24
import Gargantext.Database.Prelude
import Gargantext.Prelude
25
import Gargantext.Prelude.Config (readConfig)
26
import qualified Gargantext.Prelude.Mail as Mail
27
import Servant
28
import System.IO (FilePath)
29

30
type IniPath  = FilePath
31
-------------------------------------------------------------------
32 33 34
withDevEnv :: IniPath -> (DevEnv -> IO a) -> IO a
withDevEnv iniPath k = do
  env <- newDevEnv
35
  k env -- `finally` cleanEnv env
36 37 38 39 40

  where
    newDevEnv = do
      cfg     <- readConfig         iniPath
      dbParam <- databaseParameters iniPath
41
      --nodeStory_env <- readNodeStoryEnv (_gc_repofilepath cfg)
42
      pool    <- newPool            dbParam
43
      nodeStory_env <- readNodeStoryEnv pool
44
      setts   <- devSettings devJwkFile
45
      mail    <- Mail.readConfig iniPath
46
      pure $ DevEnv
Alexandre Delanoë's avatar
Alexandre Delanoë committed
47
        { _dev_env_pool     = pool
48
        , _dev_env_nodeStory  = nodeStory_env
49 50
        , _dev_env_settings = setts
        , _dev_env_config   = cfg
51
        , _dev_env_mail      = mail
52 53 54
        }

-- | Run Cmd Sugar for the Repl (GHCI)
55
runCmdRepl :: Show err => Cmd'' DevEnv err a -> IO a
56 57 58 59 60 61 62 63 64
runCmdRepl f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f

runCmdReplServantErr :: Cmd'' DevEnv ServerError a -> IO a
runCmdReplServantErr = runCmdRepl

-- In particular this writes the repo file after running
-- the command.
-- This function is constrained to the DevEnv rather than
-- using HasConnectionPool and HasRepoVar.
65
runCmdDev :: Show err => DevEnv -> Cmd'' DevEnv err a -> IO a
66 67 68
runCmdDev env f =
  (either (fail . show) pure =<< runCmd env f)
    `finally`
69
  runReaderT saveNodeStoryImmediate env
70

71
runCmdDevNoErr :: DevEnv -> Cmd' DevEnv () a -> IO a
72 73
runCmdDevNoErr = runCmdDev

74
runCmdDevServantErr :: DevEnv -> Cmd' DevEnv ServerError a -> IO a
75 76
runCmdDevServantErr = runCmdDev

77
runCmdReplEasy :: Cmd'' DevEnv GargError a -> IO a
Alexandre Delanoë's avatar
Alexandre Delanoë committed
78
runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f