Hello, haskellers!

Here is HDBI-1.2 and some friends

There is class `FromRow` and `ToRow` from this version as well as
hdbi-conduit package. So, you can write your code like this:

{-# LANGUAGE
  OverloadedStrings
, TemplateHaskell
  #-}

import Control.Monad.IO.Class
import Data.Conduit
import Data.Conduit.HDBI
import Database.HDBI
import Database.HDBI.SQlite
import Language.Haskell.TH.HDBI
import qualified Data.Conduit.List as L
import qualified Data.Text as T

data Animal = Animal
              { aName :: T.Text
              , aAge :: Double
              , aWeight :: Double
              }

$(deriveFromRow ''Animal)
$(deriveToRow ''Animal)

animalsList :: [Animal]
animalsList = [Animal "Puffy" 15 0.3
              ,Animal "Puppy" 1 0.5
              ,Animal "Rex" 3 5
              ,Animal "Cat" 2 2.2]

foldAnimals :: (Animal, Animal, Double) -> Animal -> (Animal, Animal, Double)
foldAnimals (a, b, sumw) c@(Animal name age weight) = (newa, newb, sumw + 
weight)
  where
    newa | age > (aAge a) = c
         | otherwise = a
    newb | weight > (aWeight b) = c
         | otherwise = b
           

main = do
  (aged, weighted, wsum) <- runResourceT $ do
    (_, c) <- allocConnection $ connectSqlite3 ":memory:"
    liftIO $ do
      runRaw c "create table animals (name, age, weight)"
      runManyRows c "insert into animals(name, age, weight) values (?,?,?)" 
animalsList
    selectRawAllRows c "select name, age, weight from animals"
      $$ L.fold foldAnimals (none, none, 0)
  putStrLn $ "The most aged is " ++ (T.unpack $ aName aged)
    ++ " with age " ++ (show $ aAge aged)
  putStrLn $ "The most weighted is " ++ (T.unpack $ aName weighted)
    ++ " with weigh " ++ (show $ aWeight weighted)
  putStrLn $ "Total biomass is " ++ show wsum
  where
    none = Animal "" 0 0


the result will be:

The most aged is Puffy with age 15.0
The most weighted is Rex with weigh 5.0
Total biomass is 8.0

This is much more type safe way to work with raw SQL queries.

Links:

http://hackage.haskell.org/package/hdbi
http://hackage.haskell.org/package/hdbi-postgresql
http://hackage.haskell.org/package/hdbi-sqlite
http://hackage.haskell.org/package/hdbi-conduit

And you are welcome on GitHub:

https://github.com/s9gf4ult/hdbi
https://github.com/s9gf4ult/hdbi-postgresql
https://github.com/s9gf4ult/hdbi-sqlite
https://github.com/s9gf4ult/hdbi-conduit


-- 
Aleksey Uymanov <s9gf4...@gmail.com>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to