]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Prelude.hs
[list] HashResponse with md5 sum for charts (caching)
[gargantext.git] / src / Gargantext / API / Prelude.hs
1 {-|
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
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE ConstraintKinds #-}
13 {-# LANGUAGE FunctionalDependencies #-}
14 {-# LANGUAGE TemplateHaskell #-}
15 {-# LANGUAGE TypeOperators #-}
16 {-# LANGUAGE UndecidableInstances #-}
17
18 module Gargantext.API.Prelude
19 ( module Gargantext.API.Prelude
20 , HasServerError(..)
21 , serverError
22 )
23 where
24
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(throwError))
30 import Control.Monad.Except (ExceptT)
31 import Control.Monad.Reader (ReaderT)
32 import Crypto.JOSE.Error as Jose
33 import Data.Aeson.Types
34 import Data.Typeable
35 import Data.Validity
36 import Gargantext.API.Admin.Orchestrator.Types
37 import Gargantext.API.Admin.Settings
38 import Gargantext.API.Ngrams
39 import Gargantext.Core.Types
40 import Gargantext.Database.Prelude
41 import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..))
42 import Gargantext.Database.Query.Tree
43 import Gargantext.Prelude
44 import Servant
45 import Servant.Job.Async (HasJobEnv)
46 import Servant.Job.Core (HasServerError(..), serverError)
47
48 class HasJoseError e where
49 _JoseError :: Prism' e Jose.Error
50
51 joseError :: (MonadError e m, HasJoseError e) => Jose.Error -> m a
52 joseError = throwError . (_JoseError #)
53
54 class ThrowAll' e a | a -> e where
55 -- | 'throwAll' is a convenience function to throw errors across an entire
56 -- sub-API
57 --
58 --
59 -- > throwAll err400 :: Handler a :<|> Handler b :<|> Handler c
60 -- > == throwError err400 :<|> throwError err400 :<|> err400
61 throwAll' :: e -> a
62
63 instance (ThrowAll' e a, ThrowAll' e b) => ThrowAll' e (a :<|> b) where
64 throwAll' e = throwAll' e :<|> throwAll' e
65
66 -- Really this shouldn't be necessary - ((->) a) should be an instance of
67 -- MonadError, no?
68 instance {-# OVERLAPPING #-} ThrowAll' e b => ThrowAll' e (a -> b) where
69 throwAll' e = const $ throwAll' e
70
71 instance {-# OVERLAPPABLE #-} (MonadError e m) => ThrowAll' e (m a) where
72 throwAll' = throwError
73
74 type GargServerC env err m =
75 ( CmdM env err m
76 , HasNodeError err
77 , HasInvalidError err
78 , HasTreeError err
79 , HasServerError err
80 , HasJoseError err
81 , ToJSON err -- TODO this is arguable
82 , Exception err
83 , HasRepo env
84 , HasSettings env
85 , HasJobEnv env JobLog JobLog
86 )
87
88 type GargServerT env err m api = GargServerC env err m => ServerT api m
89
90 type GargServer api =
91 forall env err m. GargServerT env err m api
92
93 -- This is the concrete monad. It needs to be used as little as possible,
94 -- instead, prefer GargServer, GargServerT, GargServerC.
95 type GargServerM env err = ReaderT env (ExceptT err IO)
96
97 type EnvC env =
98 ( HasConnectionPool env
99 , HasRepo env
100 , HasSettings env
101 , HasJobEnv env JobLog JobLog
102 )
103
104 -------------------------------------------------------------------
105 runCmdReplEasy :: Cmd' DevEnv GargError a -> IO a
106 runCmdReplEasy f = withDevEnv "gargantext.ini" $ \env -> runCmdDev env f
107
108 -------------------------------------------------------------------
109 -- | This Type is needed to prepare the function before the GargServer
110 type GargNoServer' env err m =
111 ( CmdM env err m
112 , HasRepo env
113 , HasSettings env
114 , HasNodeError err
115 )
116
117 type GargNoServer t =
118 forall env err m. GargNoServer' env err m => m t
119 -------------------------------------------------------------------
120
121 data GargError
122 = GargNodeError NodeError
123 | GargTreeError TreeError
124 | GargInvalidError Validation
125 | GargJoseError Jose.Error
126 | GargServerError ServerError
127 deriving (Show, Typeable)
128
129 makePrisms ''GargError
130
131 instance ToJSON GargError where
132 toJSON _ = String "SomeGargErrorPleaseReport"
133
134 instance Exception GargError
135
136 instance HasNodeError GargError where
137 _NodeError = _GargNodeError
138
139 instance HasInvalidError GargError where
140 _InvalidError = _GargInvalidError
141
142 instance HasTreeError GargError where
143 _TreeError = _GargTreeError
144
145 instance HasServerError GargError where
146 _ServerError = _GargServerError
147
148 instance HasJoseError GargError where
149 _JoseError = _GargJoseError
150
151
152 ------------------------------------------------------------------------
153 -- | Utils
154 -- | Simulate logs
155 simuLogs :: MonadBase IO m
156 => (JobLog -> m ())
157 -> Int
158 -> m JobLog
159 simuLogs logStatus t = do
160 _ <- mapM (\n -> simuTask logStatus n t) $ take t [0,1..]
161 pure $ JobLog { _scst_succeeded = Just t
162 , _scst_failed = Just 0
163 , _scst_remaining = Just 0
164 , _scst_events = Just []
165 }
166
167 simuTask :: MonadBase IO m
168 => (JobLog -> m ())
169 -> Int
170 -> Int
171 -> m ()
172 simuTask logStatus cur total = do
173 let m = (10 :: Int) ^ (6 :: Int)
174 liftBase $ threadDelay (m*5)
175
176 let status = JobLog { _scst_succeeded = Just cur
177 , _scst_failed = Just 0
178 , _scst_remaining = (-) <$> Just total <*> Just cur
179 , _scst_events = Just []
180 }
181 printDebug "status" status
182 logStatus status