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

Sqel.Data.FieldPath

Documentation

data FieldPath Source #

Constructors

FieldPath 

Fields

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

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

type family FieldPathPrim prefix sel t where ... Source #

Equations

FieldPathPrim prefix ('SelSymbol name) t = '['FieldPath (prefix ++ '[name]) t] 
FieldPathPrim _ ('SelPath path) t = '['FieldPath path t] 
FieldPathPrim _ 'SelUnused _ = '[] 
FieldPathPrim _ ('SelIndex _ _) _ = '[] 
FieldPathPrim _ 'SelAuto t = TypeError (("Internal error: A field with type " <> t) <> " was not automatically renamed.") 

type family FieldPathsComp prefix name c i t sub where ... Source #

Equations

FieldPathsComp prefix _ _ 'Merge _ sub = FieldPathsProd prefix sub 
FieldPathsComp prefix ('SelSymbol name) 'Sum _ _ (_ ': sub) = FieldPathsProd (prefix ++ '[name]) sub 
FieldPathsComp prefix ('SelSymbol name) _ _ _ sub = FieldPathsProd (prefix ++ '[name]) sub 
FieldPathsComp _ 'SelAuto _ _ t _ = TypeError (("Internal error: A composite column with type " <> QuotedType t) <> " was not automatically renamed.") 

type family FieldPathsSub prefix s where ... Source #

Equations

FieldPathsSub prefix ('DdK sel _ t 'Prim) = FieldPathPrim prefix sel t 
FieldPathsSub prefix ('DdK sel _ t ('Comp _ c i d)) = FieldPathsComp prefix sel c i t d 
FieldPathsSub _ s = TypeError ("FieldPathsSub: " <> s) 

type family FieldPathsProd prefix s where ... Source #

Equations

FieldPathsProd _ '[] = '[] 
FieldPathsProd prefix (s ': ss) = FieldPathsSub prefix s ++ FieldPathsProd prefix ss 
FieldPathsProd _ s = TypeError ("FieldPathsProd: " <> s) 

type family FieldPaths s where ... Source #

Equations

FieldPaths ('DdK ('SelSymbol name) _ t 'Prim) = '['FieldPath '[name] t] 
FieldPaths ('DdK _ _ _ ('Comp _ _ _ sub)) = FieldPathsProd '[] sub 
FieldPaths s = TypeError ("FieldPaths: " <> s) 

type family PathEq (f1 :: FieldPath) (f2 :: FieldPath) :: Bool where ... Source #

Equations

PathEq ('FieldPath path _) ('FieldPath path _) = 'True 
PathEq _ _ = 'False 

type family ShowField (field :: FieldPath) :: ErrorMessage where ... Source #

Equations

ShowField ('FieldPath path tpe) = (((" " <> JoinSep "." path) <> " [") <> tpe) <> "]" 

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

Equations

ShowFields '[] = '[] 
ShowFields (field ': fields) = ShowField field ': ShowFields fields 

class PrintFields (s :: DdK) where Source #

Minimal complete definition

Nothing

Methods

printFields :: Dd s -> () Source #

Instances

Instances details
(TypeError (Unlines (ShowFields (FieldPaths s)) % s) :: Constraint) => PrintFields s Source # 
Instance details

Defined in Sqel.Data.FieldPath

Methods

printFields :: Dd s -> () Source #