[Haskell-cafe] MonadBaseControl IO instance for conduits ?

2013-10-11 Thread Aleksey Uymanov
Hello Haskellers! 

Is it posible to create instance of MonadBaseControl IO (ConduitM i o m) ?

This would give a great posibility to catch exceptions just inside the
ConduitM monad with "lifted-base" package. And more, http-conduit's
`withManager` restricts base monad (which must be base for ConduitM)
with MonadBaseControl IO.


-- 
Aleksey Uymanov 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Announce: HDBI-1.2 and friends

2013-10-05 Thread Aleksey Uymanov
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 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Value-weak hash tables in Haskell ?

2013-08-10 Thread Aleksey Uymanov
Hello, haskellers.

Is there any package implementing magic hash tables weak in value? I
mean when the value is garbage collected, then this key+value
authomatically removes from the hash table.

-- 
Aleksey Uymanov 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Quick-check: how to generate arbitrary complex data?

2013-07-13 Thread Aleksey Uymanov
On Sat, 13 Jul 2013 10:10:39 +0200
martin  wrote:

> This requires HashedList to be a new type, right? So far my code only
> used type synonyms.
> 
> Does this mean I have to convert type synonyms into types in order to
> use QuickCheck?
> 
> Does this mean I have to "plan for QuickCheck" when I design my types?

You can still create your own Gen manually and have several generators
for different 'types'.

You will need to use 'forAll' combinator to perform the testing like this:


data A
type ListA = [A]
type OtherListA = [A]

genListA :: Gen ListA

genOtherListA :: Gen OtherListA

checkListA :: ListA -> Property

checkOtherListA :: OtherListA -> Property

prop1 = forAll genListA checkListA
prop2 = forAll genOtherListA checkOtherListA 

-- 
Aleksey Uymanov 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to debug stack overflow?

2013-06-22 Thread Aleksey Uymanov
On Sat, 22 Jun 2013 11:04:21 + (UTC)
Johannes Waldmann  wrote:

> What is the recommended method 

Try to use heap profiling. There is very high probability that the
problem is because of space leak.

-- 
Aleksey Uymanov 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe