{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
#endif
{-# LANGUAGE DataKinds           #-}
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE GADTs               #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Database.DynamoDB.Filter (
      
      FilterCondition(Not)
      
    , (&&.), (||.)
      
    , (==.), (/=.), (>=.), (>.), (<=.), (<.)
      
    , attrExists, attrMissing, beginsWith, contains, setContains, valIn, between
    , size
) where
import           Control.Lens               ((.~))
import           Data.Function              ((&))
import           Data.Maybe                 (fromMaybe)
import qualified Data.Set                   as Set
import qualified Data.Text                  as T
import qualified Network.AWS.DynamoDB.Types as D
import           Database.DynamoDB.Internal
import           Database.DynamoDB.Types
between :: (Ord typ, InCollection col tbl 'FullPath, DynamoScalar v typ)
  => Column typ ctyp col -> (typ, typ) -> FilterCondition tbl
between col (a, b) = Between (nameGen col) (dScalarEncode a) (dScalarEncode b)
valIn :: (InCollection col tbl 'FullPath, DynamoScalar v typ)
  => Column typ ctyp col -> [typ] -> FilterCondition tbl
valIn col lst = In (nameGen col) (map dScalarEncode lst)
attrExists :: (InCollection col tbl 'FullPath) => Column typ 'TypColumn col -> FilterCondition tbl
attrExists col = AttrExists (nameGen col)
attrMissing :: (InCollection col tbl 'FullPath) => Column typ 'TypColumn col -> FilterCondition tbl
attrMissing col = AttrMissing (nameGen col)
beginsWith :: (InCollection col tbl 'FullPath, IsText typ)
  => Column typ 'TypColumn col -> T.Text -> FilterCondition tbl
beginsWith col txt = BeginsWith (nameGen col) (dScalarEncode txt)
contains :: (InCollection col tbl 'FullPath, IsText typ)
  => Column typ 'TypColumn col -> T.Text -> FilterCondition tbl
contains col txt = Contains (nameGen col) (dScalarEncode txt)
setContains :: (InCollection col tbl 'FullPath, DynamoScalar v a)
  => Column (Set.Set a) 'TypColumn col -> a -> FilterCondition tbl
setContains col txt = Contains (nameGen col) (dScalarEncode txt)
size :: Column typ 'TypColumn col -> Column Int 'TypSize col
size (Column lst) = Size lst
dcomp :: (InCollection col tbl 'FullPath, DynamoEncodable typ)
  => T.Text -> Column typ ctyp col -> typ -> FilterCondition tbl
dcomp op col val = Comparison (nameGen col) op encval
  where
    
    encval = fromMaybe (D.attributeValue & D.avNULL .~ Just True) (dEncode val)
(&&.) :: FilterCondition t -> FilterCondition t -> FilterCondition t
(&&.) = And
infixr 3 &&.
(||.) :: FilterCondition t -> FilterCondition t -> FilterCondition t
(||.) = Or
infixr 3 ||.
(==.) :: (InCollection col tbl 'FullPath, DynamoEncodable typ)
  => Column typ ctyp col -> typ -> FilterCondition tbl
(==.) col val =
  case dEncode val of
    
    Nothing -> AttrMissing (nameGen col)
    
    Just encval | dIsMissing val -> AttrMissing (nameGen col) ||. Comparison (nameGen col) "=" encval
                | otherwise -> Comparison (nameGen col) "=" encval
infix 4 ==.
(/=.) :: (InCollection col tbl 'FullPath, DynamoEncodable typ)
        => Column typ ctyp col -> typ -> FilterCondition tbl
(/=.) col val = Not (col ==. val)
infix 4 /=.
(<=.) :: (InCollection col tbl 'FullPath, DynamoEncodable typ, Ord typ)
        => Column typ ctyp col -> typ -> FilterCondition tbl
(<=.) = dcomp "<="
infix 4 <=.
(<.) :: (InCollection col tbl 'FullPath, DynamoEncodable typ, Ord typ)
        => Column typ ctyp col -> typ -> FilterCondition tbl
(<.) = dcomp "<"
infix 4 <.
(>.) :: (InCollection col tbl 'FullPath, DynamoEncodable typ, Ord typ)
        => Column typ ctyp col -> typ -> FilterCondition tbl
(>.) = dcomp ">"
infix 4 >.
(>=.) :: (InCollection col tbl 'FullPath, DynamoEncodable typ, Ord typ)
        => Column typ ctyp col -> typ -> FilterCondition tbl
(>=.) = dcomp ">="
infix 4 >=.