relational-query-0.12.2.0: Typeful, Modular, Relational, algebraic query engine

Copyright2017 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellSafe
LanguageHaskell2010

Database.Relational.ProjectableClass

Contents

Description

This module provides interfaces to preserve constraints of direct product projections.

Synopsis

Literal SQL terms

class LiteralSQL a where Source #

LiteralSQL a is implicit rule to derive function to convert from haskell record type a into SQL literal row-value.

Generic programming (https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#generic-programming) with default signature is available for LiteralSQL class, so you can make instance like below:

  {-# LANGUAGE DeriveGeneric #-}
  import GHC.Generics (Generic)
  --
  data Foo = Foo { ... } deriving Generic
  instance LiteralSQL Foo

Minimal complete definition

Nothing

Methods

showLiteral' :: a -> DList StringSQL Source #

showLiteral' :: (Generic a, GLiteralSQL (Rep a)) => a -> DList StringSQL Source #

Instances
LiteralSQL Bool Source #

Constant SQL terms of Bool.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Char Source #

Constant SQL terms of Char.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Double Source #

Constant SQL terms of Double. Caution for floating-point error rate.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Float Source #

Constant SQL terms of Float. Caution for floating-point error rate.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int Source #

Constant SQL terms of Int. Use this carefully, because this is architecture dependent size of integer type.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int8 Source #

Constant SQL terms of Int8.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int16 Source #

Constant SQL terms of Int16.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int32 Source #

Constant SQL terms of Int32.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Int64 Source #

Constant SQL terms of Int64.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Integer Source # 
Instance details

Defined in Database.Relational.Pure

LiteralSQL Word Source #

Constant SQL terms of Word. Use this carefully, because this is architecture dependent size of integer type.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Word8 Source #

Constant SQL terms of Word8.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Word16 Source #

Constant SQL terms of Word16.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Word32 Source #

Constant SQL terms of Word32.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Word64 Source #

Constant SQL terms of Word64.

Instance details

Defined in Database.Relational.Pure

LiteralSQL () Source #

Constant SQL terms of '()'.

Instance details

Defined in Database.Relational.Pure

LiteralSQL String Source #

Constant SQL terms of String.

Instance details

Defined in Database.Relational.Pure

LiteralSQL ByteString Source #

Constant SQL terms of ByteString.

Instance details

Defined in Database.Relational.PureUTF8

LiteralSQL ByteString Source #

Constant SQL terms of ByteString.

Instance details

Defined in Database.Relational.PureUTF8

LiteralSQL Text Source #

Constant SQL terms of Text.

Instance details

Defined in Database.Relational.Pure

LiteralSQL Text Source #

Constant SQL terms of Text.

Instance details

Defined in Database.Relational.Pure

LiteralSQL ZonedTime Source #

Constant SQL terms of ZonedTime. This generates ***NOT STANDARD*** SQL of TIMESTAMPTZ literal.

Instance details

Defined in Database.Relational.NonStandard.PureTimestampTZ

LiteralSQL LocalTime Source #

Constant SQL terms of LocalTime.

Instance details

Defined in Database.Relational.Pure

LiteralSQL TimeOfDay Source #

Constant SQL terms of TimeOfDay.

Instance details

Defined in Database.Relational.Pure

LiteralSQL UTCTime Source #

Constant SQL terms of UTCTime. This generates ***NOT STANDARD*** SQL of TIMESTAMPTZ literal with UTC timezone.

Instance details

Defined in Database.Relational.NonStandard.PureTimestampTZ

LiteralSQL Day Source #

Constant SQL terms of Day.

Instance details

Defined in Database.Relational.Pure

(PersistableWidth a, LiteralSQL a) => LiteralSQL (Maybe a) Source #

Constant SQL terms of Maybe type. Width inference is required.

Instance details

Defined in Database.Relational.Pure

(LiteralSQL a1, LiteralSQL a2) => LiteralSQL (a1, a2) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3) => LiteralSQL (a1, a2, a3) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4) => LiteralSQL (a1, a2, a3, a4) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4, LiteralSQL a5) => LiteralSQL (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4, a5) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4, LiteralSQL a5, LiteralSQL a6) => LiteralSQL (a1, a2, a3, a4, a5, a6) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4, a5, a6) -> DList StringSQL Source #

(LiteralSQL a1, LiteralSQL a2, LiteralSQL a3, LiteralSQL a4, LiteralSQL a5, LiteralSQL a6, LiteralSQL a7) => LiteralSQL (a1, a2, a3, a4, a5, a6, a7) Source # 
Instance details

Defined in Database.Relational.TupleInstances

Methods

showLiteral' :: (a1, a2, a3, a4, a5, a6, a7) -> DList StringSQL Source #

showLiteral :: LiteralSQL a => a -> [StringSQL] Source #

Convert from haskell record to SQL literal row-value.

type StringSQL = Keyword Source #

String wrap type for SQL strings.

Deprecated.

type ShowConstantTermsSQL = LiteralSQL Source #

Deprecated: Use LiteralSQL instead of this.

Deprecated.

showConstantTermsSQL' :: ShowConstantTermsSQL a => a -> DList StringSQL Source #

Deprecated: Use showLiteral' instead of this.

showConstantTermsSQL :: ShowConstantTermsSQL a => a -> [StringSQL] Source #

Deprecated: Use showLiteral instead of this.

Deprecated.