quibble-core-0.1.0.1: Convenient SQL query language for Haskell (but only for single tables)
Safe HaskellNone
LanguageHaskell2010

Database.Quibble

Synopsis

Documentation

data Query (ctx :: Type) Source #

Instances

Instances details
DBRender (Query ctx) Source # 
Instance details

Defined in Database.Quibble

Methods

renderSQL :: Query ctx -> ByteString Source #

ctx ~ ctx' => DBWhere (Query ctx) ctx' Source # 
Instance details

Defined in Database.Quibble

Methods

whereCond :: Lens' (Query ctx) (Maybe (Expr ctx' Bool)) Source #

allRows :: Query ctx Source #

data RowsOf (ctx :: Type) Source #

Instances

Instances details
DBRender (RowsOf ctx) Source # 
Instance details

Defined in Database.Quibble

ctx ~ ctx' => DBWhere (RowsOf ctx) ctx' Source # 
Instance details

Defined in Database.Quibble

Methods

whereCond :: Lens' (RowsOf ctx) (Maybe (Expr ctx' Bool)) Source #

allRows :: RowsOf ctx Source #

class DBWhere qry ctx where Source #

Methods

whereCond :: Lens' qry (Maybe (Expr ctx Bool)) Source #

allRows :: qry Source #

A convenience function for when the user doesn't want to specify any conditions.

Instances

Instances details
ctx ~ ctx' => DBWhere (RowsOf ctx) ctx' Source # 
Instance details

Defined in Database.Quibble

Methods

whereCond :: Lens' (RowsOf ctx) (Maybe (Expr ctx' Bool)) Source #

allRows :: RowsOf ctx Source #

ctx ~ ctx' => DBWhere (Query ctx) ctx' Source # 
Instance details

Defined in Database.Quibble

Methods

whereCond :: Lens' (Query ctx) (Maybe (Expr ctx' Bool)) Source #

allRows :: Query ctx Source #

class DBRender a where Source #

Methods

renderSQL :: a -> ByteString Source #

Instances

Instances details
DBRender (RowsOf ctx) Source # 
Instance details

Defined in Database.Quibble

DBRender (Query ctx) Source # 
Instance details

Defined in Database.Quibble

Methods

renderSQL :: Query ctx -> ByteString Source #

newtype Expr (ctx :: Type) (ty :: Type) Source #

The constructor is exposed in case you need to unsafely construct | expressions. But you shouldn't rely on it too much.

Constructors

Expr 

Fields

Instances

Instances details
(KnownSymbol tbl, HasTable ctx tbl, HasColumn ctx col ty) => IsLabel col (Expr ctx ty) Source # 
Instance details

Defined in Database.Quibble

Methods

fromLabel :: Expr ctx ty #

(Show a, Fractional a) => Fractional (Expr ctx a) Source # 
Instance details

Defined in Database.Quibble

Methods

(/) :: Expr ctx a -> Expr ctx a -> Expr ctx a #

recip :: Expr ctx a -> Expr ctx a #

fromRational :: Rational -> Expr ctx a #

(Show a, Num a) => Num (Expr ctx a) Source # 
Instance details

Defined in Database.Quibble

Methods

(+) :: Expr ctx a -> Expr ctx a -> Expr ctx a #

(-) :: Expr ctx a -> Expr ctx a -> Expr ctx a #

(*) :: Expr ctx a -> Expr ctx a -> Expr ctx a #

negate :: Expr ctx a -> Expr ctx a #

abs :: Expr ctx a -> Expr ctx a #

signum :: Expr ctx a -> Expr ctx a #

fromInteger :: Integer -> Expr ctx a #

IsString (Expr ctx String) Source # 
Instance details

Defined in Database.Quibble

Methods

fromString :: String -> Expr ctx String #

IsString (Expr ctx Text) Source # 
Instance details

Defined in Database.Quibble

Methods

fromString :: String -> Expr ctx Text #

IsString (Expr ctx Text) Source # 
Instance details

Defined in Database.Quibble

Methods

fromString :: String -> Expr ctx Text #

IsString (Expr ctx ByteString) Source # 
Instance details

Defined in Database.Quibble

Methods

fromString :: String -> Expr ctx ByteString #

IsString (Expr ctx ByteString) Source # 
Instance details

Defined in Database.Quibble

Methods

fromString :: String -> Expr ctx ByteString #

data SortExpr (ctx :: Type) Source #

You can think of this as a wrapper around Expr that adds sorting direction. | Unfortunately, we can't allow ASC NULLS LAST or friends here because that's | not portable across database.

class KnownSymbol tbl => HasTable (ctx :: Type) (tbl :: Symbol) | ctx -> tbl Source #

Allows us to lookup table name by type.

class KnownSymbol col => HasColumn (ctx :: Type) (col :: Symbol) (ty :: Type) | ctx col -> ty Source #

Allows us to infer the column type from the table type and column name.

class Inline ty where Source #

Methods

inline :: ty -> Expr ctx ty Source #

Instances

Instances details
Inline Bool Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Bool -> Expr ctx Bool Source #

Inline Int16 Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Int16 -> Expr ctx Int16 Source #

Inline Int32 Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Int32 -> Expr ctx Int32 Source #

Inline Int64 Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Int64 -> Expr ctx Int64 Source #

Inline Word16 Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Word16 -> Expr ctx Word16 Source #

Inline Word32 Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Word32 -> Expr ctx Word32 Source #

Inline Word64 Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Word64 -> Expr ctx Word64 Source #

Inline String Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: String -> Expr ctx String Source #

Inline ByteString Source # 
Instance details

Defined in Database.Quibble

Inline ByteString Source # 
Instance details

Defined in Database.Quibble

Inline Text Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Text -> Expr ctx Text Source #

Inline Text Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: Text -> Expr ctx Text Source #

Inline UTCTime Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: UTCTime -> Expr ctx UTCTime Source #

Inline UUID Source # 
Instance details

Defined in Database.Quibble

Methods

inline :: UUID -> Expr ctx UUID Source #

query :: forall ctx. Query ctx Source #

A Query is meant to represent everything in a SELECT statement, other | than the columns selection and the joined tables. | This is meant to be used with -XTypeApplications, like query @Foo.

rowsOf :: forall ctx. RowsOf ctx Source #

A RowsOf is meant to represent the conditions of an UPDATE or DELETE. | This is meant to be used with -XTypeApplications, like rowsOf @Foo.

where_ :: DBWhere qry ctx => Expr ctx Bool -> qry -> qry Source #

Add a condition to the Query or RowsOf. If where_ is used multiple times, | the condition will be ANDed together. | | > rowsOf @Foo | > & where_ (...)

orderBy :: Seq (SortExpr ctx) -> Query ctx -> Query ctx Source #

Specify how the output should be sorted. If orderBy is used multiple times, | all sort expressions are concatenated together, with later calls having | lower sort precedence. | | -XOverloadedLists can help make specifying the list of sort expressions | simpler. | | > query @Foo | > & orderBy [asc col2]

limit :: Word64 -> Query ctx -> Query ctx Source #

Set the number of rows specified by a LIMIT. If limit is used multiple | times, only the result of the last call matters. | | > query @Foo | > & limit 50

offset :: Word64 -> Query ctx -> Query ctx Source #

Set the number of rows specified by an OFFSET. If offset is used | multiple times, only the result of the last call matters. | | > query Foo | > & offset 100 | | Note that in the general case, your query will still pay the cost of | looking up all the rows that were skipped! Be careful when using OFFSET@.

asc :: Expr ctx ty -> SortExpr ctx Source #

desc :: Expr ctx ty -> SortExpr ctx Source #

(.&&) :: Expr ctx Bool -> Expr ctx Bool -> Expr ctx Bool infixl 0 Source #

(.||) :: Expr ctx Bool -> Expr ctx Bool -> Expr ctx Bool infixl 1 Source #

(.==) :: Expr ctx a -> Expr ctx a -> Expr ctx Bool Source #

(./=) :: Expr ctx a -> Expr ctx a -> Expr ctx Bool Source #

isNull :: Expr ctx a -> Expr ctx Bool Source #

isNotNull :: Expr ctx a -> Expr ctx Bool Source #

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0