rethinkdb-1.8.0.3: RethinkDB driver for Haskell

Safe HaskellNone

Database.RethinkDB

Contents

Description

Haskell client driver for RethinkDB

Based upon the official Javascript, Python and Ruby API: http://www.rethinkdb.com/api/

How to use

 {-# LANGUAGE OverloadedStrings #-}
 import qualified Database.RethinkDB as R
 import qualified Database.RethinkDB.NoClash

Synopsis

Accessing RethinkDB

data RethinkDBHandle Source

A connection to the database server

connect :: HostName -> Integer -> Maybe String -> IO RethinkDBHandleSource

Create a new connection to the database server

Example: connect using the default port with no passphrase

>>> h <- connect "localhost" 28015 Nothing

close :: RethinkDBHandle -> IO ()Source

Close an open connection

use :: RethinkDBHandle -> Database -> RethinkDBHandleSource

Set the default database

The new handle is an alias for the old one. Calling close on either one will close both.

run :: (Expr query, Result r) => RethinkDBHandle -> query -> IO rSource

Run a given query and return a Result

run' :: Expr query => RethinkDBHandle -> query -> IO [Value]Source

Run a given query and return a Value

runOpts :: (Expr query, Result r) => RethinkDBHandle -> [RunOptions] -> query -> IO rSource

Run a query with the given options

next :: Cursor a -> IO (Maybe a)Source

Get the next value from a cursor

collect :: Cursor a -> IO [a]Source

A lazy stream of all the elements in the cursor

data RunOptions Source

Per-query settings

data Cursor a Source

Instances

data Response Source

The raw response to a query

class Result r whereSource

Convert the raw query response into useful values

Instances

data ReQL Source

An RQL term

Manipulating databases

data Database Source

A database, referenced by name

Constructors

Database 

Fields

databaseName :: Text
 

db :: Text -> DatabaseSource

Create a Database reference

dbCreate :: String -> ReQLSource

Create a database on the server

dbDrop :: Database -> ReQLSource

Drop a database

dbList :: ReQLSource

List the databases on the server

Manipulating Tables

data Table Source

A table description

Constructors

Table 

Fields

tableDatabase :: Maybe Database

when Nothing, use the connection's database

tableName :: Text
 
tablePrimaryKey :: Maybe Key
 

data TableCreateOptions Source

Options used to create a table

table :: Text -> TableSource

Create a simple table refence with no associated database

tableCreate :: Table -> TableCreateOptions -> ReQLSource

Create a table on the server

tableDrop :: Table -> ReQLSource

Drop a table

tableList :: Database -> ReQLSource

List the tables in a database

indexCreate :: Expr fun => String -> fun -> Table -> ReQLSource

Create an index on the table from the given function

indexDrop :: Key -> Table -> ReQLSource

Drop an index

indexList :: Table -> ReQLSource

List the indexes on the table

Writing data

insert :: (Expr table, Expr object) => object -> table -> ReQLSource

Insert a document or a list of documents into a table

upsert :: (Expr table, Expr object) => object -> table -> ReQLSource

Like insert, but update existing documents with the same primary key

update :: Expr selection => (ReQL -> ReQL) -> selection -> ReQLSource

Add to or modify the contents of a document

replace :: Expr selection => (ReQL -> ReQL) -> selection -> ReQLSource

Replace a document with another

delete :: Expr selection => selection -> ReQLSource

Delete the documents

returnVals :: ReQL -> ReQLSource

Include the value of single write operations in the returned object

Selecting data

get :: (Expr s, Expr k) => k -> s -> ReQLSource

Get a document by primary key

filter :: (Expr predicate, Expr seq) => predicate -> seq -> ReQLSource

Filter a sequence given a predicate

between :: (Expr left, Expr right, Expr seq) => Key -> left -> right -> seq -> ReQLSource

Query all the documents whose value for the given index is in a given range

getAll :: Expr value => Key -> [value] -> Table -> ReQLSource

Retreive documents by their indexed value

Joins

innerJoin :: (Expr a, Expr b, Expr c) => (ReQL -> ReQL -> c) -> a -> b -> ReQLSource

SQL-like join of two sequences. Returns each pair of rows that satisfy the 2-ary predicate.

outerJoin :: (Expr a, Expr b, Expr c) => (ReQL -> ReQL -> c) -> a -> b -> ReQLSource

SQL-like join of two sequences. Returns each pair of rows that satisfy the 2-ary predicate.

eqJoin :: (Expr a, Expr b) => Key -> a -> Key -> b -> ReQLSource

An efficient iner_join that uses a key for the first table and an index for the left table.

mergeRightLeft :: Expr a => a -> ReQLSource

Merge the left and right attributes of the objects in a sequence. Called zip in the official drivers

Transformations

map :: (Expr a, Expr b) => (ReQL -> b) -> a -> ReQLSource

Map a function over a sequence

withFields :: (Expr paths, Expr seq) => [paths] -> seq -> ReQLSource

Like hasFields followed by pluck

concatMap :: (Expr a, Expr b) => (ReQL -> b) -> a -> ReQLSource

Map a function of a sequence and concat the results

drop :: (Expr a, Expr b) => a -> b -> ReQLSource

Drop elements from the head of a sequence. Called skip in the official drivers

take :: (Expr n, Expr seq) => n -> seq -> ReQLSource

Limit the size of a sequence. Called limit in the official drivers

(!!) :: Expr a => a -> ReQL -> ReQLSource

Get the nth value of a sequence or array

slice :: (Expr a, Expr b, Expr c) => a -> b -> c -> ReQLSource

Cut out part of a sequence

orderBy :: Expr s => [Order] -> s -> ReQLSource

Order a sequence by the given keys

data Order Source

Oredering specification for orderBy

Constructors

Asc 

Fields

orderAttr :: Key
 
Desc 

Fields

orderAttr :: Key
 

indexesOf :: (Expr fun, Expr seq) => fun -> seq -> ReQLSource

The position in the sequence of the elements that match the predicate

isEmpty :: Expr seq => seq -> ReQLSource

Test if a sequence is empty

(++) :: (Expr a, Expr b) => a -> b -> ReQLSource

Join two sequences. Called union in the official drivers

sample :: (Expr n, Expr seq) => n -> seq -> ReQLSource

Select a given number of elements from a sequence with uniform random distribution

Aggregation

reduce :: (Expr base, Expr seq, Expr a) => (ReQL -> ReQL -> a) -> base -> seq -> ReQLSource

Reduce a sequence to a single value

reduce1 :: (Expr a, Expr s) => (ReQL -> ReQL -> a) -> s -> ReQLSource

Reduce a non-empty sequence to a single value

distinct :: Expr s => s -> ReQLSource

Filter out identical elements of the sequence

groupBy :: (Expr group, Expr reduction, Expr seq) => (ReQL -> group) -> (ReQL -> reduction) -> seq -> ReQLSource

Turn a grouping function and a reduction function into a grouped map reduce operation

member :: Expr o => [ReQL] -> o -> ReQLSource

Test if an object contains the given attribute. Called contains in the official drivers

Aggregators

length :: Expr a => a -> ReQLSource

The size of a sequence or an array. Called count in the official drivers

sum :: Expr s => s -> ReQLSource

The sum of a sequence

avg :: Expr s => s -> ReQLSource

The average of a sequence

Document manipulation

pluck :: Expr o => [ReQL] -> o -> ReQLSource

Keep only the given attributes

without :: Expr o => [ReQL] -> o -> ReQLSource

Remove the given attributes from an object

merge :: (Expr a, Expr b) => a -> b -> ReQLSource

Merge two objects together

append :: (Expr a, Expr b) => a -> b -> ReQLSource

Append a datum to a sequence

prepend :: (Expr datum, Expr array) => datum -> array -> ReQLSource

Prepend an element to an array

(\\) :: (Expr a, Expr b) => a -> b -> ReQLSource

Called difference in the official drivers

setInsert :: (Expr datum, Expr array) => datum -> array -> ReQLSource

Insert a datum into an array if it is not yet present

setUnion :: (Expr a, Expr b) => a -> b -> ReQLSource

The union of two sets

setIntersection :: (Expr a, Expr b) => a -> b -> ReQLSource

The intersection of two sets

setDifference :: (Expr set, Expr remove) => remove -> set -> ReQLSource

The difference of two sets

(!) :: Expr s => s -> ReQL -> ReQLSource

Get a single field form an object

hasFields :: (Expr obj, Expr paths) => paths -> obj -> ReQLSource

Test if an object has the given fields

insertAt :: (Expr n, Expr datum, Expr array) => n -> datum -> array -> ReQLSource

Insert a datum at the given position in an array

spliceAt :: (Expr n, Expr replace, Expr array) => n -> replace -> array -> ReQLSource

Splice an array at a given position inside another array

deleteAt :: (Expr n, Expr array) => n -> array -> ReQLSource

Delete an element from an array

changeAt :: (Expr n, Expr datum, Expr array) => n -> datum -> array -> ReQLSource

Change an element in an array

keys :: Expr obj => obj -> ReQLSource

The list of keys of the given object

Math and logic

(+) :: (Expr a, Expr b) => a -> b -> ReQLSource

Arithmetic Operator

(-) :: (Expr a, Expr b) => a -> b -> ReQLSource

Arithmetic Operator

(*) :: (Expr a, Expr b) => a -> b -> ReQLSource

Arithmetic Operator

(/) :: (Expr a, Expr b) => a -> b -> ReQLSource

Arithmetic Operator

mod :: (Expr a, Expr b) => a -> b -> ReQLSource

Arithmetic Operator

(&&) :: (Expr a, Expr b) => a -> b -> ReQLSource

Boolean operator

(||) :: (Expr a, Expr b) => a -> b -> ReQLSource

Boolean operator

(==) :: (Expr a, Expr b) => a -> b -> ReQLSource

Comparison operator

(/=) :: (Expr a, Expr b) => a -> b -> ReQLSource

Comparison operator

(>) :: (Expr a, Expr b) => a -> b -> ReQLSource

Comparison operator

(<) :: (Expr a, Expr b) => a -> b -> ReQLSource

Comparison operator

(<=) :: (Expr a, Expr b) => a -> b -> ReQLSource

Comparison operator

(>=) :: (Expr a, Expr b) => a -> b -> ReQLSource

Comparison operator

not :: Expr a => a -> ReQLSource

Negation

String manipulation

(=~) :: Expr string => string -> ReQL -> ReQLSource

Match a string to a regular expression. Called match in the official drivers

Dates and times

newtype UTCTime Source

Time with no time zone The default FromJSON instance for Data.Time.UTCTime is incompatible with ReQL's time type

Constructors

UTCTime UTCTime 

newtype ZonedTime Source

Time with a time zone The default FromJSON instance for Data.Time.ZonedTime is incompatible with ReQL's time type

Constructors

ZonedTime ZonedTime 

now :: ReQLSource

The time and date when the query is executed

time :: ReQL -> ReQL -> ReQL -> ReQL -> ReQL -> ReQL -> ReQL -> ReQLSource

Build a time object from the year, month, day, hour, minute, second and timezone fields

epochTime :: ReQL -> ReQLSource

Build a time object given the number of seconds since the unix epoch

iso8601 :: ReQL -> ReQLSource

Build a time object given an iso8601 string

inTimezone :: Expr time => ReQL -> time -> ReQLSource

The same time in a different timezone

during :: (Expr left, Expr right, Expr time) => Bound left -> Bound right -> time -> ReQLSource

Test if a time is between two other times

timezone :: Expr time => time -> ReQLSource

Extract part of a time value

date :: Expr time => time -> ReQLSource

Extract part of a time value

timeOfDay :: Expr time => time -> ReQLSource

Extract part of a time value

year :: Expr time => time -> ReQLSource

Extract part of a time value

month :: Expr time => time -> ReQLSource

Extract part of a time value

day :: Expr time => time -> ReQLSource

Extract part of a time value

dayOfWeek :: Expr time => time -> ReQLSource

Extract part of a time value

dayOfYear :: Expr time => time -> ReQLSource

Extract part of a time value

hours :: Expr time => time -> ReQLSource

Extract part of a time value

minutes :: Expr time => time -> ReQLSource

Extract part of a time value

seconds :: Expr time => time -> ReQLSource

Extract part of a time value

toIso8601 :: Expr t => t -> ReQLSource

Convert a time to another representation

toEpochTime :: Expr t => t -> ReQLSource

Convert a time to another representation

Control structures

apply :: (Expr fun, Expr arg) => fun -> [arg] -> ReQLSource

Apply a function to a list of arguments. Called do in the official drivers

class Javascript r whereSource

Create a javascript expression

Methods

js :: String -> rSource

if' :: (Expr a, Expr b, Expr c) => a -> b -> c -> ReQLSource

Called branch in the official drivers

forEach :: (Expr s, Expr a) => s -> (ReQL -> a) -> ReQLSource

Like map but for write queries

error :: Expr s => s -> ReQLSource

Abort the query with an error

handle :: (Expr handler, Expr reql) => handler -> reql -> ReQLSource

Catch some expections inside the query. Called default in the official drivers

class Expr e whereSource

Convert other types into ReqL expressions

Methods

expr :: e -> ReQLSource

coerceTo :: Expr x => ReQL -> x -> ReQLSource

Convert a value to a different type

asArray :: Expr x => x -> ReQLSource

Convert a value to a different type

asString :: Expr x => x -> ReQLSource

Convert a value to a different type

asNumber :: Expr x => x -> ReQLSource

Convert a value to a different type

asObject :: Expr x => x -> ReQLSource

Convert a value to a different type

asBool :: Expr x => x -> ReQLSource

Convert a value to a different type

typeOf :: Expr a => a -> ReQLSource

A string representing the type of an expression

info :: Expr a => a -> ReQLSource

Get information on a given expression. Useful for tables and databases.

json :: Expr string => string -> ReQLSource

Parse a json string into an object

Helpers

class Obj o whereSource

Convert into a ReQL object

Methods

obj :: o -> ObjectSource

Instances

data Object Source

A list of key/value pairs

Instances

data Attribute Source

A key/value pair used for building objects

Constructors

forall e . Expr e => Text := e 

Instances

str :: String -> ReQLSource

A shortcut for inserting strings into ReQL expressions Useful when OverloadedStrings makes the type ambiguous

num :: Double -> ReQLSource

A shortcut for inserting numbers into ReQL expressions

(.) :: (Expr a, Expr b, Expr c) => (ReQL -> b) -> (ReQL -> a) -> c -> ReQLSource

Specialised function composition

(#) :: (Expr a, Expr b) => a -> (ReQL -> b) -> ReQLSource

Flipped function composition

def :: Default a => a

The default value for this type.