Dev.hs 2.36 KB
Newer Older
Alexandre Delanoë's avatar
Alexandre Delanoë committed
1 2 3 4 5 6 7 8 9 10
{-|
Module      : Gargantext.API.Dev
Description : 
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 (saveNodeStory)
21 22
import Gargantext.API.Prelude
import Gargantext.Core.NodeStory
23 24
import Gargantext.Database.Prelude
import Gargantext.Prelude
25
import Gargantext.Prelude.Config (GargConfig(..), 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 43
      pool    <- newPool            dbParam
      setts   <- devSettings devJwkFile
44
      mail    <- Mail.readConfig iniPath
45
      pure $ DevEnv
Alexandre Delanoë's avatar
Alexandre Delanoë committed
46
        { _dev_env_pool     = pool
47
        , _dev_env_nodeStory  = nodeStory_env
48 49
        , _dev_env_settings = setts
        , _dev_env_config   = cfg
50
        , _dev_env_mail      = mail
51 52 53
        }

-- | Run Cmd Sugar for the Repl (GHCI)
54
runCmdRepl :: Show err => Cmd'' DevEnv err a -> IO a
55 56 57 58 59 60 61 62 63
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.
64
runCmdDev :: (Show err) => DevEnv -> Cmd'' DevEnv err a -> IO a
65 66 67
runCmdDev env f =
  (either (fail . show) pure =<< runCmd env f)
    `finally`
68
  runReaderT saveNodeStory env
69

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

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

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