module Database.PostgreSQL.PQTypes.Model.PrimaryKey (
    PrimaryKey
  , pkOnColumn
  , pkOnColumns
  , pkName
  , sqlAddPK
  , sqlAddPKUsing
  , sqlDropPK
  ) where

import Data.Monoid (mconcat)
import Data.Monoid.Utils
import Database.PostgreSQL.PQTypes
import Prelude
import Database.PostgreSQL.PQTypes.Model.Index
import Database.PostgreSQL.PQTypes.Utils.NubList

newtype PrimaryKey = PrimaryKey (NubList (RawSQL ()))
  deriving (PrimaryKey -> PrimaryKey -> Bool
(PrimaryKey -> PrimaryKey -> Bool)
-> (PrimaryKey -> PrimaryKey -> Bool) -> Eq PrimaryKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrimaryKey -> PrimaryKey -> Bool
$c/= :: PrimaryKey -> PrimaryKey -> Bool
== :: PrimaryKey -> PrimaryKey -> Bool
$c== :: PrimaryKey -> PrimaryKey -> Bool
Eq, Int -> PrimaryKey -> ShowS
[PrimaryKey] -> ShowS
PrimaryKey -> String
(Int -> PrimaryKey -> ShowS)
-> (PrimaryKey -> String)
-> ([PrimaryKey] -> ShowS)
-> Show PrimaryKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PrimaryKey] -> ShowS
$cshowList :: [PrimaryKey] -> ShowS
show :: PrimaryKey -> String
$cshow :: PrimaryKey -> String
showsPrec :: Int -> PrimaryKey -> ShowS
$cshowsPrec :: Int -> PrimaryKey -> ShowS
Show)

pkOnColumn :: RawSQL () -> Maybe PrimaryKey
pkOnColumn :: RawSQL () -> Maybe PrimaryKey
pkOnColumn RawSQL ()
column = PrimaryKey -> Maybe PrimaryKey
forall a. a -> Maybe a
Just (PrimaryKey -> Maybe PrimaryKey)
-> ([RawSQL ()] -> PrimaryKey) -> [RawSQL ()] -> Maybe PrimaryKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NubList (RawSQL ()) -> PrimaryKey
PrimaryKey (NubList (RawSQL ()) -> PrimaryKey)
-> ([RawSQL ()] -> NubList (RawSQL ()))
-> [RawSQL ()]
-> PrimaryKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RawSQL ()] -> NubList (RawSQL ())
forall a. Ord a => [a] -> NubList a
toNubList ([RawSQL ()] -> Maybe PrimaryKey)
-> [RawSQL ()] -> Maybe PrimaryKey
forall a b. (a -> b) -> a -> b
$ [RawSQL ()
column]

pkOnColumns :: [RawSQL ()] -> Maybe PrimaryKey
pkOnColumns :: [RawSQL ()] -> Maybe PrimaryKey
pkOnColumns []      = Maybe PrimaryKey
forall a. Maybe a
Nothing
pkOnColumns [RawSQL ()]
columns = PrimaryKey -> Maybe PrimaryKey
forall a. a -> Maybe a
Just (PrimaryKey -> Maybe PrimaryKey)
-> ([RawSQL ()] -> PrimaryKey) -> [RawSQL ()] -> Maybe PrimaryKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NubList (RawSQL ()) -> PrimaryKey
PrimaryKey (NubList (RawSQL ()) -> PrimaryKey)
-> ([RawSQL ()] -> NubList (RawSQL ()))
-> [RawSQL ()]
-> PrimaryKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RawSQL ()] -> NubList (RawSQL ())
forall a. Ord a => [a] -> NubList a
toNubList ([RawSQL ()] -> Maybe PrimaryKey)
-> [RawSQL ()] -> Maybe PrimaryKey
forall a b. (a -> b) -> a -> b
$ [RawSQL ()]
columns

pkName :: RawSQL () -> RawSQL ()
pkName :: RawSQL () -> RawSQL ()
pkName RawSQL ()
tname = [RawSQL ()] -> RawSQL ()
forall a. Monoid a => [a] -> a
mconcat [RawSQL ()
"pk__", RawSQL ()
tname]

sqlAddPK :: RawSQL () -> PrimaryKey -> RawSQL ()
sqlAddPK :: RawSQL () -> PrimaryKey -> RawSQL ()
sqlAddPK RawSQL ()
tname (PrimaryKey NubList (RawSQL ())
columns) = [RawSQL ()] -> RawSQL ()
forall m. (IsString m, Monoid m) => [m] -> m
smconcat [
    RawSQL ()
"ADD CONSTRAINT"
  , RawSQL () -> RawSQL ()
pkName RawSQL ()
tname
  , RawSQL ()
"PRIMARY KEY ("
  , RawSQL () -> [RawSQL ()] -> RawSQL ()
forall m. Monoid m => m -> [m] -> m
mintercalate RawSQL ()
", " ([RawSQL ()] -> RawSQL ()) -> [RawSQL ()] -> RawSQL ()
forall a b. (a -> b) -> a -> b
$ NubList (RawSQL ()) -> [RawSQL ()]
forall a. NubList a -> [a]
fromNubList NubList (RawSQL ())
columns
  , RawSQL ()
")"
  ]

-- | Convert a unique index into a primary key. Main usage is to build a unique
-- index concurrently first (so that its creation doesn't conflict with table
-- updates on the modified table) and then convert it into a primary key using
-- this function.
sqlAddPKUsing :: RawSQL () -> TableIndex -> RawSQL ()
sqlAddPKUsing :: RawSQL () -> TableIndex -> RawSQL ()
sqlAddPKUsing RawSQL ()
tname TableIndex
idx = [RawSQL ()] -> RawSQL ()
forall m. (IsString m, Monoid m) => [m] -> m
smconcat
  [ RawSQL ()
"ADD CONSTRAINT"
  , RawSQL () -> RawSQL ()
pkName RawSQL ()
tname
  , RawSQL ()
"PRIMARY KEY USING INDEX"
  , RawSQL () -> TableIndex -> RawSQL ()
indexName RawSQL ()
tname TableIndex
idx
  ]

sqlDropPK :: RawSQL () -> RawSQL ()
sqlDropPK :: RawSQL () -> RawSQL ()
sqlDropPK RawSQL ()
tname = RawSQL ()
"DROP CONSTRAINT" RawSQL () -> RawSQL () -> RawSQL ()
forall m. (IsString m, Monoid m) => m -> m -> m
<+> RawSQL () -> RawSQL ()
pkName RawSQL ()
tname