opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye

Description

An SQL-generating DSL targeting PostgreSQL. Allows Postgres queries to be written within Haskell in a typesafe and composable fashion.

You might like to look at

Synopsis

Documentation

data Nullability Source #

Constructors

NonNullable 
Nullable 
Instances
type A (H HT :: Arr Type (C k2) k2) (C ((,,) h o NN) :: C k2) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H HT :: Arr Type (C k2) k2) (C ((,,) h o NN) :: C k2) = h
type A (H NullsT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H NullsT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) = A (H NullsT :: Arr Type (C a) k2) (C t)
type A (H WT :: Arr Type (TC a) k2) (TC ((,) t Req) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H WT :: Arr Type (TC a) k2) (TC ((,) t Req) :: TC a) = A (H OT :: Arr Type (C a) k2) (C t)
type A (H OT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H OT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) = A (H OT :: Arr Type (C a) k2) (C t)
type A (H HT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H HT :: Arr Type (TC a) k2) (TC ((,) t b) :: TC a) = A (H HT :: Arr Type (C a) k2) (C t)
type A (H WT :: Arr Type (TC a) Type) (TC ((,) t Opt) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H WT :: Arr Type (TC a) Type) (TC ((,) t Opt) :: TC a) = Maybe (A (H OT :: Arr Type (C a) Type) (C t))
type A (H NullsT :: Arr Type (C Type) Type) (C ((,,) h o n) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H NullsT :: Arr Type (C Type) Type) (C ((,,) h o n) :: C Type) = Column (Nullable o)
type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) = Column (Nullable o)
type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o NN) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H OT :: Arr Type (C Type) Type) (C ((,,) h o NN) :: C Type) = Column o
type A (H HT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A (H HT :: Arr Type (C Type) Type) (C ((,,) h o N) :: C Type) = Maybe h

type family Field_ (a :: Nullability) b Source #

The name Column will be replaced by Field in version 0.7. The Field_, Field and FieldNullable types exist to help smooth the transition. We recommend that you use Field_, Field or FieldNullable instead of Column everywhere that it is sufficient.

Instances
type Field_ NonNullable a Source # 
Instance details

Defined in Opaleye.Field

type Field_ Nullable a Source # 
Instance details

Defined in Opaleye.Field

optionalRestrict Source #

Arguments

:: Default Unpackspec a a 
=> Select a

Input query

-> SelectArr (a -> Field SqlBool) (MaybeFields a)

If any rows of the input query satisfy the condition then return them (wrapped in "Just"). If none of them satisfy the condition then return a single row of "Nothing"

Convenient access to left/right join functionality. Performs a LEFT JOIN under the hood and has behaviour equivalent to the following Haskell function:

optionalRestrict :: [a] -> (a -> Bool) -> [Maybe a]
optionalRestrict xs p =
   case filter p xs of []  -> [Nothing]
                       xs' -> map Just xs'

For example,

> let l = [1, 10, 100, 1000] :: [Field SqlInt4]
> runSelect conn (proc () -> optionalRestrict (valuesSafe l) -< (.> 100000)) :: IO [Maybe Int]
[Nothing]

> runSelect conn (proc () -> optionalRestrict (valuesSafe l) -< (.> 15)) :: IO [Maybe Int]
[Just 100,Just 1000]

See the documentation of leftJoin for how to use optionalRestrict to replace leftJoin (and by symmetry, rightJoin).

leftJoin Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (fieldsL, nullableFieldsR)

Left join

We suggest you use optionalRestrict instead. Instead of writing "leftJoin qL qR cond" you can write

proc () -> do
  fieldsL <- qL -< ()
  maybeFieldsR <- optionalRestrict qR -< curry cond fieldsL
  returnA -< (fieldsL, maybeFieldsR)

Typically everything except the optionalRestrict line can be inlined in surrounding arrow notation. In such cases, readability and maintainibility increase dramatically.

leftJoinA Source #

Arguments

:: (Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) 
=> Select fieldsR

Right query

-> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR

Condition on which to join goes in, left join result comes out

We suggest you don't use this. optionalRestrict is probably better for your use case. leftJoinA is the same as except optionalRestrict without the return type wrapped in MaybeFields.

rightJoin Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, fieldsR)

Right join

We suggest you use optionalRestrict instead. See leftJoin for more details.

fullJoin Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, nullableFieldsR)

Full outer join

leftJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR) Source #

leftJoinAExplict :: Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR Source #

rightJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR) Source #

fullJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR) Source #

leftJoinInferrable Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsR ~ nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (fieldsL, nullableFieldsR)

Left join

Do not use. Will be deprecated in 0.7. Use optionalRestrict instead.

rightJoinInferrable Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Map Nulled fieldsL ~ nullableFieldsL) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, fieldsR)

Right join

Do not use. Will be deprecated in 0.7. Use optionalRestrict instead.

fullJoinInferrable Source #

Arguments

:: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsL ~ nullableFieldsL, Map Nulled fieldsR ~ nullableFieldsR) 
=> Select fieldsL

Left query

-> Select fieldsR

Right query

-> ((fieldsL, fieldsR) -> Field SqlBool)

Condition on which to join

-> Select (nullableFieldsL, nullableFieldsR)

Full outer join

Do not use. Will be deprecated in 0.7. Use rightJoinF instead.

data Nullspec fields fields' Source #

Instances
Profunctor Nullspec Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

dimap :: (a -> b) -> (c -> d) -> Nullspec b c -> Nullspec a d #

lmap :: (a -> b) -> Nullspec b c -> Nullspec a c #

rmap :: (b -> c) -> Nullspec a b -> Nullspec a c #

(#.) :: Coercible c b => q b c -> Nullspec a b -> Nullspec a c #

(.#) :: Coercible b a => Nullspec b c -> q a b -> Nullspec a c #

ProductProfunctor Nullspec Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

purePP :: b -> Nullspec a b #

(****) :: Nullspec a (b -> c) -> Nullspec a b -> Nullspec a c #

empty :: Nullspec () () #

(***!) :: Nullspec a b -> Nullspec a' b' -> Nullspec (a, a') (b, b') #

IsSqlType b => Default Nullspec a (Column b) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: Nullspec a (Column b) #

Functor (Nullspec a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

fmap :: (a0 -> b) -> Nullspec a a0 -> Nullspec a b #

(<$) :: a0 -> Nullspec a b -> Nullspec a a0 #

Applicative (Nullspec a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

pure :: a0 -> Nullspec a a0 #

(<*>) :: Nullspec a (a0 -> b) -> Nullspec a a0 -> Nullspec a b #

liftA2 :: (a0 -> b -> c) -> Nullspec a a0 -> Nullspec a b -> Nullspec a c #

(*>) :: Nullspec a a0 -> Nullspec a b -> Nullspec a b #

(<*) :: Nullspec a a0 -> Nullspec a b -> Nullspec a a0 #

data MaybeFields fields Source #

The Opaleye analogue of Maybe

Instances
Monad MaybeFields Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Functor MaybeFields Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

fmap :: (a -> b) -> MaybeFields a -> MaybeFields b #

(<$) :: a -> MaybeFields b -> MaybeFields a #

Applicative MaybeFields Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

pure :: a -> MaybeFields a #

(<*>) :: MaybeFields (a -> b) -> MaybeFields a -> MaybeFields b #

liftA2 :: (a -> b -> c) -> MaybeFields a -> MaybeFields b -> MaybeFields c #

(*>) :: MaybeFields a -> MaybeFields b -> MaybeFields b #

(<*) :: MaybeFields a -> MaybeFields b -> MaybeFields a #

Default Unpackspec a b => Default Unpackspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Default (WithNulls Binaryspec) a b => Default Binaryspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Default QueryRunner fields haskells => Default QueryRunner (MaybeFields fields) (Maybe haskells) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: QueryRunner (MaybeFields fields) (Maybe haskells) #

Default ValuesspecSafe a b => Default ValuesspecSafe (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Default IfPP a b => Default IfPP (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: IfPP (MaybeFields a) (MaybeFields b) #

Default EqPP a b => Default EqPP (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: EqPP (MaybeFields a) (MaybeFields b) #

(Default Constant a b, Default Nullspec a b) => Default Constant (Maybe a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: Constant (Maybe a) (MaybeFields b) #

Default (WithNulls Distinctspec) a b => Default Distinctspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

nothingFields :: Default Nullspec a a => MaybeFields a Source #

The Opaleye analogue of Nothing.

nothingFieldsOfTypeOf :: a -> MaybeFields a Source #

The Opaleye analogue of const Nothing. Can be useful to avoid type inference problems, because it doesn't pick up a type class constraint.

justFields :: a -> MaybeFields a Source #

The Opaleye analogue of Just. Equivalent to pure.

maybeFields :: Default IfPP b b => b -> (a -> b) -> MaybeFields a -> b Source #

The Opaleye analogue of maybe

fromMaybeFields :: Default IfPP b b => b -> MaybeFields b -> b Source #

The Opaleye analogue of fromMaybe

catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i a Source #

The Opaleye analogue of catMaybes

maybeFieldsExplicit :: IfPP b b' -> b -> (a -> b) -> MaybeFields a -> b' Source #

fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells) Source #

traverseMaybeFields Source #

Arguments

:: (Default Unpackspec a a, Default Unpackspec b b) 
=> SelectArr a b 
-> SelectArr (MaybeFields a) (MaybeFields b) 

traverseMaybeFields is analogous to Haskell's traverse :: (a -> [b]) -> Maybe a -> [Maybe b]. In particular, traverse has the following definition that generalises to traverseMaybeFields:

  • traverse _ Nothing = pure Nothing
  • traverse f (Just x) = fmap Just (f x)

data Cursor haskells Source #

Cursor within a transaction.

defaultFromField :: QueryRunnerColumnDefault sqlType haskellType => FromField sqlType haskellType Source #

fromPGSFromField :: FromField haskell => FromField pgType haskell Source #

fromPGSFieldParser :: FieldParser haskell -> FromField pgType haskell Source #

runSelect Source #

Arguments

:: Default FromFields fields haskells 
=> Connection 
-> Select fields 
-> IO [haskells] 

runSelect's use of the Default FromFields typeclass means that the compiler will have trouble inferring types. It is strongly recommended that you provide full type signatures when using runSelect.

Example type specialization:

runSelect :: Select (Field SqlInt4, Field SqlText) -> IO [(Int, String)]

Assuming the makeAdaptorAndInstance splice has been run for the product type Foo:

runSelect :: Select (Foo (Field SqlInt4) (Field SqlText) (Field SqlBool)
          -> IO [Foo Int String Bool]

runSelectTF Source #

Arguments

:: Default FromFields (rec O) (rec H) 
=> Connection 
-> Select (rec O) 
-> IO [rec H] 

runSelectTF has better type inference than runSelect but only works with "higher-kinded data" types.

runSelectFold Source #

Arguments

:: Default FromFields fields haskells 
=> Connection 
-> Select fields 
-> b 
-> (b -> haskells -> IO b) 
-> IO b 

runSelectFold streams the results of a query incrementally and consumes the results with a left fold.

This fold is not strict. The stream consumer is responsible for forcing the evaluation of its result to avoid space leaks.

unsafeFromField :: (b -> b') -> FromField sqlType b -> FromField sqlType' b' Source #

Use unsafeFromField to make an instance to allow you to run queries on your own datatypes. For example:

newtype Foo = Foo Int

instance QueryRunnerColumnDefault Foo Foo where
   defaultFromField = unsafeFromField Foo defaultFromField

It is "unsafe" because it does not check that the sqlType correctly corresponds to the Haskell type.

runSelectExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO [haskells] Source #

runSelectFoldExplicit :: FromFields fields haskells -> Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b Source #