| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Sqel.Ext
Documentation
module Sqel.Data.Dd
module Sqel.Names
module Sqel.Product
class SetIndexPrefix prefix s0 s1 | prefix s0 -> s1 where Source #
Methods
setIndexPrefix :: Dd s0 -> Dd s1 Source #
class DdType s ~ a => Con1AsColumn name a arg s | name a arg -> s where Source #
Instances
| (a ~ ConCol _name record _fields as, TypeName 'DefaultPrefix name tname, fields ~ Con1Fields (RenameCon1 name a), meta ~ MetaFor "constructor" ('Text name) "con1As", CompColumn meta fields a arg s) => Con1AsColumn (name :: Symbol) a arg ('DdK 'SelAuto (NoMods :: [Type]) a ('Comp ('TSel 'DefaultPrefix name) ('Prod ('Con as)) 'Merge s)) Source # | |
class DdType s ~ a => Con1Column a arg s | a arg -> s where Source #
Instances
| (a ~ ConCol name record fields as, TypeName 'DefaultPrefix name tname, meta ~ MetaFor "constructor" ('Text name) "con1", CompColumn meta (Con1Fields a) a arg s) => Con1Column a arg ('DdK 'SelAuto (NoMods :: [Type]) (ConCol name record fields as) ('Comp ('TSel 'DefaultPrefix name) ('Prod ('Con as)) 'Merge s)) Source # | |
class DdType s ~ a => ConColumn a arg s | a arg -> s where Source #
Instances
| (a ~ ConCol name record fields as, MkTSel ('TSel 'DefaultPrefix name), meta ~ MetaFor "constructor" ('Text name) "con", CompColumn meta fields a arg s) => ConColumn a arg ('DdK 'SelAuto (NoMods :: [Type]) (ConCol name record fields as) ('Comp ('TSel 'DefaultPrefix name) ('Prod ('Con as)) 'Nest s)) Source # | |
class DdType s ~ a => Sum a arg s | a arg -> s where Source #
Instances
| (b ~ a, CompName a ('TSel prefix name), IndexName 'DefaultPrefix name iname, fields ~ SumFields (GDatatypeInfoOf a) (GCode a), meta ~ MetaFor "sum type" ('ShowType a) "sum", CompColumn meta fields a arg s) => Sum b arg ('DdK 'SelAuto (NoMods :: [Type]) a ('Comp ('TSel prefix name) 'Sum 'Nest (IndexColumn name ': s))) Source # | |
class DdType s ~ a => SumWith a isel imods arg s | a isel imods arg -> s where Source #
Instances
| (b ~ a, CompName a ('TSel prefix name), fields ~ SumFields (GDatatypeInfoOf a) (GCode a), meta ~ MetaFor "sum type" ('ShowType a) "sum", CompColumn meta fields a arg s) => SumWith b isel imods arg ('DdK 'SelAuto (NoMods :: [Type]) a ('Comp ('TSel prefix name) 'Sum 'Nest ('DdK isel imods Int64 'Prim ': s))) Source # | |
class Column a fieldName s0 s | a fieldName s0 -> s Source #
Minimal complete definition
Instances
| a ~ b => Column a fname ('DdK ('SelSymbol name) mods b ('Comp tsel c 'Nest s)) ('DdK ('SelSymbol name) mods a ('Comp tsel c 'Nest s)) Source # | |
| a ~ b => Column a fname ('DdK ('SelSymbol name) mods b 'Prim) ('DdK ('SelSymbol name) mods a 'Prim) Source # | |
| a ~ b => Column a name ('DdK 'SelAuto mods b ('Comp tsel c 'Merge s)) ('DdK 'SelAuto mods a ('Comp tsel c 'Merge s)) Source # | |
| (a ~ b, KnownSymbol name) => Column a name ('DdK 'SelAuto mods b ('Comp tsel c 'Nest s)) ('DdK ('SelSymbol name) mods a ('Comp tsel c 'Nest s)) Source # | |
| (a ~ b, KnownSymbol name) => Column a name ('DdK 'SelAuto mods b 'Prim) ('DdK ('SelSymbol name) mods a 'Prim) Source # | |
| a ~ b => Column a name ('DdK 'SelUnused mods b 'Prim) ('DdK 'SelUnused mods a 'Prim) Source # | |
class KnownSymbol name => ReifyTSel sel name | sel -> name where Source #
class KnownSymbol name => ReifySel sel name | sel -> name where Source #
class (KnownSymbol name, KnownSymbol tpe) => TypeName prefix tpe name | prefix tpe -> name Source #
Instances
| (name ~ TypePrefixed prefixSpec tpe, KnownSymbol name, KnownSymbol tpe) => TypeName prefixSpec tpe name Source # | |
Defined in Sqel.Data.Sel | |
class KnownSymbol name => IndexName prefix tpe name | prefix tpe -> name Source #
Instances
| (name ~ IndexPrefixed prefixSpec tpe, KnownSymbol name) => IndexName prefixSpec tpe name Source # | |
Defined in Sqel.Data.Sel | |
Constructors
| Ignore |
Constructors
| Newtype (a -> w) (w -> a) |
Instances
newtype SetTableName Source #
Constructors
| SetTableName | |
Fields | |
Instances
data ArrayColumn f Source #
Constructors
| ArrayColumn |
Instances
data ReadShowColumn Source #
Constructors
| ReadShowColumn |
Instances
data EnumColumn Source #
Constructors
| EnumColumn |
Instances
| Generic EnumColumn Source # | |
Defined in Sqel.Data.Mods Associated Types type Rep EnumColumn :: Type -> Type # | |
| Show EnumColumn Source # | |
Defined in Sqel.Data.Mods Methods showsPrec :: Int -> EnumColumn -> ShowS # show :: EnumColumn -> String # showList :: [EnumColumn] -> ShowS # | |
| Eq EnumColumn Source # | |
Defined in Sqel.Data.Mods | |
| (Show a, EnumTable a) => ReifyPrimCodec FullCodec (EnumColumn ': ps) (a :: TYPE LiftedRep) Source # | |
Defined in Sqel.ReifyCodec Methods reifyPrimCodec :: NP I (EnumColumn ': ps) -> FullCodec a Source # | |
| (Show a, EnumTable a) => ReifyPrimCodec ValueCodec (EnumColumn ': ps) (a :: TYPE LiftedRep) Source # | |
Defined in Sqel.ReifyCodec Methods reifyPrimCodec :: NP I (EnumColumn ': ps) -> ValueCodec a Source # | |
| type Rep EnumColumn Source # | |
Instances
| Show PgDefault Source # | |
| ColumnConstraint PgDefault Source # | |
Defined in Sqel.ColumnConstraints Methods columnConstraint :: PgDefault -> Constraints -> Constraints Source # | |
data PrimaryKey Source #
Constructors
| PrimaryKey |
Instances
| Show PrimaryKey Source # | |
Defined in Sqel.Data.Mods Methods showsPrec :: Int -> PrimaryKey -> ShowS # show :: PrimaryKey -> String # showList :: [PrimaryKey] -> ShowS # | |
| ColumnConstraint PrimaryKey Source # | |
Defined in Sqel.ColumnConstraints Methods columnConstraint :: PrimaryKey -> Constraints -> Constraints Source # | |
Constructors
| Unique |
Instances
| Show Unique Source # | |
| ColumnConstraint Unique Source # | |
Defined in Sqel.ColumnConstraints Methods columnConstraint :: Unique -> Constraints -> Constraints Source # | |
Constructors
| Nullable |
Instances
| Show Nullable Source # | |
| ColumnConstraint Nullable Source # | |
Defined in Sqel.ColumnConstraints Methods 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 Methods reifyPrimName :: NP I (Nullable ': mods) -> PgPrimName Source # | |
class OptMod p ps res | ps p -> res where Source #
Instances
| OptMod p ('[] :: [Type]) () Source # | |
Defined in Sqel.Class.Mods | |
| OptMod p (p ': ps) p Source # | |
Defined in Sqel.Class.Mods | |
| OptMod p ps p1 => OptMod p (p0 ': ps) p1 Source # | |
Defined in Sqel.Class.Mods | |
data SelectAtom Source #
Constructors
| SelectAtom FragType (Selector -> Int -> Sql) |
Instances
| Generic SelectAtom Source # | |
Defined in Sqel.Data.SelectExpr Associated Types type Rep SelectAtom :: Type -> Type # | |
| type Rep SelectAtom Source # | |
Defined in Sqel.Data.SelectExpr type Rep SelectAtom = D1 ('MetaData "SelectAtom" "Sqel.Data.SelectExpr" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "SelectAtom" 'PrefixI 'True) (S1 ('MetaSel ('Just "type_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FragType) :*: S1 ('MetaSel ('Just "code") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Selector -> Int -> Sql)))) | |
Instances
| Generic FragType Source # | |
| Show FragType Source # | |
| Eq FragType Source # | |
| Ord FragType Source # | |
Defined in Sqel.Data.FragType | |
| type Rep FragType Source # | |
Defined in Sqel.Data.FragType type Rep FragType = D1 ('MetaData "FragType" "Sqel.Data.FragType" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) ((C1 ('MetaCons "Where" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Offset" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Limit" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Order" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Order)) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) | |
module Sqel.Data.Migration
class PrimColumn a where Source #
Minimal complete definition
Methods
primDecoder :: Value a Source #
default primDecoder :: PrimDecoder a => Value a Source #
primEncoder :: Value a Source #
default primEncoder :: PrimEncoder a => Value a Source #
pgType :: PgPrimName Source #
Instances
class ReifyCodec b s a | s -> a Source #
Minimal complete definition
Instances
| (ReifyCodecComp b sub as, ReifyCompCodec b c i ps as a) => ReifyCodec b ('DdK sel ps a ('Comp tsel c i sub)) a Source # | |
Defined in Sqel.ReifyCodec | |
| ReifyPrimCodec b ps a => ReifyCodec b ('DdK sel ps a 'Prim) a Source # | |
Defined in Sqel.ReifyCodec | |
Minimal complete definition
Instances
| (ColumnConstraints mods, MaybeMod SetTableName mods, ReifyDdComp sub) => ReifyDd ('DdK sel mods a ('Comp tsel c i sub)) Source # | |
| (ColumnConstraints mods, MaybeMod SetTableName mods, ReifyPrimName a mods, ReifySel sel name) => ReifyDd ('DdK sel mods a 'Prim) Source # | |