sqlite-simple-interpolate: Interpolated SQLite queries via quasiquotation

[ bsd3, database, library ] [ Propose Tags ]

This package provides Quasiquoters for writing SQLite queries with inline interpolation of values. The values are interpolated using toField from sqlite-simple. See the README for more details.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Flags

Automatic Flags
NameDescriptionDefault
testsEnabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1, 0.1.1, 0.2.0.0
Change log CHANGELOG.md
Dependencies base (>=4.5 && <5), haskell-src-meta (>=0.6 && <0.9), mtl (>=2.1 && <2.3), parsec (>=3.1 && <3.2), sqlite-simple (>=0.1), template-haskell (>=2.16 && <2.19) [details]
License BSD-3-Clause
Copyright ©2022 ruby0b ©2019 Elliot Cameron
Author ruby0b
Maintainer ruby0b
Category Database
Home page https://github.com/ruby0b/sqlite-simple-interpolate
Source repo head: git clone git://github.com/ruby0b/sqlite-simple-interpolate.git
Uploaded by ruby0b at 2022-12-13T00:48:45Z
Distributions
Downloads 172 total (8 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]

Readme for sqlite-simple-interpolate-0.1.1

[back to package description]

sqlite-simple-interpolate

Write natural SQL statements in Haskell using QuasiQuoters!

{-# LANGUAGE QuasiQuotes #-}

module Main where

import Control.Exception (bracket)
import Data.Char (toLower)
import Data.Function ((&))
import qualified Database.SQLite.Simple as SQL
import Database.SQLite.Simple.QQ.Interpolated

table :: String
table = "people"

main :: IO ()
main = bracket (SQL.open ":memory:") SQL.close $ \conn -> do
  conn & [iexecute|CREATE TABLE !{table} (name TEXT, age INTEGER)|]

  conn & [iexecute|INSERT INTO !{table} VALUES ("clive", 40)|]
  -- you can always use 'isql' directly but you'll have to use uncurry:
  (uncurry $ SQL.execute conn) [isql|INSERT INTO !{table} VALUES ("clara", 32)|]

  ageSum <- conn & [ifold|SELECT age FROM !{table}|] 0 (\acc (SQL.Only x) -> pure (acc + x))
  print (ageSum :: Int)

  let limit = 1 :: Int
  ages <- conn & [iquery|SELECT age FROM !{table} WHERE name = ${map toLower "CLIVE"} LIMIT ${limit}|]
  print (ages :: [SQL.Only Int])

Acknowledgements

This library is a fork of postgresql-simple-interpolate, adapted for use with sqlite-simple.

The original itself is basically just a copy of the here package by Taylor M. Hedberg with slight modifications!