{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies    #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Aws.DynamoDb.Commands.Query
-- Copyright   :  Soostone Inc
-- License     :  BSD3
--
-- Maintainer  :  Ozgun Ataman <ozgun.ataman@soostone.com>
-- Stability   :  experimental
--
-- Implementation of Amazon DynamoDb Query command.
--
-- See: @http:\/\/docs.aws.amazon.com\/amazondynamodb\/latest\/APIReference\/API_Query.html@
----------------------------------------------------------------------------

module Aws.DynamoDb.Commands.Query
    ( Query (..)
    , Slice (..)
    , query
    , QueryResponse (..)
    ) where

-------------------------------------------------------------------------------
import           Control.Applicative
import           Data.Aeson
import           Data.Default
import           Data.Maybe
import qualified Data.Text           as T
import           Data.Typeable
import qualified Data.Vector         as V
-------------------------------------------------------------------------------
import           Aws.Core
import           Aws.DynamoDb.Core
-------------------------------------------------------------------------------


-------------------------------------------------------------------------------
-- | 'Slice' is the primary constraint in a 'Query' command, per AWS
-- requirements.
--
-- All 'Query' commands must specify a hash attribute via 'DEq' and
-- optionally provide a secondary range attribute.
data Slice = Slice {
      Slice -> Attribute
sliceHash :: Attribute
    -- ^ Hash value of the primary key or index being used
    , Slice -> Maybe Condition
sliceCond :: Maybe Condition
    -- ^ An optional condition specified on the range component, if
    -- present, of the primary key or index being used.
    }  deriving (Slice -> Slice -> Bool
(Slice -> Slice -> Bool) -> (Slice -> Slice -> Bool) -> Eq Slice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Slice -> Slice -> Bool
$c/= :: Slice -> Slice -> Bool
== :: Slice -> Slice -> Bool
$c== :: Slice -> Slice -> Bool
Eq,Int -> Slice -> ShowS
[Slice] -> ShowS
Slice -> String
(Int -> Slice -> ShowS)
-> (Slice -> String) -> ([Slice] -> ShowS) -> Show Slice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Slice] -> ShowS
$cshowList :: [Slice] -> ShowS
show :: Slice -> String
$cshow :: Slice -> String
showsPrec :: Int -> Slice -> ShowS
$cshowsPrec :: Int -> Slice -> ShowS
Show,ReadPrec [Slice]
ReadPrec Slice
Int -> ReadS Slice
ReadS [Slice]
(Int -> ReadS Slice)
-> ReadS [Slice]
-> ReadPrec Slice
-> ReadPrec [Slice]
-> Read Slice
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Slice]
$creadListPrec :: ReadPrec [Slice]
readPrec :: ReadPrec Slice
$creadPrec :: ReadPrec Slice
readList :: ReadS [Slice]
$creadList :: ReadS [Slice]
readsPrec :: Int -> ReadS Slice
$creadsPrec :: Int -> ReadS Slice
Read,Eq Slice
Eq Slice
-> (Slice -> Slice -> Ordering)
-> (Slice -> Slice -> Bool)
-> (Slice -> Slice -> Bool)
-> (Slice -> Slice -> Bool)
-> (Slice -> Slice -> Bool)
-> (Slice -> Slice -> Slice)
-> (Slice -> Slice -> Slice)
-> Ord Slice
Slice -> Slice -> Bool
Slice -> Slice -> Ordering
Slice -> Slice -> Slice
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Slice -> Slice -> Slice
$cmin :: Slice -> Slice -> Slice
max :: Slice -> Slice -> Slice
$cmax :: Slice -> Slice -> Slice
>= :: Slice -> Slice -> Bool
$c>= :: Slice -> Slice -> Bool
> :: Slice -> Slice -> Bool
$c> :: Slice -> Slice -> Bool
<= :: Slice -> Slice -> Bool
$c<= :: Slice -> Slice -> Bool
< :: Slice -> Slice -> Bool
$c< :: Slice -> Slice -> Bool
compare :: Slice -> Slice -> Ordering
$ccompare :: Slice -> Slice -> Ordering
$cp1Ord :: Eq Slice
Ord,Typeable)



-- | A Query command that uses primary keys for an expedient scan.
data Query = Query {
      Query -> Text
qTableName     :: T.Text
    -- ^ Required.
    , Query -> Slice
qKeyConditions :: Slice
    -- ^ Required. Hash or hash-range main condition.
    , Query -> Conditions
qFilter        :: Conditions
    -- ^ Whether to filter results before returning to client
    , Query -> Maybe [Attribute]
qStartKey      :: Maybe [Attribute]
    -- ^ Exclusive start key to resume a previous query.
    , Query -> Maybe Int
qLimit         :: Maybe Int
    -- ^ Whether to limit result set size
    , Query -> Bool
qForwardScan   :: Bool
    -- ^ Set to False for descending results
    , Query -> QuerySelect
qSelect        :: QuerySelect
    -- ^ What to return from 'Query'
    , Query -> ReturnConsumption
qRetCons       :: ReturnConsumption
    , Query -> Maybe Text
qIndex         :: Maybe T.Text
    -- ^ Whether to use a secondary/global index
    , Query -> Bool
qConsistent    :: Bool
    } deriving (Query -> Query -> Bool
(Query -> Query -> Bool) -> (Query -> Query -> Bool) -> Eq Query
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Query -> Query -> Bool
$c/= :: Query -> Query -> Bool
== :: Query -> Query -> Bool
$c== :: Query -> Query -> Bool
Eq,Int -> Query -> ShowS
[Query] -> ShowS
Query -> String
(Int -> Query -> ShowS)
-> (Query -> String) -> ([Query] -> ShowS) -> Show Query
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Query] -> ShowS
$cshowList :: [Query] -> ShowS
show :: Query -> String
$cshow :: Query -> String
showsPrec :: Int -> Query -> ShowS
$cshowsPrec :: Int -> Query -> ShowS
Show,ReadPrec [Query]
ReadPrec Query
Int -> ReadS Query
ReadS [Query]
(Int -> ReadS Query)
-> ReadS [Query]
-> ReadPrec Query
-> ReadPrec [Query]
-> Read Query
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Query]
$creadListPrec :: ReadPrec [Query]
readPrec :: ReadPrec Query
$creadPrec :: ReadPrec Query
readList :: ReadS [Query]
$creadList :: ReadS [Query]
readsPrec :: Int -> ReadS Query
$creadsPrec :: Int -> ReadS Query
Read,Eq Query
Eq Query
-> (Query -> Query -> Ordering)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Bool)
-> (Query -> Query -> Query)
-> (Query -> Query -> Query)
-> Ord Query
Query -> Query -> Bool
Query -> Query -> Ordering
Query -> Query -> Query
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Query -> Query -> Query
$cmin :: Query -> Query -> Query
max :: Query -> Query -> Query
$cmax :: Query -> Query -> Query
>= :: Query -> Query -> Bool
$c>= :: Query -> Query -> Bool
> :: Query -> Query -> Bool
$c> :: Query -> Query -> Bool
<= :: Query -> Query -> Bool
$c<= :: Query -> Query -> Bool
< :: Query -> Query -> Bool
$c< :: Query -> Query -> Bool
compare :: Query -> Query -> Ordering
$ccompare :: Query -> Query -> Ordering
$cp1Ord :: Eq Query
Ord,Typeable)


-------------------------------------------------------------------------------
instance ToJSON Query where
    toJSON :: Query -> Value
toJSON Query{Bool
Maybe Int
Maybe [Attribute]
Maybe Text
Text
QuerySelect
ReturnConsumption
Conditions
Slice
qConsistent :: Bool
qIndex :: Maybe Text
qRetCons :: ReturnConsumption
qSelect :: QuerySelect
qForwardScan :: Bool
qLimit :: Maybe Int
qStartKey :: Maybe [Attribute]
qFilter :: Conditions
qKeyConditions :: Slice
qTableName :: Text
qConsistent :: Query -> Bool
qIndex :: Query -> Maybe Text
qRetCons :: Query -> ReturnConsumption
qSelect :: Query -> QuerySelect
qForwardScan :: Query -> Bool
qLimit :: Query -> Maybe Int
qStartKey :: Query -> Maybe [Attribute]
qFilter :: Query -> Conditions
qKeyConditions :: Query -> Slice
qTableName :: Query -> Text
..} = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
      [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes
        [ ((Key
"ExclusiveStartKey" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ) (Value -> Pair) -> ([Attribute] -> Value) -> [Attribute] -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Attribute] -> Value
attributesJson) ([Attribute] -> Pair) -> Maybe [Attribute] -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Attribute]
qStartKey
        , (Key
"Limit" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ) (Int -> Pair) -> Maybe Int -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
qLimit
        , (Key
"IndexName" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ) (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Text
qIndex
        ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
      Text -> Conditions -> [Pair]
conditionsJson Text
"QueryFilter" Conditions
qFilter [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
      QuerySelect -> [Pair]
forall t. KeyValue t => QuerySelect -> [t]
querySelectJson QuerySelect
qSelect [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
      [ Key
"ScanIndexForward" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
qForwardScan
      , Key
"TableName"Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
qTableName
      , Key
"KeyConditions" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Slice -> Value
sliceJson Slice
qKeyConditions
      , Key
"ReturnConsumedCapacity" Key -> ReturnConsumption -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= ReturnConsumption
qRetCons
      , Key
"ConsistentRead" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Bool
qConsistent
      ]


-------------------------------------------------------------------------------
-- | Construct a minimal 'Query' request.
query
    :: T.Text
    -- ^ Table name
    -> Slice
    -- ^ Primary key slice for query
    -> Query
query :: Text -> Slice -> Query
query Text
tn Slice
sl = Text
-> Slice
-> Conditions
-> Maybe [Attribute]
-> Maybe Int
-> Bool
-> QuerySelect
-> ReturnConsumption
-> Maybe Text
-> Bool
-> Query
Query Text
tn Slice
sl Conditions
forall a. Default a => a
def Maybe [Attribute]
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing Bool
True QuerySelect
forall a. Default a => a
def ReturnConsumption
forall a. Default a => a
def Maybe Text
forall a. Maybe a
Nothing Bool
False


-- | Response to a 'Query' query.
data QueryResponse = QueryResponse {
      QueryResponse -> Vector Item
qrItems    :: V.Vector Item
    , QueryResponse -> Maybe [Attribute]
qrLastKey  :: Maybe [Attribute]
    , QueryResponse -> Int
qrCount    :: Int
    , QueryResponse -> Int
qrScanned  :: Int
    , QueryResponse -> Maybe ConsumedCapacity
qrConsumed :: Maybe ConsumedCapacity
    } deriving (QueryResponse -> QueryResponse -> Bool
(QueryResponse -> QueryResponse -> Bool)
-> (QueryResponse -> QueryResponse -> Bool) -> Eq QueryResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryResponse -> QueryResponse -> Bool
$c/= :: QueryResponse -> QueryResponse -> Bool
== :: QueryResponse -> QueryResponse -> Bool
$c== :: QueryResponse -> QueryResponse -> Bool
Eq,Int -> QueryResponse -> ShowS
[QueryResponse] -> ShowS
QueryResponse -> String
(Int -> QueryResponse -> ShowS)
-> (QueryResponse -> String)
-> ([QueryResponse] -> ShowS)
-> Show QueryResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryResponse] -> ShowS
$cshowList :: [QueryResponse] -> ShowS
show :: QueryResponse -> String
$cshow :: QueryResponse -> String
showsPrec :: Int -> QueryResponse -> ShowS
$cshowsPrec :: Int -> QueryResponse -> ShowS
Show,ReadPrec [QueryResponse]
ReadPrec QueryResponse
Int -> ReadS QueryResponse
ReadS [QueryResponse]
(Int -> ReadS QueryResponse)
-> ReadS [QueryResponse]
-> ReadPrec QueryResponse
-> ReadPrec [QueryResponse]
-> Read QueryResponse
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryResponse]
$creadListPrec :: ReadPrec [QueryResponse]
readPrec :: ReadPrec QueryResponse
$creadPrec :: ReadPrec QueryResponse
readList :: ReadS [QueryResponse]
$creadList :: ReadS [QueryResponse]
readsPrec :: Int -> ReadS QueryResponse
$creadsPrec :: Int -> ReadS QueryResponse
Read,Eq QueryResponse
Eq QueryResponse
-> (QueryResponse -> QueryResponse -> Ordering)
-> (QueryResponse -> QueryResponse -> Bool)
-> (QueryResponse -> QueryResponse -> Bool)
-> (QueryResponse -> QueryResponse -> Bool)
-> (QueryResponse -> QueryResponse -> Bool)
-> (QueryResponse -> QueryResponse -> QueryResponse)
-> (QueryResponse -> QueryResponse -> QueryResponse)
-> Ord QueryResponse
QueryResponse -> QueryResponse -> Bool
QueryResponse -> QueryResponse -> Ordering
QueryResponse -> QueryResponse -> QueryResponse
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QueryResponse -> QueryResponse -> QueryResponse
$cmin :: QueryResponse -> QueryResponse -> QueryResponse
max :: QueryResponse -> QueryResponse -> QueryResponse
$cmax :: QueryResponse -> QueryResponse -> QueryResponse
>= :: QueryResponse -> QueryResponse -> Bool
$c>= :: QueryResponse -> QueryResponse -> Bool
> :: QueryResponse -> QueryResponse -> Bool
$c> :: QueryResponse -> QueryResponse -> Bool
<= :: QueryResponse -> QueryResponse -> Bool
$c<= :: QueryResponse -> QueryResponse -> Bool
< :: QueryResponse -> QueryResponse -> Bool
$c< :: QueryResponse -> QueryResponse -> Bool
compare :: QueryResponse -> QueryResponse -> Ordering
$ccompare :: QueryResponse -> QueryResponse -> Ordering
$cp1Ord :: Eq QueryResponse
Ord)


instance FromJSON QueryResponse where
    parseJSON :: Value -> Parser QueryResponse
parseJSON (Object Object
v) = Vector Item
-> Maybe [Attribute]
-> Int
-> Int
-> Maybe ConsumedCapacity
-> QueryResponse
QueryResponse
        (Vector Item
 -> Maybe [Attribute]
 -> Int
 -> Int
 -> Maybe ConsumedCapacity
 -> QueryResponse)
-> Parser (Vector Item)
-> Parser
     (Maybe [Attribute]
      -> Int -> Int -> Maybe ConsumedCapacity -> QueryResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser (Maybe (Vector Item))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:?  Key
"Items" Parser (Maybe (Vector Item)) -> Vector Item -> Parser (Vector Item)
forall a. Parser (Maybe a) -> a -> Parser a
.!= Vector Item
forall a. Vector a
V.empty
        Parser
  (Maybe [Attribute]
   -> Int -> Int -> Maybe ConsumedCapacity -> QueryResponse)
-> Parser (Maybe [Attribute])
-> Parser (Int -> Int -> Maybe ConsumedCapacity -> QueryResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((do Value
o <- Object
v Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"LastEvaluatedKey"
                 [Attribute] -> Maybe [Attribute]
forall a. a -> Maybe a
Just ([Attribute] -> Maybe [Attribute])
-> Parser [Attribute] -> Parser (Maybe [Attribute])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [Attribute]
parseAttributeJson Value
o)
             Parser (Maybe [Attribute])
-> Parser (Maybe [Attribute]) -> Parser (Maybe [Attribute])
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe [Attribute] -> Parser (Maybe [Attribute])
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe [Attribute]
forall a. Maybe a
Nothing)
        Parser (Int -> Int -> Maybe ConsumedCapacity -> QueryResponse)
-> Parser Int
-> Parser (Int -> Maybe ConsumedCapacity -> QueryResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.:  Key
"Count"
        Parser (Int -> Maybe ConsumedCapacity -> QueryResponse)
-> Parser Int -> Parser (Maybe ConsumedCapacity -> QueryResponse)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.:  Key
"ScannedCount"
        Parser (Maybe ConsumedCapacity -> QueryResponse)
-> Parser (Maybe ConsumedCapacity) -> Parser QueryResponse
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe ConsumedCapacity)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"ConsumedCapacity"
    parseJSON Value
_ = String -> Parser QueryResponse
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"QueryResponse must be an object."


instance Transaction Query QueryResponse


instance SignQuery Query where
    type ServiceConfiguration Query = DdbConfiguration
    signQuery :: Query
-> ServiceConfiguration Query queryType
-> SignatureData
-> SignedQuery
signQuery Query
gi = ByteString
-> Query
-> DdbConfiguration queryType
-> SignatureData
-> SignedQuery
forall a qt.
ToJSON a =>
ByteString
-> a -> DdbConfiguration qt -> SignatureData -> SignedQuery
ddbSignQuery ByteString
"Query" Query
gi


instance ResponseConsumer r QueryResponse where
    type ResponseMetadata QueryResponse = DdbResponse
    responseConsumer :: Request
-> r
-> IORef (ResponseMetadata QueryResponse)
-> HTTPResponseConsumer QueryResponse
responseConsumer Request
_ r
_ IORef (ResponseMetadata QueryResponse)
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp
        = IORef DdbResponse -> HTTPResponseConsumer QueryResponse
forall a. FromJSON a => IORef DdbResponse -> HTTPResponseConsumer a
ddbResponseConsumer IORef (ResponseMetadata QueryResponse)
IORef DdbResponse
ref Response (ConduitM () ByteString (ResourceT IO) ())
resp


instance AsMemoryResponse QueryResponse where
    type MemoryResponse QueryResponse = QueryResponse
    loadToMemory :: QueryResponse -> ResourceT IO (MemoryResponse QueryResponse)
loadToMemory = QueryResponse -> ResourceT IO (MemoryResponse QueryResponse)
forall (m :: * -> *) a. Monad m => a -> m a
return


instance ListResponse QueryResponse Item where
    listResponse :: QueryResponse -> [Item]
listResponse = Vector Item -> [Item]
forall a. Vector a -> [a]
V.toList (Vector Item -> [Item])
-> (QueryResponse -> Vector Item) -> QueryResponse -> [Item]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueryResponse -> Vector Item
qrItems


instance IteratedTransaction Query QueryResponse where
    nextIteratedRequest :: Query -> QueryResponse -> Maybe Query
nextIteratedRequest Query
request QueryResponse
response = case QueryResponse -> Maybe [Attribute]
qrLastKey QueryResponse
response of
        Maybe [Attribute]
Nothing -> Maybe Query
forall a. Maybe a
Nothing
        Maybe [Attribute]
key -> Query -> Maybe Query
forall a. a -> Maybe a
Just Query
request { qStartKey :: Maybe [Attribute]
qStartKey = Maybe [Attribute]
key }


sliceJson :: Slice -> Value
sliceJson :: Slice -> Value
sliceJson Slice{Maybe Condition
Attribute
sliceCond :: Maybe Condition
sliceHash :: Attribute
sliceCond :: Slice -> Maybe Condition
sliceHash :: Slice -> Attribute
..} = [Pair] -> Value
object ((Condition -> Pair) -> [Condition] -> [Pair]
forall a b. (a -> b) -> [a] -> [b]
map Condition -> Pair
conditionJson [Condition]
cs)
    where
      cs :: [Condition]
cs = [Condition]
-> (Condition -> [Condition]) -> Maybe Condition -> [Condition]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] Condition -> [Condition]
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Condition
sliceCond [Condition] -> [Condition] -> [Condition]
forall a. [a] -> [a] -> [a]
++ [Condition
hashCond]
      hashCond :: Condition
hashCond = Text -> CondOp -> Condition
Condition (Attribute -> Text
attrName Attribute
sliceHash) (DValue -> CondOp
DEq (Attribute -> DValue
attrVal Attribute
sliceHash))