{-# LANGUAGE
AllowAmbiguousTypes
, DataKinds
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, GADTs
, KindSignatures
, MultiParamTypeClasses
, OverloadedStrings
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeFamilies
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Expression.Parameter
(
HasParameter (parameter)
, param
, HasParameter'
, ParamOutOfBoundsError
, ParamTypeMismatchError
) where
import Data.Kind (Constraint)
import GHC.Exts (Any)
import GHC.TypeLits
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Type
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
class KnownNat ix => HasParameter
(ix :: Nat)
(params :: [NullType])
(ty :: NullType)
| ix params -> ty where
parameter
:: TypeExpression db ty
-> Expression grp lat with db params from ty
parameter TypeExpression db ty
ty = ByteString -> Expression grp lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from ty)
-> ByteString -> Expression grp lat with db params from ty
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
parenthesized (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
ByteString
"$" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> KnownNat ix => ByteString
forall (n :: Nat). KnownNat n => ByteString
renderNat @ix ByteString -> ByteString -> ByteString
<+> ByteString
"::"
ByteString -> ByteString -> ByteString
<+> TypeExpression db ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL TypeExpression db ty
ty
instance {-# OVERLAPS #-} (TypeError ('Text "Tried to get the param at index 0, but params are 1-indexed"), x ~ Any) => HasParameter 0 params x
instance {-# OVERLAPS #-} (KnownNat ix, HasParameter' ix params ix params x) => HasParameter ix params x
class KnownNat ix => HasParameter'
(originalIx :: Nat)
(allParams :: [NullType])
(ix :: Nat)
(params :: [NullType])
(ty :: NullType)
| ix params -> ty where
instance {-# OVERLAPS #-}
( params ~ (y ': xs)
, y ~ x
, ParamOutOfBoundsError originalIx allParams params
, ParamTypeMismatchError originalIx allParams x y
) => HasParameter' originalIx allParams 1 params x
instance {-# OVERLAPS #-}
( KnownNat ix
, HasParameter' originalIx allParams (ix-1) xs x
, params ~ (y ': xs)
, ParamOutOfBoundsError originalIx allParams params
)
=> HasParameter' originalIx allParams ix params x
type family ParamOutOfBoundsError (originalIx :: Nat) (allParams :: [NullType]) (params :: [NullType]) :: Constraint where
ParamOutOfBoundsError originalIx allParams '[] = TypeError
('Text "Index " ':<>: 'ShowType originalIx ':<>: 'Text " is out of bounds in 1-indexed parameter list:" ':$$: 'ShowType allParams)
ParamOutOfBoundsError _ _ _ = ()
type family ParamTypeMismatchError (originalIx :: Nat) (allParams :: [NullType]) (found :: NullType) (expected :: NullType) :: Constraint where
ParamTypeMismatchError _ _ found found = ()
ParamTypeMismatchError originalIx allParams found expected = TypeError
( 'Text "Type mismatch when looking up param at index " ':<>: 'ShowType originalIx
':$$: 'Text "in 1-indexed parameter list:"
':$$: 'Text " " ':<>: 'ShowType allParams
':$$: 'Text ""
':$$: 'Text "Expected: " ':<>: 'ShowType expected
':$$: 'Text "But found: " ':<>: 'ShowType found
':$$: 'Text ""
)
param
:: forall n ty lat with db params from grp
. (NullTyped db ty, HasParameter n params ty)
=> Expression grp lat with db params from ty
param :: Expression grp lat with db params from ty
param = TypeExpression db ty -> Expression grp lat with db params from ty
forall (ix :: Nat) (params :: [NullType]) (ty :: NullType)
(db :: SchemasType) (grp :: Grouping) (lat :: FromType)
(with :: FromType) (from :: FromType).
HasParameter ix params ty =>
TypeExpression db ty -> Expression grp lat with db params from ty
parameter @n (forall (db :: SchemasType) (ty :: NullType).
NullTyped db ty =>
TypeExpression db ty
forall (ty :: NullType). NullTyped db ty => TypeExpression db ty
nulltype @db)