{-# LANGUAGE GeneralizedNewtypeDeriving #-}

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

@since 1.0.0.0
-}
module Orville.PostgreSQL.Expr.Internal.Name.CursorName
  ( CursorName
  , cursorName
  )
where

import Orville.PostgreSQL.Expr.Internal.Name.Identifier (Identifier, IdentifierExpression, identifier)
import qualified Orville.PostgreSQL.Raw.RawSql as RawSql

{- |
Type to represent a SQL cursor name. 'CursorName' values constructed
via the 'cursorName' function will be properly escaped as part of the
generated SQL. E.G.

> "some_cursor_name"

'CursorName' 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 CursorName
  = CursorName Identifier
  deriving
    ( -- | @since 1.0.0.0
      RawSql -> CursorName
CursorName -> RawSql
(CursorName -> RawSql)
-> (RawSql -> CursorName) -> SqlExpression CursorName
forall a. (a -> RawSql) -> (RawSql -> a) -> SqlExpression a
$ctoRawSql :: CursorName -> RawSql
toRawSql :: CursorName -> RawSql
$cunsafeFromRawSql :: RawSql -> CursorName
unsafeFromRawSql :: RawSql -> CursorName
RawSql.SqlExpression
    , -- | @since 1.0.0.0
      Identifier -> CursorName
CursorName -> Identifier
(CursorName -> Identifier)
-> (Identifier -> CursorName) -> IdentifierExpression CursorName
forall name.
(name -> Identifier)
-> (Identifier -> name) -> IdentifierExpression name
$ctoIdentifier :: CursorName -> Identifier
toIdentifier :: CursorName -> Identifier
$cfromIdentifier :: Identifier -> CursorName
fromIdentifier :: Identifier -> CursorName
IdentifierExpression
    )

{- |
Construct a 'CursorName' from a 'String' with proper escaping as part of the generated SQL.

@since 1.0.0.0
-}
cursorName :: String -> CursorName
cursorName :: String -> CursorName
cursorName =
  Identifier -> CursorName
CursorName (Identifier -> CursorName)
-> (String -> Identifier) -> String -> CursorName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Identifier
identifier