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

-}

12 13
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TemplateHaskell #-}
14
{-# LANGUAGE MonoLocalBinds  #-}
Alexandre Delanoë's avatar
Alexandre Delanoë committed
15

16 17
module Gargantext.API.Prelude
  ( module Gargantext.API.Prelude
18 19 20
  , HasServerError(..)
  , serverError
  )
Alexandre Delanoë's avatar
Alexandre Delanoë committed
21 22
  where

23
import Control.Concurrent (threadDelay)
24
import Control.Exception (Exception)
25 26
import Control.Lens (Prism', (#))
import Control.Lens.TH (makePrisms)
27 28
import Control.Monad.Except (ExceptT)
import Control.Monad.Reader (ReaderT)
29
import Control.Monad.Error.Class (MonadError(..))
30
import Crypto.JOSE.Error as Jose
31
import Data.Aeson.Types
32
import Data.Typeable
33
import Data.Validity
34
import Gargantext.API.Admin.Orchestrator.Types
35
import Gargantext.API.Admin.Types
36
import Gargantext.Core.NodeStory
37
import Gargantext.Core.Mail.Types (HasMail)
38
import Gargantext.Core.Types
39
import Gargantext.Database.Prelude
40 41
import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..))
import Gargantext.Database.Query.Tree
42
import Gargantext.Prelude
43
import qualified Gargantext.Utils.Jobs.Monad as Jobs
44 45 46
import Servant
import Servant.Job.Async
import Servant.Job.Core (HasServerError(..), serverError)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
47

48 49 50 51 52 53
class HasJoseError e where
  _JoseError :: Prism' e Jose.Error

joseError :: (MonadError e m, HasJoseError e) => Jose.Error -> m a
joseError = throwError . (_JoseError #)

54 55
type HasJobEnv' env = HasJobEnv env JobLog JobLog

56 57 58 59 60
type EnvC env =
  ( HasConnectionPool env
  , HasSettings       env  -- TODO rename HasDbSettings
  , HasJobEnv         env JobLog JobLog
  , HasConfig         env
61 62
  , HasNodeStoryEnv   env
  , HasMail           env
63
  )
64

65 66 67 68 69 70
type ErrC err =
  ( HasNodeError     err
  , HasInvalidError  err
  , HasTreeError     err
  , HasServerError   err
  , HasJoseError     err
71
--  , ToJSON           err -- TODO this is arguable
72 73
  , Exception        err
  )
74 75

type GargServerC env err m =
76
  ( CmdRandom    env err m
77
  , HasNodeStory env err m
78 79 80
  , EnvC         env
  , ErrC             err
  , ToJSON           err
81
  )
82

83 84
type GargServerT env err m api = GargServerC env err m => ServerT api m

85
type GargServer api = forall env err m. GargServerT env err m api
86

87 88 89 90 91
-- This is the concrete monad. It needs to be used as little as possible.
type GargM env err = ReaderT env (ExceptT err IO)
-- This is the server type using GargM. It needs to be used as little as possible.
-- Instead, prefer GargServer, GargServerT.
type GargServerM env err api = (EnvC env, ErrC err) => ServerT api (GargM env err)
92

93
-------------------------------------------------------------------
94
-- | This Type is needed to prepare the function before the GargServer
95 96 97
type GargNoServer t =
  forall env err m. GargNoServer' env err m => m t

98 99
type GargNoServer' env err m =
  ( CmdM           env err m
100
  , HasNodeStory   env err m
101 102 103 104 105
  , HasSettings    env
  , HasNodeError       err
  )

-------------------------------------------------------------------
106
data GargError
107 108
  = GargNodeError    NodeError
  | GargTreeError    TreeError
109
  | GargInvalidError Validation
110 111
  | GargJoseError    Jose.Error
  | GargServerError  ServerError
112
  | GargJobError     Jobs.JobError
113
  deriving (Show, Typeable)
114 115 116

makePrisms ''GargError

117 118 119
instance ToJSON GargError where
  toJSON _ = String "SomeGargErrorPleaseReport"

120 121
instance Exception GargError

122 123 124 125 126
instance HasNodeError GargError where
  _NodeError = _GargNodeError

instance HasInvalidError GargError where
  _InvalidError = _GargInvalidError
Alexandre Delanoë's avatar
Alexandre Delanoë committed
127

128 129
instance HasTreeError GargError where
  _TreeError = _GargTreeError
Alexandre Delanoë's avatar
Alexandre Delanoë committed
130

131 132
instance HasServerError GargError where
  _ServerError = _GargServerError
Alexandre Delanoë's avatar
Alexandre Delanoë committed
133

134 135
instance HasJoseError GargError where
  _JoseError = _GargJoseError
136 137 138 139 140

------------------------------------------------------------------------
-- | Utils
-- | Simulate logs
simuLogs  :: MonadBase IO m
141
         => (JobLog -> m ())
142
         -> Int
143
         -> m JobLog
144
simuLogs logStatus t = do
145
  _ <- mapM (\n -> simuTask logStatus n t) $ take t [0,1..]
146
  pure $ JobLog { _scst_succeeded = Just t
147 148 149 150
                , _scst_failed    = Just 0
                , _scst_remaining = Just 0
                , _scst_events    = Just []
                }
151 152

simuTask :: MonadBase IO m
153
          => (JobLog -> m ())
154 155 156
          -> Int
          -> Int
          -> m ()
157
simuTask logStatus cur total = do
158
  let m = (10 :: Int) ^ (6 :: Int)
159
  liftBase $ threadDelay (m*5)
160

161
  let status =  JobLog { _scst_succeeded = Just cur
162 163 164 165
                       , _scst_failed    = Just 0
                       , _scst_remaining = (-) <$> Just total <*> Just cur
                       , _scst_events    = Just []
                       }
166 167
  printDebug "status" status
  logStatus status