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

Sqel.Prim

Documentation

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 #

type NewtypeError = ((Quoted "primNewtype" <> " declares a column for a newtype using ") <> Quoted "Generic") <> "." 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 #

newtype Prims a s Source #

Constructors

Prims 

Fields

Instances

Instances details
(a ~ b, CompColumn' meta ('Right 'SpecNP :: Either Void SpecType) fields a (NP Dd s0) s1) => CompColumn' meta ('Right 'SpecPrims :: Either Void SpecType) fields a (Prims b s0) s1 Source # 
Instance details

Defined in Sqel.Comp

Methods

compColumn' :: Prims b s0 -> NP Dd s1 Source #

Generic (Prims a s) Source # 
Instance details

Defined in Sqel.Prim

Associated Types

type Rep (Prims a s) :: Type -> Type #

Methods

from :: Prims a s -> Rep (Prims a s) x #

to :: Rep (Prims a s) x -> Prims a s #

type Rep (Prims a s) Source # 
Instance details

Defined in Sqel.Prim

type Rep (Prims a s) = D1 ('MetaData "Prims" "Sqel.Prim" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Prims" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPrims") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NP Dd s))))

class MkPrims as s | as -> s where Source #

Methods

mkPrims :: NP Dd s Source #

Instances

Instances details
MkPrims ('[] :: [k]) ('[] :: [DdK]) Source # 
Instance details

Defined in Sqel.Prim

Methods

mkPrims :: NP Dd '[] Source #

MkPrims as s => MkPrims (a ': as :: [Type]) ('DdK 'SelAuto ('[] :: [Type]) a 'Prim ': s) Source # 
Instance details

Defined in Sqel.Prim

Methods

mkPrims :: NP Dd ('DdK 'SelAuto '[] a 'Prim ': s) Source #

type family PrimProd (a :: Type) :: [Type] where ... Source #

Equations

PrimProd (ConCol _ _ _ as) = as 
PrimProd a = ProductGCode a 

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

class MkPrimNewtypes as s | as -> s where Source #

Instances

Instances details
MkPrimNewtypes ('[] :: [k]) ('[] :: [DdK]) Source # 
Instance details

Defined in Sqel.Prim

Methods

mkPrimNewtypes :: NP Dd '[] 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 #

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