Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- Basic tutorial
- Manipulation tutorial
- Advanced tutorial
- If you are confused about the
Default
typeclass, then the Default explanation
Synopsis
- module Opaleye.Adaptors
- module Opaleye.Aggregate
- module Opaleye.Binary
- module Opaleye.Column
- type Constant = ToFields
- newtype ToFields haskells fields = ToFields {
- constantExplicit :: haskells -> fields
- constant :: Default ToFields haskells fields => haskells -> fields
- toToFields :: (haskells -> fields) -> ToFields haskells fields
- module Opaleye.Distinct
- type Field a = Field_ 'NonNullable a
- type FieldNullable a = Field_ 'Nullable a
- data Nullability
- type family Field_ (a :: Nullability) b
- unsafeCoerceField :: Column a -> Column b
- module Opaleye.FunctionalJoin
- optionalRestrict :: Default Unpackspec a a => Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- leftJoin :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR)
- leftJoinA :: (Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR) => Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR
- rightJoin :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR)
- fullJoin :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Default NullMaker fieldsR nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR)
- leftJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR)
- leftJoinAExplict :: Unpackspec fieldsR fieldsR -> NullMaker fieldsR nullableFieldsR -> Select fieldsR -> SelectArr (fieldsR -> Field SqlBool) nullableFieldsR
- rightJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR)
- fullJoinExplicit :: Unpackspec fieldsL fieldsL -> Unpackspec fieldsR fieldsR -> NullMaker fieldsL nullableFieldsL -> NullMaker fieldsR nullableFieldsR -> Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR)
- optionalRestrictExplicit :: Unpackspec a a -> Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a)
- optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a)
- leftJoinInferrable :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsR nullableFieldsR, Map Nulled fieldsR ~ nullableFieldsR) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (fieldsL, nullableFieldsR)
- rightJoinInferrable :: (Default Unpackspec fieldsL fieldsL, Default Unpackspec fieldsR fieldsR, Default NullMaker fieldsL nullableFieldsL, Map Nulled fieldsL ~ nullableFieldsL) => Select fieldsL -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, fieldsR)
- fullJoinInferrable :: (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 -> Select fieldsR -> ((fieldsL, fieldsR) -> Field SqlBool) -> Select (nullableFieldsL, nullableFieldsR)
- module Opaleye.Label
- module Opaleye.Lateral
- module Opaleye.Manipulation
- data Nullspec fields fields'
- nullspecField :: IsSqlType b => Nullspec a (Column b)
- nullspecList :: Nullspec a [b]
- nullspecEitherLeft :: Nullspec a b -> Nullspec a (Either b b')
- nullspecEitherRight :: Nullspec a b' -> Nullspec a (Either b b')
- data MaybeFields fields
- nothingFields :: Default Nullspec a a => MaybeFields a
- nothingFieldsOfTypeOf :: a -> MaybeFields a
- justFields :: a -> MaybeFields a
- maybeFields :: Default IfPP b b => b -> (a -> b) -> MaybeFields a -> b
- fromMaybeFields :: Default IfPP b b => b -> MaybeFields b -> b
- maybeFieldsToSelect :: SelectArr (MaybeFields a) a
- catMaybeFields :: SelectArr i (MaybeFields a) -> SelectArr i a
- maybeFieldsExplicit :: IfPP b b' -> b -> (a -> b) -> MaybeFields a -> b'
- fromMaybeFieldsExplicit :: IfPP b b -> b -> MaybeFields b -> b
- nothingFieldsExplicit :: Nullspec a b -> MaybeFields b
- fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells)
- nullspecMaybeFields :: Nullspec a b -> Nullspec (MaybeFields a) (MaybeFields b)
- unpackspecMaybeFields :: Unpackspec a b -> Unpackspec (MaybeFields a) (MaybeFields b)
- valuesspecMaybeFields :: Valuesspec a b -> Valuesspec (MaybeFields a) (MaybeFields b)
- toFieldsMaybeFields :: Nullspec a b -> ToFields a b -> ToFields (Maybe a) (MaybeFields b)
- binaryspecMaybeFields :: WithNulls Binaryspec a b -> Binaryspec (MaybeFields a) (MaybeFields b)
- optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a)
- distinctspecMaybeFields :: WithNulls Distinctspec a b -> Distinctspec (MaybeFields a) (MaybeFields b)
- traverseMaybeFields :: (Default Unpackspec a a, Default Unpackspec b b) => SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b)
- traverseMaybeFieldsExplicit :: Unpackspec a a -> Unpackspec b b -> SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b)
- module Opaleye.Operators
- module Opaleye.Order
- module Opaleye.Internal.PGTypesExternal
- module Opaleye.QueryArr
- module Opaleye.RunQuery
- data Cursor haskells
- class DefaultFromField sqlType haskellType where
- defaultFromField :: FromField sqlType haskellType
- data FromFields columns haskells
- data FromField pgType haskellType
- fromPGSFromField :: FromField haskell => FromField pgType haskell
- fromPGSFieldParser :: FieldParser haskell -> FromField pgType haskell
- runSelect :: Default FromFields fields haskells => Connection -> Select fields -> IO [haskells]
- runSelectTF :: Default FromFields (rec O) (rec H) => Connection -> Select (rec O) -> IO [rec H]
- runSelectFold :: Default FromFields fields haskells => Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b
- unsafeFromField :: (b -> b') -> FromField sqlType b -> FromField sqlType' b'
- runSelectExplicit :: FromFields fields haskells -> Connection -> Select fields -> IO [haskells]
- runSelectFoldExplicit :: FromFields fields haskells -> Connection -> Select fields -> b -> (b -> haskells -> IO b) -> IO b
- runSelectI :: Default (Inferrable FromFields) fields haskells => Connection -> Select fields -> IO [haskells]
- module Opaleye.Sql
- module Opaleye.Select
- module Opaleye.SqlTypes
- module Opaleye.Table
- module Opaleye.ToFields
- module Opaleye.Values
Documentation
module Opaleye.Adaptors
module Opaleye.Aggregate
module Opaleye.Binary
module Opaleye.Column
newtype ToFields haskells fields Source #
ToFields | |
|
Instances
constant :: Default ToFields haskells fields => haskells -> fields Source #
Deprecated: Use toFields
instead. Will be removed in version 0.8.
toToFields :: (haskells -> fields) -> ToFields haskells fields Source #
module Opaleye.Distinct
type Field a = Field_ 'NonNullable a Source #
type FieldNullable a = Field_ 'Nullable a Source #
data Nullability Source #
Instances
type A ('H NullsT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H WT :: Arr Type (TC a) k2) ('TC '(t, Req) :: TC a) Source # | |
type A ('H OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) Source # | |
type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) Source # | |
type A ('H NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) Source # | |
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) Source # | |
type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
type family Field_ (a :: Nullability) b Source #
The name Column
will be replaced by Field
in version 0.8.
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 # | |
Defined in Opaleye.Field | |
type Field_ 'Nullable a Source # | |
Defined in Opaleye.Field |
unsafeCoerceField :: Column a -> Column b Source #
module Opaleye.FunctionalJoin
:: 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
).
:: (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
"
" you can writeleftJoin
qL qR cond
proc () -> do fieldsL <- qL -< () maybeFieldsR <-optionalRestrict
qR -<curry
cond fieldsLreturnA
-< (fieldsL, maybeFieldsR)
Typically everything except the optionalRestrict
line can be
inlined in surrounding arrow notation. In such cases, readability
and maintainibility increase dramatically.
:: (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
optionalRestrict
except without the return type wrapped in
MaybeFields
.
:: (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.
:: (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 #
optionalRestrictExplicit :: Unpackspec a a -> Select a -> SelectArr (a -> Field SqlBool) (MaybeFields a) Source #
optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a) Source #
:: (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 |
Deprecated: Use optionalRestrict
instead.
:: (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 |
Deprecated: Use optionalRestrict
instead.
:: (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 |
Deprecated: Use rightJoinF
instead.
module Opaleye.Label
module Opaleye.Lateral
module Opaleye.Manipulation
data Nullspec fields fields' Source #
Instances
Profunctor Nullspec Source # | |
Defined in Opaleye.Internal.Values 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Nullspec a b -> Nullspec a c # (.#) :: forall a b c q. Coercible b a => Nullspec b c -> q a b -> Nullspec a c # | |
ProductProfunctor Nullspec Source # | |
IsSqlType b => Default Nullspec a (Column b) Source # | |
Defined in Opaleye.Internal.Values | |
Functor (Nullspec a) Source # | |
Applicative (Nullspec a) Source # | |
Defined in Opaleye.Internal.Values |
nullspecList :: Nullspec a [b] Source #
data MaybeFields fields Source #
The Opaleye analogue of Maybe
Instances
nothingFields :: Default Nullspec a a => MaybeFields a Source #
The Opaleye analogue of Nothing
.
nothingFieldsOfTypeOf :: a -> MaybeFields a Source #
justFields :: a -> MaybeFields a Source #
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
maybeFieldsToSelect :: SelectArr (MaybeFields a) a Source #
The Opaleye analogue of maybeToList
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 #
fromMaybeFieldsExplicit :: IfPP b b -> b -> MaybeFields b -> b Source #
nothingFieldsExplicit :: Nullspec a b -> MaybeFields b Source #
fromFieldsMaybeFields :: FromFields fields haskells -> FromFields (MaybeFields fields) (Maybe haskells) Source #
nullspecMaybeFields :: Nullspec a b -> Nullspec (MaybeFields a) (MaybeFields b) Source #
unpackspecMaybeFields :: Unpackspec a b -> Unpackspec (MaybeFields a) (MaybeFields b) Source #
valuesspecMaybeFields :: Valuesspec a b -> Valuesspec (MaybeFields a) (MaybeFields b) Source #
toFieldsMaybeFields :: Nullspec a b -> ToFields a b -> ToFields (Maybe a) (MaybeFields b) Source #
binaryspecMaybeFields :: WithNulls Binaryspec a b -> Binaryspec (MaybeFields a) (MaybeFields b) Source #
optionalExplicit :: Unpackspec a a -> SelectArr i a -> SelectArr i (MaybeFields a) Source #
distinctspecMaybeFields :: WithNulls Distinctspec a b -> Distinctspec (MaybeFields a) (MaybeFields b) Source #
:: (Default Unpackspec a a, Default Unpackspec b b) | |
=> SelectArr a b | |
-> SelectArr (MaybeFields a) (MaybeFields b) |
traverseMaybeFields
is analogous to Haskell's
. In particular,
traverse
:: (a -> [b]) -> Maybe
a
-> [Maybe
b]traverse
has the following definition that
generalises to traverseMaybeFields
:
traverse _ Nothing = pure Nothing
traverse f (Just x) = fmap Just (f x)
traverseMaybeFieldsExplicit :: Unpackspec a a -> Unpackspec b b -> SelectArr a b -> SelectArr (MaybeFields a) (MaybeFields b) Source #
module Opaleye.Operators
module Opaleye.Order
module Opaleye.QueryArr
module Opaleye.RunQuery
class DefaultFromField sqlType haskellType where Source #
A DefaultFromField
sqlType
haskellType
represents
the default way to turn a sqlType
result from the database into a
Haskell value of type haskellType
.
"DefaultFromField
sqlType
haskellType
" corresponds
to postgresql-simple's "FromField
haskellType
".
Creating an instance of DefaultFromField
for your own types is
necessary for retrieving those types from the database.
You should use one of the three methods below for writing a
DefaultFromField
instance.
- If you already have a postgresql-simple
FromField
instance for yourhaskellType
, usefromPGSFromField
. (This is how most of the built-in instances are defined.) - If you don't have a postgresql-simple
FromField
instance, but you do have an OpaleyeFromField
value for the type it wraps useunsafeFromField
if possible. See the documentation forunsafeFromField
for an example. - If you have a more complicated case, but not a
FromField
instance, write aFieldParser
for your type and usefromPGSFieldParser
. You can also add aFromField
instance using this.
defaultFromField :: FromField sqlType haskellType Source #
Instances
data FromFields columns haskells Source #
A FromFields
specifies how to convert Postgres values (fields
)
into Haskell values (haskells
). Most likely you will never need
to create on of these or handle one directly. It will be provided
for you by the Default
FromFields
instance.
"FromFields
fields
haskells
" corresponds to
postgresql-simple's "RowParser
haskells
". "Default
FromFields
columns
haskells
" corresponds to
postgresql-simple's "FromRow
haskells
".
Instances
data FromField pgType haskellType Source #
A FromField
sqlType
haskellType
encodes how to turn
a value of Postgres type sqlType
into a value of Haskell type
haskellType
. For example a value of type FromField
SqlText
String
encodes how to turn a SqlText
result from the
database into a Haskell String
.
"FromField
sqlType
haskellType
" corresponds to
postgresql-simple's "FieldParser
haskellType
".
Instances
fromPGSFromField :: FromField haskell => FromField pgType haskell Source #
fromPGSFieldParser :: FieldParser haskell -> FromField pgType haskell Source #
:: Default FromFields fields haskells | |
=> Connection | |
-> Select fields | |
-> IO [haskells] |
runSelect
's use of the
typeclass means that the
compiler will have trouble inferring types. It is strongly
recommended that you provide full type signatures when using
Default
FromFields
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]
:: 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.
:: 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 DefaultFromField 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 #
:: Default (Inferrable FromFields) fields haskells | |
=> Connection | |
-> Select fields | |
-> IO [haskells] |
Version of runSelect
with better type inference
module Opaleye.Sql
module Opaleye.Select
module Opaleye.SqlTypes
module Opaleye.Table
module Opaleye.ToFields
module Opaleye.Values