rethinkdb-1.15.1.0: A driver for RethinkDB 1.15

Safe HaskellNone

Database.RethinkDB.Functions

Contents

Description

ReQL Functions

ReQL was designed for dynamic languages. Many operations take optional positional and named arguments.

Optional named arguments can be added using ex, for example `upsert = ex insert [conflict := update]`

For optional positional arguments this module defines an extra function if the functionality is not available otherwise. For example argmax for max and splitOn for split but skip instead of sliceFrom and `avg . (!k)` instead of `avgOf k`.

Synopsis

Documentation

Get the doctests ready

>>> :load Database.RethinkDB.NoClash
>>> import qualified Database.RethinkDB as R
>>> default (Datum, ReQL, String, Int, Double)
>>> import Prelude
>>> import Data.Text (Text)
>>> import Data.Maybe
>>> import Control.Exception
>>> import Database.RethinkDB.Functions ()
>>> import Database.RethinkDB ()
>>> import Data.List (sort)
>>> :set -XOverloadedStrings
>>> let try' x = (try x `asTypeOf` return (Left (undefined :: SomeException))) >> return ()
>>> h <- fmap (use "doctests") $ connect "localhost" 28015 def
>>> try' $ run' h $ dbCreate "doctests"
>>> try' $ run' h $ tableCreate "foo"
>>> try' $ run' h $ delete $ table "foo"
>>> try' $ run' h $ tableCreate "bar"
>>> try' $ run' h $ delete $ table "bar"
>>> try' $ run' h $ tableDrop "bar"
>>> try' $ run' h $ tableCreate (table "posts")
>>> try' $ run' h $ delete $ table "posts"
>>> try' $ run' h $ tableCreate (table "users"){ tablePrimaryKey = Just "name" }
>>> try' $ run' h $ delete $ table "users"
>>> try' $ run' h $ table "users" # indexDrop "occupation"
>>> try' $ run' h $ table "users" # indexDrop "location"
>>> try' $ run' h $ table "users" # indexDrop "friends"

tableCreate :: Table -> ReQL

Create a table on the server

 >>> run' h $ tableCreate (table "posts") def
 [{"created":1}]
 >>> run' h $ tableCreate (table "users"){ tablePrimaryKey = Just "name" } def
 [{"created":1}]
 >>> run' h $ tableCreate (Table (Just "doctests") "bar" (Just "name")) def
 [{"created":1}]
 >>> run' h $ ex tableCreate ["datacenter":="orion"] (Table (Just "doctests") "bar" (Just "name")) def
 [{"created":1}]

insert :: Expr object => object -> Table -> ReQL

Insert a document or a list of documents into a table

>>> run h $ table "users" # insert (map (\x -> ["name":=x]) ["bill", "bob", "nancy" :: Text]) :: IO WriteResponse
{inserted:3}
>>> run h $ table "posts" # insert ["author" := str "bill", "message" := str "hi", "id" := 1] :: IO WriteResponse
{inserted:1}
>>> run h $ table "posts" # insert ["author" := str "bill", "message" := str "hello", "id" := 2, "flag" := str "deleted"] :: IO WriteResponse
{inserted:1}
>>> run h $ table "posts" # insert ["author" := str "bob", "message" := str "lorem ipsum", "id" := 3, "flag" := str "pinned"] :: IO WriteResponse
{inserted:1}

update :: (Expr selection, Expr a) => (ReQL -> a) -> selection -> ReQL

Add to or modify the contents of a document

>>> run h $ table "users" # getAll "name" [str "bob"] # update (const ["occupation" := str "tailor"]) :: IO WriteResponse
{replaced:1}

replace :: (Expr selection, Expr a) => (ReQL -> a) -> selection -> ReQL

Replace a document with another

>>> run h $ replace (\user -> ["name" := user!"name", "occupation" := str "clothier"]) . R.filter ((R.== str "tailor") . (!?"occupation")) $ table "users" :: IO WriteResponse
{replaced:1}

delete :: Expr selection => selection -> ReQL

Delete the documents

>>> run h $ delete . getAll "name" [str "bob"] $ table "users" :: IO WriteResponse
{deleted:1}

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

Like map but for write queries

>>> _ <- run' h $ table "users" # replace (without ["post_count"])
>>> run h $ forEach (table "users") (\user -> table "users" # get (user!"name") # ex update [nonAtomic] (const ["post_count" := R.count (table "posts" # R.filter (\post -> post!"author" R.== user!"name"))])) :: IO WriteResponse
{replaced:2}

table :: Text -> Table

A table

>>> fmap sort $ run h $ table "users" :: IO [Datum]
[{"post_count":2,"name":"bill"},{"post_count":0,"name":"nancy"}]

tableDrop :: Table -> ReQL

Drop a table

>>> run' h $ tableDrop (table "foo")
{"dropped":1}

tableList :: Database -> ReQL

List the tables in a database

>>> fmap sort $ run h $ tableList (db "doctests") :: IO [String]
["places","posts","users"]

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

Addition or concatenation

Use the Num instance, or a qualified operator.

>>> run h $ 2 + 5
7
>>> run h $ str "foo" R.+ str "bar"
"foobar"

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

Subtraction

>>> run h $ 2 - 5
-3

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

Multiplication

>>> run h $ 2 * 5
10

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

Division

>>> run h $ 2 R./ 5
0.4

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

Mod

>>> run h $ 5 `mod` 2
1

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

Boolean or

>>> run h $ True R.|| False
true

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

Boolean and

>>> run h $ True R.&& False
false

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

Test for equality

>>> run h $ ["a" := 1] R.== ["a" := 1]
true

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

Test for inequality

>>> run h $ 1 R./= False
true

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

Greater than

>>> run h $ 3 R.> 2
true

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

Lesser than

>>> run h $ (str "a") R.< (str "b")
true

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

Greater than or equal to

>>> run h $ [1] R.>= Null
false

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

Lesser than or equal to

>>> run h $ 2 R.<= 2
true

not :: Expr a => a -> ReQL

Negation

>>> run h $ R.not False
true
>>> run h $ R.not Null
true

Lists and Streams

count :: Expr a => a -> ReQL

The size of a sequence or an array.

>>> run h $ count (table "users")
2

union :: (Expr a, Expr b) => a -> b -> ReQL

Join two sequences.

>>> run h $ [1,2,3] `union` ["a", "b", "c" :: Text]
[1,2,3,"a","b","c"]

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

Map a function over a sequence

>>> run h $ R.map (!"a") [["a" := 1], ["a" := 2]]
[1,2]

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

Filter a sequence given a predicate

>>> run h $ R.filter (R.< 4) [3, 1, 4, 1, 5, 9, 2, 6]
[3,1,1,2]

between :: (Expr left, Expr right, Expr seq) => Index -> Bound left -> Bound right -> seq -> ReQL

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

>>> run h $ table "users" # between "name" (Closed $ str "a") (Open $ str "c")
[{"post_count":2,"name":"bill"}]

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

Append a datum to a sequence

>>> run h $ append 3 [1, 2]
[1,2,3]

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

Map a function of a sequence and concat the results

>>> run h $ concatMap id [[1, 2], [3], [4, 5]]
[1,2,3,4,5]

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

SQL-like inner join of two sequences

>>> run' h $ innerJoin (\user post -> user!"name" R.== post!"author") (table "users") (table "posts") # R.zip # orderBy [asc "id"] # pluck ["name", "message"]
[{"name":"bill","message":"hi"},{"name":"bill","message":"hello"}]

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

SQL-like outer join of two sequences

>>> run' h $ outerJoin (\user post -> user!"name" R.== post!"author") (table "users") (table "posts") # R.zip # orderBy [asc "id", asc "name"] # pluck ["name", "message"]
[{"name":"nancy"},{"name":"bill","message":"hi"},{"name":"bill","message":"hello"}]

eqJoin :: (Expr fun, Expr right, Expr left) => fun -> right -> Index -> left -> ReQL

An efficient inner_join that uses a key for the left table and an index for the right table.

>>> run' h $ table "posts" # eqJoin "author" (table "users") "name" # R.zip # orderBy [asc "id"] # pluck ["name", "message"]
[{"name":"bill","message":"hi"},{"name":"bill","message":"hello"}]

skip :: (Expr n, Expr seq) => n -> seq -> ReQL

Drop elements from the head of a sequence.

>>> run h $ skip 2 [1, 2, 3, 4]
[3,4]

limit :: (Expr n, Expr seq) => n -> seq -> ReQL

Limit the size of a sequence.

>>> run h $ limit 2 [1, 2, 3, 4]
[1,2]

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

Cut out part of a sequence

>>> run h $ slice 2 4 [1, 2, 3, 4, 5]
[3,4]

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

Reduce a sequence to a single value

>>> run h $ reduce0 (+) 0 [1, 2, 3]
6

reduce :: (Expr a, Expr s) => (ReQL -> ReQL -> a) -> s -> ReQL

Reduce a non-empty sequence to a single value

>>> run h $ reduce (+) [1, 2, 3]
6

distinct :: Expr s => s -> ReQL

Filter out identical elements of the sequence

>>> fmap sort $ run h $ distinct (table "posts" ! "flag") :: IO [String]
["deleted","pinned"]

zip :: Expr a => a -> ReQL

Merge the left and right attributes of the objects in a sequence.

>>> fmap sort $ run h $ table "posts" # eqJoin "author" (table "users") "name" # R.zip :: IO [Datum]
[{"post_count":2,"flag":"deleted","name":"bill","author":"bill","id":2,"message":"hello"},{"post_count":2,"name":"bill","author":"bill","id":1,"message":"hi"}]

orderBy :: Expr s => [ReQL] -> s -> ReQL

Order a sequence by the given keys

>>> run' h $ table "users" # orderBy [desc "post_count", asc "name"] # pluck ["name", "post_count"]
[{"post_count":2,"name":"bill"},{"post_count":0,"name":"nancy"}]
>>> run' h $ table "users" # ex orderBy ["index":="name"] [] # pluck ["name"]
[{"name":"bill"},{"name":"nancy"}]

asc :: ReQL -> ReQL

Ascending order

desc :: ReQL -> ReQL

Descending order

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

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

>>> run' h $ table "posts" # group (!"author") (reduce (\a b -> a + "\n" + b) . R.map (!"message"))
[{"group":"bill","reduction":"hi\nhello"},{"group":"bob","reduction":"lorem ipsum"}]
>>> run' h $ table "users" # group ((!0) . splitOn "" . (!"name")) (\users -> let pc = users!"post_count" in [avg pc, R.sum pc])
[{"group":"b","reduction":[2,2]},{"group":"n","reduction":[0,0]}]

mapReduce :: (Expr reduction, Expr seq) => (ReQL -> reduction) -> seq -> ReQL

Rewrite multiple reductions into a single map/reduce operation

sum :: Expr s => s -> ReQL

The sum of a sequence

>>> run h $ sum [1, 2, 3]
6

avg :: Expr s => s -> ReQL

The average of a sequence

>>> run h $ avg [1, 2, 3, 4]
2.5

min :: Expr s => s -> ReQL

Minimum value

argmin :: (Expr s, Expr a) => (ReQL -> a) -> s -> ReQL

Value that minimizes the function

max :: Expr s => s -> ReQL

Minimum value

argmax :: (Expr s, Expr a) => (ReQL -> a) -> s -> ReQL

Value that maximizes the function

Accessors

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

Get a single field from an object or an element of an array

>>> run h $ ["foo" := True] ! "foo"
true
>>> run h $ [1, 2, 3] ! 0
1

Or a single field from each object in a sequence

>>> run h $ [["foo" := True], ["foo" := False]] ! "foo"
[true,false]

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

Get a single field, or null if not present

>>> run' h $ empty !? "foo"
null

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

Keep only the given attributes

>>> run' h $ [["a" := 1, "b" := 2], ["a" := 2, "c" := 7], ["b" := 4]] # pluck ["a"]
[{"a":1},{"a":2},{}]

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

Remove the given attributes from an object

>>> run' h $ [["a" := 1, "b" := 2], ["a" := 2, "c" := 7], ["b" := 4]] # without ["a"]
[{"b":2},{"c":7},{"b":4}]

contains :: (Expr x, Expr seq) => x -> seq -> ReQL

Test if a sequence contains a given element

>>> run' h $ [1,2,3] # contains 1
true

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

Merge two objects together

>>> run' h $ merge ["a" := 1, "b" := 1] ["b" := 1, "c" := 2]
{"a":1,"b":1,"c":2}

literal :: Expr a => a -> ReQL

Literal objects, in a merge or update, are not processed recursively.

>>> run' h $ ["a" := ["b" := 1]] # merge ["a" := literal ["c" := 2]]
{"a":{"c":2}}

remove :: ReQL

Remove fields when doing a merge or update

>>> run' h $ ["a" := ["b" := 1]] # merge ["a" := remove]
{}

js :: ReQL -> ReQL

Evaluate a JavaScript expression

>>> run' h $ js "Math.PI"
3.141592653589793
>>> let r_sin x = js "Math.sin" `apply` [x]
>>> run h $ R.map r_sin [pi, pi/2]
[1.2246063538223773e-16,1]

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

Server-side if

>>> run h $ branch (1 R.< 2) 3 4
3

error :: Expr s => s -> ReQL

Abort the query with an error

>>> run' h $ R.error (str "haha") R./ 2 + 1
*** Exception: RethinkDB: Runtime error: "haha"
  in add(div({- HERE -} error("haha"), 2), 1)

db :: Text -> Database

Create a Database reference

>>> run' h $ db "test" # info
{"name":"test","type":"DB"}

dbCreate :: String -> ReQL

Create a database on the server

>>> run' h $ dbCreate "dev"
{"created":1}

dbDrop :: Database -> ReQL

Drop a database

>>> run' h $ dbDrop (db "dev")
{"dropped":1}

dbList :: ReQL

List the databases on the server

>>> _ <- run' h $ dbList

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

Create an index on the table from the given function

>>> run' h $ table "users" # indexCreate "occupation" (!"occupation")
{"created":1}
>>> run' h $ table "users" # ex indexCreate ["multi":=True] "friends" (!"friends")
{"created":1}
>>> run' h $ table "users" # ex indexCreate ["geo":=True] "location" (!"location")
{"created":1}

indexStatus :: Expr table => [ReQL] -> table -> ReQL

Get the status of the given indexes

 run' h $ table "users" # indexStatus []

indexWait :: Expr table => [ReQL] -> table -> ReQL

Wait for an index to be built

 run' h $ table "users" # indexWait []

indexRename :: Expr table => ReQL -> ReQL -> table -> ReQL

sync :: Expr table => table -> ReQL

Ensures that writes on a given table are written to permanent storage

>>> run' h $ sync (table "users")
{"synced":1}

indexList :: Table -> ReQL

List the indexes on the table

>>> run' h $ indexList (table "users")
["friends","location","occupation"]

indexDrop :: Key -> Table -> ReQL

Drop an index

>>> run' h $ table "users" # indexDrop "occupation"
{"dropped":1}

getAll :: Expr values => Index -> values -> Table -> ReQL

Retreive documents by their indexed value

>>> run' h $ table "users" # getAll PrimaryKey [str "bill"]
[{"post_count":2,"name":"bill"}]

get :: Expr s => ReQL -> s -> ReQL

Get a document by primary key

>>> run' h $ table "users" # get "nancy"
{"post_count":0,"name":"nancy"}

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

Convert a value to a different type

>>> run h $ coerceTo "STRING" 1
"1"

asArray :: Expr x => x -> ReQL

Convert a value to an array

>>> run h $ asArray $ ["a" := 1, "b" := 2] :: IO [(String, Int)]
[("a",1),("b",2)]

asString :: Expr x => x -> ReQL

Convert a value to a string

>>> run h $ asString $ ["a" := 1, "b" := 2]
"{\n\t\"a\":\t1,\n\t\"b\":\t2\n}"

asNumber :: Expr x => x -> ReQL

Convert a value to a number

>>> run h $ asNumber (str "34")
34

asObject :: Expr x => x -> ReQL

Convert a value to an object

>>> run' h $ asObject $ [(str "a",1),("b",2)]
{"a":1,"b":2}

asBool :: Expr x => x -> ReQL

Convert a value to a boolean

withFields :: Expr seq => [ReQL] -> seq -> ReQL

Like hasFields followed by pluck

>>> run' h $ [["a" := 1, "b" := 2], ["a" := 2, "c" := 7], ["b" := 4]] # withFields ["a"]
[{"a":1},{"a":2}]

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

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

>>> run h $ indexesOf (match "ba.") [str "foo", "bar", "baz"]
[1,2]

isEmpty :: Expr seq => seq -> ReQL

Test if a sequence is empty

>>> run h $ isEmpty [1]
false

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

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

>>> _ <- run' h $ sample 3 [0,1,2,3,4,5,6,7,8,9]

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

Prepend an element to an array

>>> run h $ prepend 1 [2,3]
[1,2,3]

difference :: (Expr a, Expr b) => a -> b -> ReQL

The different of two lists

>>> run h $ [1,2,3,4,5] # difference [2,5]
[1,3,4]

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

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

>>> run h $ setInsert 3 [1,2,4,4,5]
[1,2,4,5,3]

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

The union of two sets

>>> run h $ [1,2] `setUnion` [2,3]
[2,3,1]

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

The intersection of two sets

>>> run h $ [1,2] `setIntersection` [2,3]
[2]

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

The difference of two sets

>>> run h $ [2,3] # setDifference [1,2]
[3]

hasFields :: Expr obj => ReQL -> obj -> ReQL

Test if an object has the given fields

>>> run h $ hasFields "a" $ ["a" := 1]
true

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

Insert a datum at the given position in an array

>>> run h $ insertAt 1 4 [1,2,3]
[1,4,2,3]

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

Splice an array at a given position inside another array

>>> run h $ spliceAt 2 [4,5] [1,2,3]
[1,2,4,5,3]

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

Delete an element from an array

>>> run h $ deleteAt 1 [1,2,3]
[1,3]

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

Change an element in an array

>>> run h $ changeAt 1 4 [1,2,3]
[1,4,3]

keys :: Expr object => object -> ReQL

The list of keys of the given object

>>> run h $ keys ["a" := 1, "b" := 2]
["a","b"]

match :: Expr string => ReQL -> string -> ReQL

Match a string to a regular expression.

>>> run' h $ str "foobar" # match "f(.)+[bc](.+)"
{"groups":[{"start":2,"end":3,"str":"o"},{"start":4,"end":6,"str":"ar"}],"start":0,"end":6,"str":"foobar"}

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

Apply a function to a list of arguments.

Called do in the official drivers

>>> run h $ (\x -> x R.* 2) `apply` [4]
8

handle :: (Expr instead, Expr reql) => (ReQL -> instead) -> reql -> ReQL

Catch some expections inside the query.

Called default in the official drivers

>>> run h $ R.handle (const 0) $ ["a" := 1] ! "b"
0
>>> run h $ R.handle (expr . id) $ ["a" := 1] ! "b"
"No attribute `b` in object:\n{\n\t\"a\":\t1\n}"

typeOf :: Expr a => a -> ReQL

A string representing the type of an expression

>>> run h $ typeOf 1
"NUMBER"

info :: Expr a => a -> ReQL

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

>>> run h $ info $ table "users"
{"primary_key":"name","name":"users","indexes":["friends","location"],"type":"TABLE","db":{"name":"doctests","type":"DB"}}

json :: ReQL -> ReQL

Parse a json string into an object

>>> run' h $ json "{\"a\":1}"
{"a":1}

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

Flipped function application

upcase :: Expr str => str -> ReQL

Convert to upper case

>>> run h $ upcase (str "Foo")
"FOO"

downcase :: Expr str => str -> ReQL

Convert to lower case

>>> run h $ downcase (str "Foo")
"foo"

split :: Expr str => str -> ReQL

Split a string on whitespace characters

>>> run' h $ split (str "foo bar")
["foo","bar"]

splitOn :: Expr str => ReQL -> str -> ReQL

Split a string on a given delimiter

>>> run' h $ str "foo, bar" # splitOn ","
["foo"," bar"]
>>> run' h $ str "foo" # splitOn ""
["f","o","o"]

splitMax :: Expr str => ReQL -> ReQL -> str -> ReQL

Split a string up to a given number of times

>>> run' h $ str "a:b:c:d" # splitMax ":" 2
["a","b","c:d"]

random :: ReQL

A random float between 0 and 1

>>> run' h $ (\x -> x R.< 1 R.&& x R.>= 0) `apply` [random]
true

randomTo :: ReQL -> ReQL

A random number between 0 and n

>>> run' h $ (\x -> x R.< 10 R.&& x R.>= 0) `apply` [randomTo 10]
true

randomFromTo :: ReQL -> ReQL -> ReQL

A random number between 0 and n

>>> run' h $ (\x -> x R.< 10 R.&& x R.>= 5) `apply` [randomFromTo 5 10]
true

data HttpMethod

Constructors

GET 
POST 
PUT 
PATCH 
DELETE 
HEAD 

http :: Expr url => url -> HttpOptions -> ReQL

Retrieve data from the specified URL over HTTP

>>> _ <- run' h $ http "http://httpbin.org/get" def{ httpParams = Just ["foo" := 1] }
>>> _ <- run' h $ http "http://httpbin.org/put" def{ httpMethod = Just PUT, httpData = Just $ expr ["foo" := "bar"] }

args :: Expr array => array -> ReQL

Splice a list of values into an argument list

changes :: Expr seq => seq -> ReQL

Return an infinite stream of objects representing changes to a table

>>> cursor <- run h $ table "posts" # changes :: IO (Cursor Datum)
>>> run h $ table "posts" # insert ["author" := "bill", "message" := "bye", "id" := 4] :: IO WriteResponse
{inserted:1}
>>> next cursor
Just {"new_val":{"author":"bill","id":4,"message":"bye"},"old_val":null}

returnChanges :: Attribute a

Optional argument for returning an array of objects describing the changes made

>>> run h $ table "users" # ex insert [returnChanges] ["name" := "sabrina"] :: IO WriteResponse
{inserted:1,changes:[{"old_val":null,"new_val":{"name":"sabrina"}}]}

data Durability

Constructors

Hard 
Soft 

Instances

durability :: Durability -> Attribute a

Optional argument for soft durability writes

nonAtomic :: Attribute a

Optional argument for non-atomic writes

>>> run' h $ table "users" # get "sabrina" # update (merge ["lucky_number" := random])
*** Exception: RethinkDB: Runtime error: "Could not prove function deterministic.  Maybe you want to use the non_atomic flag?"
  in
    {- HERE -}
    update(
      get(table(db("doctests"), "users"), "sabrina"),
      (\b -> merge(b, {lucky_number: random()})))
>>> run h $ table "users" # get "sabrina" # ex update [nonAtomic] (merge ["lucky_number" := random]) :: IO WriteResponse
{replaced:1}