Difference between revisions of "Cookbook/Databases access"

From HaskellWiki
Jump to navigation Jump to search
 
(→‎SQLite: add sqlite-simple)
 
(One intermediate revision by one other user not shown)
Line 1: Line 1:
 
There are two packages you can use to connect to MySQL, PostgreSQL, Sqlite3 and ODBC databases: [http://software.complete.org/software/projects/show/hdbc HDBC] and Hsql
 
There are two packages you can use to connect to MySQL, PostgreSQL, Sqlite3 and ODBC databases: [http://software.complete.org/software/projects/show/hdbc HDBC] and Hsql
   
= MySQL =
+
== MySQL ==
   
 
TODO
 
TODO
   
= PostgreSQL =
+
== PostgreSQL ==
   
 
TODO
 
TODO
   
= SQLite =
+
== SQLite ==
  +
 
Suppose you have created a 'test.db' database like this,
 
Suppose you have created a 'test.db' database like this,
   
$ sqlite3 test.db "create table t1 (t1key INTEGER PRIMARY KEY,data TEXT,num double,timeEnter DATE);"
+
$ sqlite3 test.db "create table t1 (t1key INTEGER PRIMARY KEY,data TEXT NOT NULL,num double,timeEnter DATE);"
   
 
$ sqlite3 test.db "insert into t1 (data,num) values ('This is sample data',3);"
 
$ sqlite3 test.db "insert into t1 (data,num) values ('This is sample data',3);"
Line 20: Line 21:
 
$ sqlite3 test.db "insert into t1 (data,num) values ('And a little more',9);"
 
$ sqlite3 test.db "insert into t1 (data,num) values ('And a little more',9);"
   
  +
=== HDBC ===
 
Using HDBC and HDBC-sqlite3 packages, you can connect and query it like this:
 
Using HDBC and HDBC-sqlite3 packages, you can connect and query it like this:
 
<haskell>
 
<haskell>
Line 43: Line 45:
   
 
[SqlString "3",SqlString "And a little more",SqlString "9.0",SqlNull]
 
[SqlString "3",SqlString "And a little more",SqlString "9.0",SqlNull]
  +
  +
=== sqlite-simple ===
  +
Using sqlite-simple:
  +
<haskell>
  +
{-# LANGUAGE OverloadedStrings #-}
  +
import Database.SQLite.Simple
  +
import Database.SQLite.Simple.FromRow
  +
import Database.SQLite.Simple.FromField
  +
import Data.Time.Clock (UTCTime)
  +
  +
main :: IO ()
  +
main = do
  +
conn <- open "test.db"
  +
rows <- query_ conn "SELECT * from t1" :: IO [(Int, String, Maybe Double, Maybe UTCTime)]
  +
mapM_ print rows
  +
close conn
  +
</haskell>
  +
  +
$ ghc --make sqlite.hs
  +
  +
$ ./sqlite
  +
  +
output:
  +
  +
(1,"This is sample data",Just 3.0,Nothing)
  +
  +
(2,"More sample data",Just 6.0,Nothing)
  +
  +
(3,"And a little more",Just 9.0,Nothing)

Latest revision as of 09:57, 29 March 2022

There are two packages you can use to connect to MySQL, PostgreSQL, Sqlite3 and ODBC databases: HDBC and Hsql

MySQL

TODO

PostgreSQL

TODO

SQLite

Suppose you have created a 'test.db' database like this,

$ sqlite3 test.db "create table t1 (t1key INTEGER PRIMARY KEY,data TEXT NOT NULL,num double,timeEnter DATE);"

$ sqlite3 test.db "insert into t1 (data,num) values ('This is sample data',3);"

$ sqlite3 test.db "insert into t1 (data,num) values ('More sample data',6);"

$ sqlite3 test.db "insert into t1 (data,num) values ('And a little more',9);"

HDBC

Using HDBC and HDBC-sqlite3 packages, you can connect and query it like this:

import Control.Monad
import Database.HDBC
import Database.HDBC.Sqlite3

main = do conn <- connectSqlite3 "test.db"
          rows <- quickQuery' conn "SELECT * from t1" []
          forM_ rows $ \row -> putStrLn $ show row


$ ghc --make sqlite.hs

$ ./sqlite

output:

[SqlString "1",SqlString "This is sample data",SqlString "3.0",SqlNull]

[SqlString "2",SqlString "More sample data",SqlString "6.0",SqlNull]

[SqlString "3",SqlString "And a little more",SqlString "9.0",SqlNull]

sqlite-simple

Using sqlite-simple:

{-# LANGUAGE OverloadedStrings #-}
import Database.SQLite.Simple
import Database.SQLite.Simple.FromRow
import Database.SQLite.Simple.FromField
import Data.Time.Clock (UTCTime)

main :: IO ()
main = do
  conn <- open "test.db"
  rows <- query_ conn "SELECT * from t1" :: IO [(Int, String, Maybe Double, Maybe UTCTime)]
  mapM_ print rows
  close conn

$ ghc --make sqlite.hs

$ ./sqlite

output:

(1,"This is sample data",Just 3.0,Nothing)

(2,"More sample data",Just 6.0,Nothing)

(3,"And a little more",Just 9.0,Nothing)