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

Opaleye.SQLite.Internal.RunQuery

Synopsis

Documentation

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.

Constructors

QueryRunnerColumn (Unpackspec (Column sqlType) ()) (FieldParser haskellType) 

data QueryRunner columns haskells Source #

Constructors

QueryRunner (Unpackspec columns ()) (columns -> RowParser haskells) (columns -> Bool)

Have we actually requested any columns? If we asked for zero columns then the SQL generator will have to put a dummy 0 into the SELECT statement, since we can't select zero columns. In that case we have to make sure we read a single Int.

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 #

class QueryRunnerColumnDefault pgType haskellType where Source #

A QueryRunnerColumnDefault pgType haskellType represents the default way to turn a pgType result from the database into a Haskell value of type haskelType.

Methods

queryRunnerColumnDefault :: QueryRunnerColumn pgType haskellType Source #

Instances

Instances details
QueryRunnerColumnDefault PGBytea ByteString Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGBytea ByteString Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGTimestamptz UTCTime Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGText Text Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGText Text Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGText String Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGInt4 Int Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGInt8 Int64 Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGFloat8 Double Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGDate Day Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault PGBool Bool Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery

QueryRunnerColumnDefault a b => QueryRunnerColumnDefault (Nullable a) (Maybe b) Source # 
Instance details

Defined in Opaleye.SQLite.Internal.RunQuery