Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
a :> b infixr 3 |
Instances
(CheckCompItem meta field arg0 s0, CompColumn' (MetaNext meta) ('Right 'SpecDsl :: Either Void SpecType) fields a args s1) => CompColumn' meta ('Right 'SpecDsl :: Either Void SpecType) (field ': fields) a (arg0 :> args) (s0 ': s1) Source # | |
SymNP p1 ps => SymNP (p0 :> p1) (p0 ': ps) Source # | |
MkMigrations old (mig1 ': migs) => MkMigrations (Migration ('Mig from to m ext) :> old) ('Mig from to m ext ': (mig1 ': migs)) Source # | |
Defined in Sqel.Data.Migration |
Instances
(MkTSel sel, fields ~ ProductFields (GDatatypeInfoOf a) (GCode a), meta ~ MetaFor "product type" ('ShowType a) "prod", CompColumn meta fields a arg s) => ProductSel (sel :: TSel) a arg ('DdK 'SelAuto (NoMods :: [Type]) a ('Comp sel ('Prod 'Reg) 'Nest s)) Source # | |
type family ProdPrimsNewtype (a :: Type) :: DdK where ... Source #
ProdPrimsNewtype a = ProdPrimsNewtype' a (GCode a) (GDatatypeInfoOf a) |
type family ProdPrims (a :: Type) :: DdK where ... Source #
ProdPrims a = ProdPrims' a (GCode a) (GDatatypeInfoOf a) |
type family PrimNewtype (name :: Symbol) (a :: Type) :: DdK where ... Source #
PrimNewtype name a = Mod (Newtype a (NewtypeWrapped a)) (Prim name a) |
type family PrimUnused (a :: Type) :: DdK where ... Source #
PrimUnused a = PrimSel 'SelUnused a |
type IndexColumn name = IndexColumnWith 'DefaultPrefix name Source #
primNewtype :: forall a w err. err ~ NewtypeError => UnwrapNewtype err a w => Dd ('DdK 'SelAuto '[Newtype a w] a 'Prim) Source #
primIndex :: forall tpe name. IndexName 'DefaultPrefix tpe name => Dd (IndexColumn tpe) Source #
json :: forall a. ToJSON a => FromJSON a => Dd ('DdK 'SelAuto [PgPrimName, PrimValueCodec a] a 'Prim) Source #
enum :: forall a. Dd ('DdK 'SelAuto [PgPrimName, EnumColumn] a 'Prim) Source #
readShow :: forall a. Dd ('DdK 'SelAuto [PgPrimName, ReadShowColumn] a 'Prim) Source #
array :: forall f a p sel. Dd ('DdK sel p a 'Prim) -> Dd ('DdK sel (ArrayColumn f ': p) (f a) 'Prim) Source #
migrateDef :: forall s0 s1. MapMod (MigrationDefault (DdType s0)) s0 s1 => DdType s0 -> Dd s0 -> Dd s1 Source #
migrateRename :: forall name s0 s1. MapMod (MigrationRename name) s0 s1 => Dd s0 -> Dd s1 Source #
migrateRenameType :: forall name s0 s1. MapMod (MigrationRenameType name) s0 s1 => Dd s0 -> Dd s1 Source #
migrateDelete :: forall s0 s1. MapMod MigrationDelete s0 s1 => Dd s0 -> Dd s1 Source #
primNewtypes :: forall (a :: Type) (s :: [DdK]). MkPrimNewtypes (PrimProd a) s => Prims a s Source #
prodSel :: ProductSel sel a arg s => arg -> Dd s Source #
prodAs :: forall (name :: Symbol) (a :: Type) (s :: DdK) (arg :: Type). Product a arg s => Rename s (SetName s name) => arg -> Dd (SetName s name) Source #
con1As :: Con1AsColumn name a arg s => arg -> Dd s Source #
con1 :: Con1Column a arg s => arg -> Dd s Source #
sumAs :: forall (name :: Symbol) (a :: Type) (s :: DdK) (arg :: Type). Sum a arg s => Rename s (SetName s name) => arg -> Dd (SetName s name) Source #
mergeSum :: forall (a :: Type) (s :: DdK) (arg :: Type). Sum a arg s => arg -> Dd (Merge s) Source #
conAs :: forall (name :: Symbol) (a :: Type) (s :: DdK) (arg :: Type). ConColumn a arg s => Rename s (SetName s name) => arg -> Dd (SetName s name) Source #
indexPrefix :: forall prefix s0 s1. SetIndexPrefix prefix s0 s1 => Dd s0 -> Dd s1 Source #
typePrefix :: forall prefix s0 s1. SetTypePrefix prefix s0 s1 => Dd s0 -> Dd s1 Source #
Uid i a |
Instances
Functor (Uid i) Source # | |
(FromJSON a, FromJSON i) => FromJSON (Uid i a) Source # | |
(ToJSON a, ToJSON i) => ToJSON (Uid i a) Source # | |
Defined in Sqel.Data.Uid | |
Generic (Uid i a) Source # | |
(Show i, Show a) => Show (Uid i a) Source # | |
(Eq i, Eq a) => Eq (Uid i a) Source # | |
CompName a sel => CompName (Uid i a) sel Source # | |
type Rep (Uid i a) Source # | |
Defined in Sqel.Data.Uid type Rep (Uid i a) = D1 ('MetaData "Uid" "Sqel.Data.Uid" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "Uid" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
type UidDd si sa = TypeSel (DdTypeSel sa) (Prod (Uid (DdType si) (DdType sa))) *> (Name "id" si > Merge sa) Source #
uid :: forall (i :: Type) (a :: Type) (si :: DdK) (sa :: DdK) (s :: DdK). UidColumn i a si sa s => Dd si -> Dd sa -> Dd s Source #
uidAs :: forall (name :: Symbol) (i :: Type) (a :: Type) (si :: DdK) (sa :: DdK) (s :: DdK). UidColumn i a si sa s => Rename s (SetTypeName s name) => Dd si -> Dd sa -> Dd (SetTypeName s name) Source #
named :: forall (name :: Symbol) (s0 :: DdK). Rename s0 (SetName s0 name) => Dd s0 -> Dd (SetName s0 name) Source #
typeAs :: forall (name :: Symbol) (s0 :: DdK). Rename2 s0 (SetTypeName s0 name) => Dd s0 -> Dd (SetTypeName s0 name) Source #
nullableAs :: forall name s0 s1 s2. AddMod Nullable s0 s1 => MkNullable s1 s2 => Rename s2 (SetName s2 name) => Dd s0 -> Dd (SetName s2 name) Source #
tableName :: forall s0 s1. MapMod SetTableName s0 s1 => PgTableName -> Dd s0 -> Dd s1 Source #
Instances
data SetTableName Source #
Instances
data ArrayColumn f Source #
Instances
data ReadShowColumn Source #
Instances
Generic ReadShowColumn Source # | |
Defined in Sqel.Data.Mods type Rep ReadShowColumn :: Type -> Type # from :: ReadShowColumn -> Rep ReadShowColumn x # to :: Rep ReadShowColumn x -> ReadShowColumn # | |
Show ReadShowColumn Source # | |
Defined in Sqel.Data.Mods showsPrec :: Int -> ReadShowColumn -> ShowS # show :: ReadShowColumn -> String # showList :: [ReadShowColumn] -> ShowS # | |
Eq ReadShowColumn Source # | |
Defined in Sqel.Data.Mods (==) :: ReadShowColumn -> ReadShowColumn -> Bool # (/=) :: ReadShowColumn -> ReadShowColumn -> Bool # | |
(Show a, Read a) => ReifyPrimCodec FullCodec (ReadShowColumn ': ps) (a :: TYPE LiftedRep) Source # | |
Defined in Sqel.ReifyCodec reifyPrimCodec :: NP I (ReadShowColumn ': ps) -> FullCodec a Source # | |
(Show a, Read a) => ReifyPrimCodec ValueCodec (ReadShowColumn ': ps) (a :: TYPE LiftedRep) Source # | |
Defined in Sqel.ReifyCodec reifyPrimCodec :: NP I (ReadShowColumn ': ps) -> ValueCodec a Source # | |
type Rep ReadShowColumn Source # | |
data EnumColumn Source #
Instances
Generic EnumColumn Source # | |
Defined in Sqel.Data.Mods type Rep EnumColumn :: Type -> Type # from :: EnumColumn -> Rep EnumColumn x # to :: Rep EnumColumn x -> EnumColumn # | |
Show EnumColumn Source # | |
Defined in Sqel.Data.Mods showsPrec :: Int -> EnumColumn -> ShowS # show :: EnumColumn -> String # showList :: [EnumColumn] -> ShowS # | |
Eq EnumColumn Source # | |
Defined in Sqel.Data.Mods (==) :: EnumColumn -> EnumColumn -> Bool # (/=) :: EnumColumn -> EnumColumn -> Bool # | |
(Show a, EnumTable a) => ReifyPrimCodec FullCodec (EnumColumn ': ps) (a :: TYPE LiftedRep) Source # | |
Defined in Sqel.ReifyCodec reifyPrimCodec :: NP I (EnumColumn ': ps) -> FullCodec a Source # | |
(Show a, EnumTable a) => ReifyPrimCodec ValueCodec (EnumColumn ': ps) (a :: TYPE LiftedRep) Source # | |
Defined in Sqel.ReifyCodec reifyPrimCodec :: NP I (EnumColumn ': ps) -> ValueCodec a Source # | |
type Rep EnumColumn Source # | |
Instances
Show PgDefault Source # | |
ColumnConstraint PgDefault Source # | |
Defined in Sqel.ColumnConstraints columnConstraint :: PgDefault -> Constraints -> Constraints Source # |
data PrimaryKey Source #
Instances
Show PrimaryKey Source # | |
Defined in Sqel.Data.Mods showsPrec :: Int -> PrimaryKey -> ShowS # show :: PrimaryKey -> String # showList :: [PrimaryKey] -> ShowS # | |
ColumnConstraint PrimaryKey Source # | |
Defined in Sqel.ColumnConstraints columnConstraint :: PrimaryKey -> Constraints -> Constraints Source # |
Instances
Show Unique Source # | |
ColumnConstraint Unique Source # | |
Defined in Sqel.ColumnConstraints columnConstraint :: Unique -> Constraints -> Constraints Source # |
Instances
Show Nullable Source # | |
ColumnConstraint Nullable Source # | |
Defined in Sqel.ColumnConstraints columnConstraint :: Nullable -> Constraints -> Constraints Source # | |
ReifyPrimCodec Value ps a => ReifyPrimCodec Encoder (Nullable ': ps) (Maybe a :: Type) Source # | |
Defined in Sqel.ReifyCodec | |
ReifyPrimCodec ValueCodec ps a => ReifyPrimCodec FullCodec (Nullable ': ps) (Maybe a :: Type) Source # | |
Defined in Sqel.ReifyCodec | |
ReifyPrimName a mods => ReifyPrimName (Maybe a :: Type) (Nullable ': mods) Source # | |
Defined in Sqel.ReifyDd reifyPrimName :: NP I (Nullable ': mods) -> PgPrimName Source # |
module Sqel.Query.Combinators
Instances
Generic Order Source # | |
Show Order Source # | |
Eq Order Source # | |
ToSql Order Source # | |
type Rep Order Source # | |
Defined in Sqel.Data.Order type Rep Order = D1 ('MetaData "Order" "Sqel.Data.Order" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "Asc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Desc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Using" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data Migrations m migs Source #
migrate :: MkMigrations arg migs => arg -> Migrations m migs Source #
noMigrations :: Migrations m '[] Source #
migrateAuto :: AutoMigration old new => Dd old -> Dd new -> Migration ('Mig (DdType old) (DdType new) m Void) Source #
module Sqel.Sql
class CheckedProjection (proj :: DdK) (table :: DdK) Source #
Instances
(MatchProjection proj table match, CheckedProjection' match proj) => CheckedProjection proj table Source # | |
Defined in Sqel.PgType checkedProjection :: Dd proj -> ProjectionWitness (DdType proj) (DdType table) Source # |
class MkTableSchema table where Source #
tableSchema :: Dd table -> TableSchema (DdType table) Source #
Instances
(ReifyDd table, ReifyCodec FullCodec table (DdType table)) => MkTableSchema table Source # | |
Defined in Sqel.PgType tableSchema :: Dd table -> TableSchema (DdType table) Source # |
projection :: MkTableSchema proj => MkTableSchema table => CheckedProjection proj table => Dd proj -> Dd table -> Projection (DdType proj) (DdType table) Source #
fullProjection :: MkTableSchema table => CheckedProjection table table => Dd table -> Projection (DdType table) (DdType table) Source #
toFullProjection :: TableSchema table -> Projection table table Source #
type EmptyQuery = 'DdK ('SelSymbol "") NoMods () ('Comp ('TSel 'DefaultPrefix "") ('Prod 'Reg) 'Nest '[]) Source #
class CheckQuery query table where Source #
checkQuery :: Dd query -> Dd table -> QuerySchema (DdType query) (DdType table) Source #
Instances
(CheckedQuery query table, ReifyCodec Encoder query (DdType query)) => CheckQuery query table Source # | |
Defined in Sqel.Query checkQuery :: Dd query -> Dd table -> QuerySchema (DdType query) (DdType table) Source # |
class MatchViewPath ('FieldPath '[path] t) (FieldPaths table) 'True => HasField path t table Source #
Instances
MatchViewPath ('FieldPath '[path] t) (FieldPaths table) 'True => HasField path t table Source # | |
Defined in Sqel.Class.MatchView |
class MatchViewPath ('FieldPath path t) (FieldPaths table) 'True => HasPath path t table Source #
Instances
MatchViewPath ('FieldPath path t) (FieldPaths table) 'True => HasPath path t table Source # | |
Defined in Sqel.Class.MatchView |
data TableSchema a Source #
Instances
data Projection proj table Source #
Instances
data QuerySchema q a Source #
Instances
ToSql (SelectQuery (QuerySchema q a)) Source # | |
Defined in Sqel.Data.QuerySchema toSql :: SelectQuery (QuerySchema q a) -> Sql Source # | |
Generic (QuerySchema q a) Source # | |
Defined in Sqel.Data.QuerySchema type Rep (QuerySchema q a) :: Type -> Type # from :: QuerySchema q a -> Rep (QuerySchema q a) x # to :: Rep (QuerySchema q a) x -> QuerySchema q a # | |
type Rep (QuerySchema q a) Source # | |
Defined in Sqel.Data.QuerySchema type Rep (QuerySchema q a) = D1 ('MetaData "QuerySchema" "Sqel.Data.QuerySchema" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "QuerySchema" 'PrefixI 'True) (S1 ('MetaSel ('Just "frags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SelectFragment]) :*: S1 ('MetaSel ('Just "encoder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Encoder q)))) |
emptyQuerySchema :: QuerySchema () a Source #