Skip to content

Commit e47745f

Browse files
committed
Reformat files with ormolu, fix warnings
1 parent 3c70e25 commit e47745f

File tree

21 files changed

+804
-715
lines changed

21 files changed

+804
-715
lines changed

src/FoundationDB.hs

Lines changed: 43 additions & 36 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,8 @@
1+
{-# LANGUAGE ExistentialQuantification #-}
2+
{-# LANGUAGE FlexibleContexts #-}
3+
{-# LANGUAGE NamedFieldPuns #-}
4+
{-# LANGUAGE RecordWildCards #-}
5+
16
-- | This module contains all of the basics needed to build a program that
27
-- interacts with <https://apple.github.io/foundationdb/index.html FoundationDB>.
38
-- The documentation throughout this library assumes that you have already read
@@ -15,35 +20,32 @@
1520
-- Whichever you choose, all errors you can encounter are defined in
1621
-- "FoundationDB.Error".
1722
-- * See <https://github.com/crclark/foundationdb-haskell/blob/master/tests/Properties/FoundationDB/Transaction.hs#L48 the tests> for basic usage examples.
23+
module FoundationDB
24+
( -- * Initialization
25+
FDB.currentAPIVersion,
26+
withFoundationDB,
27+
FoundationDBOptions (..),
28+
defaultOptions,
29+
Database,
30+
apiVersionInUse,
1831

19-
{-# LANGUAGE FlexibleContexts #-}
20-
{-# LANGUAGE ExistentialQuantification #-}
21-
{-# LANGUAGE RecordWildCards #-}
22-
{-# LANGUAGE NamedFieldPuns #-}
32+
-- * Transactions
33+
module FoundationDB.Transaction,
2334

24-
module FoundationDB (
25-
-- * Initialization
26-
FDB.currentAPIVersion
27-
, withFoundationDB
28-
, FoundationDBOptions(..)
29-
, defaultOptions
30-
, Database
31-
, apiVersionInUse
32-
-- * Transactions
33-
, module FoundationDB.Transaction
34-
-- * Errors
35-
, module FoundationDB.Error
36-
-- * Helpers for ghci
37-
, startFoundationDB
38-
, stopFoundationDB
39-
) where
35+
-- * Errors
36+
module FoundationDB.Error,
37+
38+
-- * Helpers for ghci
39+
startFoundationDB,
40+
stopFoundationDB,
41+
)
42+
where
4043

4144
import Control.Concurrent (forkFinally)
42-
import Control.Concurrent.MVar (newEmptyMVar, takeMVar, putMVar, MVar)
45+
import Control.Concurrent.MVar (MVar, newEmptyMVar, putMVar, takeMVar)
4346
import Control.Exception
4447
import Control.Monad.Except
4548
import Data.Maybe (fromMaybe)
46-
4749
import FoundationDB.Error
4850
import FoundationDB.Error.Internal
4951
import qualified FoundationDB.Internal.Bindings as FDB
@@ -55,8 +57,9 @@ import System.IO.Unsafe (unsafePerformIO)
5557
-- open source release).
5658
validateVersion :: Int -> IO ()
5759
validateVersion v =
58-
when (v < 520)
59-
(throw (Error UnsupportedAPIVersion))
60+
when
61+
(v < 520)
62+
(throw (Error UnsupportedAPIVersion))
6063

6164
#if FDB_API_VERSION < 610
6265
initCluster :: FilePath -> IO FDB.Cluster
@@ -94,10 +97,11 @@ withDatabase opts@FoundationDBOptions{clusterFile} =
9497
-- | Handles correctly starting up the network connection to the DB.
9598
-- Can only be called once per process! Throws an 'Error' if any part of
9699
-- setting up the connection to FoundationDB fails.
97-
withFoundationDB :: FoundationDBOptions
98-
-> (Database -> IO a)
99-
-> IO a
100-
withFoundationDB opts@FoundationDBOptions{..} m = do
100+
withFoundationDB ::
101+
FoundationDBOptions ->
102+
(Database -> IO a) ->
103+
IO a
104+
withFoundationDB opts@FoundationDBOptions {..} m = do
101105
validateVersion apiVersion
102106
done <- newEmptyMVar
103107
fdbThrowing' $ FDB.selectAPIVersion apiVersion
@@ -108,9 +112,9 @@ withFoundationDB opts@FoundationDBOptions{..} m = do
108112
where
109113
start done = void $ forkFinally FDB.runNetwork (\_ -> putMVar done ())
110114
stop done = FDB.stopNetwork >> takeMVar done
111-
run db@Database{databasePtr} = do
112-
forM_ databaseOptions (fdbThrowing' . FDB.databaseSetOption databasePtr)
113-
m db
115+
run db@Database {databasePtr} = do
116+
forM_ databaseOptions (fdbThrowing' . FDB.databaseSetOption databasePtr)
117+
m db
114118

115119
startFoundationDBGlobalLock :: MVar ()
116120
startFoundationDBGlobalLock = unsafePerformIO newEmptyMVar
@@ -121,15 +125,18 @@ startFoundationDBGlobalLock = unsafePerformIO newEmptyMVar
121125
-- since it handles cleanup. This function is only intended to be used in GHCi.
122126
-- Can only be called once per process! Throws an 'Error' if any part of
123127
-- setting up the connection FoundationDB fails.
124-
startFoundationDB :: FoundationDBOptions
125-
-> IO Database
126-
startFoundationDB opts@FoundationDBOptions{..} = do
128+
startFoundationDB ::
129+
FoundationDBOptions ->
130+
IO Database
131+
startFoundationDB opts@FoundationDBOptions {..} = do
127132
validateVersion apiVersion
128133
fdbThrowing' $ FDB.selectAPIVersion apiVersion
129134
forM_ networkOptions (fdbThrowing' . FDB.networkSetOption)
130135
fdbThrowing' FDB.setupNetwork
131-
void $ forkFinally FDB.runNetwork
132-
(\_ -> putMVar startFoundationDBGlobalLock ())
136+
void $
137+
forkFinally
138+
FDB.runNetwork
139+
(\_ -> putMVar startFoundationDBGlobalLock ())
133140
#if FDB_API_VERSION < 610
134141
cluster <- initCluster (fromMaybe "" clusterFile)
135142
db <- initDB cluster

src/FoundationDB/Error.hs

Lines changed: 10 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,13 @@
11
-- | Types for all errors that can be thrown while using this library.
2-
module FoundationDB.Error (
3-
Error(..),
4-
DirLayerUserError(..),
5-
FDBHsError(..),
6-
CError(..),
7-
ConflictRange(..),
8-
retryable,
9-
retryableNotCommitted
10-
) where
2+
module FoundationDB.Error
3+
( Error (..),
4+
DirLayerUserError (..),
5+
FDBHsError (..),
6+
CError (..),
7+
ConflictRange (..),
8+
retryable,
9+
retryableNotCommitted,
10+
)
11+
where
1112

1213
import FoundationDB.Error.Internal

src/FoundationDB/Error/Internal.hs

Lines changed: 58 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -2,14 +2,12 @@
22

33
module FoundationDB.Error.Internal where
44

5-
65
import 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 (..))
98
import Data.ByteString (ByteString)
109
import Data.Maybe (fromJust)
1110
import Data.Word (Word32)
12-
1311
import qualified FoundationDB.Internal.Bindings as FDB
1412

1513
fdbEither :: 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
2424
fdbExcept 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 ()
3739
fdbExcept' x = do
3840
e <- liftIO $ fdbEither' x
3941
liftEither e
4042

4143
liftFDBError :: MonadError Error m => Either FDB.CFDBError a -> m a
4244
liftFDBError = either (throwError . CError . fromJust . toError) return
4345

44-
4546
fdbThrowing :: IO (FDB.CFDBError, a) -> IO a
4647
fdbThrowing a = do
4748
(e, res) <- a
@@ -69,67 +70,66 @@ data Error = CError CError | Error FDBHsError
6970

7071
instance 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

src/FoundationDB/Internal/Database.hs

Lines changed: 24 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -1,39 +1,42 @@
1-
module FoundationDB.Internal.Database (
2-
FoundationDBOptions(..),
3-
defaultOptions,
4-
Database(..),
5-
apiVersionInUse
6-
) where
1+
module FoundationDB.Internal.Database
2+
( FoundationDBOptions (..),
3+
defaultOptions,
4+
Database (..),
5+
apiVersionInUse,
6+
)
7+
where
78

89
import qualified FoundationDB.Internal.Bindings as FDB
9-
import FoundationDB.Options.DatabaseOption (DatabaseOption(..))
10-
import FoundationDB.Options.NetworkOption (NetworkOption(..))
10+
import FoundationDB.Options.DatabaseOption (DatabaseOption (..))
11+
import FoundationDB.Options.NetworkOption (NetworkOption (..))
1112

1213
-- | Options set at the connection level for FoundationDB.
1314
data FoundationDBOptions = FoundationDBOptions
14-
{ apiVersion :: Int
15-
-- ^ Desired API version. See 'currentAPIVersion' for the latest
15+
{ -- | Desired API version. See 'currentAPIVersion' for the latest
1616
-- version installed on your system. The C API (and this library) allow you
1717
-- to choose any version earlier than 'currentAPIVersion' to get the client
1818
-- behavior of that version of the FoundationDB client library.
19-
, clusterFile :: Maybe FilePath
20-
-- ^ Path to your @fdb.cluster@ file. If 'Nothing', uses
21-
-- default location.
22-
, networkOptions :: [NetworkOption]
23-
-- ^ Additional network options. Each will be set in order.
24-
, databaseOptions :: [DatabaseOption]
25-
-- ^ Additional database options. Each will be set in order.
26-
} deriving (Show, Eq, Ord)
19+
apiVersion :: Int,
20+
-- | Path to your @fdb.cluster@ file. If 'Nothing', uses
21+
-- default location.
22+
clusterFile :: Maybe FilePath,
23+
-- | Additional network options. Each will be set in order.
24+
networkOptions :: [NetworkOption],
25+
-- | Additional database options. Each will be set in order.
26+
databaseOptions :: [DatabaseOption]
27+
}
28+
deriving (Show, Eq, Ord)
2729

2830
-- | Uses the current API version, the default cluster file location, and no
2931
-- additional options.
3032
defaultOptions :: FoundationDBOptions
3133
defaultOptions = FoundationDBOptions FDB.currentAPIVersion Nothing [] []
3234

3335
data Database = Database
34-
{ databasePtr :: FDB.DatabasePtr
35-
, databaseFoundationDBOptions :: FoundationDBOptions
36-
} deriving (Show, Eq)
36+
{ databasePtr :: FDB.DatabasePtr,
37+
databaseFoundationDBOptions :: FoundationDBOptions
38+
}
39+
deriving (Show, Eq)
3740

3841
-- | Returns the API version that was specified in the 'apiVersion' field when
3942
-- the FDB client was initialized.

0 commit comments

Comments
 (0)