sqel-0.0.1.0: Guided derivation for Hasql statements
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sqel.Class.MatchView

Documentation

type family CheckAvail (fields :: [FieldPath]) :: Type where ... Source #

Equations

CheckAvail ('FieldPath _ t ': _) = t 

type family AvailableColumns (fields :: [FieldPath]) :: ErrorMessage where ... Source #

Equations

AvailableColumns fields = "The specified table contains these fields:" % Unlines (ShowFields fields) 

type family NoViewMatch viewType avail path where ... Source #

Equations

NoViewMatch viewType avail ('FieldPath path tpe) = (((((("The " <> viewType) <> " column ") <> QuotedError (JoinSym "." path)) <> " with type ") <> QuotedType tpe) <> " does not correspond to a table column.") % AvailableColumns avail 

type family UnknownMsg (viewType :: Symbol) (field :: FieldPath) :: ErrorMessage where ... Source #

Equations

UnknownMsg viewType ('FieldPath path tpe) = ((((("This " <> viewType) <> " cannot determine whether the column ") <> QuotedError (JoinSym "." path)) <> " with type ") <> QuotedType tpe) % "corresponds to a table column." 

type family PathConstraint (path :: [Symbol]) :: ErrorMessage where ... Source #

Equations

PathConstraint '[field] = "HasField " <> 'ShowType field 
PathConstraint path = "HasPath " <> path 

type family AvailStuckMsg (viewType :: Symbol) (table :: DdK) (field :: FieldPath) :: ErrorMessage where ... Source #

Equations

AvailStuckMsg viewType table ('FieldPath path tpe) = UnknownMsg viewType ('FieldPath path tpe) % ((("This is likely due to the structure type " <> QuotedType table) <> " being polymorphic.") % ("Try adding the constraint:" % (" " <> QuotedError ((((PathConstraint path <> " ") <> tpe) <> " ") <> table)))) 

type family MatchStuckMsg viewType avail path where ... Source #

Equations

MatchStuckMsg viewType avail field = UnknownMsg viewType field % AvailableColumns avail 

type family MatchStuck (viewType :: Symbol) (field :: FieldPath) (avail :: [FieldPath]) :: k where ... Source #

Equations

MatchStuck viewType field avail = TypeError (MatchStuckMsg viewType avail field) 

type family AvailStuck (viewType :: Symbol) (table :: DdK) (field :: FieldPath) :: k where ... Source #

Equations

AvailStuck viewType table field = TypeError (AvailStuckMsg viewType table field) 

type family CheckMatch viewType table vfield avail match where ... Source #

Equations

CheckMatch viewType table vfield avail match = IfStuck match (IfStuck (CheckAvail avail) (AvailStuck viewType table vfield) (Pure (MatchStuck viewType vfield avail))) (Pure match) 

class MatchPath view avail match | view avail -> match Source #

Instances

Instances details
match ~ PathEq view avail => MatchPath view avail match Source # 
Instance details

Defined in Sqel.Class.MatchView

class CheckPathMatch view avail match finalMatch | view avail match -> finalMatch Source #

Instances

Instances details
MatchViewPath view avail match => CheckPathMatch view avail 'False match Source # 
Instance details

Defined in Sqel.Class.MatchView

CheckPathMatch view avail 'True 'True Source # 
Instance details

Defined in Sqel.Class.MatchView

class MatchViewPath view avail match | view avail -> match Source #

Instances

Instances details
MatchViewPath view ('[] :: [FieldPath]) 'False Source # 
Instance details

Defined in Sqel.Class.MatchView

(MatchPath view tfield match, CheckPathMatch view tfields match finalMatch) => MatchViewPath view (tfield ': tfields) finalMatch Source # 
Instance details

Defined in Sqel.Class.MatchView

class CheckViewPathError viewType table vfield vfields avail match error | viewType table vfield vfields avail match -> error Source #

Instances

Instances details
MatchViewPaths viewType table vfields avail error => CheckViewPathError viewType table vfield vfields avail 'True error Source # 
Instance details

Defined in Sqel.Class.MatchView

err ~ NoViewMatch viewType avail vfield => CheckViewPathError viewType table vfield vfields avail 'False ('Just err) Source # 
Instance details

Defined in Sqel.Class.MatchView

class MatchViewPaths viewType table view avail error | viewType table view avail -> error Source #

Instances

Instances details
MatchViewPaths viewType table ('[] :: [FieldPath]) avail ('Nothing :: Maybe ErrorMessage) Source # 
Instance details

Defined in Sqel.Class.MatchView

(MatchViewPath vfield avail match, CheckViewPathError viewType table vfield vfields avail (CheckMatch viewType table vfield avail match) finalError) => MatchViewPaths viewType table (vfield ': vfields) avail finalError Source # 
Instance details

Defined in Sqel.Class.MatchView

type family MaybeError (msg :: Maybe ErrorMessage) :: Maybe k where ... Source #

Equations

MaybeError 'Nothing = 'Nothing 
MaybeError ('Just msg) = 'Just (TypeError msg) 

class MatchView viewType view avail error | viewType view avail -> error Source #

Instances

Instances details
(MatchViewPaths viewType table (FieldPaths view) (FieldPaths table) msg, error ~ (MaybeError msg :: Maybe Void)) => MatchView viewType view table error Source # 
Instance details

Defined in Sqel.Class.MatchView

type MatchQuery view table error = MatchView "query" view table error Source #

type MatchProjection view table error = MatchView "projection" view table error Source #

class MatchViewPath ('FieldPath path t) (FieldPaths table) 'True => HasPath path t table Source #

Instances

Instances details
MatchViewPath ('FieldPath path t) (FieldPaths table) 'True => HasPath path t table Source # 
Instance details

Defined in Sqel.Class.MatchView

class MatchViewPath ('FieldPath '[path] t) (FieldPaths table) 'True => HasField path t table Source #

Instances

Instances details
MatchViewPath ('FieldPath '[path] t) (FieldPaths table) 'True => HasField path t table Source # 
Instance details

Defined in Sqel.Class.MatchView