rethinkdb-2.1.0.2: A driver for RethinkDB 2.1

Safe HaskellNone
LanguageHaskell98

Database.RethinkDB.ReQL

Description

Building RQL queries in Haskell

Synopsis

Documentation

data ReQL Source

A ReQL Term

Constructors

ReQL 

Instances

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

op :: Arr a => TermType -> a -> ReQL Source

Build a term with no optargs

op' :: Arr a => TermType -> a -> [Attribute Static] -> ReQL Source

Build a term

data Term Source

Internal representation of a ReQL Term

Constructors

Term 
Datum 

Fields

termDatum :: Datum
 
Note 

Fields

termNote :: String
 
termTerm :: Term
 

Instances

data Frame Source

Constructors

FramePos Int 
FrameOpt Text 

class Expr e where Source

Convert other types into ReQL expressions

Minimal complete definition

Nothing

Methods

expr :: e -> ReQL Source

exprList :: [e] -> ReQL Source

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 LonLat 
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 (Set a) 
Expr a => Expr (Vector a) 
Expr a => Expr (Bound a) 
Expr (Attribute a) 
((~) * a ReQL, (~) * b ReQL, (~) * c ReQL, (~) * d ReQL, (~) * e ReQL) => Expr (a -> b -> c -> d -> e -> ReQL) 
((~) * a ReQL, (~) * b ReQL, (~) * c ReQL, (~) * d ReQL) => Expr (a -> b -> c -> d -> ReQL) 
((~) * a ReQL, (~) * b ReQL, (~) * c ReQL) => Expr (a -> b -> c -> ReQL) 
((~) * 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) 

str :: String -> ReQL Source

A shortcut for inserting strings into ReQL expressions Useful when OverloadedStrings makes the type ambiguous

num :: Double -> ReQL Source

A shortcut for inserting numbers into ReQL expressions

data Attribute a where Source

A key/value pair used for building objects

Constructors

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

Instances

class OptArgs a where Source

An operation that accepts optional arguments

Methods

ex :: a -> [Attribute Static] -> a Source

Extend an operation with optional arguments

Instances

OptArgs ReQL 
OptArgs b => OptArgs (a -> b) 

cons :: Expr e => e -> ArgList -> ArgList Source

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
 
MinVal 
MaxVal 

Instances

Functor Bound 
Num a => Num (Bound a) 
Expr a => Expr (Bound a) 

empty :: ReQL Source

An empty object

newtype WireQuery Source

Constructors

WireQuery 

Fields

queryJSON :: Datum
 

Instances

newtype WireBacktrace Source

Constructors

WireBacktrace 

Fields

backtraceJSON :: Datum
 

note :: String -> ReQL -> ReQL Source

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.

(?:=) :: Expr e => Text -> Maybe e -> Attribute a Source

class Arr a where Source

Build arrays of exprs

Methods

arr :: a -> ArgList Source

Instances

Arr () 
Expr a => Arr [a] 
(Expr a, Expr b) => Arr (a, b) 
(Expr a, Expr b, Expr c) => Arr (a, b, c) 
(Expr a, Expr b, Expr c, Expr d) => Arr (a, b, c, d)