mongoDB-2.7.1.2: Driver (client) for MongoDB, a free, scalable, fast, document DBMS
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.MongoDB.Connection

Description

Connect to a single server or a replica set of servers

Synopsis

Util

Connection

type Pipe = Pipeline Source #

Thread-safe TCP connection with pipelined requests. In long-running applications the user is expected to use it as a "client": create a Pipe at startup, use it as long as possible, watch out for possible timeouts, and close it on shutdown. Bearing in mind that disconnections may be triggered by MongoDB service providers, the user is responsible for re-creating their Pipe whenever necessary.

close :: Pipeline -> IO () Source #

Close pipe and underlying connection

isClosed :: Pipeline -> IO Bool Source #

Server

data Host Source #

Constructors

Host HostName PortID 

Instances

Instances details
Show Host Source # 
Instance details

Defined in Database.MongoDB.Internal.Network

Methods

showsPrec :: Int -> Host -> ShowS #

show :: Host -> String #

showList :: [Host] -> ShowS #

Eq Host Source # 
Instance details

Defined in Database.MongoDB.Internal.Network

Methods

(==) :: Host -> Host -> Bool #

(/=) :: Host -> Host -> Bool #

Ord Host Source # 
Instance details

Defined in Database.MongoDB.Internal.Network

Methods

compare :: Host -> Host -> Ordering #

(<) :: Host -> Host -> Bool #

(<=) :: Host -> Host -> Bool #

(>) :: Host -> Host -> Bool #

(>=) :: Host -> Host -> Bool #

max :: Host -> Host -> Host #

min :: Host -> Host -> Host #

data PortID Source #

Wraps network's PortID Used to ease compatibility between older and newer network versions.

Instances

Instances details
Show PortID Source # 
Instance details

Defined in Database.MongoDB.Internal.Network

Eq PortID Source # 
Instance details

Defined in Database.MongoDB.Internal.Network

Methods

(==) :: PortID -> PortID -> Bool #

(/=) :: PortID -> PortID -> Bool #

Ord PortID Source # 
Instance details

Defined in Database.MongoDB.Internal.Network

defaultPort :: PortID Source #

Default MongoDB port = 27017

showHostPort :: Host -> String Source #

Display host as "host:port" TODO: Distinguish Service port

readHostPort :: String -> Host Source #

Read string "hostname:port" as Host hostname (PortNumber port) or "hostname" as host hostname (default port). Error if string does not match either syntax.

readHostPortM :: MonadFail m => String -> m Host Source #

Read string "hostname:port" as Host hosthame (PortNumber port) or "hostname" as host hostname (default port). Fail if string does not match either syntax.

globalConnectTimeout :: IORef Secs Source #

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 :: Host -> IO Pipe Source #

Connect to Host returning pipelined TCP connection. Throw IOError if connection refused or no response within globalConnectTimeout.

connect' :: Secs -> Host -> IO Pipe Source #

Connect to Host returning pipelined TCP connection. Throw IOError if connection refused or no response within given number of seconds.

Replica Set

openReplicaSet :: (ReplicaSetName, [Host]) -> IO ReplicaSet Source #

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' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet Source #

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. Supplied seconds timeout is used for connect attempts to members.

openReplicaSetTLS :: (ReplicaSetName, [Host]) -> IO ReplicaSet Source #

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' :: Secs -> (ReplicaSetName, [Host]) -> IO ReplicaSet Source #

Open secure 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. Supplied seconds timeout is used for connect attempts to members.

openReplicaSetSRV :: HostName -> IO ReplicaSet Source #

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 -> IO ReplicaSet Source #

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.

The preferred connection method for cloud MongoDB providers. A typical connecting sequence is shown in the example below.

Example

Expand
  do
  pipe <- openReplicatSetSRV' "cluster#.xxxxx.yyyyy.zzz"
  is_auth <- access pipe master "admin" $ auth user_name password
  unless is_auth (throwIO $ userError "Authentication failed!")

openReplicaSetSRV'' :: Secs -> HostName -> IO ReplicaSet Source #

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''' :: Secs -> HostName -> IO ReplicaSet Source #

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.

data ReplicaSet Source #

Maintains a connection (created on demand) to each server in the named replica set

primary :: ReplicaSet -> IO Pipe Source #

Return connection to current primary of replica set. Fail if no primary available.

secondaryOk :: ReplicaSet -> IO Pipe Source #

Return connection to a random secondary, or primary if no secondaries available.

routedHost :: ((Host, Bool) -> (Host, Bool) -> IO Ordering) -> ReplicaSet -> IO Pipe Source #

Return a connection to a host using a user-supplied sorting function, which sorts based on a tuple containing the host and a boolean indicating whether the host is primary.

closeReplicaSet :: ReplicaSet -> IO () Source #

Close all connections to replica set

replSetName :: ReplicaSet -> Text Source #

Get the name of connected replica set.