rethinkdb-client-driver-0.0.23: Client driver for RethinkDB

Safe HaskellNone
LanguageHaskell2010

Database.RethinkDB

Contents

Synopsis

Documentation

defaultPort :: Int Source #

The default port where RethinkDB accepts client driver connections.

newHandle :: Text -> Int -> Maybe Text -> Exp Database -> IO Handle Source #

Create a new handle to the RethinkDB server.

handleDatabase :: Handle -> Exp Database Source #

The Database which some expressions will use when not explicitly given one (eg. Table).

close :: Handle -> IO () Source #

Close the given handle. You MUST NOT use the handle after this.

serverInfo :: Handle -> IO (Either Error ServerInfo) Source #

High-level query API

run :: FromResponse (Result a) => Handle -> Exp a -> IO (Res a) Source #

Start a new query and wait for its (first) result. If the result is an single value (Datum), then there will be no further results. If it is a sequence, then you must consume results until the sequence ends.

nextChunk :: FromResponse (Sequence a) => Handle -> Sequence a -> IO (Either Error (Sequence a)) Source #

Get the next chunk of a sequence. It is an error to request the next chunk if the sequence is already Done,

collect :: FromDatum a => Handle -> Sequence a -> IO (Either Error (Vector a)) Source #

Collect all the values in a sequence and make them available as a 'Vector a'.

Low-level query API

start :: Handle -> Exp a -> IO Token Source #

Start a new query. Returns the Token which can be used to track its progress.

continue :: Handle -> Token -> IO () Source #

Let the server know that it can send the next response corresponding to the given token.

stop :: Handle -> Token -> IO () Source #

Stop (abort?) a query.

wait :: Handle -> Token -> IO () Source #

Wait until a previous query (which was started with the noreply option) finishes.

type Token = Word64 Source #

A token is used to refer to queries and the corresponding responses. This driver uses a monotonically increasing counter.

data Error Source #

Errors include a plain-text description which includes further details. The RethinkDB protocol also includes a backtrace which we currently don't parse.

Constructors

ProtocolError !Text

An error on the protocol level. Perhaps the socket was closed unexpectedly, or the server sent a message which the driver could not parse.

ClientError !Text

Means the client is buggy. An example is if the client sends a malformed protobuf, or tries to send [CONTINUE] for an unknown token.

CompileError !Text

Means the query failed during parsing or type checking. For example, if you pass too many arguments to a function.

RuntimeError !Text

Means the query failed at runtime. An example is if you add together two values from a table, but they turn out at runtime to be booleans rather than numbers.

Instances

Eq Error Source # 

Methods

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

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

Show Error Source # 

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

data Response Source #

Constructors

Response 

Fields

The Datum type

data Datum Source #

A sumtype covering all the primitive types which can appear in queries or responses.

It is similar to the aeson Value type, except that RethinkDB has a few more types (like Time), which have a special encoding in JSON.

Instances

Eq Datum Source #

We can't automatically derive Eq because ZonedTime does not have an instance of Eq. See the eqTime function for why we can compare times.

Methods

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

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

Show Datum Source # 

Methods

showsPrec :: Int -> Datum -> ShowS #

show :: Datum -> String #

showList :: [Datum] -> ShowS #

Generic Datum Source # 

Associated Types

type Rep Datum :: * -> * #

Methods

from :: Datum -> Rep Datum x #

to :: Rep Datum x -> Datum #

ToJSON Datum Source # 
FromJSON Datum Source # 
FromDatum Object Source # 
FromDatum Datum Source # 
ToDatum Object Source # 

Methods

toDatum :: Object -> Datum Source #

ToDatum Datum Source # 

Methods

toDatum :: Datum -> Datum Source #

FromResponse Object Source # 
FromResponse Datum Source # 
IsObject Object Source # 
IsDatum Object Source # 
IsDatum Datum Source # 
FromResponse (Maybe Datum) Source # 
type Rep Datum Source # 
type Result Object Source # 
type Result Datum Source # 

type Array a = Vector a Source #

Arrays are vectors of Datum.

type Object = HashMap Text Datum Source #

Objects are maps from Text to Datum. Like Aeson, we're using a strict HashMap.

class ToDatum a where Source #

Types which can be converted to or from a Datum.

Minimal complete definition

toDatum

Methods

toDatum :: a -> Datum Source #

class FromDatum a where Source #

Minimal complete definition

parseDatum

Methods

parseDatum :: Datum -> Parser a Source #

Instances

FromDatum Bool Source # 
FromDatum Char Source # 
FromDatum Double Source # 
FromDatum Float Source # 
FromDatum Int Source # 
FromDatum () Source # 

Methods

parseDatum :: Datum -> Parser () Source #

FromDatum Text Source # 
FromDatum UTCTime Source # 
FromDatum Value Source # 
FromDatum ZonedTime Source # 
FromDatum Object Source # 
FromDatum Datum Source # 
FromDatum ChangeNotification Source # 
FromDatum [Char] Source # 
FromDatum a => FromDatum [a] Source # 

Methods

parseDatum :: Datum -> Parser [a] Source #

FromDatum a => FromDatum (Maybe a) Source # 

Methods

parseDatum :: Datum -> Parser (Maybe a) Source #

FromDatum a => FromDatum (Array a) Source # 

Methods

parseDatum :: Datum -> Parser (Array a) Source #

FromDatum a => FromDatum (Sequence a) Source # 
(FromDatum a, FromDatum b) => FromDatum (a, b) Source # 

Methods

parseDatum :: Datum -> Parser (a, b) Source #

(FromDatum a, FromDatum b, FromDatum c) => FromDatum (a, b, c) Source # 

Methods

parseDatum :: Datum -> Parser (a, b, c) Source #

(.=) :: ToDatum a => Text -> a -> (Text, Datum) Source #

data Exp a where Source #

Constructors

Constant :: ToDatum a => a -> Exp a 
MkArray :: [Exp a] -> Exp (Array a) 
ListDatabases :: Exp (Array Text) 
CreateDatabase :: Exp Text -> Exp Object 
DropDatabase :: Exp Text -> Exp Object 
WaitDatabase :: Exp Database -> Exp Object 
ListTables :: Exp Database -> Exp (Array Text) 
CreateTable :: Exp Database -> Exp Text -> Exp Object 
DropTable :: Exp Database -> Exp Text -> Exp Object 
WaitTable :: Exp Table -> Exp Object 
ListIndices :: Exp Table -> Exp (Array Text) 
CreateIndex :: IsDatum a => Exp Table -> Exp Text -> (Exp Object -> Exp a) -> Exp Object 
DropIndex :: Exp Table -> Exp Text -> Exp Object 
IndexStatus :: Exp Table -> [Exp Text] -> Exp (Array Object) 
WaitIndex :: Exp Table -> [Exp Text] -> Exp (Array Object) 
Database :: Exp Text -> Exp Database 
Table :: Maybe (Exp Database) -> Exp Text -> Exp Table 
Coerce :: Exp a -> Exp Text -> Exp b 
Eq :: (IsDatum a, IsDatum b) => Exp a -> Exp b -> Exp Bool 
Ne :: (IsDatum a, IsDatum b) => Exp a -> Exp b -> Exp Bool 
Not :: Exp Bool -> Exp Bool 
Match :: Exp Text -> Exp Text -> Exp Datum 
Get :: Exp Table -> Exp Text -> Exp SingleSelection 
GetAll :: IsDatum a => Exp Table -> [Exp a] -> Exp (Array Datum) 
GetAllIndexed :: IsDatum a => Exp Table -> [Exp a] -> Text -> Exp (Sequence Datum) 
Add :: Num a => [Exp a] -> Exp a 
Sub :: Num a => [Exp a] -> Exp a 
Multiply :: Num a => [Exp a] -> Exp a 
All :: [Exp Bool] -> Exp Bool 
Any :: [Exp Bool] -> Exp Bool 
GetField :: (IsObject a, IsDatum r) => Exp Text -> Exp a -> Exp r 
HasFields :: IsObject a => [Text] -> Exp a -> Exp Bool 
Take :: IsSequence s => Exp Double -> Exp s -> Exp s 
Append :: IsDatum a => Exp (Array a) -> Exp a -> Exp (Array a) 
Prepend :: IsDatum a => Exp (Array a) -> Exp a -> Exp (Array a) 
IsEmpty :: IsSequence a => Exp a -> Exp Bool 
Delete :: Exp a -> Exp Object 
InsertObject :: ConflictResolutionStrategy -> Exp Table -> Object -> Exp Object 
InsertSequence :: IsSequence s => Exp Table -> Exp s -> Exp Object 
Filter :: IsSequence s => (Exp a -> Exp Bool) -> Exp s -> Exp s 
Map :: IsSequence s => (Exp a -> Exp b) -> Exp s -> Exp (Sequence b) 
Between :: IsSequence s => (Bound, Bound) -> Exp s -> Exp s 
BetweenIndexed :: IsSequence s => Text -> (Bound, Bound) -> Exp s -> Exp s 
OrderBy :: IsSequence s => [Order] -> Exp s -> Exp s 
OrderByIndexed :: IsSequence s => Order -> Exp s -> Exp s 
Keys :: IsObject a => Exp a -> Exp (Array Text) 
Var :: Int -> Exp a 
Function :: State Context ([Int], Exp a) -> Exp f 
Call :: Exp f -> [SomeExp] -> Exp r 
Limit :: IsSequence s => Double -> Exp s -> Exp s 
Nth :: (IsSequence s, IsDatum r) => Double -> Exp s -> Exp r 
UUID :: Exp Text 
Now :: Exp ZonedTime 
Timezone :: Exp ZonedTime -> Exp Text 
RandomInteger :: Exp Int -> Exp Int -> Exp Int 
RandomFloat :: Exp Double -> Exp Double -> Exp Double 
Info :: Exp a -> Exp Object 
Default :: Exp a -> Exp a -> Exp a 
Error :: Exp Text -> Exp a 
SequenceChanges :: IsSequence s => Exp s -> Exp (Sequence ChangeNotification) 
SingleSelectionChanges :: IsDatum a => Exp a -> Exp (Sequence ChangeNotification) 

Instances

Num (Exp Double) Source # 
IsString (Exp Text) Source #

Convenience to for automatically converting a Text to a constant expression.

Methods

fromString :: String -> Exp Text #

data SomeExp where Source #

Because the arguments to functions are polymorphic (the individual arguments can, and often have, different types).

Constructors

SomeExp :: Exp a -> SomeExp 

data Bound Source #

Bounds are used in Between.

Constructors

Open !Datum 
Closed !Datum 

data Order Source #

Used in OrderBy.

Constructors

Ascending !Text 
Descending !Text 

data Sequence a Source #

Sequences are a bounded list of items. The server may split the sequence into multiple chunks when sending it to the client. When the response is a partial sequence, the client may request additional chunks until it gets a Done.

Constructors

Done !(Vector a) 
Partial !Token !(Vector a) 

data Table Source #

Tables are something you can select objects from.

This type is not exported, and merely serves as a sort of phantom type. On the client tables are converted to a Sequence.

data Database Source #

A Database is something which contains tables. It is a server-only type.

type Res a = Either Error (Result a) Source #

The result of a query. It is either an error or a result (which depends on the type of the query expression). This type is named to be symmetrical to Exp, so we get this nice type for run.

run :: Handle -> Exp a -> IO (Res a)

type family Result a Source #

The type of result you get when executing a query of 'Exp a'.

class FromResponse a Source #

A value which can be converted from a Response. All types which are defined as being a 'Result a' should have a 'FromResponse a'. Because, uhm.. you really want to be able to extract the result from the response.

There are two parsers defined here, one for atoms and the other for sequences. These are the only two implementations of parseResponse which should be used.

Minimal complete definition

parseResponse

data ConflictResolutionStrategy Source #

ConflictResolutionStrategy

How conflicts should be resolved.

Constructors

CRError

Do not insert the new document and record the conflict as an error. This is the default.

CRReplace

Replace the old document in its entirety with the new one.

CRUpdate

Update fields of the old document with fields from the new one.

lift :: Lift c e => e -> c (Simplified e) Source #

call1 :: (Exp a -> Exp r) -> Exp a -> Exp r Source #

Call an unary function with the given argument.

call2 :: (Exp a -> Exp b -> Exp r) -> Exp a -> Exp b -> Exp r Source #

Call an binary function with the given arguments.

class IsDatum a Source #

Instances

IsDatum Bool Source #

For a boolean type, we're reusing the standard Haskell Bool type.

IsDatum Double Source #

Numbers are Double (unlike Aeson, which uses Scientific). No particular reason.

IsDatum Text Source #

For strings, we're using the Haskell Text type.

IsDatum UTCTime Source # 
IsDatum ZonedTime Source #

Time in RethinkDB is represented similar to the ZonedTime type. Except that the JSON representation on the wire looks different from the default used by Aeson. Therefore we have a custom FromRSON and ToRSON instances.

IsDatum Object Source # 
IsDatum Datum Source # 
IsDatum SingleSelection Source # 
IsDatum a => IsDatum (Array a) Source #

Arrays are vectors of Datum.

class IsDatum a => IsObject a Source #

Objects are maps from Text to Datum. Like Aeson, we're using HashMap.