{-# LANGUAGE GeneralizedNewtypeDeriving #-}

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

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

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

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

> "some_constraint_name"

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

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

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