{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleContexts #-}

-- | @ORDER BY@, @LIMIT@, @OFFSET@ and @DISTINCT ON@

module Opaleye.Order ( -- * Order by
                       orderBy
                     , O.Order
                     -- * Order direction
                     , asc
                     , desc
                     , ascNullsFirst
                     , descNullsLast
                     -- * Limit and offset
                     , limit
                     , offset
                     -- * Distinct on
                     , distinctOnCorrect
                     , distinctOnByCorrect
                     -- * Exact ordering
                     , O.exact
                     -- * Other
                     , PGOrd
                     , SqlOrd
                     -- * Deprecated
                     , distinctOn
                     , distinctOnBy
                     ) where

import qualified Data.Profunctor.Product.Default as D
import qualified Opaleye.Column as C
import qualified Opaleye.Internal.HaskellDB.PrimQuery as HPQ
import qualified Opaleye.Internal.Order as O
import qualified Opaleye.Internal.QueryArr as Q
import qualified Opaleye.Internal.Unpackspec as U
import qualified Opaleye.Select         as S
import qualified Opaleye.SqlTypes as T

-- We can probably disable ConstraintKinds and TypeSynonymInstances
-- when we move to Sql... instead of PG..

{-| Order the rows of a `S.Select` according to the `O.Order`.

@
import Data.Monoid ((\<\>))

\-- Order by the first field ascending.  When first fields are equal
\-- order by second field descending.
example :: 'S.Select' ('Opaleye.Field.Field' 'T.SqlInt4', 'Opaleye.Field.Field' 'T.SqlText')
        -> 'S.Select' ('Opaleye.Field.Field' 'T.SqlInt4', 'Opaleye.Field.Field' 'T.SqlText')
example = 'orderBy' ('asc' fst \<\> 'desc' snd)
@

-}
orderBy :: O.Order a -> S.Select a -> S.Select a
orderBy :: Order a -> Select a -> Select a
orderBy Order a
os Select a
q =
  (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Order a -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
forall a. Order a -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
O.orderByU Order a
os ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
q)

-- | Specify an ascending ordering by the given expression.
--   (Any NULLs appear last)
asc :: SqlOrd b => (a -> C.Column b) -> O.Order a
asc :: (a -> Column b) -> Order a
asc = OrderOp -> (a -> Column b) -> Order a
forall a b. OrderOp -> (a -> Column b) -> Order a
O.order OrderOp :: OrderDirection -> OrderNulls -> OrderOp
HPQ.OrderOp { orderDirection :: OrderDirection
HPQ.orderDirection = OrderDirection
HPQ.OpAsc
                          , orderNulls :: OrderNulls
HPQ.orderNulls     = OrderNulls
HPQ.NullsLast }

-- | Specify an descending ordering by the given expression.
--   (Any NULLs appear first)
desc :: SqlOrd b => (a -> C.Column b) -> O.Order a
desc :: (a -> Column b) -> Order a
desc = OrderOp -> (a -> Column b) -> Order a
forall a b. OrderOp -> (a -> Column b) -> Order a
O.order OrderOp :: OrderDirection -> OrderNulls -> OrderOp
HPQ.OrderOp { orderDirection :: OrderDirection
HPQ.orderDirection = OrderDirection
HPQ.OpDesc
                           , orderNulls :: OrderNulls
HPQ.orderNulls     = OrderNulls
HPQ.NullsFirst }

-- | Specify an ascending ordering by the given expression.
--   (Any NULLs appear first)
ascNullsFirst :: SqlOrd b => (a -> C.Column b) -> O.Order a
ascNullsFirst :: (a -> Column b) -> Order a
ascNullsFirst = OrderOp -> (a -> Column b) -> Order a
forall a b. OrderOp -> (a -> Column b) -> Order a
O.order OrderOp :: OrderDirection -> OrderNulls -> OrderOp
HPQ.OrderOp { orderDirection :: OrderDirection
HPQ.orderDirection = OrderDirection
HPQ.OpAsc
                                    , orderNulls :: OrderNulls
HPQ.orderNulls     = OrderNulls
HPQ.NullsFirst }


-- | Specify an descending ordering by the given expression.
--   (Any NULLs appear last)
descNullsLast :: SqlOrd b => (a -> C.Column b) -> O.Order a
descNullsLast :: (a -> Column b) -> Order a
descNullsLast = OrderOp -> (a -> Column b) -> Order a
forall a b. OrderOp -> (a -> Column b) -> Order a
O.order OrderOp :: OrderDirection -> OrderNulls -> OrderOp
HPQ.OrderOp { orderDirection :: OrderDirection
HPQ.orderDirection = OrderDirection
HPQ.OpDesc
                                    , orderNulls :: OrderNulls
HPQ.orderNulls     = OrderNulls
HPQ.NullsLast }

-- * Limit and offset

{- |
Limit the results of the given 'S.Select' to the given maximum number of
items.

/WARNING:/ If you're planning on using limit/offset together please use
'offset' /before/ you use 'limit', e.g.:

@
limit 10 (offset 50 yourSelect)
@

This is because Opaleye applies @OFFSET@ and @LIMIT@ to the @SELECT@ separately.
The result of the 'S.Select' given above is the following, which will return
10 rows after skipping the first 50 (probably what you want).

@
SELECT * FROM (SELECT * FROM yourTable OFFSET 50) LIMIT 10
@

However, reversing the order of the limit\/offset will result in the
following, which will result in /no rows being returned/ (probably
not what you want).

@
SELECT * FROM (SELECT * FROM yourTable LIMIT 10) OFFSET 50
@
-}
limit :: Int -> S.Select a -> S.Select a
limit :: Int -> Select a -> Select a
limit Int
n Select a
a = (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Int -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
forall a. Int -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
O.limit' Int
n ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
a)

{- |
Offset the results of the given 'S.Select' by the given amount, skipping
that many result rows.

/WARNING:/ Please read the documentation of 'limit' before combining
'offset' with 'limit'.
-}
offset :: Int -> S.Select a -> S.Select a
offset :: Int -> Select a -> Select a
offset Int
n Select a
a = (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Int -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
forall a. Int -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
O.offset' Int
n ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
a)

-- * Distinct on

-- | Keep a row from each set where the given function returns the same result. No
--   ordering is guaranteed. Multiple fields may be distinguished by projecting out
--   tuples of 'Opaleye.Field.Field_'s. Use 'distinctOnBy' to control how the rows
--   are chosen.
distinctOnCorrect :: D.Default U.Unpackspec b b
                  => (a -> b)
                  -> S.Select a
                  -> S.Select a
distinctOnCorrect :: (a -> b) -> Select a -> Select a
distinctOnCorrect a -> b
proj Select a
q = (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Unpackspec b b
-> (a -> b) -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
forall b a.
Unpackspec b b
-> (a -> b) -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
O.distinctOnCorrect Unpackspec b b
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def a -> b
proj ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
q)


-- | Keep the row from each set where the given function returns the same result. The
--   row is chosen according to which comes first by the supplied ordering. However, no
--   output ordering is guaranteed. Mutliple fields may be distinguished by projecting
--   out tuples of 'Opaleye.Field.Field_'s.
distinctOnByCorrect :: D.Default U.Unpackspec b b
                    => (a -> b)
                    -> O.Order a
                    -> S.Select a
                    -> S.Select a
distinctOnByCorrect :: (a -> b) -> Order a -> Select a -> Select a
distinctOnByCorrect a -> b
proj Order a
ord Select a
q = (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Unpackspec b b
-> (a -> b)
-> Order a
-> (a, PrimQuery, Tag)
-> (a, PrimQuery, Tag)
forall b a.
Unpackspec b b
-> (a -> b)
-> Order a
-> (a, PrimQuery, Tag)
-> (a, PrimQuery, Tag)
O.distinctOnByCorrect Unpackspec b b
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def a -> b
proj Order a
ord ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
q)


-- * Other

-- | Typeclass for Postgres types which support ordering operations.
class SqlOrd a where

{-# DEPRECATED PGOrd "Use SqlOrd instead" #-}
type PGOrd = SqlOrd

instance SqlOrd T.SqlBool
instance SqlOrd T.SqlDate
instance SqlOrd T.SqlFloat8
instance SqlOrd T.SqlFloat4
instance SqlOrd T.SqlInt8
instance SqlOrd T.SqlInt4
instance SqlOrd T.SqlInt2
instance SqlOrd T.SqlNumeric
instance SqlOrd T.SqlText
instance SqlOrd T.SqlTime
instance SqlOrd T.SqlTimestamptz
instance SqlOrd T.SqlTimestamp
instance SqlOrd T.SqlCitext
instance SqlOrd T.SqlUuid
instance SqlOrd a => SqlOrd (C.Nullable a)

-- | Use 'distinctOnCorrect' instead.  This version has a bug whereby
-- it returns the whole query if zero columns are chosen to be
-- distinct (it should just return the first row).  Will be deprecated
-- in version 0.8.
distinctOn :: D.Default U.Unpackspec b b => (a -> b) -> S.Select a -> S.Select a
distinctOn :: (a -> b) -> Select a -> Select a
distinctOn a -> b
proj Select a
q = (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Unpackspec b b
-> (a -> b) -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
forall b a.
Unpackspec b b
-> (a -> b) -> (a, PrimQuery, Tag) -> (a, PrimQuery, Tag)
O.distinctOn Unpackspec b b
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def a -> b
proj ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
q)

-- | Use 'distinctOnByCorrect' instead.  This version has a bug
-- whereby it returns the whole query if zero columns are chosen to be
-- distinct (it should just return the first row).  Will be deprecated
-- in version 0.8.
distinctOnBy :: D.Default U.Unpackspec b b => (a -> b) -> O.Order a
             -> S.Select a -> S.Select a
distinctOnBy :: (a -> b) -> Order a -> Select a -> Select a
distinctOnBy a -> b
proj Order a
ord Select a
q = (((), Tag) -> (a, PrimQuery, Tag)) -> Select a
forall a b. ((a, Tag) -> (b, PrimQuery, Tag)) -> QueryArr a b
Q.productQueryArr (Unpackspec b b
-> (a -> b)
-> Order a
-> (a, PrimQuery, Tag)
-> (a, PrimQuery, Tag)
forall b a.
Unpackspec b b
-> (a -> b)
-> Order a
-> (a, PrimQuery, Tag)
-> (a, PrimQuery, Tag)
O.distinctOnBy Unpackspec b b
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def a -> b
proj Order a
ord ((a, PrimQuery, Tag) -> (a, PrimQuery, Tag))
-> (((), Tag) -> (a, PrimQuery, Tag))
-> ((), Tag)
-> (a, PrimQuery, Tag)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Select a -> ((), Tag) -> (a, PrimQuery, Tag)
forall a b. QueryArr a b -> (a, Tag) -> (b, PrimQuery, Tag)
Q.runSimpleQueryArr Select a
q)