rethinkdb-1.15.0.0: A driver for the RethinkDB database server

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

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

data RethinkDBHandle Source

A connection to the database server

Instances

close :: RethinkDBHandle -> IO ()Source

Close an open connection

use :: Database -> RethinkDBHandle -> 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 DatumSource

Run a given query and return a Datum

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

Run a query with the given options

data ReQL Source

A ReQL Term

Instances

Floating ReQL 
Fractional ReQL 
Num ReQL 
Show ReQL 
IsString ReQL 
Expr ReQL 
OptArgs ReQL 
(~ * a ReQL, ~ * b ReQL) => Expr (a -> b -> ReQL) 
~ * a ReQL => Expr (a -> ReQL) 

class ToDatum a whereSource

Methods

toDatum :: a -> DatumSource

Instances

ToDatum Bool 
ToDatum Char 
ToDatum Double 
ToDatum Float 
ToDatum Int 
ToDatum Int8 
ToDatum Int16 
ToDatum Int32 
ToDatum Int64 
ToDatum Integer 
ToDatum Word 
ToDatum Word8 
ToDatum Word16 
ToDatum Word32 
ToDatum Word64 
ToDatum () 
ToDatum ByteString 
ToDatum ByteString 
ToDatum Text 
ToDatum UTCTime 
ToDatum Value 
ToDatum Text 
ToDatum ZonedTime 
ToDatum Datum 
ToDatum [Char] 
ToDatum a => ToDatum [a] 
ToDatum (Ratio Integer) 
ToDatum a => ToDatum (Maybe a) 
ToDatum a => ToDatum (Vector a) 
ToDatum a => ToDatum (Set a) 
(ToDatum a, ToDatum b) => ToDatum (Either a b) 
(ToDatum a, ToDatum b) => ToDatum (a, b) 
ToDatum a => ToDatum (HashMap [Char] a) 
ToDatum a => ToDatum (HashMap Text a) 
ToDatum a => ToDatum (Map [Char] a) 
ToDatum a => ToDatum (Map Text a) 
(ToDatum a, ToDatum b, ToDatum c) => ToDatum (a, b, c) 
(ToDatum a, ToDatum b, ToDatum c, ToDatum d) => ToDatum (a, b, c, d) 
(ToDatum a, ToDatum b, ToDatum c, ToDatum d, ToDatum e) => ToDatum (a, b, c, d, e) 

class FromDatum a whereSource

Instances

FromDatum Bool 
FromDatum Char 
FromDatum Double 
FromDatum Float 
FromDatum Int 
FromDatum Int8 
FromDatum Int16 
FromDatum Int32 
FromDatum Int64 
FromDatum Integer 
FromDatum Word 
FromDatum Word8 
FromDatum Word16 
FromDatum Word32 
FromDatum Word64 
FromDatum String 
FromDatum () 
FromDatum ByteString 
FromDatum ByteString 
FromDatum Text 
FromDatum UTCTime 
FromDatum Value 
FromDatum Text 
FromDatum ZonedTime 
FromDatum Datum 
FromDatum Frame 
FromDatum Change 
FromDatum WriteResponse 
FromDatum a => FromDatum [a] 
FromDatum (Ratio Integer) 
FromDatum a => FromDatum (Maybe a) 
FromDatum a => FromDatum (Vector a) 
(Ord a, FromDatum a) => FromDatum (Set a) 
(FromDatum a, FromDatum b) => FromDatum (Either a b) 
(FromDatum a, FromDatum b) => FromDatum (a, b) 
FromDatum a => FromDatum (HashMap [Char] a) 
FromDatum a => FromDatum (HashMap Text a) 
FromDatum a => FromDatum (Map [Char] a) 
FromDatum a => FromDatum (Map Text a) 
(FromDatum a, FromDatum b, FromDatum c) => FromDatum (a, b, c) 
(FromDatum a, FromDatum b, FromDatum c, FromDatum d) => FromDatum (a, b, c, d) 
(FromDatum a, FromDatum b, FromDatum c, FromDatum d, FromDatum e) => FromDatum (a, b, c, d, e) 

data RunFlag Source

Per-query settings

Constructors

UseOutdated 
NoReply 
Durability Durability 
Profile 
ArrayLimit Int 

noReplyWait :: RethinkDBHandle -> IO ()Source

Wait for NoReply queries to complete on the server

>>> () <- runOpts h [NoReply] $ table "users" # get "bob" # update (\row -> merge row ["occupation" := "teacher"])
>>> noReplyWait h

data RethinkDBError Source

Instances

Show RethinkDBError 
Typeable RethinkDBError 
Exception RethinkDBError 

data Response Source

The response to a query

Instances

class Result r whereSource

Convert the raw query response into useful values

Methods

convertResult :: MVar Response -> IO rSource

Instances

Result Bool 
Result Char 
Result Double 
Result Float 
Result Int 
Result Int8 
Result Int16 
Result Int32 
Result Int64 
Result Integer 
Result Word 
Result Word8 
Result Word16 
Result Word32 
Result Word64 
Result String 
Result () 
Result ByteString 
Result ByteString 
Result Text 
Result UTCTime 
Result Value 
Result Text 
Result ZonedTime 
Result Datum 
Result Response 
Result WriteResponse 
FromDatum a => Result [a] 
Result (Ratio Integer) 
FromDatum a => Result (Maybe a) 
FromDatum a => Result (Vector a) 
(Ord a, FromDatum a) => Result (Set a) 
FromDatum a => Result (Cursor a) 
(FromDatum a, FromDatum b) => Result (Either a b) 
(FromDatum a, FromDatum b) => Result (a, b) 
FromDatum a => Result (HashMap [Char] a) 
FromDatum a => Result (HashMap Text a) 
FromDatum a => Result (Map [Char] a) 
FromDatum a => Result (Map Text a) 
(FromDatum a, FromDatum b, FromDatum c) => Result (a, b, c) 
(FromDatum a, FromDatum b, FromDatum c, FromDatum d) => Result (a, b, c, d) 
(FromDatum a, FromDatum b, FromDatum c, FromDatum d, FromDatum e) => Result (a, b, c, d, e) 

Cursors

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

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

A strict version of collect

each :: Cursor a -> (a -> IO b) -> IO ()Source

data Cursor a Source

Instances

Functor Cursor 
FromDatum a => Result (Cursor a) 

Manipulating databases

data Database Source

A database, referenced by name

Constructors

Database 

Fields

databaseName :: Text
 

Instances

Eq Database 
Ord Database 
Show Database 
IsString Database 
Expr Database 

dbCreate :: String -> ReQLSource

Create a database on the server

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

dbDrop :: Database -> ReQLSource

Drop a database

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

dbList :: ReQLSource

List the databases on the server

>>> _ <- run' h $ dbList

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
 

Instances

Eq Table 
Ord Table 
Show Table 
IsString Table 
Expr Table 

tableCreate :: Table -> ReQLSource

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}]

tableDrop :: Table -> ReQLSource

Drop a table

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

tableList :: Database -> ReQLSource

List the tables in a database

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

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

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}

indexDrop :: Key -> Table -> ReQLSource

Drop an index

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

indexList :: Table -> ReQLSource

List the indexes on the table

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

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

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

Get the status of the given indexes

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

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

Wait for an index to be built

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

changes :: Expr seq => seq -> ReQLSource

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}

Writing data

data Change Source

Constructors

Change 

Fields

oldVal :: Datum
 
newVal :: Datum
 

Instances

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

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 -> ReQLSource

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 -> ReQLSource

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 -> ReQLSource

Delete the documents

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

sync :: Expr table => table -> ReQLSource

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

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

returnChanges :: Attribute aSource

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"}}]}

nonAtomic :: Attribute aSource

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}

durability :: Durability -> Attribute aSource

Optional argument for soft durability writes

Selecting data

db :: Text -> DatabaseSource

Create a Database reference

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

table :: Text -> TableSource

A table

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

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

Get a document by primary key

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

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

Retreive documents by their indexed value

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

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

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 -> ReQLSource

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"}]

data Bound a Source

An upper or lower bound for between and during

Constructors

Open

An inclusive bound

Fields

getBound :: a
 
Closed

An exclusive bound

Fields

getBound :: a
 
DefaultBound 

Fields

getBound :: a
 

Instances

Functor Bound 
Num a => Num (Bound a) 

Joins

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

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 -> ReQLSource

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 -> ReQLSource

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"}]

zip :: Expr a => a -> ReQLSource

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"}]

data Index Source

Constructors

PrimaryKey 
Index Key 

Instances

IsString Index 

Transformations

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

Map a function over a sequence

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

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

Like hasFields followed by pluck

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

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

Map a function of a sequence and concat the results

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

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

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 -> ReQLSource

Ascending order

desc :: ReQL -> ReQLSource

Descending order

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

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 -> ReQLSource

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 -> ReQLSource

Cut out part of a sequence

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

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

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 -> ReQLSource

Test if a sequence is empty

>>> run h $ isEmpty [1]
false

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

Join two sequences.

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

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

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]

Aggregation

group :: (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

>>> 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]}]

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

Reduce a non-empty sequence to a single value

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

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

Reduce a sequence to a single value

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

distinct :: Expr s => s -> ReQLSource

Filter out identical elements of the sequence

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

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

Test if a sequence contains a given element

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

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

Rewrite multiple reductions into a single map/reduce operation

Aggregators

count :: Expr a => a -> ReQLSource

The size of a sequence or an array.

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

sum :: Expr s => s -> ReQLSource

The sum of a sequence

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

avg :: Expr s => s -> ReQLSource

The average of a sequence

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

min :: Expr s => s -> ReQLSource

Minimum value

max :: Expr s => s -> ReQLSource

Minimum value

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

Value that minimizes the function

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

Value that maximizes the function

Document manipulation

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

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 -> ReQLSource

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}]

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

Merge two objects together

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

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

Append a datum to a sequence

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

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

Prepend an element to an array

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

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

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 -> ReQLSource

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 -> ReQLSource

The union of two sets

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

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

The intersection of two sets

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

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

The difference of two sets

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

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

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 -> ReQLSource

Get a single field, or null if not present

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

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

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 -> ReQLSource

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 -> ReQLSource

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 -> ReQLSource

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 -> ReQLSource

Change an element in an array

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

keys :: Expr object => object -> ReQLSource

The list of keys of the given object

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

literal :: Expr a => a -> ReQLSource

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 :: ReQLSource

Remove fields when doing a merge or update

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

data Attribute a whereSource

A key/value pair used for building objects

Constructors

:= :: Expr e => Text -> e -> Attribute a 
::= :: (Expr k, Expr v) => k -> v -> Attribute Dynamic 
NoAttribute :: Attribute a 

Instances

String manipulation

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

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"}

upcase :: Expr str => str -> ReQLSource

Convert to upper case

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

downcase :: Expr str => str -> ReQLSource

Convert to lower case

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

split :: Expr str => str -> ReQLSource

Split a string on whitespace characters

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

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

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 -> ReQLSource

Split a string up to a given number of times

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

Math and logic

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

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 -> ReQLSource

Subtraction

>>> run h $ 2 - 5
-3

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

Multiplication

>>> run h $ 2 * 5
10

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

Division

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

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

Mod

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

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

Boolean and

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

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

Boolean or

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

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

Test for equality

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

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

Test for inequality

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

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

Greater than

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

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

Greater than or equal to

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

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

Lesser than

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

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

Lesser than or equal to

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

not :: Expr a => a -> ReQLSource

Negation

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

random :: ReQLSource

A random float between 0 and 1

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

randomTo :: ReQL -> ReQLSource

A random number between 0 and n

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

randomFromTo :: ReQL -> ReQL -> ReQLSource

A random number between 0 and n

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

Dates and times

now :: ReQLSource

The time and date when the query is executed

 >>> run' h $ now

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

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

>>> run' h $ time 2011 12 24 23 59 59 "Z"
Time<2011-12-24 23:59:59 +0000>

epochTime :: ReQL -> ReQLSource

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

>>> run' h $ epochTime 1147162826
Time<2006-05-09 08:20:26 +0000>

iso8601 :: ReQL -> ReQLSource

Build a time object given an iso8601 string

>>> run' h $ iso8601 "2012-01-07T08:34:00-0700"
Time<2012-01-07 08:34:00 -0700>

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

The same time in a different timezone

>>> _ <- run' h $ inTimezone "+0800" now

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

Test if a time is between two other times

>>> run' h $ during (Open $ now R.- (60*60)) (Closed now) $ epochTime 1382919271
false

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

args :: Expr array => array -> ReQLSource

Splice a list of values into an argument list

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

Apply a function to a list of arguments.

Called do in the official drivers

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

js :: ReQL -> ReQLSource

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 -> ReQLSource

Server-side if

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

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

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}

error :: Expr s => s -> ReQLSource

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)

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

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}"

class Expr e whereSource

Convert other types into ReQL expressions

Methods

expr :: e -> ReQLSource

exprList :: [e] -> ReQLSource

Instances

Expr Bool 
Expr Char 
Expr Double 
Expr Float 
Expr Int 
Expr Int8 
Expr Int16 
Expr Int32 
Expr Int64 
Expr Integer 
Expr Word 
Expr Word8 
Expr Word16 
Expr Word32 
Expr Word64 
Expr () 
Expr ByteString 
Expr ByteString 
Expr Text 
Expr UTCTime 
Expr Value 
Expr Text 
Expr ZonedTime 
Expr Datum 
Expr Table 
Expr Database 
Expr ReQL 
Expr Term 
Expr Unit 
Expr ConflictResolution 
Expr Durability 
Expr PaginationStrategy 
Expr HttpMethod 
Expr HttpResultFormat 
Expr a => Expr [a] 
Expr (Ratio Integer) 
Expr a => Expr (Maybe a) 
Expr a => Expr (Vector a) 
Expr a => Expr (Set a) 
Expr (Attribute a) 
(~ * a ReQL, ~ * b ReQL) => Expr (a -> b -> ReQL) 
~ * a ReQL => Expr (a -> ReQL) 
(Expr a, Expr b) => Expr (Either a b) 
(Expr a, Expr b) => Expr (a, b) 
Expr a => Expr (HashMap [Char] a) 
(Expr k, Expr v) => Expr (HashMap k v) 
Expr a => Expr (HashMap Text a) 
Expr a => Expr (Map [Char] a) 
Expr a => Expr (Map Text a) 
(Expr a, Expr b, Expr c) => Expr (a, b, c) 
(Expr a, Expr b, Expr c, Expr d) => Expr (a, b, c, d) 
(Expr a, Expr b, Expr c, Expr d, Expr e) => Expr (a, b, c, d, e) 

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

Convert a value to a different type

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

asArray :: Expr x => x -> ReQLSource

Convert a value to an array

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

asString :: Expr x => x -> ReQLSource

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 -> ReQLSource

Convert a value to a number

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

asObject :: Expr x => x -> ReQLSource

Convert a value to an object

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

asBool :: Expr x => x -> ReQLSource

Convert a value to a boolean

typeOf :: Expr a => a -> ReQLSource

A string representing the type of an expression

>>> run h $ typeOf 1
"NUMBER"

info :: Expr a => a -> ReQLSource

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 -> ReQLSource

Parse a json string into an object

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

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

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"] }

data HttpOptions Source

Constructors

HttpOptions 

Fields

httpTimeout :: Maybe Int
 
httpReattempts :: Maybe Int
 
httpRedirects :: Maybe Int
 
httpVerify :: Maybe Bool
 
httpResultFormat :: Maybe HttpResultFormat
 
httpMethod :: Maybe HttpMethod
 
httpAuth :: Maybe [Attribute Dynamic]
 
httpParams :: Maybe [Attribute Dynamic]
 
httpHeader :: Maybe [Attribute Dynamic]
 
httpData :: Maybe ReQL
 
httpPage :: Maybe PaginationStrategy
 
httpPageLimit :: Maybe Int
 

Instances

data HttpMethod Source

Constructors

GET 
POST 
PUT 
PATCH 
DELETE 
HEAD 

Instances

Geospatial commands

circle :: (Expr point, Expr radius) => point -> radius -> ReQLSource

Create a polygon approximating a circle

>>> run' h $ ex circle [numVertices 6, unit Kilometer] (point (-73) 40) 100
Polygon<[[-73,39.099310036015424],[-74.00751390838496,39.54527799206398],[-74.02083610406069,40.445812561599965],[-73,40.900549591978255],[-71.97916389593931,40.445812561599965],[-71.99248609161504,39.54527799206398],[-73,39.099310036015424]]>

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

Distance between a point and another geometry object

>>> run' h $ distance (point (-73) 40) (point (-122) 37)
4233453.467303547
>>> run' h $ ex distance [unit Mile] (point (-73) 40) (point (-122) 37)
2630.54602825968

fill :: Expr line => line -> ReQLSource

Convert a line object into a polygon

>>> run' h $ fill $ line [[-122,37], [-120,39], [-121,38]]
Polygon<[[-122,37],[-120,39],[-121,38],[-122,37]]>

geoJSON :: Expr geojson => geojson -> ReQLSource

Convert a GeoJSON object into a RethinkDB geometry object

>>> run' h $ geoJSON ["type" := "Point", "coordinates" := [-45,80]]
Point<[-45,80]>

toGeoJSON :: Expr geo => geo -> ReQLSource

Convert a RethinkDB geometry object into a GeoJSON object

>>> run' h $ toGeoJSON $ point (-122.423246) 37.779388
{"coordinates":[-122.423246,37.779388],"type":"Point"}

getIntersecting :: (Expr geo, Expr table) => geo -> Index -> table -> ReQLSource

Search a geospatial index for intersecting objects

>>> run' h $ table "places" # getIntersecting (point (-122) 37) (Index "geo")
[]

getNearest :: (Expr point, Expr table) => point -> Index -> table -> ReQLSource

Query a geospatial index for the nearest matches

>>> run' h $ table "places" # getNearest (point (-122) 37) (Index "location")
[]
>>> run' h $ table "places" # ex getNearest [maxResults 5, maxDist 10, unit Kilometer] (point (-122) 37) (Index "location")
[]

includes :: (Expr area, Expr geo) => geo -> area -> ReQLSource

Test whether a geometry object includes another

>>> run' h $ circle (point (-122) 37) 5000 # includes (point (-120) 48)
false

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

Test if two geometry objects intersects

>>> run' h $ intersects (line [[-122,37],[-120,48]]) (line [[-120,49],[-122,48]])
false

line :: Expr points => points -> ReQLSource

Create a line object

>>> run' h $ line [[-73,45],[-122,37]]
Line<[-73,45],[-122,37]>

point :: (Expr longitude, Expr latitude) => longitude -> latitude -> ReQLSource

Create a point objects

>>> run' h $ point (-73) 40
Point<[-73,40]>

polygon :: Expr points => points -> ReQLSource

Create a polygon object

>>> run' h $ polygon [[-73,45],[-122,37],[-73,40]]
Polygon<[[-73,45],[-122,37],[-73,40],[-73,45]]>

polygonSub :: (Expr polygon, Expr hole) => hole -> polygon -> ReQLSource

Punch a hole in a polygon

>>> run' h $ (polygon [[-73,45],[-122,37],[-73,40]]) # polygonSub (polygon [[-73.2,40.1],[-73.2,40.2],[-73.3,40.1]])
Polygon<[[-73,45],[-122,37],[-73,40],[-73,45]],[[-73.2,40.1],[-73.2,40.2],[-73.3,40.1],[-73.2,40.1]]>

data LonLat Source

Constructors

LonLat 

Fields

longitude :: Double
 
latitude :: Double
 

Instances

maxResults :: ReQL -> Attribute aSource

Optional argument for getNearest

maxDist :: ReQL -> Attribute aSource

Optional argument for getNearest

unit :: Unit -> Attribute aSource

Optional argument for getNearest, circle and distance

numVertices :: ReQL -> Attribute aSource

Optional argument for circle

data Unit Source

Instances

Helpers

ex :: OptArgs a => a -> [Attribute Static] -> aSource

Extend an operation with optional arguments

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) => a -> (a -> b) -> ReQLSource

Flipped function application

note :: String -> ReQL -> ReQLSource

Add a note a a ReQL Term

This note does not get sent to the server. It is used to annotate backtraces and help debugging.

empty :: ReQLSource

An empty object

def :: Default a => a

The default value for this type.