rethinkdb-0.1.0.0: RethinkDB client library for haskell

Safe HaskellNone

Database.RethinkDB

Contents

Description

RethinkDB client library for Haskell

Modelled upon the official Javascript and Python API: http://www.rethinkdb.com/api/

How to use

>>> import Database.RethinkDB
>>> import qualified Database.RethinkDB.Functions as R

Synopsis

Accessing RethinkDB

data RethinkDBHandle Source

A connection to the database server

openConnection :: HostName -> Maybe PortID -> Maybe String -> IO RethinkDBHandleSource

Create a new connection to the database server

Example: connect using the default port (28015) and specifying the default database for all queries.

>>> h <- openConnection "localhost" Nothing (Just "test")

closeConnection :: RethinkDBHandle -> IO ()Source

Close an open connection

>>> closeConnection h

use :: RethinkDBHandle -> Database -> RethinkDBHandleSource

Set the default connection

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

>>> let h' = h `use` (db "players")

run :: ToQuery a v => RethinkDBHandle -> a -> IO vSource

Run a query on the connection

The return value depends on the type of the second argument.

When the return value is polymorphic, type annotations may be required.

>>> run h $ table "fruits" :: IO [(Document, Value)]

runMaybe :: ToQuery a v => RethinkDBHandle -> a -> IO (Maybe v)Source

Run a query on the connection, returning Nothing on error

runEither :: ToQuery a v => RethinkDBHandle -> a -> IO (Either String v)Source

Run a query on the connection, returning (Left message) on error

runRaw :: (ToBuildQuery q, JSONQuery (BuildViewQuery q)) => RethinkDBHandle -> q -> IO ResponseSource

Run a query on the connection and return the raw response

runJSON :: (JSONQuery (BuildViewQuery q), ToBuildQuery q) => RethinkDBHandle -> q -> IO [Value]Source

Run a query on the connection and return the resulting JSON value

runBatch :: ToQuery q [a] => RethinkDBHandle -> q -> IO (Results a)Source

Run a query on the connection and a return a lazy result list

>>> res <- runBatch h <- (arrayToStream [1,2,3] :: NumberStream)
>>> next res
Just 1
>>> collect res
[2,3]

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

Read the next value from a lazy query. Fetch it from the server if needed.

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

Return all the results of a lazy query.

resultsError :: Results a -> IO (Maybe String)Source

Get the last error from a lazy query.

If both next and resultsError return Nothing, then all results have been fetched without error.

Manipulating databases

data Database Source

A database, referenced by name

Constructors

Database 

Fields

databaseName :: String
 

db :: String -> DatabaseSource

Create a Database reference

dbCreate :: String -> Query False DatabaseSource

Create a database on the server

dbDrop :: Database -> Query False ()Source

Drop a database

dbList :: Query False [Database]Source

List the databases on the server

>>> run h $ dbList
[test, dev, prod]

Manipulating Tables

data Table Source

A table description

Constructors

Table 

Fields

tableDatabase :: Maybe Database

when Nothing, use the rdbDatabase

tableName :: String
 
_tablePrimaryAttr :: Maybe String

when Nothing, id is used

data TableCreateOptions Source

Options used to create a table

table :: String -> TableSource

Create a simple table refence with no associated database or primary key

>>> table "music"

Another way to create table references is to use the Table constructor:

>>> Table (Just "mydatabase") "music" (Just "tuneid")

tableCreate :: Table -> TableCreateOptions -> Query False TableSource

Create a table on the server

def can be imported from Data.Default

>>> t <- run h $ tableCreate (table "fruits") def

tableDrop :: Table -> Query False ()Source

Drop a table

tableList :: Database -> Query False [Table]Source

List the tables in a database

Writing data

insert :: (ToValue a, ToValueType (ExprType a) ~ ObjectType) => Table -> a -> WriteQuery DocumentSource

Insert a document into a table

>>> d <- run h $ insert t (object ["name" .= "banana", "color" .= "red"])

insertMany :: (ToValue a, ToValueType (ExprType a) ~ ObjectType) => Table -> [a] -> WriteQuery [Document]Source

Insert many documents into a table

upsert :: (ToValue a, ToValueType (ExprType a) ~ ObjectType) => Table -> a -> WriteQuery DocumentSource

Insert a document into a table, overwriting a document with the same primary key if one exists.

upsertMany :: (ToValue a, ToValueType (ExprType a) ~ ObjectType) => Table -> [a] -> WriteQuery [Document]Source

Insert many documents into a table, overwriting any existing documents with the same primary key.

update :: (ToExpr sel, ExprType sel ~ StreamType True out, ToMapping map, MappingFrom map ~ out, MappingTo map ~ ObjectType) => sel -> map -> WriteQuery ()Source

Update a table

>>> t <- run h $ tableCreate (table "example") def
>>> run h $ insertMany t [object ["a" .= 1, "b" .= 11], object ["a" .= 2, "b" .= 12]]
>>> run h $ update t (object ["b" .= 20])
>>> run h $ t

replace :: (ToExpr sel, ExprIsView sel ~ True, ToJSON a) => sel -> a -> WriteQuery ()Source

Replace documents in a table

delete :: (ToExpr sel, ExprIsView sel ~ True) => sel -> WriteQuery ()Source

Delete one or more documents from a table

Selecting data

get :: (ToExpr e, ExprType e ~ StreamType True ObjectType, ToValue k) => e -> k -> ObjectExprSource

Get a document by primary key

filter' :: (ToMapping m, ToStream e, MappingFrom m `HasToStreamValueOf` e) => m -> e -> Expr (ExprType e)Source

Get all the documents for which the given predicate is true

between :: (ToJSON a, ToStream e, ObjectType `HasToStreamValueOf` e) => Maybe a -> Maybe a -> e -> Expr (ExprType e)Source

Get all documents between two primary keys (both keys are inclusive)

Joins

Transformations

Aggregation

reduce :: (ToValue z, ToValueType (ExprType z) ~ a, ToStream e, b `HasToStreamValueOf` e, ToExpr c, ExprIsView c ~ False) => e -> z -> (ValueExpr a -> ValueExpr b -> c) -> Expr (ExprType c)Source

groupedMapReduce :: (ToValue group, ToValue value, ToValue acc, ToValueType (ExprType acc) ~ b, ToValue acc', ToValueType (ExprType acc') ~ b, ToStream e, a `HasToStreamValueOf` e) => (ValueExpr a -> group) -> (ValueExpr a -> value) -> acc -> (ValueExpr b -> ValueExpr v -> acc') -> e -> Expr (StreamType False b)Source

Reductions

Document manipulation

(!) :: (ToExpr a, ExprValueType a ~ ObjectType) => a -> String -> ValueExpr tSource

Get the value of the field of an object

When GHC thinks the result is ambiguous, it may have to be annotated.

>>> run h $ (get (table "tea") "black" ! "water_temperature" :: NumberExpr)
95

Operators

concat :: (HaveValueType a b v, CanConcat v) => a -> b -> Expr (ValueType v)Source

eq :: (HasValueType a x, HasValueType b y) => a -> b -> BoolExprSource

ne :: (HasValueType a x, HasValueType b y) => a -> b -> BoolExprSource

gt :: (HaveValueType a b v, CanCompare v) => a -> b -> BoolExprSource

ge :: (HaveValueType a b v, CanCompare v) => a -> b -> BoolExprSource

lt :: (HaveValueType a b v, CanCompare v) => a -> b -> BoolExprSource

le :: (HaveValueType a b v, CanCompare v) => a -> b -> BoolExprSource

Control structures

bind :: ToValue e => e -> (ValueExpr (ToValueType (ExprType e)) -> Expr t) -> Expr tSource

let' :: [Attribute] -> Expr t -> Expr tSource

forEach :: (ToStream a, v `HasToStreamValueOf` a) => a -> (ValueExpr v -> WriteQuery b) -> WriteQuery ()Source

Execute a write query for each element of the stream

>>> run h $ forEach [1,2,3::Int] (\x -> insert (table "fruits") (obj ["n" := x]))

js :: String -> Expr (ValueType any)Source

A javascript expression

It is often necessary to specify the result type:

>>> run h $ (js "1 + 2" :: NumberExpr)
3

jsfun :: ToValue e => String -> e -> Expr (ValueType y)Source

A javascript function

>>> let squareRoot = jsfun "Math.sqrt" :: NumberExpr -> NumberExpr
>>> run h $ squareRoot 5 :: IO Double
2.23606797749979

Sequence conversion

streamToArray :: (ToExpr e, ExprType e ~ StreamType w t) => e -> Expr (ValueType ArrayType)Source

Convert a stream into an array

arrayToStream :: (ToExpr e, ExprType e ~ ValueType ArrayType) => e -> Expr (StreamType False t)Source

Convert an array into a stream

Short constructors

data Obj Source

A list of String/Expr pairs

data Attribute Source

Constructors

forall e . ToValue e => String := e 

obj :: [Attribute] -> ObjSource

Build an Obj

nil :: ValueExpr ArrayTypeSource

The empty list expression

Types and type classes

data Query b a Source

A query returning a

Instances

data ExprTypeKind Source

The type of a RQL expression

The type hierarchy has 3 branches:

  • A read-only sequence: StreamType False
  • A selection (also called a view): StreamType True
  • A value (a JSON object, array or primitive type): ExprType

Constructors

StreamType Bool ValueTypeKind

When the flag is true, it can be updated or deleted

ValueType ValueTypeKind 

type family ExprValueType expr :: ValueTypeKindSource

The type of the value of an Expr

class ToExpr o whereSource

Convert something into an Expr

Associated Types

type ExprType o :: ExprTypeKindSource

Methods

toExpr :: o -> Expr (ExprType o)Source

class ToValue e whereSource

Convert something into a value Expr

type HasValueType a v = (ToValue a, ToValueType (ExprType a) ~ v)Source

Aliases for type constraints on expressions

type NumberExpr = Expr (ValueType NumberType)Source

Simple aliases for different Expr types

class CanCompare a Source

What values can be compared with eq, ne, lt, gt, le and ge

data Order Source

Constructors

Asc 

Fields

orderAttr :: String
 
Desc 

Fields

orderAttr :: String
 

Instances

class ToOrder a whereSource

Methods

toOrder :: a -> OrderSource

class Sequence e Source

A sequence is either a stream or an array

Associated Types

type SequenceType e t :: ConstraintSource

data Mapping from to Source

A mapping is a like single-parameter function

Constructors

Mapping (QueryM Mapping) 

class ToMapping map whereSource

Convert objects into mappings

Associated Types

type MappingFrom map :: ValueTypeKindSource

type MappingTo map :: ValueTypeKindSource

Methods

toMapping :: map -> Mapping (MappingFrom map) (MappingTo map)Source

Instances