{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-| This module contains RethinkDB Expressions which are used to build queries. -} module Avers.Storage.Expressions where import Prelude hiding (lookup) import Data.Text (Text) import Database.RethinkDB as R -- | The primary key in all our documents is the default "id". primaryKeyField :: Text primaryKeyField = "id" -- | Expression which represents the primary key field. primaryKeyFieldE :: Exp Text primaryKeyFieldE = lift primaryKeyField -- | Expression which represents the value of a field inside of an Object. objectFieldE :: (IsDatum a) => Text -> Exp Object -> Exp a objectFieldE field obj = GetField (lift field) obj -- | True if the object field matches the given value. objectFieldEqE :: (ToDatum a) => Text -> a -> Exp Object -> Exp Bool objectFieldEqE field value obj = Eq (objectFieldE field obj :: Exp Datum) (lift $ toDatum value) -- | True if the object's primary key matches the given string. primaryKeyEqE :: Text -> Exp Object -> Exp Bool primaryKeyEqE = objectFieldEqE primaryKeyField -- | Take the first item out of a sequence. headE :: (IsSequence a, IsDatum r) => Exp a -> Exp r headE = Nth 0