22
33module FoundationDB.Error.Internal where
44
5-
65import Control.Exception
7- import Control.Monad.Error.Class (MonadError (.. ), liftEither )
8- import Control.Monad.IO.Class (MonadIO (.. ))
6+ import Control.Monad.Error.Class (MonadError (.. ), liftEither )
7+ import Control.Monad.IO.Class (MonadIO (.. ))
98import Data.ByteString (ByteString )
109import Data.Maybe (fromJust )
1110import Data.Word (Word32 )
12-
1311import qualified FoundationDB.Internal.Bindings as FDB
1412
1513fdbEither :: MonadIO m => m (FDB. CFDBError , a ) -> m (Either Error a )
@@ -19,8 +17,10 @@ fdbEither f = do
1917 Just x -> return $ Left $ CError x
2018 Nothing -> return (Right res)
2119
22- fdbExcept :: (MonadError Error m , MonadIO m )
23- => IO (FDB. CFDBError , a ) -> m a
20+ fdbExcept ::
21+ (MonadError Error m , MonadIO m ) =>
22+ IO (FDB. CFDBError , a ) ->
23+ m a
2424fdbExcept x = do
2525 e <- liftIO $ fdbEither x
2626 liftEither e
@@ -32,16 +32,17 @@ fdbEither' f = do
3232 Just x -> return $ Left $ CError x
3333 Nothing -> return (Right () )
3434
35- fdbExcept' :: (MonadError Error m , MonadIO m ) =>
36- IO FDB. CFDBError -> m ()
35+ fdbExcept' ::
36+ (MonadError Error m , MonadIO m ) =>
37+ IO FDB. CFDBError ->
38+ m ()
3739fdbExcept' x = do
3840 e <- liftIO $ fdbEither' x
3941 liftEither e
4042
4143liftFDBError :: MonadError Error m => Either FDB. CFDBError a -> m a
4244liftFDBError = either (throwError . CError . fromJust . toError) return
4345
44-
4546fdbThrowing :: IO (FDB. CFDBError , a ) -> IO a
4647fdbThrowing a = do
4748 (e, res) <- a
@@ -69,67 +70,66 @@ data Error = CError CError | Error FDBHsError
6970
7071instance Exception Error
7172
72- data DirLayerUserError =
73- CannotOpenRoot
74- -- ^ Thrown if the user attempts to open the root directory.
75- | PrefixInUse
76- -- ^ Thrown if the user specifies a manual prefix that is already in use.
77- | ManualPrefixConflict ByteString
78- -- ^ Thrown if a prefix manually specified by the user previously conflicts
79- -- with a prefix chosen by the automatic allocator. Includes the conflicting
80- -- prefix.
81- | LayerMismatch ByteString ByteString
82- -- ^ The @layer@ bytestring provided to @open'@ does not match the layer
83- -- already present. The mismatched layers are included in this constructor.
84- | VersionError Word32 Word32 Word32
85- -- ^ Thrown if the directory layer structure already in FoundationDB is a
86- -- newer major version than that provided by this library. This would mean
87- -- that the directory layer was originally created by a newer version of one
88- -- of the FoundationDB client libraries. The major, minor, micro version
89- -- of the directory layer are provided to this constructor.
90-
73+ data DirLayerUserError
74+ = -- | Thrown if the user attempts to open the root directory.
75+ CannotOpenRoot
76+ | -- | Thrown if the user specifies a manual prefix that is already in use.
77+ PrefixInUse
78+ | -- | Thrown if a prefix manually specified by the user previously conflicts
79+ -- with a prefix chosen by the automatic allocator. Includes the conflicting
80+ -- prefix.
81+ ManualPrefixConflict ByteString
82+ | -- | The @layer@ bytestring provided to @open'@ does not match the layer
83+ -- already present. The mismatched layers are included in this constructor.
84+ LayerMismatch ByteString ByteString
85+ | -- | Thrown if the directory layer structure already in FoundationDB is a
86+ -- newer major version than that provided by this library. This would mean
87+ -- that the directory layer was originally created by a newer version of one
88+ -- of the FoundationDB client libraries. The major, minor, micro version
89+ -- of the directory layer are provided to this constructor.
90+ VersionError Word32 Word32 Word32
9191 deriving (Show , Eq , Ord )
9292
9393-- | Errors arising from the foundationdb-haskell library implementation.
94- data FDBHsError =
95- DirLayerUserError DirLayerUserError
96- -- ^ Errors that can occur from user error when using the directory layer.
97- | DirectoryLayerInternalError String
98- -- ^ Errors that can occur when doing directory layer operations .
99- -- These can be indicative of bugs in foundationdb-haskell.
100- | ParseError String
101- -- ^ Errors in parsing tuples.
102- | MaxRetriesExceeded Error
103- -- ^ Thrown by foundationdb-haskell's transaction retry logic. Contains the
104- -- underlying error from the C bindings that caused the transaction to be
105- -- retried.
106- | UnsupportedAPIVersion
107- -- ^ Thrown by foundationdb-haskell on startup if the Haskell code doesn't
108- -- support the desired API version. This can happen even if the underlying C
109- -- library does support the desired version -- we sometimes drop support
110- -- for older versions sooner than the C API.
111- | ConflictRangeParseFailure [( ByteString , ByteString )]
112- -- ^ The structure of keys returned by the transaction module of the special
113- -- keys keyspace was not in the expected format. The raw key/values
114- -- are returned, unparsed.
115- | TupleIntTooLarge
116- -- ^ Thrown when an integer to be encoded by the tuple layer would take more
117- -- than 255 bytes to encode.
94+ data FDBHsError
95+ = -- | Errors that can occur from user error when using the directory layer.
96+ DirLayerUserError DirLayerUserError
97+ | -- | Errors that can occur when doing directory layer operations.
98+ -- These can be indicative of bugs in foundationdb-haskell .
99+ DirectoryLayerInternalError String
100+ | -- | Errors in parsing tuples.
101+ ParseError String
102+ | -- | Thrown by foundationdb-haskell's transaction retry logic. Contains the
103+ -- underlying error from the C bindings that caused the transaction to be
104+ -- retried.
105+ MaxRetriesExceeded Error
106+ | -- | Thrown by foundationdb-haskell on startup if the Haskell code doesn't
107+ -- support the desired API version. This can happen even if the underlying C
108+ -- library does support the desired version -- we sometimes drop support
109+ -- for older versions sooner than the C API.
110+ UnsupportedAPIVersion
111+ | -- | The structure of keys returned by the transaction module of the special
112+ -- keys keyspace was not in the expected format. The raw key/values
113+ -- are returned, unparsed.
114+ ConflictRangeParseFailure [( ByteString , ByteString )]
115+ | -- | Thrown when an integer to be encoded by the tuple layer would take more
116+ -- than 255 bytes to encode.
117+ TupleIntTooLarge
118118 deriving (Show , Eq , Ord )
119119
120120-- | Errors that can come from the underlying C library.
121121-- Most error names are self-explanatory.
122122-- See https://apple.github.io/foundationdb/api-error-codes.html#developer-guide-error-codes
123123-- for a description of these errors.
124- data CError =
125- OperationFailed
124+ data CError
125+ = OperationFailed
126126 | TimedOut
127127 | TransactionTooOld
128128 | FutureVersion
129- | NotCommitted [ ConflictRange ]
130- -- ^ Returned if a transaction failed because of a conflict. If
131- -- 'FoundationDB.Transaction.getConflictingKeys' is set, returns conflicting
132- -- key ranges.
129+ | -- | Returned if a transaction failed because of a conflict. If
130+ -- 'FoundationDB.Transaction.getConflictingKeys' is set, returns conflicting
131+ -- key ranges.
132+ NotCommitted [ ConflictRange ]
133133 | CommitUnknownResult
134134 | TransactionCanceled
135135 | TransactionTimedOut
0 commit comments