2 Module : Gargantext.API.Prelude
3 Description : Server API main Types
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# LANGUAGE ConstraintKinds #-}
13 {-# LANGUAGE FunctionalDependencies #-}
14 {-# LANGUAGE TemplateHaskell #-}
15 {-# LANGUAGE TypeOperators #-}
16 {-# LANGUAGE UndecidableInstances #-}
18 module Gargantext.API.Prelude
19 ( module Gargantext.API.Prelude
25 import Control.Concurrent (threadDelay)
26 import Control.Exception (Exception)
27 import Control.Lens (Prism', (#))
28 import Control.Lens.TH (makePrisms)
29 import Control.Monad.Error.Class (MonadError(..))
30 import Control.Monad.Except (ExceptT)
31 import Control.Monad.Reader (ReaderT)
32 import Crypto.JOSE.Error as Jose
33 import Data.Aeson.Types
37 import Servant.Job.Async
38 import Servant.Job.Core (HasServerError(..), serverError)
40 import Gargantext.API.Admin.Orchestrator.Types
41 import Gargantext.API.Admin.Types
42 import Gargantext.API.Ngrams.Types
43 import Gargantext.Core.Types
44 import Gargantext.Database.Prelude
45 import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..))
46 import Gargantext.Database.Query.Tree
47 import Gargantext.Prelude
49 class HasJoseError e where
50 _JoseError :: Prism' e Jose.Error
52 joseError :: (MonadError e m, HasJoseError e) => Jose.Error -> m a
53 joseError = throwError . (_JoseError #)
55 class ThrowAll' e a | a -> e where
56 -- | 'throwAll' is a convenience function to throw errors across an entire
60 -- > throwAll err400 :: Handler a :<|> Handler b :<|> Handler c
61 -- > == throwError err400 :<|> throwError err400 :<|> err400
64 instance (ThrowAll' e a, ThrowAll' e b) => ThrowAll' e (a :<|> b) where
65 throwAll' e = throwAll' e :<|> throwAll' e
67 -- Really this shouldn't be necessary - ((->) a) should be an instance of
69 instance {-# OVERLAPPING #-} ThrowAll' e b => ThrowAll' e (a -> b) where
70 throwAll' e = const $ throwAll' e
72 instance {-# OVERLAPPABLE #-} (MonadError e m) => ThrowAll' e (m a) where
73 throwAll' = throwError
75 type GargServerC env err m =
82 , ToJSON err -- TODO this is arguable
84 , HasRepo env -- TODO rename HasNgramsRepo
85 , HasSettings env -- TODO rename HasDbSettings
86 , HasJobEnv env JobLog JobLog
92 forall env err m. GargServerT env err m api
94 type GargServerT env err m api = GargServerC env err m => ServerT api m
96 -- This is the concrete monad. It needs to be used as little as possible,
97 -- instead, prefer GargServer, GargServerT, GargServerC.
98 type GargServerM env err = ReaderT env (ExceptT err IO)
101 ( HasConnectionPool env
104 , HasJobEnv env JobLog JobLog
108 -------------------------------------------------------------------
109 -- | This Type is needed to prepare the function before the GargServer
110 type GargNoServer t =
111 forall env err m. GargNoServer' env err m => m t
113 type GargNoServer' env err m =
120 -------------------------------------------------------------------
123 = GargNodeError NodeError
124 | GargTreeError TreeError
125 | GargInvalidError Validation
126 | GargJoseError Jose.Error
127 | GargServerError ServerError
128 deriving (Show, Typeable)
130 makePrisms ''GargError
132 instance ToJSON GargError where
133 toJSON _ = String "SomeGargErrorPleaseReport"
135 instance Exception GargError
137 instance HasNodeError GargError where
138 _NodeError = _GargNodeError
140 instance HasInvalidError GargError where
141 _InvalidError = _GargInvalidError
143 instance HasTreeError GargError where
144 _TreeError = _GargTreeError
146 instance HasServerError GargError where
147 _ServerError = _GargServerError
149 instance HasJoseError GargError where
150 _JoseError = _GargJoseError
153 ------------------------------------------------------------------------
156 simuLogs :: MonadBase IO m
160 simuLogs logStatus t = do
161 _ <- mapM (\n -> simuTask logStatus n t) $ take t [0,1..]
162 pure $ JobLog { _scst_succeeded = Just t
163 , _scst_failed = Just 0
164 , _scst_remaining = Just 0
165 , _scst_events = Just []
168 simuTask :: MonadBase IO m
173 simuTask logStatus cur total = do
174 let m = (10 :: Int) ^ (6 :: Int)
175 liftBase $ threadDelay (m*5)
177 let status = JobLog { _scst_succeeded = Just cur
178 , _scst_failed = Just 0
179 , _scst_remaining = (-) <$> Just total <*> Just cur
180 , _scst_events = Just []
182 printDebug "status" status