{-# LANGUAGE GeneralizedNewtypeDeriving #-}

{- |
Copyright : Flipstone Technology Partners 2023
License   : MIT
Stability : Stable

@since 1.0.0.0
-}
module Orville.PostgreSQL.Expr.OffsetExpr
  ( OffsetExpr
  , offsetExpr
  )
where

import qualified Orville.PostgreSQL.Raw.RawSql as RawSql
import qualified Orville.PostgreSQL.Raw.SqlValue as SqlValue

{- |
Type to represent a SQL offset expression. E.G.

> OFFSET 10

'OffsetExpr' provides a 'RawSql.SqlExpression' instance. See
'RawSql.unsafeSqlExpression' for how to construct a value with your own custom
SQL.

@since 1.0.0.0
-}
newtype OffsetExpr
  = OffsetExpr RawSql.RawSql
  deriving
    ( -- | @since 1.0.0.0
      RawSql -> OffsetExpr
OffsetExpr -> RawSql
(OffsetExpr -> RawSql)
-> (RawSql -> OffsetExpr) -> SqlExpression OffsetExpr
forall a. (a -> RawSql) -> (RawSql -> a) -> SqlExpression a
$ctoRawSql :: OffsetExpr -> RawSql
toRawSql :: OffsetExpr -> RawSql
$cunsafeFromRawSql :: RawSql -> OffsetExpr
unsafeFromRawSql :: RawSql -> OffsetExpr
RawSql.SqlExpression
    )

{- | Create an 'OffsetExpr' for the given 'Int'. This ensures that the input value is used
as a parameter in the generated SQL.

@since 1.0.0.0
-}
offsetExpr :: Int -> OffsetExpr
offsetExpr :: Int -> OffsetExpr
offsetExpr Int
offsetValue =
  RawSql -> OffsetExpr
OffsetExpr (RawSql -> OffsetExpr) -> RawSql -> OffsetExpr
forall a b. (a -> b) -> a -> b
$
    String -> RawSql
RawSql.fromString String
"OFFSET " RawSql -> RawSql -> RawSql
forall a. Semigroup a => a -> a -> a
<> SqlValue -> RawSql
RawSql.parameter (Int -> SqlValue
SqlValue.fromInt Int
offsetValue)