opaleye-sqlite-0.0.1.1: An SQL-generating DSL targeting SQLite
Safe HaskellNone
LanguageHaskell2010

Opaleye.SQLite.RunQuery

Synopsis

Documentation

runQuery :: Default QueryRunner columns haskells => Connection -> Query columns -> IO [haskells] Source #

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

Example type specialization:

runQuery :: Query (Column PGInt4, Column PGText) -> IO [(Column Int, Column String)]

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

runQuery :: Query (Foo (Column PGInt4) (Column PGText) (Column PGBool)
         -> IO [(Foo (Column Int) (Column String) (Column Bool)]

Opaleye types are converted to Haskell types based on instances of the QueryRunnerColumnDefault typeclass.

runQueryExplicit :: QueryRunner columns haskells -> Connection -> Query columns -> IO [haskells] Source #

queryRunnerColumn :: (Column a' -> Column a) -> (b -> b') -> QueryRunnerColumn a b -> QueryRunnerColumn a' b' Source #

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

newtype Foo = Foo Int
instance Default QueryRunnerColumn Foo Foo where
   def = queryRunnerColumn (unsafeCoerce :: Column Foo -> Column PGInt4) Foo def

data QueryRunner columns haskells Source #

Instances

Instances details
Profunctor QueryRunner Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

Methods

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

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

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

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

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

ProductProfunctor QueryRunner Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

Methods

purePP :: b -> QueryRunner a b #

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

empty :: QueryRunner () () #

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

SumProfunctor QueryRunner Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

Methods

(+++!) :: QueryRunner a b -> QueryRunner a' b' -> QueryRunner (Either a a') (Either b b') #

QueryRunnerColumnDefault a b => Default QueryRunner (Column a) b Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

Methods

def :: QueryRunner (Column a) b #

Functor (QueryRunner c) Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

Methods

fmap :: (a -> b) -> QueryRunner c a -> QueryRunner c b #

(<$) :: a -> QueryRunner c b -> QueryRunner c a #

Applicative (QueryRunner c) Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

Methods

pure :: a -> QueryRunner c a #

(<*>) :: QueryRunner c (a -> b) -> QueryRunner c a -> QueryRunner c b #

liftA2 :: (a -> b -> c0) -> QueryRunner c a -> QueryRunner c b -> QueryRunner c c0 #

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

(<*) :: QueryRunner c a -> QueryRunner c b -> QueryRunner c a #

data QueryRunnerColumn sqlType haskellType Source #

A QueryRunnerColumn pgType haskellType encodes how to turn a value of Postgres type pgType into a value of Haskell type haskellType. For example a value of type QueryRunnerColumn PGText String encodes how to turn a PGText result from the database into a Haskell String.