Commit 922529c3 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Initial work on the FrontendError facade

This commit starts adding the conversion functions from a
`BackendInternalError` to a `FrontendError`.
parent 405a3082
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
module Gargantext.API.Errors ( module Gargantext.API.Errors (
module Types module Types
...@@ -6,6 +7,7 @@ module Gargantext.API.Errors ( ...@@ -6,6 +7,7 @@ module Gargantext.API.Errors (
-- * Conversion functions -- * Conversion functions
, backendErrorToFrontendError , backendErrorToFrontendError
, frontendErrorToServerError
-- * Temporary shims -- * Temporary shims
, showAsServantJSONErr , showAsServantJSONErr
...@@ -15,15 +17,17 @@ import Prelude ...@@ -15,15 +17,17 @@ import Prelude
import Gargantext.API.Errors.Class as Class import Gargantext.API.Errors.Class as Class
import Gargantext.API.Errors.Types as Types import Gargantext.API.Errors.Types as Types
import Gargantext.Database.Query.Table.Node.Error import Gargantext.Database.Query.Table.Node.Error hiding (nodeError)
import Servant.Server import Servant.Server
import qualified Data.Aeson as JSON import qualified Data.Aeson as JSON
import qualified Network.HTTP.Types.Status as HTTP import qualified Network.HTTP.Types.Status as HTTP
import Data.Data
import qualified Data.Text as T
_backendErrorTypeToErrStatus :: BackendErrorType -> HTTP.Status backendErrorTypeToErrStatus :: BackendErrorType -> HTTP.Status
_backendErrorTypeToErrStatus = \case backendErrorTypeToErrStatus = \case
BE_phylo_corpus_not_ready -> HTTP.status500 BE_node_error_root_not_found -> HTTP.status404
BE_node_not_found -> HTTP.status500 BE_node_error_corpus_not_found -> HTTP.status404
BE_tree_error_root_not_found -> HTTP.status404 BE_tree_error_root_not_found -> HTTP.status404
-- | Transforms a backend internal error into something that the frontend -- | Transforms a backend internal error into something that the frontend
...@@ -31,8 +35,8 @@ _backendErrorTypeToErrStatus = \case ...@@ -31,8 +35,8 @@ _backendErrorTypeToErrStatus = \case
-- as we later encode this into a 'ServerError' in the main server handler. -- as we later encode this into a 'ServerError' in the main server handler.
backendErrorToFrontendError :: BackendInternalError -> FrontendError backendErrorToFrontendError :: BackendInternalError -> FrontendError
backendErrorToFrontendError = \case backendErrorToFrontendError = \case
InternalNodeError _nodeError InternalNodeError nodeError
-> undefined -> nodeErrorToFrontendError nodeError
InternalTreeError _treeError InternalTreeError _treeError
-> undefined -> undefined
InternalValidationError _validationError InternalValidationError _validationError
...@@ -44,9 +48,56 @@ backendErrorToFrontendError = \case ...@@ -44,9 +48,56 @@ backendErrorToFrontendError = \case
InternalJobError _jobError InternalJobError _jobError
-> undefined -> undefined
nodeErrorToFrontendError :: NodeError -> FrontendError
nodeErrorToFrontendError ne = case ne of
NoListFound _lid
-> undefined
NoRootFound
-> mkFrontendErr' renderedError Proxy FE_node_error_root_not_found
NoCorpusFound
-> mkFrontendErr' renderedError Proxy FE_node_error_corpus_not_found
NoUserFound _ur
-> undefined
MkNode
-> undefined
UserNoParent
-> undefined
HasParent
-> undefined
ManyParents
-> undefined
NegativeId
-> undefined
NotImplYet
-> undefined
ManyNodeUsers
-> undefined
DoesNotExist _nodeId
-> undefined
NoContextFound _contextId
-> undefined
NeedsConfiguration
-> undefined
NodeError _txt
-> undefined
QueryNoParse _txt
-> undefined
where
renderedError = T.pack (show ne)
-- | Converts a 'FrontendError' into a 'ServerError' that the servant app can
-- return to the frontend.
frontendErrorToServerError :: FrontendError -> ServerError
frontendErrorToServerError fe@(FrontendError diag ty _) =
ServerError { errHTTPCode = HTTP.statusCode $ backendErrorTypeToErrStatus ty
, errReasonPhrase = T.unpack diag
, errBody = JSON.encode fe
, errHeaders = mempty
}
showAsServantJSONErr :: BackendInternalError -> ServerError showAsServantJSONErr :: BackendInternalError -> ServerError
showAsServantJSONErr (InternalNodeError err@(NoListFound {})) = err404 { errBody = JSON.encode err } showAsServantJSONErr (InternalNodeError err@(NoListFound {})) = err404 { errBody = JSON.encode err }
showAsServantJSONErr (InternalNodeError err@NoRootFound) = err404 { errBody = JSON.encode err } showAsServantJSONErr (InternalNodeError err@NoRootFound{}) = err404 { errBody = JSON.encode err }
showAsServantJSONErr (InternalNodeError err@NoCorpusFound) = err404 { errBody = JSON.encode err } showAsServantJSONErr (InternalNodeError err@NoCorpusFound) = err404 { errBody = JSON.encode err }
showAsServantJSONErr (InternalNodeError err@NoUserFound{}) = err404 { errBody = JSON.encode err } showAsServantJSONErr (InternalNodeError err@NoUserFound{}) = err404 { errBody = JSON.encode err }
showAsServantJSONErr (InternalNodeError err@(DoesNotExist {})) = err404 { errBody = JSON.encode err } showAsServantJSONErr (InternalNodeError err@(DoesNotExist {})) = err404 { errBody = JSON.encode err }
......
...@@ -19,6 +19,7 @@ module Gargantext.API.Errors.Types ( ...@@ -19,6 +19,7 @@ module Gargantext.API.Errors.Types (
-- * The internal backend type and an enumeration of all possible backend error types -- * The internal backend type and an enumeration of all possible backend error types
, BackendErrorType(..) , BackendErrorType(..)
, BackendInternalError(..) , BackendInternalError(..)
, ToFrontendErrorData(..)
-- * Constructing frontend errors -- * Constructing frontend errors
, mkFrontendErr , mkFrontendErr
...@@ -56,6 +57,7 @@ import qualified Crypto.JWT as Jose ...@@ -56,6 +57,7 @@ import qualified Crypto.JWT as Jose
import qualified Data.Text as T import qualified Data.Text as T
import qualified Gargantext.Utils.Jobs.Monad as Jobs import qualified Gargantext.Utils.Jobs.Monad as Jobs
import qualified Servant.Job.Types as SJ import qualified Servant.Job.Types as SJ
import Text.Read (readMaybe)
-- | A 'WithStacktrace' carries an error alongside its -- | A 'WithStacktrace' carries an error alongside its
-- 'CallStack', to be able to print the correct source location -- 'CallStack', to be able to print the correct source location
...@@ -115,10 +117,13 @@ instance HasJoseError BackendInternalError where ...@@ -115,10 +117,13 @@ instance HasJoseError BackendInternalError where
-- | A (hopefully and eventually) exhaustive list of backend errors. -- | A (hopefully and eventually) exhaustive list of backend errors.
data BackendErrorType data BackendErrorType
= BE_phylo_corpus_not_ready =
| BE_node_not_found -- node errors
BE_node_error_root_not_found
| BE_node_error_corpus_not_found
-- tree errors
| BE_tree_error_root_not_found | BE_tree_error_root_not_found
deriving (Show, Eq, Enum, Bounded) deriving (Show, Read, Eq, Enum, Bounded)
$(genSingletons [''BackendErrorType]) $(genSingletons [''BackendErrorType])
...@@ -155,9 +160,9 @@ class ( SingI payload ...@@ -155,9 +160,9 @@ class ( SingI payload
) => IsFrontendErrorData payload where ) => IsFrontendErrorData payload where
isFrontendErrorData :: Proxy payload -> Dict IsFrontendErrorData payload isFrontendErrorData :: Proxy payload -> Dict IsFrontendErrorData payload
instance IsFrontendErrorData 'BE_phylo_corpus_not_ready where instance IsFrontendErrorData 'BE_node_error_root_not_found where
isFrontendErrorData _ = Dict isFrontendErrorData _ = Dict
instance IsFrontendErrorData 'BE_node_not_found where instance IsFrontendErrorData 'BE_node_error_corpus_not_found where
isFrontendErrorData _ = Dict isFrontendErrorData _ = Dict
instance IsFrontendErrorData 'BE_tree_error_root_not_found where instance IsFrontendErrorData 'BE_tree_error_root_not_found where
isFrontendErrorData _ = Dict isFrontendErrorData _ = Dict
...@@ -166,14 +171,16 @@ instance IsFrontendErrorData 'BE_tree_error_root_not_found where ...@@ -166,14 +171,16 @@ instance IsFrontendErrorData 'BE_tree_error_root_not_found where
-- This data family maps a 'BackendErrorType' into a concrete payload. -- This data family maps a 'BackendErrorType' into a concrete payload.
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
data NoFrontendErrorData = NoFrontendErrorData
data family ToFrontendErrorData (payload :: BackendErrorType) :: Type data family ToFrontendErrorData (payload :: BackendErrorType) :: Type
data instance ToFrontendErrorData 'BE_phylo_corpus_not_ready = data instance ToFrontendErrorData 'BE_node_error_root_not_found =
PhyloCorpusNotReady { _pcnr_corpusId :: CorpusId } FE_node_error_root_not_found
deriving (Show, Eq, Generic) deriving (Show, Eq, Generic)
data instance ToFrontendErrorData 'BE_node_not_found = data instance ToFrontendErrorData 'BE_node_error_corpus_not_found =
NodeNotFound { _nnf_nodeId :: NodeId } FE_node_error_corpus_not_found
deriving (Show, Eq, Generic) deriving (Show, Eq, Generic)
data instance ToFrontendErrorData 'BE_tree_error_root_not_found = data instance ToFrontendErrorData 'BE_tree_error_root_not_found =
...@@ -184,22 +191,17 @@ data instance ToFrontendErrorData 'BE_tree_error_root_not_found = ...@@ -184,22 +191,17 @@ data instance ToFrontendErrorData 'BE_tree_error_root_not_found =
-- JSON instances. It's important to have nice and human readable instances. -- JSON instances. It's important to have nice and human readable instances.
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
instance ToJSON (ToFrontendErrorData 'BE_phylo_corpus_not_ready) where instance ToJSON (ToFrontendErrorData 'BE_node_error_root_not_found) where
toJSON PhyloCorpusNotReady{..} = toJSON _ = JSON.Null
object [ "corpus_id" .= toJSON _pcnr_corpusId ]
instance FromJSON (ToFrontendErrorData 'BE_phylo_corpus_not_ready) where instance FromJSON (ToFrontendErrorData 'BE_node_error_root_not_found) where
parseJSON = withObject "PhyloCorpusNotReady" $ \o -> do parseJSON _ = pure FE_node_error_root_not_found
_pcnr_corpusId <- o .: "corpus_id"
pure PhyloCorpusNotReady{..}
instance ToJSON (ToFrontendErrorData 'BE_node_not_found) where instance ToJSON (ToFrontendErrorData 'BE_node_error_corpus_not_found) where
toJSON NodeNotFound{..} = object [ "node_id" .= toJSON _nnf_nodeId ] toJSON _ = JSON.Null
instance FromJSON (ToFrontendErrorData 'BE_node_not_found) where instance FromJSON (ToFrontendErrorData 'BE_node_error_corpus_not_found) where
parseJSON = withObject "NodeNotFound" $ \o -> do parseJSON _ = pure FE_node_error_corpus_not_found
_nnf_nodeId <- o .: "node_id"
pure NodeNotFound{..}
instance ToJSON (ToFrontendErrorData 'BE_tree_error_root_not_found) where instance ToJSON (ToFrontendErrorData 'BE_tree_error_root_not_found) where
toJSON RootNotFound{..} = object [ "root_id" .= toJSON _rnf_rootId ] toJSON RootNotFound{..} = object [ "root_id" .= toJSON _rnf_rootId ]
...@@ -233,12 +235,10 @@ instance Arbitrary FrontendError where ...@@ -233,12 +235,10 @@ instance Arbitrary FrontendError where
genFrontendErr :: T.Text -> BackendErrorType -> Gen FrontendError genFrontendErr :: T.Text -> BackendErrorType -> Gen FrontendError
genFrontendErr txt be = case be of genFrontendErr txt be = case be of
BE_phylo_corpus_not_ready BE_node_error_root_not_found
-> do corpusId <- arbitrary -> pure $ mkFrontendErr' txt (Proxy @'BE_node_error_root_not_found) FE_node_error_root_not_found
pure $ mkFrontendErr' txt (Proxy @'BE_phylo_corpus_not_ready) (PhyloCorpusNotReady corpusId) BE_node_error_corpus_not_found
BE_node_not_found -> pure $ mkFrontendErr' txt (Proxy @'BE_node_error_corpus_not_found) FE_node_error_corpus_not_found
-> do nodeId <- arbitrary
pure $ mkFrontendErr' txt (Proxy @'BE_node_not_found) (NodeNotFound nodeId)
BE_tree_error_root_not_found BE_tree_error_root_not_found
-> do rootId <- arbitrary -> do rootId <- arbitrary
pure $ mkFrontendErr' txt (Proxy @'BE_tree_error_root_not_found) (RootNotFound rootId) pure $ mkFrontendErr' txt (Proxy @'BE_tree_error_root_not_found) (RootNotFound rootId)
...@@ -246,20 +246,15 @@ genFrontendErr txt be = case be of ...@@ -246,20 +246,15 @@ genFrontendErr txt be = case be of
-- | This compiles if we use the correct payload type, or otherwise it won't: -- | This compiles if we use the correct payload type, or otherwise it won't:
-- >>> mkFrontendErr (Proxy @'BE_phylo_corpus_not_ready) NodeNotFound -- >>> mkFrontendErr (Proxy @'BE_phylo_corpus_not_ready) NodeNotFound
_myTest :: FrontendError _myTest :: FrontendError
_myTest = mkFrontendErr (Proxy @'BE_phylo_corpus_not_ready) (PhyloCorpusNotReady 42) _myTest = mkFrontendErr (Proxy @'BE_node_error_root_not_found) FE_node_error_root_not_found
instance ToJSON BackendErrorType where instance ToJSON BackendErrorType where
toJSON = \case toJSON = JSON.String . T.pack . drop 3 . show
BE_phylo_corpus_not_ready -> JSON.String "phylo_corpus_not_ready"
BE_node_not_found -> JSON.String "node_not_found"
BE_tree_error_root_not_found -> JSON.String "tree_error_root_not_found"
instance FromJSON BackendErrorType where instance FromJSON BackendErrorType where
parseJSON (String s) = case s of parseJSON (String s) = case readMaybe (T.unpack $ "BE_" <> s) of
"phylo_corpus_not_ready" -> pure BE_phylo_corpus_not_ready Just v -> pure v
"node_not_found" -> pure BE_node_not_found Nothing -> fail $ "FromJSON BackendErrorType unexpected value: " <> T.unpack s
"tree_error_root_not_found" -> pure BE_tree_error_root_not_found
unexpected -> fail $ "FromJSON BackendErrorType unexpected value: " <> T.unpack unexpected
parseJSON ty = typeMismatch "BackendErrorType" ty parseJSON ty = typeMismatch "BackendErrorType" ty
instance ToJSON FrontendError where instance ToJSON FrontendError where
...@@ -274,11 +269,11 @@ instance FromJSON FrontendError where ...@@ -274,11 +269,11 @@ instance FromJSON FrontendError where
(fe_diagnostic :: T.Text) <- o .: "diagnostic" (fe_diagnostic :: T.Text) <- o .: "diagnostic"
(fe_type :: BackendErrorType) <- o .: "type" (fe_type :: BackendErrorType) <- o .: "type"
case fe_type of case fe_type of
BE_phylo_corpus_not_ready -> do BE_node_error_root_not_found -> do
(fe_data :: ToFrontendErrorData 'BE_phylo_corpus_not_ready) <- o .: "data" (fe_data :: ToFrontendErrorData 'BE_node_error_root_not_found) <- o .: "data"
pure FrontendError{..} pure FrontendError{..}
BE_node_not_found -> do BE_node_error_corpus_not_found -> do
(fe_data :: ToFrontendErrorData 'BE_node_not_found) <- o .: "data" (fe_data :: ToFrontendErrorData 'BE_node_error_corpus_not_found) <- o .: "data"
pure FrontendError{..} pure FrontendError{..}
BE_tree_error_root_not_found -> do BE_tree_error_root_not_found -> do
(fe_data :: ToFrontendErrorData 'BE_tree_error_root_not_found) <- o .: "data" (fe_data :: ToFrontendErrorData 'BE_tree_error_root_not_found) <- o .: "data"
......
...@@ -42,8 +42,8 @@ data NodeError = NoListFound ListId ...@@ -42,8 +42,8 @@ data NodeError = NoListFound ListId
instance Prelude.Show NodeError instance Prelude.Show NodeError
where where
show (NoListFound {}) = "No list found" show (NoListFound {}) = "No list found"
show NoRootFound = "No Root found" show NoRootFound = "No root found"
show NoCorpusFound = "No Corpus found" show NoCorpusFound = "No corpus found"
show (NoUserFound ur) = "User(" <> T.unpack (renderUser ur) <> ") not found" show (NoUserFound ur) = "User(" <> T.unpack (renderUser ur) <> ") not found"
show MkNode = "Cannot make node" show MkNode = "Cannot make node"
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment