module Rel8.Query.Distinct
  ( distinct
  , distinctOn
  , distinctOnBy
  )
where

-- base
import Prelude ()

-- opaleye
import qualified Opaleye.Distinct as Opaleye
import qualified Opaleye.Order as Opaleye

-- rel8
import Rel8.Order ( Order( Order ) )
import Rel8.Query ( Query )
import Rel8.Query.Opaleye ( mapOpaleye )
import Rel8.Table.Eq ( EqTable )
import Rel8.Table.Opaleye ( distinctspec, unpackspec )


-- | Select all distinct rows from a query, removing duplicates.  @distinct q@
-- is equivalent to the SQL statement @SELECT DISTINCT q@.
distinct :: EqTable a => Query a -> Query a
distinct :: Query a -> Query a
distinct = (Select a -> Select a) -> Query a -> Query a
forall a b. (Select a -> Select b) -> Query a -> Query b
mapOpaleye (Distinctspec a a -> Select a -> Select a
forall fields fields'.
Distinctspec fields fields' -> Select fields -> Select fields'
Opaleye.distinctExplicit Distinctspec a a
forall a. Table Expr a => Distinctspec a a
distinctspec)


-- | Select all distinct rows from a query, where rows are equivalent according
-- to a projection. If multiple rows have the same projection, it is
-- unspecified which row will be returned. If this matters, use 'distinctOnBy'.
distinctOn :: EqTable b => (a -> b) -> Query a -> Query a
distinctOn :: (a -> b) -> Query a -> Query a
distinctOn a -> b
proj = (Select a -> Select a) -> Query a -> Query a
forall a b. (Select a -> Select b) -> Query a -> Query b
mapOpaleye (Unpackspec b b -> (a -> b) -> Select a -> Select a
forall b a. Unpackspec b b -> (a -> b) -> Select a -> Select a
Opaleye.distinctOnExplicit Unpackspec b b
forall a. Table Expr a => Unpackspec a a
unpackspec a -> b
proj)


-- | Select all distinct rows from a query, where rows are equivalent according
-- to a projection. If there are multiple rows with the same projection, the
-- first row according to the specified 'Order' will be returned.
distinctOnBy :: EqTable b => (a -> b) -> Order a -> Query a -> Query a
distinctOnBy :: (a -> b) -> Order a -> Query a -> Query a
distinctOnBy a -> b
proj (Order Order a
order) = (Select a -> Select a) -> Query a -> Query a
forall a b. (Select a -> Select b) -> Query a -> Query b
mapOpaleye (Unpackspec b b -> (a -> b) -> Order a -> Select a -> Select a
forall b a.
Unpackspec b b -> (a -> b) -> Order a -> Select a -> Select a
Opaleye.distinctOnByExplicit Unpackspec b b
forall a. Table Expr a => Unpackspec a a
unpackspec a -> b
proj Order a
order)