{-# LANGUAGE Arrows #-}
{-# LANGUAGE FlexibleContexts #-}
module Opaleye.Operators (module Opaleye.Operators,
                          (O..&&)) where
import qualified Control.Arrow as A
import qualified Data.Foldable as F
import           Opaleye.Internal.Column (Column(Column), unsafeCase_,
                                          unsafeIfThenElse, unsafeGt)
import qualified Opaleye.Internal.Column as C
import           Opaleye.Internal.QueryArr (QueryArr(QueryArr), Query)
import qualified Opaleye.Internal.PrimQuery as PQ
import qualified Opaleye.Internal.Operators as O
import           Opaleye.Internal.Helpers   ((.:))
import qualified Opaleye.Order as Ord
import qualified Opaleye.PGTypes as T
import qualified Opaleye.Column   as Column
import qualified Opaleye.Distinct as Distinct
import qualified Opaleye.Join     as Join
import qualified Opaleye.Internal.HaskellDB.PrimQuery as HPQ
import qualified Data.Profunctor.Product.Default as D
restrict :: QueryArr (Column T.PGBool) ()
restrict = QueryArr f where
  f (Column predicate, primQ, t0) = ((), PQ.restrict predicate primQ, t0)
keepWhen :: (a -> Column T.PGBool) -> QueryArr a a
keepWhen p = proc a -> do
  restrict  -< p a
  A.returnA -< a
infix 4 .==
(.==) :: Column a -> Column a -> Column T.PGBool
(.==) = C.binOp (HPQ.:==)
infix 4 ./=
(./=) :: Column a -> Column a -> Column T.PGBool
(./=) = C.binOp (HPQ.:<>)
infix 4 .===
(.===) :: D.Default O.EqPP columns columns => columns -> columns -> Column T.PGBool
(.===) = (O..==)
infix 4 ./==
(./==) :: D.Default O.EqPP columns columns => columns -> columns -> Column T.PGBool
(./==) = Opaleye.Operators.not .: (O..==)
infix 4 .>
(.>) :: Ord.PGOrd a => Column a -> Column a -> Column T.PGBool
(.>) = unsafeGt
infix 4 .<
(.<) :: Ord.PGOrd a => Column a -> Column a -> Column T.PGBool
(.<) = C.binOp (HPQ.:<)
infix 4 .<=
(.<=) :: Ord.PGOrd a => Column a -> Column a -> Column T.PGBool
(.<=) = C.binOp (HPQ.:<=)
infix 4 .>=
(.>=) :: Ord.PGOrd a => Column a -> Column a -> Column T.PGBool
(.>=) = C.binOp (HPQ.:>=)
quot_ :: C.PGIntegral a => Column a -> Column a -> Column a
quot_ = C.binOp (HPQ.:/)
rem_ :: C.PGIntegral a => Column a -> Column a -> Column a
rem_ = C.binOp HPQ.OpMod
case_ :: [(Column T.PGBool, Column a)] -> Column a -> Column a
case_ = unsafeCase_
ifThenElse :: Column T.PGBool -> Column a -> Column a -> Column a
ifThenElse = unsafeIfThenElse
infixr 2 .||
(.||) :: Column T.PGBool -> Column T.PGBool -> Column T.PGBool
(.||) = C.binOp HPQ.OpOr
not :: Column T.PGBool -> Column T.PGBool
not = C.unOp HPQ.OpNot
(.++) :: Column T.PGText -> Column T.PGText -> Column T.PGText
(.++) = C.binOp (HPQ.:||)
lower :: Column T.PGText -> Column T.PGText
lower = C.unOp HPQ.OpLower
upper :: Column T.PGText -> Column T.PGText
upper = C.unOp HPQ.OpUpper
like :: Column T.PGText -> Column T.PGText -> Column T.PGBool
like = C.binOp HPQ.OpLike
charLength :: C.PGString a => Column a -> Column Int
charLength (Column e) = Column (HPQ.FunExpr "char_length" [e])
ors :: F.Foldable f => f (Column T.PGBool) -> Column T.PGBool
ors = F.foldl' (.||) (T.pgBool False)
in_ :: (Functor f, F.Foldable f) => f (Column a) -> Column a -> Column T.PGBool
in_ hs w = ors . fmap (w .==) $ hs
inQuery :: D.Default O.EqPP columns columns
        => columns -> QueryArr () columns -> Query (Column T.PGBool)
inQuery c q = qj'
  where 
        
        q' = A.arr (const 1)
             A.<<< keepWhen (c .===)
             A.<<< q
        
        
        
        qj :: Query (Column T.PGInt4, Column (C.Nullable T.PGInt4))
        qj = Join.leftJoin (A.arr (const 1))
                           (Distinct.distinct q')
                           (uncurry (.==))
                          
        
        qj' :: Query (Column T.PGBool)
        qj' = A.arr (Opaleye.Operators.not
                     . Column.isNull
                     . snd)
              A.<<< qj
timestamptzAtTimeZone :: Column T.PGTimestamptz
                      -> Column T.PGText
                      -> Column T.PGTimestamp
timestamptzAtTimeZone = C.binOp HPQ.OpAtTimeZone
emptyArray :: T.IsSqlType a => Column (T.PGArray a)
emptyArray = T.pgArray id []
arrayPrepend :: Column a -> Column (T.PGArray a) -> Column (T.PGArray a)
arrayPrepend (Column e) (Column es) = Column (HPQ.FunExpr "array_prepend" [e, es])
singletonArray :: T.IsSqlType a => Column a -> Column (T.PGArray a)
singletonArray x = arrayPrepend x emptyArray
class PGIsJson a
instance PGIsJson T.PGJson
instance PGIsJson T.PGJsonb
class PGJsonIndex a
instance PGJsonIndex T.PGInt4
instance PGJsonIndex T.PGInt8
instance PGJsonIndex T.PGText
infixl 8 .->
(.->) :: (PGIsJson a, PGJsonIndex k)
      => Column (C.Nullable a) 
      -> Column k 
      -> Column (C.Nullable a)
(.->) = C.binOp (HPQ.:->)
infixl 8 .->>
(.->>) :: (PGIsJson a, PGJsonIndex k)
       => Column (C.Nullable a) 
       -> Column k 
       -> Column (C.Nullable T.PGText)
(.->>) = C.binOp (HPQ.:->>)
infixl 8 .#>
(.#>) :: (PGIsJson a)
      => Column (C.Nullable a) 
      -> Column (T.PGArray T.PGText) 
      -> Column (C.Nullable a)
(.#>) = C.binOp (HPQ.:#>)
infixl 8 .#>>
(.#>>) :: (PGIsJson a)
       => Column (C.Nullable a) 
       -> Column (T.PGArray T.PGText) 
       -> Column (C.Nullable T.PGText)
(.#>>) = C.binOp (HPQ.:#>>)
infix 4 .@>
(.@>) :: Column T.PGJsonb -> Column T.PGJsonb -> Column T.PGBool
(.@>) = C.binOp (HPQ.:@>)
infix 4 .<@
(.<@) :: Column T.PGJsonb -> Column T.PGJsonb -> Column T.PGBool
(.<@) = C.binOp (HPQ.:<@)
infix 4 .?
(.?) :: Column T.PGJsonb -> Column T.PGText -> Column T.PGBool
(.?) = C.binOp (HPQ.:?)
infix 4 .?|
(.?|) :: Column T.PGJsonb -> Column (T.PGArray T.PGText) -> Column T.PGBool
(.?|) = C.binOp (HPQ.:?|)
infix 4 .?&
(.?&) :: Column T.PGJsonb -> Column (T.PGArray T.PGText) -> Column T.PGBool
(.?&) = C.binOp (HPQ.:?&)
doubleOfInt :: Column T.PGInt4 -> Column T.PGFloat8
doubleOfInt (Column e) = Column (HPQ.CastExpr "float8" e)