Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
out-of-line parameters
Synopsis
- 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
- 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
- class KnownNat ix => HasParameter' (originalIx :: Nat) (allParams :: [NullType]) (ix :: Nat) (params :: [NullType]) (ty :: NullType) | ix params -> ty
- type family ParamOutOfBoundsError (originalIx :: Nat) (allParams :: [NullType]) (params :: [NullType]) :: Constraint where ...
- type family ParamTypeMismatchError (originalIx :: Nat) (allParams :: [NullType]) (found :: NullType) (expected :: NullType) :: Constraint where ...
Parameter
class KnownNat ix => HasParameter (ix :: Nat) (params :: [NullType]) (ty :: NullType) | ix params -> ty where Source #
A HasParameter
constraint is used to indicate a value that is
supplied externally to a SQL statement.
manipulateParams
,
queryParams
and
traversePrepared
support specifying data values
separately from the SQL command string, in which case param
s are used to
refer to the out-of-line data values.
Nothing
parameter :: TypeExpression db ty -> Expression grp lat with db params from ty Source #
parameter
takes a Nat
using type application and a TypeExpression
.
>>>
printSQL (parameter @1 int4)
($1 :: int4)
Instances
(KnownNat ix, HasParameter' ix params ix params x) => HasParameter ix params x Source # | |
Defined in Squeal.PostgreSQL.Expression.Parameter parameter :: forall (db :: SchemasType) (grp :: Grouping) (lat :: FromType) (with :: FromType) (from :: FromType). TypeExpression db x -> Expression grp lat with db params from x Source # | |
(TypeError ('Text "Tried to get the param at index 0, but params are 1-indexed") :: Constraint, x ~ (Any :: NullType)) => HasParameter 0 params x Source # | |
Defined in Squeal.PostgreSQL.Expression.Parameter parameter :: forall (db :: SchemasType) (grp :: Grouping) (lat :: FromType) (with :: FromType) (from :: FromType). TypeExpression db x -> Expression grp lat with db params from x Source # |
:: 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 |
param
takes a Nat
using type application and for basic types,
infers a TypeExpression
.
>>>
printSQL (param @1 @('Null 'PGint4))
($1 :: int4)
Parameter Internals
class KnownNat ix => HasParameter' (originalIx :: Nat) (allParams :: [NullType]) (ix :: Nat) (params :: [NullType]) (ty :: NullType) | ix params -> ty Source #
HasParameter'
is an implementation detail of HasParameter
allowing us to
include the full parameter list in our errors.
Instances
(KnownNat ix, HasParameter' originalIx allParams (ix - 1) xs x, params ~ (y ': xs), ParamOutOfBoundsError originalIx allParams params) => HasParameter' originalIx allParams ix params x Source # | |
Defined in Squeal.PostgreSQL.Expression.Parameter | |
(params ~ (y ': xs), y ~ x, ParamOutOfBoundsError originalIx allParams params, ParamTypeMismatchError originalIx allParams x y) => HasParameter' originalIx allParams 1 params x Source # | |
Defined in Squeal.PostgreSQL.Expression.Parameter |
type family ParamOutOfBoundsError (originalIx :: Nat) (allParams :: [NullType]) (params :: [NullType]) :: Constraint where ... Source #
ParamOutOfBoundsError
reports a nicer error with more context when we try to do an out-of-bounds lookup successfully do a lookup but
find a different field than we expected, or when we find ourself out of bounds
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 ... Source #
ParamTypeMismatchError
reports a nicer error with more context when we successfully do a lookup but
find a different field than we expected, or when we find ourself out of bounds
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 "") |