Format documentation

PR#113
This commit is contained in:
Victor Denisov 2020-04-04 14:24:38 -07:00
commit 69f5dd450f
4 changed files with 95 additions and 71 deletions

View file

@ -78,7 +78,7 @@ renameCollection from to = do
useDb admin $ runCommand ["renameCollection" =: db <.> from, "to" =: db <.> to, "dropTarget" =: True] useDb admin $ runCommand ["renameCollection" =: db <.> from, "to" =: db <.> to, "dropTarget" =: True]
dropCollection :: (MonadIO m, MonadFail m) => Collection -> Action m Bool dropCollection :: (MonadIO m, MonadFail m) => Collection -> Action m Bool
-- ^ Delete the given collection! Return True if collection existed (and was deleted); return False if collection did not exist (and no action). -- ^ Delete the given collection! Return @True@ if collection existed (and was deleted); return @False@ if collection did not exist (and no action).
dropCollection coll = do dropCollection coll = do
resetIndexCache resetIndexCache
r <- runCommand ["drop" =: coll] r <- runCommand ["drop" =: coll]
@ -87,7 +87,7 @@ dropCollection coll = do
fail $ "dropCollection failed: " ++ show r fail $ "dropCollection failed: " ++ show r
validateCollection :: (MonadIO m) => Collection -> Action m Document validateCollection :: (MonadIO m) => Collection -> Action m Document
-- ^ This operation takes a while -- ^ Validate the given collection, scanning the data and indexes for correctness. This operation takes a while.
validateCollection coll = runCommand ["validate" =: coll] validateCollection coll = runCommand ["validate" =: coll]
-- ** Index -- ** Index
@ -112,7 +112,7 @@ idxDocument Index{..} db = [
"dropDups" =: iDropDups ] ++ (maybeToList $ fmap ((=:) "expireAfterSeconds") iExpireAfterSeconds) "dropDups" =: iDropDups ] ++ (maybeToList $ fmap ((=:) "expireAfterSeconds") iExpireAfterSeconds)
index :: Collection -> Order -> Index index :: Collection -> Order -> Index
-- ^ Spec of index of ordered keys on collection. Name is generated from keys. Unique and dropDups are False. -- ^ Spec of index of ordered keys on collection. 'iName' is generated from keys. 'iUnique' and 'iDropDups' are @False@.
index coll keys = Index coll keys (genName keys) False False Nothing index coll keys = Index coll keys (genName keys) False False Nothing
genName :: Order -> IndexName genName :: Order -> IndexName
@ -133,7 +133,7 @@ createIndex :: (MonadIO m) => Index -> Action m ()
createIndex idx = insert_ "system.indexes" . idxDocument idx =<< thisDatabase createIndex idx = insert_ "system.indexes" . idxDocument idx =<< thisDatabase
dropIndex :: (MonadIO m) => Collection -> IndexName -> Action m Document dropIndex :: (MonadIO m) => Collection -> IndexName -> Action m Document
-- ^ Remove the index -- ^ Remove the index from the given collection.
dropIndex coll idxName = do dropIndex coll idxName = do
resetIndexCache resetIndexCache
runCommand ["deleteIndexes" =: coll, "index" =: idxName] runCommand ["deleteIndexes" =: coll, "index" =: idxName]
@ -198,7 +198,7 @@ allUsers = map (exclude ["_id"]) `liftM` (rest =<< find
addUser :: (MonadIO m) addUser :: (MonadIO m)
=> Bool -> Username -> Password -> Action m () => Bool -> Username -> Password -> Action m ()
-- ^ Add user with password with read-only access if bool is True or read-write access if bool is False -- ^ Add user with password with read-only access if the boolean argument is @True@, or read-write access if it's @False@
addUser readOnly user pass = do addUser readOnly user pass = do
mu <- findOne (select ["user" =: user] "system.users") mu <- findOne (select ["user" =: user] "system.users")
let usr = merge ["readOnly" =: readOnly, "pwd" =: pwHash user pass] (maybe ["user" =: user] id mu) let usr = merge ["readOnly" =: readOnly, "pwd" =: pwHash user pass] (maybe ["user" =: user] id mu)
@ -211,11 +211,11 @@ removeUser user = delete (select ["user" =: user] "system.users")
-- ** Database -- ** Database
admin :: Database admin :: Database
-- ^ \"admin\" database -- ^ The \"admin\" database, which stores user authorization and authentication data plus other system collections.
admin = "admin" admin = "admin"
cloneDatabase :: (MonadIO m) => Database -> Host -> Action m Document cloneDatabase :: (MonadIO m) => Database -> Host -> Action m Document
-- ^ Copy database from given host to the server I am connected to. Fails and returns @"ok" = 0@ if we don't have permission to read from given server (use copyDatabase in this case). -- ^ Copy database from given host to the server I am connected to. Fails and returns @"ok" = 0@ if we don't have permission to read from given server (use 'copyDatabase' in this case).
cloneDatabase db fromHost = useDb db $ runCommand ["clone" =: showHostPort fromHost] cloneDatabase db fromHost = useDb db $ runCommand ["clone" =: showHostPort fromHost]
copyDatabase :: (MonadIO m) => Database -> Host -> Maybe (Username, Password) -> Database -> Action m Document copyDatabase :: (MonadIO m) => Database -> Host -> Maybe (Username, Password) -> Database -> Action m Document
@ -239,9 +239,11 @@ repairDatabase db = useDb db $ runCommand ["repairDatabase" =: (1 :: Int)]
-- ** Server -- ** Server
serverBuildInfo :: (MonadIO m) => Action m Document serverBuildInfo :: (MonadIO m) => Action m Document
-- ^ Return a document containing the parameters used to compile the server instance.
serverBuildInfo = useDb admin $ runCommand ["buildinfo" =: (1 :: Int)] serverBuildInfo = useDb admin $ runCommand ["buildinfo" =: (1 :: Int)]
serverVersion :: (MonadIO m) => Action m Text serverVersion :: (MonadIO m) => Action m Text
-- ^ Return the version of the server instance.
serverVersion = at "version" `liftM` serverBuildInfo serverVersion = at "version" `liftM` serverBuildInfo
-- * Diagnostics -- * Diagnostics
@ -249,15 +251,19 @@ serverVersion = at "version" `liftM` serverBuildInfo
-- ** Collection -- ** Collection
collectionStats :: (MonadIO m) => Collection -> Action m Document collectionStats :: (MonadIO m) => Collection -> Action m Document
-- ^ Return some storage statistics for the given collection.
collectionStats coll = runCommand ["collstats" =: coll] collectionStats coll = runCommand ["collstats" =: coll]
dataSize :: (MonadIO m) => Collection -> Action m Int dataSize :: (MonadIO m) => Collection -> Action m Int
-- ^ Return the total uncompressed size (in bytes) in memory of all records in the given collection. Does not include indexes.
dataSize c = at "size" `liftM` collectionStats c dataSize c = at "size" `liftM` collectionStats c
storageSize :: (MonadIO m) => Collection -> Action m Int storageSize :: (MonadIO m) => Collection -> Action m Int
-- ^ Return the total bytes allocated to the given collection. Does not include indexes.
storageSize c = at "storageSize" `liftM` collectionStats c storageSize c = at "storageSize" `liftM` collectionStats c
totalIndexSize :: (MonadIO m) => Collection -> Action m Int totalIndexSize :: (MonadIO m) => Collection -> Action m Int
-- ^ The total size in bytes of all indexes in this collection.
totalIndexSize c = at "totalIndexSize" `liftM` collectionStats c totalIndexSize c = at "totalIndexSize" `liftM` collectionStats c
totalSize :: MonadIO m => Collection -> Action m Int totalSize :: MonadIO m => Collection -> Action m Int
@ -270,34 +276,45 @@ totalSize coll = do
-- ** Profiling -- ** Profiling
data ProfilingLevel = Off | Slow | All deriving (Show, Enum, Eq) -- | The available profiler levels.
data ProfilingLevel
= Off -- ^ No data collection.
| Slow -- ^ Data collected only for slow operations. The slow operation time threshold is 100ms by default, but can be changed using 'setProfilingLevel'.
| All -- ^ Data collected for all operations.
deriving (Show, Enum, Eq)
getProfilingLevel :: (MonadIO m) => Action m ProfilingLevel getProfilingLevel :: (MonadIO m) => Action m ProfilingLevel
-- ^ Get the profiler level.
getProfilingLevel = (toEnum . at "was") `liftM` runCommand ["profile" =: (-1 :: Int)] getProfilingLevel = (toEnum . at "was") `liftM` runCommand ["profile" =: (-1 :: Int)]
type MilliSec = Int type MilliSec = Int
setProfilingLevel :: (MonadIO m) => ProfilingLevel -> Maybe MilliSec -> Action m () setProfilingLevel :: (MonadIO m) => ProfilingLevel -> Maybe MilliSec -> Action m ()
-- ^ Set the profiler level, and optionally the slow operation time threshold (in milliseconds).
setProfilingLevel p mSlowMs = setProfilingLevel p mSlowMs =
runCommand (["profile" =: fromEnum p] ++ ("slowms" =? mSlowMs)) >> return () runCommand (["profile" =: fromEnum p] ++ ("slowms" =? mSlowMs)) >> return ()
-- ** Database -- ** Database
dbStats :: (MonadIO m) => Action m Document dbStats :: (MonadIO m) => Action m Document
-- ^ Return some storage statistics for the given database.
dbStats = runCommand ["dbstats" =: (1 :: Int)] dbStats = runCommand ["dbstats" =: (1 :: Int)]
currentOp :: (MonadIO m) => Action m (Maybe Document) currentOp :: (MonadIO m) => Action m (Maybe Document)
-- ^ See currently running operation on the database, if any -- ^ See currently running operation on the database, if any
currentOp = findOne (select [] "$cmd.sys.inprog") currentOp = findOne (select [] "$cmd.sys.inprog")
-- | An operation indentifier.
type OpNum = Int type OpNum = Int
killOp :: (MonadIO m) => OpNum -> Action m (Maybe Document) killOp :: (MonadIO m) => OpNum -> Action m (Maybe Document)
-- ^ Terminate the operation specified by the given 'OpNum'.
killOp op = findOne (select ["op" =: op] "$cmd.sys.killop") killOp op = findOne (select ["op" =: op] "$cmd.sys.killop")
-- ** Server -- ** Server
serverStatus :: (MonadIO m) => Action m Document serverStatus :: (MonadIO m) => Action m Document
-- ^ Return a document with an overview of the state of the database.
serverStatus = useDb admin $ runCommand ["serverStatus" =: (1 :: Int)] serverStatus = useDb admin $ runCommand ["serverStatus" =: (1 :: Int)]

View file

@ -84,6 +84,7 @@ showHostPort (Host _ (UnixSocket path)) = "unix:" ++ path
readHostPortM :: (MonadFail m) => String -> m Host readHostPortM :: (MonadFail m) => String -> m Host
-- ^ Read string \"hostname:port\" as @Host hosthame (PortNumber port)@ or \"hostname\" as @host hostname@ (default port). Fail if string does not match either syntax. -- ^ Read string \"hostname:port\" as @Host hosthame (PortNumber port)@ or \"hostname\" as @host hostname@ (default port). Fail if string does not match either syntax.
-- TODO: handle Service port -- TODO: handle Service port
readHostPortM = either (fail . show) return . parse parser "readHostPort" where readHostPortM = either (fail . show) return . parse parser "readHostPort" where
hostname = many1 (letter <|> digit <|> char '-' <|> char '.' <|> char '_') hostname = many1 (letter <|> digit <|> char '-' <|> char '.' <|> char '_')
@ -109,16 +110,16 @@ readHostPort = fromJust . readHostPortM
type Secs = Double type Secs = Double
globalConnectTimeout :: IORef Secs globalConnectTimeout :: IORef Secs
-- ^ 'connect' (and 'openReplicaSet') fails if it can't connect within this many seconds (default is 6 seconds). Use 'connect\'' (and 'openReplicaSet\'') if you want to ignore this global and specify your own timeout. Note, this timeout only applies to initial connection establishment, not when reading/writing to the connection. -- ^ 'connect' (and 'openReplicaSet') fails if it can't connect within this many seconds (default is 6 seconds). Use 'connect'' (and 'openReplicaSet'') if you want to ignore this global and specify your own timeout. Note, this timeout only applies to initial connection establishment, not when reading/writing to the connection.
globalConnectTimeout = unsafePerformIO (newIORef 6) globalConnectTimeout = unsafePerformIO (newIORef 6)
{-# NOINLINE globalConnectTimeout #-} {-# NOINLINE globalConnectTimeout #-}
connect :: Host -> IO Pipe connect :: Host -> IO Pipe
-- ^ Connect to Host returning pipelined TCP connection. Throw IOError if connection refused or no response within 'globalConnectTimeout'. -- ^ Connect to Host returning pipelined TCP connection. Throw 'IOError' if connection refused or no response within 'globalConnectTimeout'.
connect h = readIORef globalConnectTimeout >>= flip connect' h connect h = readIORef globalConnectTimeout >>= flip connect' h
connect' :: Secs -> Host -> IO Pipe connect' :: Secs -> Host -> IO Pipe
-- ^ Connect to Host returning pipelined TCP connection. Throw IOError if connection refused or no response within given number of seconds. -- ^ Connect to Host returning pipelined TCP connection. Throw 'IOError' if connection refused or no response within given number of seconds.
connect' timeoutSecs (Host hostname port) = do connect' timeoutSecs (Host hostname port) = do
mh <- timeout (round $ timeoutSecs * 1000000) (connectTo hostname port) mh <- timeout (round $ timeoutSecs * 1000000) (connectTo hostname port)
handle <- maybe (ioError $ userError "connect timed out") return mh handle <- maybe (ioError $ userError "connect timed out") return mh
@ -137,11 +138,11 @@ data TransportSecurity = Secure | Unsecure
data ReplicaSet = ReplicaSet ReplicaSetName (MVar [(Host, Maybe Pipe)]) Secs TransportSecurity data ReplicaSet = ReplicaSet ReplicaSetName (MVar [(Host, Maybe Pipe)]) Secs TransportSecurity
replSetName :: ReplicaSet -> Text replSetName :: ReplicaSet -> Text
-- ^ name of connected replica set -- ^ Get the name of connected replica set.
replSetName (ReplicaSet rsName _ _ _) = rsName replSetName (ReplicaSet rsName _ _ _) = rsName
openReplicaSet :: (ReplicaSetName, [Host]) -> IO ReplicaSet openReplicaSet :: (ReplicaSetName, [Host]) -> IO ReplicaSet
-- ^ Open connections (on demand) to servers in replica set. Supplied hosts is seed list. At least one of them must be a live member of the named replica set, otherwise fail. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSet\'' instead. -- ^ Open connections (on demand) to servers in replica set. Supplied hosts is seed list. At least one of them must be a live member of the named replica set, otherwise fail. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSet'' instead.
openReplicaSet rsSeed = readIORef globalConnectTimeout >>= flip openReplicaSet' rsSeed openReplicaSet rsSeed = readIORef globalConnectTimeout >>= flip openReplicaSet' rsSeed
openReplicaSet' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet openReplicaSet' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet
@ -149,7 +150,7 @@ openReplicaSet' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet
openReplicaSet' timeoutSecs (rs, hosts) = _openReplicaSet timeoutSecs (rs, hosts, Unsecure) openReplicaSet' timeoutSecs (rs, hosts) = _openReplicaSet timeoutSecs (rs, hosts, Unsecure)
openReplicaSetTLS :: (ReplicaSetName, [Host]) -> IO ReplicaSet openReplicaSetTLS :: (ReplicaSetName, [Host]) -> IO ReplicaSet
-- ^ Open secure connections (on demand) to servers in the replica set. Supplied hosts is seed list. At least one of them must be a live member of the named replica set, otherwise fail. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSetTLS\'' instead. -- ^ Open secure connections (on demand) to servers in the replica set. Supplied hosts is seed list. At least one of them must be a live member of the named replica set, otherwise fail. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSetTLS'' instead.
openReplicaSetTLS rsSeed = readIORef globalConnectTimeout >>= flip openReplicaSetTLS' rsSeed openReplicaSetTLS rsSeed = readIORef globalConnectTimeout >>= flip openReplicaSetTLS' rsSeed
openReplicaSetTLS' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet openReplicaSetTLS' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet
@ -164,23 +165,23 @@ _openReplicaSet timeoutSecs (rsName, seedList, transportSecurity) = do
return rs return rs
openReplicaSetSRV :: HostName -> IO ReplicaSet openReplicaSetSRV :: HostName -> IO ReplicaSet
-- ^ Open non-secure connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSetSRV\'\'\'' instead. -- ^ Open /non-secure/ connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSetSRV''' instead.
openReplicaSetSRV hostname = do openReplicaSetSRV hostname = do
timeoutSecs <- readIORef globalConnectTimeout timeoutSecs <- readIORef globalConnectTimeout
_openReplicaSetSRV timeoutSecs Unsecure hostname _openReplicaSetSRV timeoutSecs Unsecure hostname
openReplicaSetSRV' :: HostName -> IO ReplicaSet openReplicaSetSRV' :: HostName -> IO ReplicaSet
-- ^ Open secure connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSetSRV\'\'\'\'' instead. -- ^ Open /secure/ connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. The value of 'globalConnectTimeout' at the time of this call is the timeout used for future member connect attempts. To use your own value call 'openReplicaSetSRV'''' instead.
openReplicaSetSRV' hostname = do openReplicaSetSRV' hostname = do
timeoutSecs <- readIORef globalConnectTimeout timeoutSecs <- readIORef globalConnectTimeout
_openReplicaSetSRV timeoutSecs Secure hostname _openReplicaSetSRV timeoutSecs Secure hostname
openReplicaSetSRV'' :: Secs -> HostName -> IO ReplicaSet openReplicaSetSRV'' :: Secs -> HostName -> IO ReplicaSet
-- ^ Open non-secure connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. Supplied seconds timeout is used for connect attempts to members. -- ^ Open /non-secure/ connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. Supplied seconds timeout is used for connect attempts to members.
openReplicaSetSRV'' timeoutSecs = _openReplicaSetSRV timeoutSecs Unsecure openReplicaSetSRV'' timeoutSecs = _openReplicaSetSRV timeoutSecs Unsecure
openReplicaSetSRV''' :: Secs -> HostName -> IO ReplicaSet openReplicaSetSRV''' :: Secs -> HostName -> IO ReplicaSet
-- ^ Open secure connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. Supplied seconds timeout is used for connect attempts to members. -- ^ Open /secure/ connections (on demand) to servers in a replica set. The seedlist and replica set name is fetched from the SRV and TXT DNS records for the given hostname. Supplied seconds timeout is used for connect attempts to members.
openReplicaSetSRV''' timeoutSecs = _openReplicaSetSRV timeoutSecs Secure openReplicaSetSRV''' timeoutSecs = _openReplicaSetSRV timeoutSecs Secure
_openReplicaSetSRV :: Secs -> TransportSecurity -> HostName -> IO ReplicaSet _openReplicaSetSRV :: Secs -> TransportSecurity -> HostName -> IO ReplicaSet

View file

@ -385,8 +385,8 @@ data Request =
qFullCollection :: FullCollection, qFullCollection :: FullCollection,
qSkip :: Int32, -- ^ Number of initial matching documents to skip qSkip :: Int32, -- ^ Number of initial matching documents to skip
qBatchSize :: Int32, -- ^ The number of document to return in each batch response from the server. 0 means use Mongo default. Negative means close cursor after first batch and use absolute value as batch size. qBatchSize :: Int32, -- ^ The number of document to return in each batch response from the server. 0 means use Mongo default. Negative means close cursor after first batch and use absolute value as batch size.
qSelector :: Document, -- ^ \[\] = return all documents in collection qSelector :: Document, -- ^ @[]@ = return all documents in collection
qProjector :: Document -- ^ \[\] = return whole document qProjector :: Document -- ^ @[]@ = return whole document
} | GetMore { } | GetMore {
gFullCollection :: FullCollection, gFullCollection :: FullCollection,
gBatchSize :: Int32, gBatchSize :: Int32,
@ -394,13 +394,15 @@ data Request =
deriving (Show, Eq) deriving (Show, Eq)
data QueryOption = data QueryOption =
TailableCursor -- ^ Tailable means cursor is not closed when the last data is retrieved. Rather, the cursor marks the final object's position. You can resume using the cursor later, from where it was located, if more data were received. Like any "latent cursor", the cursor may become invalid at some point for example if the final object it references were deleted. Thus, you should be prepared to requery on CursorNotFound exception. TailableCursor -- ^ Tailable means cursor is not closed when the last data is retrieved. Rather, the cursor marks the final object's position. You can resume using the cursor later, from where it was located, if more data were received. Like any "latent cursor", the cursor may become invalid at some point for example if the final object it references were deleted. Thus, you should be prepared to requery on @CursorNotFound@ exception.
| SlaveOK -- ^ Allow query of replica slave. Normally these return an error except for namespace "local". | SlaveOK -- ^ Allow query of replica slave. Normally these return an error except for namespace "local".
| NoCursorTimeout -- ^ The server normally times out idle cursors after 10 minutes to prevent a memory leak in case a client forgets to close a cursor. Set this option to allow a cursor to live forever until it is closed. | NoCursorTimeout -- ^ The server normally times out idle cursors after 10 minutes to prevent a memory leak in case a client forgets to close a cursor. Set this option to allow a cursor to live forever until it is closed.
| AwaitData -- ^ Use with TailableCursor. If we are at the end of the data, block for a while rather than returning no data. After a timeout period, we do return as normal. | AwaitData -- ^ Use with TailableCursor. If we are at the end of the data, block for a while rather than returning no data. After a timeout period, we do return as normal.
-- | Exhaust -- ^ Stream the data down full blast in multiple "more" packages, on the assumption that the client will fully read all data queried. Faster when you are pulling a lot of data and know you want to pull it all down. Note: the client is not allowed to not read all the data unless it closes the connection. -- | Exhaust -- ^ Stream the data down full blast in multiple "more" packages, on the assumption that the client will fully read all data queried. Faster when you are pulling a lot of data and know you want to pull it all down. Note: the client is not allowed to not read all the data unless it closes the connection.
-- Exhaust commented out because not compatible with current `Pipeline` implementation -- Exhaust commented out because not compatible with current `Pipeline` implementation
| Partial -- ^ Get partial results from a _mongos_ if some shards are down, instead of throwing an error.
| Partial -- ^ Get partial results from a /mongos/ if some shards are down, instead of throwing an error.
deriving (Show, Eq) deriving (Show, Eq)
-- *** Binary format -- *** Binary format

View file

@ -136,17 +136,17 @@ data Failure =
instance Exception Failure instance Exception Failure
type ErrorCode = Int type ErrorCode = Int
-- ^ Error code from getLastError or query failure -- ^ Error code from @getLastError@ or query failure.
-- | Type of reads and writes to perform -- | Type of reads and writes to perform.
data AccessMode = data AccessMode =
ReadStaleOk -- ^ Read-only action, reading stale data from a slave is OK. ReadStaleOk -- ^ Read-only action, reading stale data from a slave is OK.
| UnconfirmedWrites -- ^ Read-write action, slave not OK, every write is fire & forget. | UnconfirmedWrites -- ^ Read-write action, slave not OK, every write is fire & forget.
| ConfirmWrites GetLastError -- ^ Read-write action, slave not OK, every write is confirmed with getLastError. | ConfirmWrites GetLastError -- ^ Read-write action, slave not OK, every write is confirmed with @getLastError@.
deriving Show deriving Show
type GetLastError = Document type GetLastError = Document
-- ^ Parameters for getLastError command. For example @[\"w\" =: 2]@ tells the server to wait for the write to reach at least two servers in replica set before acknowledging. See <http://www.mongodb.org/display/DOCS/Last+Error+Commands> for more options. -- ^ Parameters for @getLastError@ command. For example @[\"w\" =: 2]@ tells the server to wait for the write to reach at least two servers in replica set before acknowledging. See <http://www.mongodb.org/display/DOCS/Last+Error+Commands> for more options.
class Result a where class Result a where
isFailed :: a -> Bool isFailed :: a -> Bool
@ -200,7 +200,8 @@ writeMode (ConfirmWrites z) = Confirm z
data MongoContext = MongoContext { data MongoContext = MongoContext {
mongoPipe :: Pipe, -- ^ operations read/write to this pipelined TCP connection to a MongoDB server mongoPipe :: Pipe, -- ^ operations read/write to this pipelined TCP connection to a MongoDB server
mongoAccessMode :: AccessMode, -- ^ read/write operation will use this access mode mongoAccessMode :: AccessMode, -- ^ read/write operation will use this access mode
mongoDatabase :: Database } -- ^ operations query/update this database mongoDatabase :: Database -- ^ operations query/update this database
}
mongoReadMode :: MongoContext -> ReadMode mongoReadMode :: MongoContext -> ReadMode
mongoReadMode = readMode . mongoAccessMode mongoReadMode = readMode . mongoAccessMode
@ -430,7 +431,7 @@ insertMany :: (MonadIO m) => Collection -> [Document] -> Action m [Value]
-- ^ Insert documents into collection and return their \"_id\" values, -- ^ Insert documents into collection and return their \"_id\" values,
-- which are created automatically if not supplied. -- which are created automatically if not supplied.
-- If a document fails to be inserted (eg. due to duplicate key) -- If a document fails to be inserted (eg. due to duplicate key)
-- then remaining docs are aborted, and LastError is set. -- then remaining docs are aborted, and @LastError@ is set.
-- An exception will be throw if any error occurs. -- An exception will be throw if any error occurs.
insertMany = insert' [] insertMany = insert' []
@ -632,12 +633,12 @@ updateCommandDocument col ordered updates writeConcern =
] ]
{-| Bulk update operation. If one update fails it will not update the remaining {-| Bulk update operation. If one update fails it will not update the remaining
- documents. Current returned value is only a place holder. With mongodb server documents. Current returned value is only a place holder. With mongodb server
- before 2.6 it will send update requests one by one. In order to receive before 2.6 it will send update requests one by one. In order to receive
- error messages in versions under 2.6 you need to user confirmed writes. error messages in versions under 2.6 you need to user confirmed writes.
- Otherwise even if the errors had place the list of errors will be empty and Otherwise even if the errors had place the list of errors will be empty and
- the result will be success. After 2.6 it will use bulk update feature in the result will be success. After 2.6 it will use bulk update feature in
- mongodb. mongodb.
-} -}
updateMany :: (MonadIO m) updateMany :: (MonadIO m)
=> Collection => Collection
@ -646,11 +647,11 @@ updateMany :: (MonadIO m)
updateMany = update' True updateMany = update' True
{-| Bulk update operation. If one update fails it will proceed with the {-| Bulk update operation. If one update fails it will proceed with the
- remaining documents. With mongodb server before 2.6 it will send update remaining documents. With mongodb server before 2.6 it will send update
- requests one by one. In order to receive error messages in versions under requests one by one. In order to receive error messages in versions under
- 2.6 you need to use confirmed writes. Otherwise even if the errors had 2.6 you need to use confirmed writes. Otherwise even if the errors had
- place the list of errors will be empty and the result will be success. place the list of errors will be empty and the result will be success.
- After 2.6 it will use bulk update feature in mongodb. After 2.6 it will use bulk update feature in mongodb.
-} -}
updateAll :: (MonadIO m) updateAll :: (MonadIO m)
=> Collection => Collection
@ -846,9 +847,9 @@ deleteHelper opts (Select sel col) = do
liftIO $ runReaderT (void $ write (Delete (db <.> col) opts sel)) ctx liftIO $ runReaderT (void $ write (Delete (db <.> col) opts sel)) ctx
{-| Bulk delete operation. If one delete fails it will not delete the remaining {-| Bulk delete operation. If one delete fails it will not delete the remaining
- documents. Current returned value is only a place holder. With mongodb server documents. Current returned value is only a place holder. With mongodb server
- before 2.6 it will send delete requests one by one. After 2.6 it will use before 2.6 it will send delete requests one by one. After 2.6 it will use
- bulk delete feature in mongodb. bulk delete feature in mongodb.
-} -}
deleteMany :: (MonadIO m) deleteMany :: (MonadIO m)
=> Collection => Collection
@ -857,9 +858,9 @@ deleteMany :: (MonadIO m)
deleteMany = delete' True deleteMany = delete' True
{-| Bulk delete operation. If one delete fails it will proceed with the {-| Bulk delete operation. If one delete fails it will proceed with the
- remaining documents. Current returned value is only a place holder. With remaining documents. Current returned value is only a place holder. With
- mongodb server before 2.6 it will send delete requests one by one. After 2.6 mongodb server before 2.6 it will send delete requests one by one. After 2.6
- it will use bulk delete feature in mongodb. it will use bulk delete feature in mongodb.
-} -}
deleteAll :: (MonadIO m) deleteAll :: (MonadIO m)
=> Collection => Collection
@ -998,15 +999,15 @@ readModeOption StaleOk = [SlaveOK]
-- | Use 'select' to create a basic query with defaults, then modify if desired. For example, @(select sel col) {limit = 10}@ -- | Use 'select' to create a basic query with defaults, then modify if desired. For example, @(select sel col) {limit = 10}@
data Query = Query { data Query = Query {
options :: [QueryOption], -- ^ Default = [] options :: [QueryOption], -- ^ Default = @[]@
selection :: Selection, selection :: Selection,
project :: Projector, -- ^ \[\] = all fields. Default = [] project :: Projector, -- ^ @[]@ = all fields. Default = @[]@
skip :: Word32, -- ^ Number of initial matching documents to skip. Default = 0 skip :: Word32, -- ^ Number of initial matching documents to skip. Default = 0
limit :: Limit, -- ^ Maximum number of documents to return, 0 = no limit. Default = 0 limit :: Limit, -- ^ Maximum number of documents to return, 0 = no limit. Default = 0
sort :: Order, -- ^ Sort results by this order, [] = no sort. Default = [] sort :: Order, -- ^ Sort results by this order, @[]@ = no sort. Default = @[]@
snapshot :: Bool, -- ^ If true assures no duplicates are returned, or objects missed, which were present at both the start and end of the query's execution (even if the object were updated). If an object is new during the query, or deleted during the query, it may or may not be returned, even with snapshot mode. Note that short query responses (less than 1MB) are always effectively snapshotted. Default = False snapshot :: Bool, -- ^ If true assures no duplicates are returned, or objects missed, which were present at both the start and end of the query's execution (even if the object were updated). If an object is new during the query, or deleted during the query, it may or may not be returned, even with snapshot mode. Note that short query responses (less than 1MB) are always effectively snapshotted. Default = @False@
batchSize :: BatchSize, -- ^ The number of document to return in each batch response from the server. 0 means use Mongo default. Default = 0 batchSize :: BatchSize, -- ^ The number of document to return in each batch response from the server. 0 means use Mongo default. Default = 0
hint :: Order -- ^ Force MongoDB to use this index, [] = no hint. Default = [] hint :: Order -- ^ Force MongoDB to use this index, @[]@ = no hint. Default = @[]@
} deriving (Show, Eq) } deriving (Show, Eq)
type Projector = Document type Projector = Document
@ -1035,7 +1036,7 @@ find q@Query{selection, batchSize} = do
newCursor db (coll selection) batchSize dBatch newCursor db (coll selection) batchSize dBatch
findOne :: (MonadIO m) => Query -> Action m (Maybe Document) findOne :: (MonadIO m) => Query -> Action m (Maybe Document)
-- ^ Fetch first document satisfying query or Nothing if none satisfy it -- ^ Fetch first document satisfying query or @Nothing@ if none satisfy it
findOne q = do findOne q = do
pipe <- asks mongoPipe pipe <- asks mongoPipe
qr <- queryRequest False q {limit = 1} qr <- queryRequest False q {limit = 1}
@ -1047,14 +1048,17 @@ fetch :: (MonadIO m) => Query -> Action m Document
-- ^ Same as 'findOne' except throw 'DocNotFound' if none match -- ^ Same as 'findOne' except throw 'DocNotFound' if none match
fetch q = findOne q >>= maybe (liftIO $ throwIO $ DocNotFound $ selection q) return fetch q = findOne q >>= maybe (liftIO $ throwIO $ DocNotFound $ selection q) return
data FindAndModifyOpts = FamRemove Bool -- | Options for @findAndModify@
data FindAndModifyOpts
= FamRemove Bool -- ^ remove the selected document when the boolean is @True@
| FamUpdate | FamUpdate
{ famUpdate :: Document { famUpdate :: Document -- ^ the update instructions, or a replacement document
, famNew :: Bool , famNew :: Bool -- ^ return the document with the modifications made on the update
, famUpsert :: Bool , famUpsert :: Bool -- ^ create a new document if no documents match the query
} }
deriving Show deriving Show
-- | Default options used by 'findAndModify'.
defFamUpdateOpts :: Document -> FindAndModifyOpts defFamUpdateOpts :: Document -> FindAndModifyOpts
defFamUpdateOpts ups = FamUpdate defFamUpdateOpts ups = FamUpdate
{ famNew = True { famNew = True
@ -1062,10 +1066,10 @@ defFamUpdateOpts ups = FamUpdate
, famUpdate = ups , famUpdate = ups
} }
-- | runs the findAndModify command as an update without an upsert and new set to true. -- | Run the @findAndModify@ command as an update without an upsert and new set to @True@.
-- Returns a single updated document (new option is set to true). -- Return a single updated document (@new@ option is set to @True@).
-- --
-- see 'findAndModifyOpts' if you want to use findAndModify in a differnt way -- See 'findAndModifyOpts' for more options.
findAndModify :: (MonadIO m, MonadFail m) findAndModify :: (MonadIO m, MonadFail m)
=> Query => Query
-> Document -- ^ updates -> Document -- ^ updates
@ -1079,8 +1083,8 @@ findAndModify q ups = do
Nothing -> Left "findAndModify: impossible null result" Nothing -> Left "findAndModify: impossible null result"
Just doc -> Right doc Just doc -> Right doc
-- | runs the findAndModify command, -- | Run the @findAndModify@ command
-- allows more options than 'findAndModify' -- (allows more options than 'findAndModify')
findAndModifyOpts :: (MonadIO m, MonadFail m) findAndModifyOpts :: (MonadIO m, MonadFail m)
=> Query => Query
-> FindAndModifyOpts -> FindAndModifyOpts
@ -1335,12 +1339,12 @@ data Group = Group {
gKey :: GroupKey, -- ^ Fields to group by gKey :: GroupKey, -- ^ Fields to group by
gReduce :: Javascript, -- ^ @(doc, agg) -> ()@. The reduce function reduces (aggregates) the objects iterated. Typical operations of a reduce function include summing and counting. It takes two arguments, the current document being iterated over and the aggregation value, and updates the aggregate value. gReduce :: Javascript, -- ^ @(doc, agg) -> ()@. The reduce function reduces (aggregates) the objects iterated. Typical operations of a reduce function include summing and counting. It takes two arguments, the current document being iterated over and the aggregation value, and updates the aggregate value.
gInitial :: Document, -- ^ @agg@. Initial aggregation value supplied to reduce gInitial :: Document, -- ^ @agg@. Initial aggregation value supplied to reduce
gCond :: Selector, -- ^ Condition that must be true for a row to be considered. [] means always true. gCond :: Selector, -- ^ Condition that must be true for a row to be considered. @[]@ means always true.
gFinalize :: Maybe Javascript -- ^ @agg -> () | result@. An optional function to be run on each item in the result set just before the item is returned. Can either modify the item (e.g., add an average field given a count and a total) or return a replacement object (returning a new object with just _id and average fields). gFinalize :: Maybe Javascript -- ^ @agg -> () | result@. An optional function to be run on each item in the result set just before the item is returned. Can either modify the item (e.g., add an average field given a count and a total) or return a replacement object (returning a new object with just @_id@ and average fields).
} deriving (Show, Eq) } deriving (Show, Eq)
data GroupKey = Key [Label] | KeyF Javascript deriving (Show, Eq) data GroupKey = Key [Label] | KeyF Javascript deriving (Show, Eq)
-- ^ Fields to group by, or function (@doc -> key@) returning a "key object" to be used as the grouping key. Use KeyF instead of Key to specify a key that is not an existing member of the object (or, to access embedded members). -- ^ Fields to group by, or function (@doc -> key@) returning a "key object" to be used as the grouping key. Use 'KeyF' instead of 'Key' to specify a key that is not an existing member of the object (or, to access embedded members).
groupDocument :: Group -> Document groupDocument :: Group -> Document
-- ^ Translate Group data into expected document form -- ^ Translate Group data into expected document form
@ -1359,17 +1363,17 @@ group g = at "retval" `liftM` runCommand ["group" =: groupDocument g]
-- ** MapReduce -- ** MapReduce
-- | Maps every document in collection to a list of (key, value) pairs, then for each unique key reduces all its associated values to a single result. There are additional parameters that may be set to tweak this basic operation. -- | Maps every document in collection to a list of (key, value) pairs, then for each unique key reduces all its associated values to a single result. There are additional parameters that may be set to tweak this basic operation.
-- This implements the latest version of map-reduce that requires MongoDB 1.7.4 or greater. To map-reduce against an older server use runCommand directly as described in http://www.mongodb.org/display/DOCS/MapReduce. -- This implements the latest version of map-reduce that requires MongoDB 1.7.4 or greater. To map-reduce against an older server use 'runCommand' directly as described in http://www.mongodb.org/display/DOCS/MapReduce.
data MapReduce = MapReduce { data MapReduce = MapReduce {
rColl :: Collection, rColl :: Collection,
rMap :: MapFun, rMap :: MapFun,
rReduce :: ReduceFun, rReduce :: ReduceFun,
rSelect :: Selector, -- ^ Operate on only those documents selected. Default is [] meaning all documents. rSelect :: Selector, -- ^ Operate on only those documents selected. Default is @[]@ meaning all documents.
rSort :: Order, -- ^ Default is [] meaning no sort rSort :: Order, -- ^ Default is @[]@ meaning no sort
rLimit :: Limit, -- ^ Default is 0 meaning no limit rLimit :: Limit, -- ^ Default is 0 meaning no limit
rOut :: MROut, -- ^ Output to a collection with a certain merge policy. Default is no collection ('Inline'). Note, you don't want this default if your result set is large. rOut :: MROut, -- ^ Output to a collection with a certain merge policy. Default is no collection ('Inline'). Note, you don't want this default if your result set is large.
rFinalize :: Maybe FinalizeFun, -- ^ Function to apply to all the results when finished. Default is Nothing. rFinalize :: Maybe FinalizeFun, -- ^ Function to apply to all the results when finished. Default is Nothing.
rScope :: Document, -- ^ Variables (environment) that can be accessed from map/reduce/finalize. Default is []. rScope :: Document, -- ^ Variables (environment) that can be accessed from map/reduce/finalize. Default is @[]@.
rVerbose :: Bool -- ^ Provide statistics on job execution time. Default is False. rVerbose :: Bool -- ^ Provide statistics on job execution time. Default is False.
} deriving (Show, Eq) } deriving (Show, Eq)