{-# LANGUAGE OverloadedStrings #-}

module Hasql.Private.Types where

-- bytestring-tree-builder
import ByteString.TreeBuilder (Builder)

-- | A PostgreSQL transaction isolation level
data IsolationLevel
  = ReadCommitted
  | RepeatableRead
  | Serializable
  deriving (Int -> IsolationLevel -> ShowS
[IsolationLevel] -> ShowS
IsolationLevel -> String
(Int -> IsolationLevel -> ShowS)
-> (IsolationLevel -> String)
-> ([IsolationLevel] -> ShowS)
-> Show IsolationLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IsolationLevel] -> ShowS
$cshowList :: [IsolationLevel] -> ShowS
show :: IsolationLevel -> String
$cshow :: IsolationLevel -> String
showsPrec :: Int -> IsolationLevel -> ShowS
$cshowsPrec :: Int -> IsolationLevel -> ShowS
Show, IsolationLevel -> IsolationLevel -> Bool
(IsolationLevel -> IsolationLevel -> Bool)
-> (IsolationLevel -> IsolationLevel -> Bool) -> Eq IsolationLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsolationLevel -> IsolationLevel -> Bool
$c/= :: IsolationLevel -> IsolationLevel -> Bool
== :: IsolationLevel -> IsolationLevel -> Bool
$c== :: IsolationLevel -> IsolationLevel -> Bool
Eq)

isolationLevelToSQL :: IsolationLevel -> Builder
isolationLevelToSQL :: IsolationLevel -> Builder
isolationLevelToSQL = \case
  IsolationLevel
ReadCommitted -> Builder
"READ COMMITTED"
  IsolationLevel
RepeatableRead -> Builder
"REPEATABLE READ"
  IsolationLevel
Serializable -> Builder
"SERIALIZABLE"

-- | A PostgreSQL transaction mode
data Mode = ReadWrite | ReadOnly
  deriving (Int -> Mode -> ShowS
[Mode] -> ShowS
Mode -> String
(Int -> Mode -> ShowS)
-> (Mode -> String) -> ([Mode] -> ShowS) -> Show Mode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mode] -> ShowS
$cshowList :: [Mode] -> ShowS
show :: Mode -> String
$cshow :: Mode -> String
showsPrec :: Int -> Mode -> ShowS
$cshowsPrec :: Int -> Mode -> ShowS
Show, Mode -> Mode -> Bool
(Mode -> Mode -> Bool) -> (Mode -> Mode -> Bool) -> Eq Mode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mode -> Mode -> Bool
$c/= :: Mode -> Mode -> Bool
== :: Mode -> Mode -> Bool
$c== :: Mode -> Mode -> Bool
Eq)
  
modeToSQL :: Mode -> Builder
modeToSQL :: Mode -> Builder
modeToSQL = \case
  Mode
ReadWrite -> Builder
"READ WRITE"
  Mode
ReadOnly -> Builder
"READ ONLY"

-- | A PostgreSQL transaction deferrability designation
data Deferrable = Deferrable | NotDeferrable
  deriving (Int -> Deferrable -> ShowS
[Deferrable] -> ShowS
Deferrable -> String
(Int -> Deferrable -> ShowS)
-> (Deferrable -> String)
-> ([Deferrable] -> ShowS)
-> Show Deferrable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Deferrable] -> ShowS
$cshowList :: [Deferrable] -> ShowS
show :: Deferrable -> String
$cshow :: Deferrable -> String
showsPrec :: Int -> Deferrable -> ShowS
$cshowsPrec :: Int -> Deferrable -> ShowS
Show, Deferrable -> Deferrable -> Bool
(Deferrable -> Deferrable -> Bool)
-> (Deferrable -> Deferrable -> Bool) -> Eq Deferrable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Deferrable -> Deferrable -> Bool
$c/= :: Deferrable -> Deferrable -> Bool
== :: Deferrable -> Deferrable -> Bool
$c== :: Deferrable -> Deferrable -> Bool
Eq)

deferrableToSQL :: Deferrable -> Builder
deferrableToSQL :: Deferrable -> Builder
deferrableToSQL = \case
  Deferrable
Deferrable -> Builder
"DEFERRABLE"
  Deferrable
NotDeferrable -> Builder
"NOT DEFERRABLE"