{-# LANGUAGE
DataKinds
, GADTs
, LambdaCase
, OverloadedStrings
, PatternSynonyms
, PolyKinds
, QuantifiedConstraints
, RankNTypes
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.Default
(
Optional (..)
, mapOptional
, pattern NotDefault
) where
import Data.Kind
import Generics.SOP
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
data Optional (expr :: k -> Type) (ty :: (Optionality, k)) where
Default :: Optional expr ('Def :=> ty)
Set :: expr ty -> Optional expr (def :=> ty)
instance (forall x. RenderSQL (expr x)) => RenderSQL (Optional expr ty) where
renderSQL :: Optional expr ty -> ByteString
renderSQL = \case
Optional expr ty
Default -> ByteString
"DEFAULT"
Set expr ty
x -> expr ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL expr ty
x
mapOptional
:: (expr x -> expr y)
-> Optional expr (def :=> x)
-> Optional expr (def :=> y)
mapOptional :: (expr x -> expr y)
-> Optional expr (def :=> x) -> Optional expr (def :=> y)
mapOptional expr x -> expr y
f = \case
Optional expr (def :=> x)
Default -> Optional expr (def :=> y)
forall k (expr :: k -> *) (ty :: k). Optional expr ('Def :=> ty)
Default
Set expr ty
x -> expr y -> Optional expr (def :=> y)
forall k (expr :: k -> *) (ty :: k) (def :: Optionality).
expr ty -> Optional expr (def :=> ty)
Set (expr x -> expr y
f expr x
expr ty
x)
pattern NotDefault :: ty -> Optional I ('Def :=> ty)
pattern $bNotDefault :: ty -> Optional I ('Def :=> ty)
$mNotDefault :: forall r ty.
Optional I ('Def :=> ty) -> (ty -> r) -> (Void# -> r) -> r
NotDefault x = Set (I x)