rethinkdb-0.1.0.0: RethinkDB client library for haskell

Safe HaskellNone

Database.RethinkDB.Driver

Contents

Description

The core of the haskell client library for RethinkDB

Synopsis

Network

data RethinkDBHandle Source

A connection to the database server

Constructors

RethinkDBHandle 

Fields

rdbHandle :: Handle
 
rdbToken :: IORef Int64

The next token to use

rdbDatabase :: Database

When no database is specified, this one will be used

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

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

closeConnection :: RethinkDBHandle -> IO ()Source

Close an open connection

>>> closeConnection h

recvAll :: RethinkDBHandle -> Int -> IO ByteStringSource

Receive a fixed amoutn of data

sendAll :: RethinkDBHandle -> ByteString -> IO ()Source

Send a bytestring

getNewToken :: RethinkDBHandle -> IO Int64Source

Get a request token and increment the token counter

data Response Source

The raw response to a query

Instances

runQLQuery :: RethinkDBHandle -> Query -> IO ResponseSource

Execute a raw protobuffer query and return the raw response

CRUD

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]

data TableCreateOptions Source

Options used to create a table

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

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

uTableKey :: Table -> Utf8Source

Get the primary key of the table as a Utf8, or id if there is none

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

Get a document by primary key

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

Queries

data Query b a whereSource

A query returning a

Constructors

Query :: QueryM Query -> ([Value] -> Either String a) -> Query False a 

Fields

_queryBuild :: QueryM Query
 
_queryExtract :: [Value] -> Either String a
 
ViewQuery :: QueryM (Table, Query) -> ([(Document, Value)] -> Either String a) -> Query True a 

Instances

queryBuild :: Query w a -> QueryM (MaybeView w, Query)Source

type family If p a b :: kSource

class ToBuildQuery a whereSource

Convert things like tables and documents into queries

Associated Types

type BuildViewQuery a :: BoolSource

mapMSnd :: Monad m => (a -> m b) -> [(c, a)] -> m [(c, b)]Source

data Proxy t Source

Constructors

Proxy 

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

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

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

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

Run a query on the connection, returning Nothing 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

class JSONQuery b whereSource

Methods

jsonQuery :: (forall a. ([If b (Document, Value) Value] -> Either String a) -> Query b a) -> Query b [Value]Source

data QueryViewPair a whereSource

Constructors

QueryViewPair :: Query w a -> MaybeView w -> QueryViewPair a 

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.

Expressions

type family ExprTypeIsView expr :: BoolSource

Can the Expr be written to? (updated or deleted)

type family ExprValueType expr :: ValueTypeKindSource

The type of the value of an Expr

type family ExprTypeStreamType t :: ValueTypeKindSource

The type of the stream of an Expr

mkView :: ExprIsView (Expr t) ~ True => Table -> QueryM Term -> Expr tSource

data MaybeView w whereSource

Constructors

NoView :: MaybeView False 
ViewOf :: Table -> MaybeView True 

class ToExpr o whereSource

Convert something into an Expr

Associated Types

type ExprType o :: ExprTypeKindSource

Methods

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

type family ToValueType t :: ValueTypeKindSource

The result type of toValue

class ToValue e whereSource

Convert something into a value Expr

type family FromMaybe a m :: kSource

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

class Sequence e Source

A sequence is either a stream or an array

Associated Types

type SequenceType e t :: ConstraintSource

data Obj Source

A list of String/Expr pairs

Constructors

Obj [Attribute] 

data Attribute Source

Constructors

forall e . ToValue e => String := e 

obj :: [Attribute] -> ObjSource

Build an Obj

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

Mappings

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

QueryM Monad

Utilities

mappingToPredicate :: Mapping -> PredicateSource

Convert a protobuf Mapping into a Predicate

tableToTerm :: Table -> QueryM TermSource

Convert a table to a raw protobuf term

mapping :: ToMapping m => m -> QueryM MappingSource

Convert into a raw protobuf mapping

expr :: ToExpr e => e -> QueryM TermSource

Convert an Expr to a term

exprV :: ToExpr e => e -> QueryM (MaybeView (ExprIsView e), Term)Source

stream :: ToStream a => a -> QueryM TermSource

Convert a stream to a term

value :: ToValue a => a -> QueryM TermSource

Convert a value to a term

toJsonTerm :: ToJSON a => a -> TermSource

build a raw protobuf Term

(.?) :: FromJSON a => Value -> String -> Maybe aSource

Test if a field is present in a json Value and return it

whenSuccess :: FromJSON a => String -> (a -> Either String b) -> [Value] -> Either String bSource

Helper function to handle responses to a query

whenSuccess_ :: b -> [Value] -> Either String bSource

same as whenSuccess, but ignore the response when there is no error

decodeAny :: FromJSON a => ByteString -> Maybe aSource

Like aeson's decode, but but works on numbers and strings, not only objects and arrays

convert :: FromJSON a => Value -> Maybe aSource

Convert a JSON Value into another type

metaQuery :: QueryM MetaQuery -> QueryM QuerySource

Extract the error message from a Response if there is an error | Help build meta queries

packUInt :: Int -> ByteStringSource

Convert an int to a 4-byte bytestring

unpackUInt :: ByteString -> IntSource

Convert a 4-bte byestring to an int

op :: BuiltinType -> BuiltinSource

apply :: Builtin -> [QueryM Term] -> QueryM TermSource

rapply :: [QueryM Term] -> Builtin -> QueryM TermSource

simpleOp :: ExprIsView (Expr t) ~ False => BuiltinType -> [QueryM Term] -> Expr tSource

withView :: MaybeView b -> QueryM Term -> QueryM (MaybeView b, Term)Source

comparison :: ExprTypeIsView t ~ False => Comparison -> [QueryM Term] -> Expr tSource

tableRef :: Table -> QueryM TableRefSource

Build a protobuf TableRef object

extractTerm :: ToExpr e => e -> TermSource