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

Sqel

Documentation

type family Sqel a p = r | r -> p a where ... Source #

Equations

Sqel a '(sel, mods, s) = Dd ('DdK sel mods a s) 

type family Sqel' sel mods a s = r | r -> sel mods a s where ... Source #

Equations

Sqel' sel mods a s = Dd ('DdK sel mods a s) 

data a :> b infixr 3 Source #

Constructors

a :> b infixr 3 

Instances

Instances details
(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 # 
Instance details

Defined in Sqel.Comp

Methods

compColumn' :: (arg0 :> args) -> NP Dd (s0 ': s1) Source #

SymNP p1 ps => SymNP (p0 :> p1) (p0 ': ps) Source # 
Instance details

Defined in Sqel.Class.Mods

Methods

symNP :: (p0 :> p1) -> NP I (p0 ': ps) Source #

MkMigrations old (mig1 ': migs) => MkMigrations (Migration ('Mig from to m ext) :> old) ('Mig from to m ext ': (mig1 ': migs)) Source # 
Instance details

Defined in Sqel.Data.Migration

Methods

mkMigrations :: (Migration ('Mig from to m ext) :> old) -> NP Migration ('Mig from to m ext ': (mig1 ': migs)) Source #

data Dd s where Source #

Constructors

Dd :: SelW sel -> Mods mods -> DdStruct s -> Dd ('DdK sel mods a s) 

Instances

Instances details
Column a fieldName s0 s1 => CompItemOrError err ('ProductField fieldName a) (Dd s0) s1 Source # 
Instance details

Defined in Sqel.Comp

Methods

compItemOrError :: Proxy err -> Dd s0 -> Dd s1 Source #

PrettyNP sub => Pretty (Dd ('DdK sel p a ('Comp tsel c i sub))) Source # 
Instance details

Defined in Sqel.Data.Dd

Methods

pretty :: Dd ('DdK sel p a ('Comp tsel c i sub)) -> Doc ann #

prettyList :: [Dd ('DdK sel p a ('Comp tsel c i sub))] -> Doc ann #

Pretty (Mods p) => Pretty (Dd ('DdK sel p a 'Prim)) Source # 
Instance details

Defined in Sqel.Data.Dd

Methods

pretty :: Dd ('DdK sel p a 'Prim) -> Doc ann #

prettyList :: [Dd ('DdK sel p a 'Prim)] -> Doc ann #

data TSel Source #

Constructors

TSel SelPrefix Symbol 

Instances

Instances details
(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 # 
Instance details

Defined in Sqel.Product

Methods

prodSel :: arg -> Dd ('DdK 'SelAuto NoMods a ('Comp sel ('Prod 'Reg) 'Nest s)) Source #

type family MSelect (dd :: DdK) :: DdK where ... Source #

Equations

MSelect dd = Mod SelectAtom dd 

type family Mod (mod :: Type) (dd :: DdK) :: DdK where ... Source #

Equations

Mod mod dd = Mods '[mod] dd 

type family ModsR (mods :: [Type]) (dd :: DdK) :: DdK where ... Source #

Equations

ModsR new ('DdK sel old a s) = 'DdK sel (old ++ new) a s 

type family Mods (mods :: [Type]) (dd :: DdK) :: DdK where ... Source #

Equations

Mods new ('DdK sel old a s) = 'DdK sel (new ++ old) a s 

type family ProdPrimsNewtype (a :: Type) :: DdK where ... Source #

type family ProdPrims (a :: Type) :: DdK where ... Source #

Equations

ProdPrims a = ProdPrims' a (GCode a) (GDatatypeInfoOf a) 

type family TypeSel (tsel :: TSel) (dd :: DdK) :: DdK where ... Source #

Equations

TypeSel tsel ('DdK sel mods a ('Comp _ c i sub)) = 'DdK sel mods a ('Comp tsel c i sub) 

type family Name (name :: Symbol) (dd :: DdK) :: DdK where ... Source #

Equations

Name name ('DdK _ mods a s) = 'DdK ('SelSymbol name) mods a s 

type family PrimNewtype (name :: Symbol) (a :: Type) :: DdK where ... Source #

Equations

PrimNewtype name a = Mod (Newtype a (NewtypeWrapped a)) (Prim name a) 

type family Prim (name :: Symbol) (a :: Type) :: DdK where ... Source #

Equations

Prim name a = PrimSel ('SelSymbol name) a 

type family PrimUnused (a :: Type) :: DdK where ... Source #

Equations

PrimUnused a = PrimSel 'SelUnused a 

type family PrimSel (sel :: Sel) (a :: Type) :: DdK where ... Source #

Equations

PrimSel sel a = 'DdK sel NoMods a 'Prim 

type family a > b infixr 5 Source #

Instances

Instances details
type a > (b :: DdK) Source # 
Instance details

Defined in Sqel.Type

type a > (b :: DdK) = '[a, b]
type a > (b :: [DdK]) Source # 
Instance details

Defined in Sqel.Type

type a > (b :: [DdK]) = a ': b

type family base *> sub infix 4 Source #

Instances

Instances details
type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: DdK) Source # 
Instance details

Defined in Sqel.Type

type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: DdK) = 'DdK sel mods a ('Comp tsel c i '[sub])
type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: [DdK]) Source # 
Instance details

Defined in Sqel.Type

type ('DdK sel mods a ('Comp tsel c i ('[] :: [DdK]))) *> (sub :: [DdK]) = 'DdK sel mods a ('Comp tsel c i sub)

type family Merge (dd :: DdK) :: DdK where ... Source #

Equations

Merge ('DdK sel mods a ('Comp tsel c _ sub)) = 'DdK sel mods a ('Comp tsel c 'Merge sub) 
Merge s = s 

type family Prod (a :: Type) :: DdK where ... Source #

Equations

Prod a = 'DdK 'SelAuto NoMods a ('Comp ('TSel 'DefaultPrefix (DataName a)) ('Prod 'Reg) 'Nest '[]) 

merge :: Dd s -> Dd (Merge s) Source #

type IndexColumnWith prefix name = 'DdK ('SelIndex prefix name) NoMods Int64 'Prim Source #

column :: Mods p -> Dd ('DdK 'SelAuto p a 'Prim) Source #

mods :: SymNP p ps => p -> Mods ps Source #

primMod :: p -> Dd ('DdK 'SelAuto '[p] a 'Prim) Source #

primMods :: SymNP p ps => p -> Dd ('DdK 'SelAuto ps a 'Prim) Source #

prim :: forall a. Dd ('DdK 'SelAuto NoMods a 'Prim) Source #

ignore :: forall a. Dd ('DdK 'SelUnused '[Ignore] a 'Prim) Source #

primNewtype :: forall a w err. err ~ NewtypeError => UnwrapNewtype err a w => Dd ('DdK 'SelAuto '[Newtype a w] a 'Prim) Source #

primCoerce :: forall a w. Coercible 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 #

primNullable :: forall a. Dd ('DdK 'SelAuto '[Nullable] (Maybe a) 'Prim) Source #

primAs :: forall name a. KnownSymbol name => Dd ('DdK ('SelSymbol name) '[] 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 #

prims :: forall (a :: Type) (s :: [DdK]). MkPrims (PrimProd a) s => Prims a s Source #

primNewtypes :: forall (a :: Type) (s :: [DdK]). MkPrimNewtypes (PrimProd a) s => Prims a s Source #

prod :: Product a arg s => arg -> Dd 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 #

con :: ConColumn a arg s => arg -> Dd s Source #

sum :: Sum a arg s => arg -> Dd s Source #

sumWith :: SumWith a isel imods arg s => Dd ('DdK isel imods Int64 'Prim) -> 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 #

data Uid i a Source #

Constructors

Uid i a 

Instances

Instances details
Functor (Uid i) Source # 
Instance details

Defined in Sqel.Data.Uid

Methods

fmap :: (a -> b) -> Uid i a -> Uid i b #

(<$) :: a -> Uid i b -> Uid i a #

(FromJSON a, FromJSON i) => FromJSON (Uid i a) Source # 
Instance details

Defined in Sqel.Data.Uid

Methods

parseJSON :: Value -> Parser (Uid i a) #

parseJSONList :: Value -> Parser [Uid i a] #

(ToJSON a, ToJSON i) => ToJSON (Uid i a) Source # 
Instance details

Defined in Sqel.Data.Uid

Methods

toJSON :: Uid i a -> Value #

toEncoding :: Uid i a -> Encoding #

toJSONList :: [Uid i a] -> Value #

toEncodingList :: [Uid i a] -> Encoding #

Generic (Uid i a) Source # 
Instance details

Defined in Sqel.Data.Uid

Associated Types

type Rep (Uid i a) :: Type -> Type #

Methods

from :: Uid i a -> Rep (Uid i a) x #

to :: Rep (Uid i a) x -> Uid i a #

(Show i, Show a) => Show (Uid i a) Source # 
Instance details

Defined in Sqel.Data.Uid

Methods

showsPrec :: Int -> Uid i a -> ShowS #

show :: Uid i a -> String #

showList :: [Uid i a] -> ShowS #

(Eq i, Eq a) => Eq (Uid i a) Source # 
Instance details

Defined in Sqel.Data.Uid

Methods

(==) :: Uid i a -> Uid i a -> Bool #

(/=) :: Uid i a -> Uid i a -> Bool #

CompName a sel => CompName (Uid i a) sel Source # 
Instance details

Defined in Sqel.Comp

Methods

compName :: TSelW sel Source #

type Rep (Uid i a) Source # 
Instance details

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 #

pk :: AddMod PrimaryKey s0 s1 => Dd s0 -> Dd s1 Source #

nullable :: forall s0 s1 s2. AddMod Nullable s0 s1 => MkNullable s1 s2 => Dd s0 -> Dd s2 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 #

pgDefault :: AddMod PgDefault s0 s1 => Sql -> Dd s0 -> Dd s1 Source #

data Ignore Source #

Instances

Instances details
Generic Ignore Source # 
Instance details

Defined in Sqel.Data.Mods

Associated Types

type Rep Ignore :: Type -> Type #

Methods

from :: Ignore -> Rep Ignore x #

to :: Rep Ignore x -> Ignore #

Show Ignore Source # 
Instance details

Defined in Sqel.Data.Mods

Eq Ignore Source # 
Instance details

Defined in Sqel.Data.Mods

Methods

(==) :: Ignore -> Ignore -> Bool #

(/=) :: Ignore -> Ignore -> Bool #

ReifyPrimCodec Encoder (Ignore ': ps) (a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (Ignore ': ps) -> Encoder a Source #

ReifyPrimCodec FullCodec (Ignore ': ps) (a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (Ignore ': ps) -> FullCodec a Source #

type Rep Ignore Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep Ignore = D1 ('MetaData "Ignore" "Sqel.Data.Mods" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "Ignore" 'PrefixI 'False) (U1 :: Type -> Type))

data Newtype a w Source #

Instances

Instances details
ReifyPrimName w mods => ReifyPrimName (a :: Type) (Newtype a w ': mods) Source # 
Instance details

Defined in Sqel.ReifyDd

Methods

reifyPrimName :: NP I (Newtype a w ': mods) -> PgPrimName Source #

ReifyPrimCodec Value mods w => ReifyPrimCodec Value (Newtype a w ': mods) (a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (Newtype a w ': mods) -> Value a Source #

(ReifyPrimCodec c mods w, Invariant c) => ReifyPrimCodec (c :: Type -> Type) (Newtype a w ': mods) (a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (Newtype a w ': mods) -> c a Source #

(MkPrimNewtypes as s, err ~ NewtypeError, UnwrapNewtype err a w) => MkPrimNewtypes (a ': as :: [Type]) ('DdK 'SelAuto '[Newtype a w] a 'Prim ': s) Source # 
Instance details

Defined in Sqel.Prim

Methods

mkPrimNewtypes :: NP Dd ('DdK 'SelAuto '[Newtype a w] a 'Prim ': s) Source #

Generic (Newtype a w) Source # 
Instance details

Defined in Sqel.Data.Mods

Associated Types

type Rep (Newtype a w) :: Type -> Type #

Methods

from :: Newtype a w -> Rep (Newtype a w) x #

to :: Rep (Newtype a w) x -> Newtype a w #

Show (Newtype a w) Source # 
Instance details

Defined in Sqel.Data.Mods

Methods

showsPrec :: Int -> Newtype a w -> ShowS #

show :: Newtype a w -> String #

showList :: [Newtype a w] -> ShowS #

type Rep (Newtype a w) Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep (Newtype a w) = D1 ('MetaData "Newtype" "Sqel.Data.Mods" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "Newtype" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> w)) :*: S1 ('MetaSel ('Just "wrap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> a))))

data SetTableName Source #

Instances

Instances details
IsString SetTableName Source # 
Instance details

Defined in Sqel.Data.Mods

Generic SetTableName Source # 
Instance details

Defined in Sqel.Data.Mods

Associated Types

type Rep SetTableName :: Type -> Type #

Show SetTableName Source # 
Instance details

Defined in Sqel.Data.Mods

Eq SetTableName Source # 
Instance details

Defined in Sqel.Data.Mods

Ord SetTableName Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep SetTableName Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep SetTableName = D1 ('MetaData "SetTableName" "Sqel.Data.Mods" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "SetTableName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSetTableName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PgTableName)))

data ArrayColumn f Source #

Instances

Instances details
(ReifyPrimCodec ValueCodec ps a, Foldable f, ArrayDecoder f a) => ReifyPrimCodec FullCodec (ArrayColumn f ': ps) (f a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (ArrayColumn f ': ps) -> FullCodec (f a) Source #

(ReifyPrimCodec ValueCodec ps a, Foldable f, ArrayDecoder f a) => ReifyPrimCodec ValueCodec (ArrayColumn f ': ps) (f a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (ArrayColumn f ': ps) -> ValueCodec (f a) Source #

ReifyPrimName a mods => ReifyPrimName (f a :: Type) (ArrayColumn f ': mods) Source # 
Instance details

Defined in Sqel.ReifyDd

Methods

reifyPrimName :: NP I (ArrayColumn f ': mods) -> PgPrimName Source #

Generic (ArrayColumn f) Source # 
Instance details

Defined in Sqel.Data.Mods

Associated Types

type Rep (ArrayColumn f) :: Type -> Type #

Methods

from :: ArrayColumn f -> Rep (ArrayColumn f) x #

to :: Rep (ArrayColumn f) x -> ArrayColumn f #

Show (ArrayColumn f) Source # 
Instance details

Defined in Sqel.Data.Mods

Eq (ArrayColumn f) Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep (ArrayColumn f) Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep (ArrayColumn f) = D1 ('MetaData "ArrayColumn" "Sqel.Data.Mods" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "ArrayColumn" 'PrefixI 'False) (U1 :: Type -> Type))

data ReadShowColumn Source #

Instances

Instances details
Generic ReadShowColumn Source # 
Instance details

Defined in Sqel.Data.Mods

Associated Types

type Rep ReadShowColumn :: Type -> Type #

Show ReadShowColumn Source # 
Instance details

Defined in Sqel.Data.Mods

Eq ReadShowColumn Source # 
Instance details

Defined in Sqel.Data.Mods

(Show a, Read a) => ReifyPrimCodec FullCodec (ReadShowColumn ': ps) (a :: TYPE LiftedRep) Source # 
Instance details

Defined in Sqel.ReifyCodec

(Show a, Read a) => ReifyPrimCodec ValueCodec (ReadShowColumn ': ps) (a :: TYPE LiftedRep) Source # 
Instance details

Defined in Sqel.ReifyCodec

type Rep ReadShowColumn Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep ReadShowColumn = D1 ('MetaData "ReadShowColumn" "Sqel.Data.Mods" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "ReadShowColumn" 'PrefixI 'False) (U1 :: Type -> Type))

data EnumColumn Source #

Instances

Instances details
Generic EnumColumn Source # 
Instance details

Defined in Sqel.Data.Mods

Associated Types

type Rep EnumColumn :: Type -> Type #

Show EnumColumn Source # 
Instance details

Defined in Sqel.Data.Mods

Eq EnumColumn Source # 
Instance details

Defined in Sqel.Data.Mods

(Show a, EnumTable a) => ReifyPrimCodec FullCodec (EnumColumn ': ps) (a :: TYPE LiftedRep) Source # 
Instance details

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 # 
Instance details

Defined in Sqel.ReifyCodec

type Rep EnumColumn Source # 
Instance details

Defined in Sqel.Data.Mods

type Rep EnumColumn = D1 ('MetaData "EnumColumn" "Sqel.Data.Mods" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "EnumColumn" 'PrefixI 'False) (U1 :: Type -> Type))

data PgDefault Source #

Instances

Instances details
Show PgDefault Source # 
Instance details

Defined in Sqel.Data.Mods

ColumnConstraint PgDefault Source # 
Instance details

Defined in Sqel.ColumnConstraints

data PrimaryKey Source #

Instances

Instances details
Show PrimaryKey Source # 
Instance details

Defined in Sqel.Data.Mods

ColumnConstraint PrimaryKey Source # 
Instance details

Defined in Sqel.ColumnConstraints

data Unique Source #

Instances

Instances details
Show Unique Source # 
Instance details

Defined in Sqel.Data.Mods

ColumnConstraint Unique Source # 
Instance details

Defined in Sqel.ColumnConstraints

data Nullable Source #

Instances

Instances details
Show Nullable Source # 
Instance details

Defined in Sqel.Data.Mods

ColumnConstraint Nullable Source # 
Instance details

Defined in Sqel.ColumnConstraints

ReifyPrimCodec Value ps a => ReifyPrimCodec Encoder (Nullable ': ps) (Maybe a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (Nullable ': ps) -> Encoder (Maybe a) Source #

ReifyPrimCodec ValueCodec ps a => ReifyPrimCodec FullCodec (Nullable ': ps) (Maybe a :: Type) Source # 
Instance details

Defined in Sqel.ReifyCodec

Methods

reifyPrimCodec :: NP I (Nullable ': ps) -> FullCodec (Maybe a) Source #

ReifyPrimName a mods => ReifyPrimName (Maybe a :: Type) (Nullable ': mods) Source # 
Instance details

Defined in Sqel.ReifyDd

Methods

reifyPrimName :: NP I (Nullable ': mods) -> PgPrimName Source #

type NoMods = '[] Source #

data Order Source #

Constructors

Asc 
Desc 
Using Text 

Instances

Instances details
Generic Order Source # 
Instance details

Defined in Sqel.Data.Order

Associated Types

type Rep Order :: Type -> Type #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

Show Order Source # 
Instance details

Defined in Sqel.Data.Order

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

Eq Order Source # 
Instance details

Defined in Sqel.Data.Order

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

ToSql Order Source # 
Instance details

Defined in Sqel.Data.Order

Methods

toSql :: Order -> Sql Source #

type Rep Order Source # 
Instance details

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 #

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 #

Minimal complete definition

checkedProjection

Instances

Instances details
(MatchProjection proj table match, CheckedProjection' match proj) => CheckedProjection proj table Source # 
Instance details

Defined in Sqel.PgType

Methods

checkedProjection :: Dd proj -> ProjectionWitness (DdType proj) (DdType table) Source #

class MkTableSchema table where Source #

Methods

tableSchema :: Dd table -> TableSchema (DdType table) Source #

Instances

Instances details
(ReifyDd table, ReifyCodec FullCodec table (DdType table)) => MkTableSchema table Source # 
Instance details

Defined in Sqel.PgType

Methods

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 #

type EmptyQuery = 'DdK ('SelSymbol "") NoMods () ('Comp ('TSel 'DefaultPrefix "") ('Prod 'Reg) 'Nest '[]) Source #

class CheckQuery query table where Source #

Methods

checkQuery :: Dd query -> Dd table -> QuerySchema (DdType query) (DdType table) Source #

Instances

Instances details
(CheckedQuery query table, ReifyCodec Encoder query (DdType query)) => CheckQuery query table Source # 
Instance details

Defined in Sqel.Query

Methods

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

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

Defined in Sqel.Class.MatchView

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

data TableSchema a Source #

Instances

Instances details
Generic (TableSchema a) Source # 
Instance details

Defined in Sqel.Data.TableSchema

Associated Types

type Rep (TableSchema a) :: Type -> Type #

Methods

from :: TableSchema a -> Rep (TableSchema a) x #

to :: Rep (TableSchema a) x -> TableSchema a #

Show (TableSchema a) Source # 
Instance details

Defined in Sqel.Data.TableSchema

ToSql (Create (TableSchema a)) Source # 
Instance details

Defined in Sqel.Data.TableSchema

Methods

toSql :: Create (TableSchema a) -> Sql Source #

ToSql (Select (TableSchema a)) Source # 
Instance details

Defined in Sqel.Data.TableSchema

Methods

toSql :: Select (TableSchema a) -> Sql Source #

type Rep (TableSchema a) Source # 
Instance details

Defined in Sqel.Data.TableSchema

type Rep (TableSchema a) = D1 ('MetaData "TableSchema" "Sqel.Data.TableSchema" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "TableSchema" 'PrefixI 'True) (S1 ('MetaSel ('Just "pg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PgTable a)) :*: (S1 ('MetaSel ('Just "decoder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Row a)) :*: S1 ('MetaSel ('Just "encoder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Params a)))))

data Projection proj table Source #

Instances

Instances details
ToSql (Select (Projection proj table)) Source # 
Instance details

Defined in Sqel.Data.Projection

Methods

toSql :: Select (Projection proj table) -> Sql Source #

Generic (Projection proj table) Source # 
Instance details

Defined in Sqel.Data.Projection

Associated Types

type Rep (Projection proj table) :: Type -> Type #

Methods

from :: Projection proj table -> Rep (Projection proj table) x #

to :: Rep (Projection proj table) x -> Projection proj table #

Show (Projection proj table) Source # 
Instance details

Defined in Sqel.Data.Projection

Methods

showsPrec :: Int -> Projection proj table -> ShowS #

show :: Projection proj table -> String #

showList :: [Projection proj table] -> ShowS #

type Rep (Projection proj table) Source # 
Instance details

Defined in Sqel.Data.Projection

type Rep (Projection proj table) = D1 ('MetaData "Projection" "Sqel.Data.Projection" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'False) (C1 ('MetaCons "Projection" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PgTable proj)) :*: S1 ('MetaSel ('Just "decoder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Row proj))) :*: (S1 ('MetaSel ('Just "encoder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Params proj)) :*: (S1 ('MetaSel ('Just "table") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TableSchema table)) :*: S1 ('MetaSel ('Just "witness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProjectionWitness proj table))))))

data QuerySchema q a Source #

Instances

Instances details
ToSql (SelectQuery (QuerySchema q a)) Source # 
Instance details

Defined in Sqel.Data.QuerySchema

Generic (QuerySchema q a) Source # 
Instance details

Defined in Sqel.Data.QuerySchema

Associated Types

type Rep (QuerySchema q a) :: Type -> Type #

Methods

from :: QuerySchema q a -> Rep (QuerySchema q a) x #

to :: Rep (QuerySchema q a) x -> QuerySchema q a #

type Rep (QuerySchema q a) Source # 
Instance details

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))))