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

Sqel.Data.SqlFragment

Documentation

newtype CommaSep a Source #

Constructors

CommaSep 

Fields

Instances

Instances details
Generic (CommaSep a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (CommaSep a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> CommaSep a -> ShowS #

show :: CommaSep a -> String #

showList :: [CommaSep a] -> ShowS #

Eq a => Eq (CommaSep a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: CommaSep a -> CommaSep a -> Bool #

(/=) :: CommaSep a -> CommaSep a -> Bool #

ToSql (CommaSep PgColumns) Source # 
Instance details

Defined in Sqel.Data.PgType

ToSql (CommaSep TableSelectors) Source # 
Instance details

Defined in Sqel.Data.PgType

ToSql a => ToSql (CommaSep [a]) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

toSql :: CommaSep [a] -> Sql Source #

type Rep (CommaSep a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (CommaSep a) = D1 ('MetaData "CommaSep" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "CommaSep" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCommaSep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Delete a Source #

Constructors

Delete 

Fields

Instances

Instances details
Generic (Delete a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Delete a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> Delete a -> ShowS #

show :: Delete a -> String #

showList :: [Delete a] -> ShowS #

Eq a => Eq (Delete a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Delete a -> Delete a -> Bool #

(/=) :: Delete a -> Delete a -> Bool #

ToSql (Delete (PgTable a)) Source # 
Instance details

Defined in Sqel.Data.PgType

Methods

toSql :: Delete (PgTable a) -> Sql Source #

type Rep (Delete a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Delete a) = D1 ('MetaData "Delete" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Delete" 'PrefixI 'True) (S1 ('MetaSel ('Just "unDelete") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype From a Source #

Constructors

From 

Fields

Instances

Instances details
Generic (From a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (From a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> From a -> ShowS #

show :: From a -> String #

showList :: [From a] -> ShowS #

Eq a => Eq (From a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: From a -> From a -> Bool #

(/=) :: From a -> From a -> Bool #

ToSql (From PgTableName) Source # 
Instance details

Defined in Sqel.Data.PgTypeName

type Rep (From a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (From a) = D1 ('MetaData "From" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "From" 'PrefixI 'True) (S1 ('MetaSel ('Just "unFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Insert a Source #

Constructors

Insert 

Fields

Instances

Instances details
Generic (Insert a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Insert a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> Insert a -> ShowS #

show :: Insert a -> String #

showList :: [Insert a] -> ShowS #

Eq a => Eq (Insert a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Insert a -> Insert a -> Bool #

(/=) :: Insert a -> Insert a -> Bool #

ToSql (Insert (PgTable a)) Source # 
Instance details

Defined in Sqel.Data.PgType

Methods

toSql :: Insert (PgTable a) -> Sql Source #

type Rep (Insert a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Insert a) = D1 ('MetaData "Insert" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Insert" 'PrefixI 'True) (S1 ('MetaSel ('Just "unInsert") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Into a Source #

Constructors

Into 

Fields

Instances

Instances details
Generic (Into a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Into a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> Into a -> ShowS #

show :: Into a -> String #

showList :: [Into a] -> ShowS #

Eq a => Eq (Into a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Into a -> Into a -> Bool #

(/=) :: Into a -> Into a -> Bool #

ToSql (Into PgTableName) Source # 
Instance details

Defined in Sqel.Data.PgTypeName

type Rep (Into a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Into a) = D1 ('MetaData "Into" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Into" 'PrefixI 'True) (S1 ('MetaSel ('Just "unInto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Returning a Source #

Constructors

Returning 

Fields

Instances

Instances details
Generic (Returning a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Returning a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Eq a => Eq (Returning a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Returning a -> Returning a -> Bool #

(/=) :: Returning a -> Returning a -> Bool #

ToSql (Returning (PgTable a)) Source # 
Instance details

Defined in Sqel.Data.PgType

Methods

toSql :: Returning (PgTable a) -> Sql Source #

type Rep (Returning a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Returning a) = D1 ('MetaData "Returning" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Returning" 'PrefixI 'True) (S1 ('MetaSel ('Just "unReturning") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Select a Source #

Constructors

Select 

Fields

Instances

Instances details
Generic (Select a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Select a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> Select a -> ShowS #

show :: Select a -> String #

showList :: [Select a] -> ShowS #

Eq a => Eq (Select a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Select a -> Select a -> Bool #

(/=) :: Select a -> Select a -> Bool #

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

Defined in Sqel.Data.PgType

Methods

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

ToSql (Select TableSelectors) Source # 
Instance details

Defined in Sqel.Data.PgType

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

Defined in Sqel.Data.Projection

Methods

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

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

Defined in Sqel.Data.TableSchema

Methods

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

type Rep (Select a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Select a) = D1 ('MetaData "Select" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Select" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSelect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype SelectQuery a Source #

Constructors

SelectQuery 

Fields

Instances

Instances details
Generic (SelectQuery a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (SelectQuery a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Eq a => Eq (SelectQuery a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

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

Defined in Sqel.Data.QuerySchema

type Rep (SelectQuery a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (SelectQuery a) = D1 ('MetaData "SelectQuery" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "SelectQuery" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSelectQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Update a Source #

Constructors

Update 

Fields

Instances

Instances details
Generic (Update a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Update a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> Update a -> ShowS #

show :: Update a -> String #

showList :: [Update a] -> ShowS #

Eq a => Eq (Update a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Update a -> Update a -> Bool #

(/=) :: Update a -> Update a -> Bool #

ToSql (Update (PgTable a)) Source # 
Instance details

Defined in Sqel.Data.PgType

Methods

toSql :: Update (PgTable a) -> Sql Source #

type Rep (Update a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Update a) = D1 ('MetaData "Update" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Update" 'PrefixI 'True) (S1 ('MetaSel ('Just "unUpdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

newtype Create a Source #

Constructors

Create 

Fields

Instances

Instances details
Generic (Create a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Associated Types

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

Methods

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

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

Show a => Show (Create a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

showsPrec :: Int -> Create a -> ShowS #

show :: Create a -> String #

showList :: [Create a] -> ShowS #

Eq a => Eq (Create a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

Methods

(==) :: Create a -> Create a -> Bool #

(/=) :: Create a -> Create a -> Bool #

ToSql (Create PgColumn) Source # 
Instance details

Defined in Sqel.Data.PgType

ToSql (Create PgColumns) Source # 
Instance details

Defined in Sqel.Data.PgType

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

Defined in Sqel.Data.PgType

Methods

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

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

Defined in Sqel.Data.TableSchema

Methods

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

type Rep (Create a) Source # 
Instance details

Defined in Sqel.Data.SqlFragment

type Rep (Create a) = D1 ('MetaData "Create" "Sqel.Data.SqlFragment" "sqel-0.0.1.0-5k4czMecwS553bFrfF1Jzu" 'True) (C1 ('MetaCons "Create" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSelect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))