2 Module : Gargantext.API.Admin.Types
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 FlexibleContexts #-}
14 {-# LANGUAGE FlexibleInstances #-}
15 {-# LANGUAGE FunctionalDependencies #-}
16 {-# LANGUAGE MultiParamTypeClasses #-}
17 {-# LANGUAGE NoImplicitPrelude #-}
18 {-# LANGUAGE OverloadedStrings #-}
19 {-# LANGUAGE RankNTypes #-}
20 {-# LANGUAGE TemplateHaskell #-}
21 {-# LANGUAGE TypeOperators #-}
22 {-# LANGUAGE UndecidableInstances #-}
24 module Gargantext.API.Admin.Types
25 ( module Gargantext.API.Admin.Types
31 import Control.Exception (Exception)
32 import Control.Lens (Prism', (#))
33 import Control.Lens.TH (makePrisms)
34 import Control.Monad.Error.Class (MonadError(throwError))
35 import Crypto.JOSE.Error as Jose
36 import Data.Aeson.Types
39 import Gargantext.API.Admin.Orchestrator.Types
40 import Gargantext.API.Admin.Settings
41 import Gargantext.API.Ngrams
42 import Gargantext.Core.Types
43 import Gargantext.Database.Query.Tree
44 import Gargantext.Database.Query.Table.Node.Error (NodeError(..), HasNodeError(..))
45 import Gargantext.Database.Prelude
46 import Gargantext.Prelude
48 import Servant.Job.Async (HasJobEnv)
49 import Servant.Job.Core (HasServerError(..), serverError)
51 class HasJoseError e where
52 _JoseError :: Prism' e Jose.Error
54 joseError :: (MonadError e m, HasJoseError e) => Jose.Error -> m a
55 joseError = throwError . (_JoseError #)
57 class ThrowAll' e a | a -> e where
58 -- | 'throwAll' is a convenience function to throw errors across an entire
62 -- > throwAll err400 :: Handler a :<|> Handler b :<|> Handler c
63 -- > == throwError err400 :<|> throwError err400 :<|> err400
66 instance (ThrowAll' e a, ThrowAll' e b) => ThrowAll' e (a :<|> b) where
67 throwAll' e = throwAll' e :<|> throwAll' e
69 -- Really this shouldn't be necessary - ((->) a) should be an instance of
71 instance {-# OVERLAPPING #-} ThrowAll' e b => ThrowAll' e (a -> b) where
72 throwAll' e = const $ throwAll' e
74 instance {-# OVERLAPPABLE #-} (MonadError e m) => ThrowAll' e (m a) where
75 throwAll' = throwError
77 type GargServerC env err m =
84 , ToJSON err -- TODO this is arguable
88 , HasJobEnv env ScraperStatus ScraperStatus
91 type GargServerT env err m api = GargServerC env err m => ServerT api m
94 forall env err m. GargServerT env err m api
96 -------------------------------------------------------------------
97 -- | This Type is needed to prepare the function before the GargServer
98 type GargNoServer' env err m =
105 type GargNoServer t =
106 forall env err m. GargNoServer' env err m => m t
107 -------------------------------------------------------------------
110 = GargNodeError NodeError
111 | GargTreeError TreeError
112 | GargInvalidError Validation
113 | GargJoseError Jose.Error
114 | GargServerError ServerError
115 deriving (Show, Typeable)
117 makePrisms ''GargError
119 instance ToJSON GargError where
120 toJSON _ = String "SomeGargErrorPleaseReport"
122 instance Exception GargError
124 instance HasNodeError GargError where
125 _NodeError = _GargNodeError
127 instance HasInvalidError GargError where
128 _InvalidError = _GargInvalidError
130 instance HasTreeError GargError where
131 _TreeError = _GargTreeError
133 instance HasServerError GargError where
134 _ServerError = _GargServerError
136 instance HasJoseError GargError where
137 _JoseError = _GargJoseError