module PostgREST.Request.Preferences where
import GHC.Show
import Protolude
data PreferResolution
= MergeDuplicates
| IgnoreDuplicates
instance Show PreferResolution where
show :: PreferResolution -> String
show PreferResolution
MergeDuplicates = String
"resolution=merge-duplicates"
show PreferResolution
IgnoreDuplicates = String
"resolution=ignore-duplicates"
data PreferRepresentation
= Full
|
| None
deriving PreferRepresentation -> PreferRepresentation -> Bool
(PreferRepresentation -> PreferRepresentation -> Bool)
-> (PreferRepresentation -> PreferRepresentation -> Bool)
-> Eq PreferRepresentation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreferRepresentation -> PreferRepresentation -> Bool
$c/= :: PreferRepresentation -> PreferRepresentation -> Bool
== :: PreferRepresentation -> PreferRepresentation -> Bool
$c== :: PreferRepresentation -> PreferRepresentation -> Bool
Eq
instance Show PreferRepresentation where
show :: PreferRepresentation -> String
show PreferRepresentation
Full = String
"return=representation"
show PreferRepresentation
None = String
"return=minimal"
show PreferRepresentation
HeadersOnly = String
"return=headers-only"
data PreferParameters
= SingleObject
| MultipleObjects
deriving PreferParameters -> PreferParameters -> Bool
(PreferParameters -> PreferParameters -> Bool)
-> (PreferParameters -> PreferParameters -> Bool)
-> Eq PreferParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreferParameters -> PreferParameters -> Bool
$c/= :: PreferParameters -> PreferParameters -> Bool
== :: PreferParameters -> PreferParameters -> Bool
$c== :: PreferParameters -> PreferParameters -> Bool
Eq
instance Show PreferParameters where
show :: PreferParameters -> String
show PreferParameters
SingleObject = String
"params=single-object"
show PreferParameters
MultipleObjects = String
"params=multiple-objects"
data PreferCount
= ExactCount
| PlannedCount
| EstimatedCount
deriving PreferCount -> PreferCount -> Bool
(PreferCount -> PreferCount -> Bool)
-> (PreferCount -> PreferCount -> Bool) -> Eq PreferCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreferCount -> PreferCount -> Bool
$c/= :: PreferCount -> PreferCount -> Bool
== :: PreferCount -> PreferCount -> Bool
$c== :: PreferCount -> PreferCount -> Bool
Eq
instance Show PreferCount where
show :: PreferCount -> String
show PreferCount
ExactCount = String
"count=exact"
show PreferCount
PlannedCount = String
"count=planned"
show PreferCount
EstimatedCount = String
"count=estimated"
data PreferTransaction
= Commit
| Rollback
deriving PreferTransaction -> PreferTransaction -> Bool
(PreferTransaction -> PreferTransaction -> Bool)
-> (PreferTransaction -> PreferTransaction -> Bool)
-> Eq PreferTransaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PreferTransaction -> PreferTransaction -> Bool
$c/= :: PreferTransaction -> PreferTransaction -> Bool
== :: PreferTransaction -> PreferTransaction -> Bool
$c== :: PreferTransaction -> PreferTransaction -> Bool
Eq
instance Show PreferTransaction where
show :: PreferTransaction -> String
show PreferTransaction
Commit = String
"tx=commit"
show PreferTransaction
Rollback = String
"tx=rollback"