2 Module : Gargantext.Database.Types.Error
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
11 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
12 {-# OPTIONS_GHC -fno-warn-orphans #-}
14 {-# LANGUAGE Arrows #-}
15 {-# LANGUAGE ConstraintKinds #-}
16 {-# LANGUAGE FunctionalDependencies #-}
17 {-# LANGUAGE TemplateHaskell #-}
18 {-# LANGUAGE TypeFamilies #-}
20 module Gargantext.Database.Query.Table.Node.Error where
22 import Gargantext.Database.Admin.Types.Node (NodeId)
23 import Control.Lens (Prism', (#), (^?))
24 import Control.Monad.Error.Class (MonadError(..))
25 import Gargantext.Prelude hiding (sum, head)
26 import Prelude hiding (null, id, map, sum)
28 ------------------------------------------------------------------------
29 data NodeError = NoListFound
43 instance Show NodeError
45 show NoListFound = "No list found"
46 show NoRootFound = "No Root found"
47 show NoCorpusFound = "No Corpus found"
48 show NoUserFound = "No user found"
50 show MkNode = "Cannot make node"
51 show NegativeId = "Node with negative Id"
52 show UserNoParent = "Should not have parent"
53 show HasParent = "NodeType has parent"
54 show NotImplYet = "Not implemented yet"
55 show ManyParents = "Too many parents"
56 show ManyNodeUsers = "Many userNode/user"
57 show (DoesNotExist n) = "Node does not exist" <> show n
58 show NeedsConfiguration = "Needs configuration"
60 class HasNodeError e where
61 _NodeError :: Prism' e NodeError
63 nodeError :: ( MonadError e m
66 nodeError ne = throwError $ _NodeError # ne
68 catchNodeError :: (MonadError e m, HasNodeError e) => m a -> (NodeError -> m a) -> m a
69 catchNodeError f g = catchError f (\e -> maybe (throwError e) g (e ^? _NodeError))