rethinkdb-0.1.0.0: RethinkDB client library for haskell

Safe HaskellNone

Database.RethinkDB.Functions

Contents

Description

Functions from the ReQL (RethinkDB Query Language)

Synopsis

Numbers, Booleans and Comparisons

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

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

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

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

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

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

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

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

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

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

Lists and Streams

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

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

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

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)

nil :: ValueExpr ArrayTypeSource

The empty list expression

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

A fold

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

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

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

data Order Source

Constructors

Asc 

Fields

orderAttr :: String
 
Desc 

Fields

orderAttr :: String
 

Instances

class ToOrder a whereSource

Methods

toOrder :: a -> OrderSource

data MapReduce a b c d Source

Constructors

MapReduce (ValueExpr a -> ValueExpr b) (ValueExpr c) (ValueExpr c -> ValueExpr b -> ValueExpr c) (ValueExpr c -> ValueExpr d) 

Accessors

(!) :: (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

Control Structures, Functions and Javascript

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

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

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

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