beam-core-0.9.2.0: Type-safe, feature-complete SQL query and manipulation interface for Haskell
Safe HaskellNone
LanguageHaskell2010

Database.Beam.Query.Adhoc

Description

This module contains support for defining "ad-hoc" queries. That is queries on tables that do not necessarily have corresponding Beamable table types.

Synopsis

Documentation

class Adhoc structure where Source #

Associated Types

type AdhocTable structure (f :: Type -> Type) :: Type Source #

Methods

mkAdhocField :: (forall a. Text -> f a) -> structure -> AdhocTable structure f Source #

Instances

Instances details
Adhoc (NamedField a) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (NamedField a) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f a0) -> NamedField a -> AdhocTable (NamedField a) f Source #

(Adhoc a, Adhoc b) => Adhoc (a, b) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f a0) -> (a, b) -> AdhocTable (a, b) f Source #

(Adhoc a, Adhoc b, Adhoc c) => Adhoc (a, b, c) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b, c) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f a0) -> (a, b, c) -> AdhocTable (a, b, c) f Source #

(Adhoc a, Adhoc b, Adhoc c, Adhoc d) => Adhoc (a, b, c, d) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b, c, d) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f a0) -> (a, b, c, d) -> AdhocTable (a, b, c, d) f Source #

(Adhoc a, Adhoc b, Adhoc c, Adhoc d, Adhoc e) => Adhoc (a, b, c, d, e) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b, c, d, e) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f a0) -> (a, b, c, d, e) -> AdhocTable (a, b, c, d, e) f Source #

(Adhoc a, Adhoc b, Adhoc c, Adhoc d, Adhoc e, Adhoc f) => Adhoc (a, b, c, d, e, f) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b, c, d, e, f) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f0 a0) -> (a, b, c, d, e, f) -> AdhocTable (a, b, c, d, e, f) f0 Source #

(Adhoc a, Adhoc b, Adhoc c, Adhoc d, Adhoc e, Adhoc f, Adhoc g) => Adhoc (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b, c, d, e, f, g) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f0 a0) -> (a, b, c, d, e, f, g) -> AdhocTable (a, b, c, d, e, f, g) f0 Source #

(Adhoc a, Adhoc b, Adhoc c, Adhoc d, Adhoc e, Adhoc f, Adhoc g, Adhoc h) => Adhoc (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (a, b, c, d, e, f, g, h) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f0 a0) -> (a, b, c, d, e, f, g, h) -> AdhocTable (a, b, c, d, e, f, g, h) f0 Source #

data NamedField a Source #

Instances

Instances details
Adhoc (NamedField a) Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

Associated Types

type AdhocTable (NamedField a) f Source #

Methods

mkAdhocField :: (forall a0. Text -> f a0) -> NamedField a -> AdhocTable (NamedField a) f Source #

type AdhocTable (NamedField a) f Source # 
Instance details

Defined in Database.Beam.Query.Adhoc

type AdhocTable (NamedField a) f = f a

table_ :: forall be db structure s. (Adhoc structure, BeamSqlBackend be, Projectible be (AdhocTable structure (QExpr be s))) => Maybe Text -> Text -> structure -> Q be db s (AdhocTable structure (QExpr be s)) Source #

Introduce a table into a query without using the Beamable and Database machinery.

The first argument is the optional name of the schema the table is in and the second is the name of the table to source from.

The third argument is a tuple (or any nesting of tuples) where each value is of type NamedField (use field_ to construct).

The return value is a tuple (or any nesting of tuples) of the same shape as structure but where each value is a QExpr.

For example, to source from the table Table1, with fields Field1 (A boolean), Field2 (a timestamp), and Field3 (a string)

table_ Nothing "Table1" ( field_ @Bool "Field1", field_ @UTCTime "Field2", field_ @Text "Field3" )

field_ :: forall a. Text -> NamedField a Source #

Used to construct NamedFields, most often with an explicitly applied type.

The type can be omitted if the value is used unambiguously elsewhere.