Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Jason Dagit
On Wed, Jul 7, 2010 at 1:16 PM, Michael Snoyman  wrote:

>
>
> * I wanted the SQLite backend to be the default backend that anyone could
> use, without library dependencies. It would be nice if HDBC-sqlite3 had an
> option to build against the sqlite3 amalgamation instead of system
> libraries. (In fact, it would be cool if that were the default, and system
> libraries the option.)
>

If only we had an RDBMS in pure Haskell :)

>
> * I'm not fond of the Convertible typeclass. In particular, it makes no
> distinction between conversions which are guaranteed to succeed (Int ->
> String) and conversions which might fail (String -> Int). As a result, the
> fromSql function can easily throw a runtime error. (For that matter, toSql
> could as well, but that is much less likely.)
>
> Hmm...yes, partial functions are no fun.  That sounds quite unpleasant.  I
would probably want to make a wrapper that can catch the exception and
returns an Either or Maybe type.


> * I would like to be able to explicitly finalize statements. I believe I've
> gotten some exceptions in the past when trying to close a database
> connection because some statements were not finalized, but I can't remember
> the details right now.
>
> * I don't like that the lazy versions of functions are the default, and you
> have to add the ' for strict. It's too easy to make mistakes with the
> results of a lazy database query. I would even go so far as to recommend
> removing them entirely, but I think most people will not like that.
>

These last two items are reasons to use Takusen.  The left fold enumerator
style of Takusen means that all resource allocation can be controlled by the
library, usually very precisely, and that lazy IO can be avoided.  We did
find one bug in the ODBC backend related to Takusen letting a finalizer run
too soon, but that's fixed in the darcs repo of the Takusen sources.  I've
asked Alistair to release a new version of Takusen with the fix, hopefully
that will happen soon.

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


Re: [Haskell-cafe] Suggestions for an MSc Project?

2010-07-07 Thread Han Joosten

Hi John

I am involved in a research project of the Open University in the
netherlands. We are working on a tool suite for Rule Based application
developement. This is a 100% Haskell project, with lots of oppertunities for
a good MSc project, depending on your specific interests. I'd be happy to
talk to you about the possibilities. 
If you are interested, send me a mail with details how I could get in touch:
han  joosten  atosorigin  com

cheers

Han.
-- 
View this message in context: 
http://old.nabble.com/Suggestions-for-an-MSc-Project--tp29067884p29100221.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] checking types with type families

2010-07-07 Thread C. McCann
On Sat, Jul 3, 2010 at 4:28 PM, Dan Doel  wrote:
> It's potentially not just a violation of intent, but of soundness. The
> following code doesn't actually work, but one could imagine it working:
>
>  class C a b | a -> b
>
>  instance C () a
>
>  -- Theoretically works because C a b, C a c implies that b ~ c
>  --
>  -- GHC says b doesn't match c, though.
>  f :: (C a b, C a c) => a -> (b -> r) -> c -> r
>  f x g y = g y

The funny part is that GHC eventually would decide they match, but not
until after it complains about (g y). For instance, if you do this:

f :: (C a b, C a c) => a -> (b -> r) -> c -> r
f x g y = undefined

...and load it into GHCi, it says the type is:

> :t f
f :: (C a c) => a -> (c -> r) -> c -> r

As far as I can tell, type variables in scope simultaneously that
"should" be equal because of fundeps will eventually be unified, but
too late to make use of it without using some sort of type class-based
indirection. This can lead to interesting results when combined with
UndecidableInstances. For instance, consider the following:

class C a b c | a b -> c where
c :: a -> c -> c
c = flip const

instance C () b (c, c)

f x = (c x ('a', 'b'), c x (True, False))

g :: (c, c) -> (c, c)
g = c ()

This works fine: Because "b" remains ambiguous, the "c" parameters
also remain distinct; yet for the same reason, "a" effectively
determines "c" anyway, such that g ends up with the type (forall c.
(c, c) -> (c, c)), rather than something like (forall c. c -> c) or
(forall b c. (C () b c) => c -> c). But if we remove the (seemingly
unused) parameter b from the fundep...

class C a b c | a -> c where

...GHC now, understandably enough, complains that it can't match Char
with Bool. It will still accept this:

f x = c x ('a', 'b')
g x = c x (True, False)

...but not if you add this as well:

h x = (f x, g x)

Or even this:

h = (f (), g ())

On the other hand, this is still A-OK:

f = c () ('a', 'b')
g = c () (True, False)

h = (f, g)

Note that all of the above is without venturing into the
OverlappingInstances pit of despair.

I don't know if this is how people expect this stuff to work, but I've
made occasional use of it--introducing a spurious parameter in order
to have a fundep that uniquely determines a polymorphic type. Perhaps
there's a better way to do that?

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


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Edward Z. Yang
To answer the question in your subject, “Very Carefully.”

While I don’t know much about your particular problem domain (and it seems
others have given useful advice), I can say some general things about
making mutable things immutable.

There is a very simple way to make something mutable immutable: say that you
won’t ever mutate it again!  Doing this correctly is two-fold: you first have
to know when you can do this and when it is useful (which requires in-depth
understanding of the side-effects that the low-level API invokes), and second
is knowing how to encapsulate your interface so that there is no type-checking
use-case of your code (without unsafePerformIO) that accidentally mutates a
pure structure.

You can use this to do a standard pattern seen in ST and others: mutate during
creation inside a monad, but when the monad is done running, return a pure
version of the output with unsafePerformIO.  If you can guarantee that another
caching the pointer so that if someone else calls your function with the
same arguments, you return the same pointer, is safe, then this is ok.

Memcopying a datastructure when you need to modify it, while a cringe-worthy
offense in your theoretical CS class, is a surprisingly practical and not-to-bad
performing technique for making your data persistent.  It works better the 
smaller
the data structure is, and you'd be surprised how many C libraries implement
some feature with a memory copy (moving GC, anyone?)

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


Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread Ivan Miljenovic
On 8 July 2010 13:48, Ertugrul Soeylemez  wrote:
> Ivan Miljenovic  wrote:
>
>> On 8 July 2010 13:36, Ertugrul Soeylemez  wrote:
>> > To be honest, I don't know any strength of MTL compared to
>> > transformers and monadLib.  Actually even transformers is quite
>> > primitive compared to monadLib.  The only real advantage is that it
>> > has flipped run functions and a built-in MaybeT.
>>
>> mtl's advantages: wide pre-existing user base, etc.
>
> As said, I don't think this is a valid argument.  Windows has a much
> larger user base than Linux.  C++ has a much larger user base than
> Haskell.  We still use Haskell, and many of us use Linux.

My point was, was that if you need to pick a monad transformer library
and you've never done any before, then some people are likely to
choose mtl because it's currently the most-used library, it comes with
the platform and if they need to interact with another package that
uses a monad transformer library then it's more likely to be using mtl
than anything else.

>> transformers (especially when used with monads-{fd,tf}) advantage over
>> monadLib: pre-existing type aliases, documentation, easier to port old
>> code that was using mtl.
>
> If you don't use monadLib-specific features, then most code will run in
> monadLib as well as transformers without changes.  The Haddock
> documentation of monadLib is quite brief, but if you know how to use
> monad transformers, you won't have any problems.

I for one don't know how to use monad transformers (I mean, I've read
the section in RWH and could figure it out, but off the top of my head
I can't recall how to do all the lifting stuff, etc.).

> And I don't know what you mean by "pre-existing type aliases".

http://hackage.haskell.org/packages/archive/transformers/0.2.1.0/doc/html/Control-Monad-Trans-State-Lazy.html#t%3AState


-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread Ertugrul Soeylemez
Ivan Miljenovic  wrote:

> On 8 July 2010 13:36, Ertugrul Soeylemez  wrote:
> > To be honest, I don't know any strength of MTL compared to
> > transformers and monadLib.  Actually even transformers is quite
> > primitive compared to monadLib.  The only real advantage is that it
> > has flipped run functions and a built-in MaybeT.
>
> mtl's advantages: wide pre-existing user base, etc.

As said, I don't think this is a valid argument.  Windows has a much
larger user base than Linux.  C++ has a much larger user base than
Haskell.  We still use Haskell, and many of us use Linux.


> transformers (especially when used with monads-{fd,tf}) advantage over
> monadLib: pre-existing type aliases, documentation, easier to port old
> code that was using mtl.

If you don't use monadLib-specific features, then most code will run in
monadLib as well as transformers without changes.  The Haddock
documentation of monadLib is quite brief, but if you know how to use
monad transformers, you won't have any problems.  And I don't know what
you mean by "pre-existing type aliases".


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread Ivan Miljenovic
On 8 July 2010 13:36, Ertugrul Soeylemez  wrote:
> To be honest, I don't know any strength of MTL compared to transformers
> and monadLib.  Actually even transformers is quite primitive compared to
> monadLib.  The only real advantage is that it has flipped run functions
> and a built-in MaybeT.

mtl's advantages: wide pre-existing user base, etc.

transformers (especially when used with monads-{fd,tf}) advantage over
monadLib: pre-existing type aliases, documentation, easier to port old
code that was using mtl.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread Ertugrul Soeylemez
a...@spamcop.net wrote:

> Quoting Ertugrul Soeylemez :
>
> > In its highest level "not fragmenting the user base" means going
> > back to C++ and Windows.
>
> Ha.  You wouldn't say that if you were familiar with the current state
> of C++ on Windows.
>
> Since nobody has come out and admitted it, here's the real problem:
> What constitutes the best API for a monad library is still a research
> problem.  This is evidenced by the fact that a few times a year we get
> yet another paper which proposes a fundamental change to the API which
> would improve matters in yet another direction.

What's the matter?  The more popular languages don't even go that far to
implement an advanced concept like monads /at all/.  They are slowly
adopting what Haskell programmers take for granted.  Look at how monads
are implemented in F# or even C#.  This is WAY behind Haskell.  They
don't even know about transformers, only about monads, and only in a
very modest way.

Do you realize at what level we are complaining?  We are complaining
that a wonderful feature could be implemented in a more elegant, more
wonderful way.  Programmers in other languages wouldn't even know that
this wonderful feature exists.

But my point is that "not fragmenting the user base" means not using
Haskell or Linux, because everybody uses Windows and C++.  This is not
related to quality at all.  This is just to show how invalid the
argument is that "we shouldn't fragment the user base".


> Transformers, monadLib and MTL all have their respective strengths and
> weaknesses, but they are all considerably behind the state of the art,
> if you go by published research.

To be honest, I don't know any strength of MTL compared to transformers
and monadLib.  Actually even transformers is quite primitive compared to
monadLib.  The only real advantage is that it has flipped run functions
and a built-in MaybeT.

Iavor S. Diatchki has done a great job.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] does () match with a??

2010-07-07 Thread Hector Guilarte
On Wed, Jul 7, 2010 at 8:48 PM, John Meacham  wrote:

> Are you sure you are interpreting what 'die' should do properly? Your
> code makes sense if die should decrement your life counter and continue
> along, however if 'die' is meant to end your whole game, then there is
> another implementation that does type check.
>
>John
>

You're absolutely right, I sen't the wrong code, here's the "correct" one
and a little bit more explanation about what checkpoint does.

The result of die makes sense for the checkPoint function since there are
three cases for it:
1) The player died and has no remaining lifes. The game can't continue, I
just return Noting in the die function and in checkpoint make the
corresponding case.
2) The player died and has remaining lifes. The game can be retried with a
life subtracted. I would need to tell checkpoint that I died and I want to
retry, that's where I think the result is important, because of the next
case.
3) The player didn't died, it finished the particular game and checkpoint m
equals m. Here I would need to see if the result of the game was different
from the result from die, and continue.

instance GameMonad Game where
  extraLife= Game $ \l -> Just ((),l+1)
  getLives = Game $ \l -> Just (l,l)
  die  = do
n <- getLives
if n <= 0 then Game $ \_ -> Nothing
  else Game $ \_ -> Just ("player died",n-1)
  checkPoint a = do
n <- getLives
case execGame a n of
  Nothing -> Game $ \_ -> Nothing
  Just c  -> gameOn $ fst c
where gameOn "player died" = a >>= \_ -> (checkPoint a)
  gameOn _ = a

Obviously this fails to compile because I'm returning a String and it
doesn't match with a either, but the idea of what I think I need to do is
right there.

Ivan Miljenovic told me to use error, and actually I though something like
that. in STM retry combined with atomically does something similar as what I
need checkpoint and die to do, and they use exceptions to accomplish it. I
really think that's the solution I want, but then I have another question,
when I 'throw' the exception in die and 'catch' it in checkpoint to call it
again, is the number of lives gonna be lives - 1?

Thanks for answering so quickly,

Hector Guilarte

Pd: Here's an example run of how my homework should work after is finished

printLives :: ( GameMonad m , MonadIO m ) = > String -> m ()
printLives = do
  n <- getLives
  liftIO $ putStrLn $ s ++ " " ++ show n
test1 :: ( GameMonad m , MonadIO m ) = > m ()
test1 = checkPoint $ do
  printLives " Vidas : "
  die
  liftIO $ putStrLn " Ganamos ! "

lastChance :: GameMonad m = > m ()
lastChance = do
  n <- getLives
  if n == 1 then return ()
 else die
test2 :: ( GameMonad m , MonadIO m ) = > m String
test2 = checkPoint $ do
  printLives " Inicio "
  n <- getLives
  if n == 1
then do
  liftIO $ putStrLn " Final "
  return " Victoria ! "
else do
  checkPoint $ do
printLives " Checkpoint anidado "
lastChance
  extraLife
  printLives " Vida extra ! "
  die

AND THE OUTPUT TO SOME CALLS

ghci > runGameT test1 3
Vidas : 3
Vidas : 2
Vidas : 1
Nothing
ghci > runGameT test2 3
Inicio 3
Checkpoint anidado 3
Checkpoint anidado 2
Checkpoint anidado 1
Vida extra ! 2
Inicio 1
Finish
Just ( " Victoria ! " ,1)

--
> John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread ajb

G'day all.

Quoting Ertugrul Soeylemez :


In its highest level "not fragmenting the user base" means going back to
C++ and Windows.


Ha.  You wouldn't say that if you were familiar with the current state
of C++ on Windows.

Since nobody has come out and admitted it, here's the real problem: What
constitutes the best API for a monad library is still a research problem.
This is evidenced by the fact that a few times a year we get yet another
paper which proposes a fundamental change to the API which would improve
matters in yet another direction.

Transformers, monadLib and MTL all have their respective strengths and
weaknesses, but they are all considerably behind the state of the art,
if you go by published research.

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


Re: [Haskell-cafe] does () match with a??

2010-07-07 Thread John Meacham
Are you sure you are interpreting what 'die' should do properly? Your
code makes sense if die should decrement your life counter and continue
along, however if 'die' is meant to end your whole game, then there is
another implementation that does type check.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] does () match with a??

2010-07-07 Thread Ivan Miljenovic
On 8 July 2010 10:55, Hector Guilarte  wrote:
> Hey everyone,
> I'm making a Game Monad for an assignment (yes, homework) . Here's a little
> explanation of what I need to do (I can't use anything from Control.Monad.*,
> I need to do everything myself):
> I need to define my newtype Game and make it's Monad instance
> I need to make the function :
> runGame :: Game a            -- A particular game
>               -> Int                   -- Initial amount of lives
>               -> Maybe (a , Int ) -- Result and remaining lives.
> I need to make the instance for this class:
> class Monad m = > GameMonad m where
>   extraLife :: m ()
>   getLives   :: m Int
>   checkPoint :: m a -> m a
>   die        :: m a
> now what I've done (I was inspired by the State Monad)
> I defined my Game type as follows:
>> newtype Game r = Game { execGame :: Int -> Maybe (r,Int) }
> My Monad instance like this:
>> instance Monad Game where
>>     return a = Game $ \r -> Just (a,r)
>>     m >>= k  = Game $ \r -> let x = execGame m r
>>         in case x of
>>           Just (a, r') -> execGame (k a) r'
>>           Nothing      -> Nothing
> and my GameMonad instance:
>> instance GameMonad Game where
>>   extraLife    = Game $ \l -> Just ((),l+1)
>>   getLives     = Game $ \l -> Just (l,l)
>>   die          = do
>>     n <- getLives
>>     Game $ \_ -> Just ((),n-1) -- Here's the problem
> so, what's bothering me? Look at the type signature of die in the GameMonad
> class, it's supposed to return something of type (m a), but I don't know
> what to return in that case, and whatever I try to return it doesn't work,
> because when I try to compile it says that it couldn't match expected type
> 'a' against infered type 'whatever' ('whatever' being anything, from (), to
> string, or a number). shouldn't 'a' match with anything I put there?
> Note that I can't change the signatures because they were giving to me that
> way and I already checked with teacher if they were right. (I fixed it
> returning Maybe (Maybe a, Int) instead, but I can't change the signature of
> the function runGame)

The `die' function doesn't make much sense, because as you've intuited
it must be of _any_ type.  You could have "die = return undefined"
which matches the type signature, but isn't very helpfull, especially
if you try to use the value inside the Monad.

The only other option you have is to use `error', similar to the
default fail method in Monad but with a set message.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] does () match with a??

2010-07-07 Thread Hector Guilarte
Hey everyone,

I'm making a Game Monad for an assignment (yes, homework) . Here's a little
explanation of what I need to do (I can't use anything from Control.Monad.*,
I need to do everything myself):

I need to define my newtype Game and make it's Monad instance

I need to make the function :
runGame :: Game a-- A particular game
  -> Int   -- Initial amount of lives
  -> Maybe (a , Int ) -- Result and remaining lives.

I need to make the instance for this class:
class Monad m = > GameMonad m where
  extraLife :: m ()
  getLives   :: m Int
  checkPoint :: m a -> m a
  die:: m a

now what I've done (I was inspired by the State Monad)

I defined my Game type as follows:
> newtype Game r = Game { execGame :: Int -> Maybe (r,Int) }

My Monad instance like this:
> instance Monad Game where
> return a = Game $ \r -> Just (a,r)
> m >>= k  = Game $ \r -> let x = execGame m r
> in case x of
>   Just (a, r') -> execGame (k a) r'
>   Nothing  -> Nothing

and my GameMonad instance:
> instance GameMonad Game where
>   extraLife= Game $ \l -> Just ((),l+1)
>   getLives = Game $ \l -> Just (l,l)
>   die  = do
> n <- getLives
> Game $ \_ -> Just ((),n-1) -- Here's the problem

so, what's bothering me? Look at the type signature of die in the GameMonad
class, it's supposed to return something of type (m a), but I don't know
what to return in that case, and whatever I try to return it doesn't work,
because when I try to compile it says that it couldn't match expected type
'a' against infered type 'whatever' ('whatever' being anything, from (), to
string, or a number). shouldn't 'a' match with anything I put there?

Note that I can't change the signatures because they were giving to me that
way and I already checked with teacher if they were right. (I fixed it
returning Maybe (Maybe a, Int) instead, but I can't change the signature of
the function runGame)

Thanks you,

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


[Haskell-cafe] monadic design patterns for the web -- a 2 day, hands-on workshop

2010-07-07 Thread Greg Meredith
Dear Haskellians,

Biosimilarity and Stellar Scala Consulting will be running a 2 day workshop
in Seattle in September on monadic design patterns for the web. You can get
the details here .

Best wishes,

--greg

-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
1219 NW 83rd St
Seattle, WA 98117

+1 206.650.3740

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


[Haskell-cafe] C9 video on monads and coordinate systems

2010-07-07 Thread Greg Meredith
Dear Haskellians,

You may be interested in this video i did with Brian
Beckmanon
monads, location and coordinate systems.

Best wishes,

--greg

-- 
L.G. Meredith
Managing Partner
Biosimilarity LLC
1219 NW 83rd St
Seattle, WA 98117

+1 206.650.3740

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


[Haskell-cafe] Fundeps and overlapping instances

2010-07-07 Thread Simon Peyton-Jones
Oleg points out, and Martin also mentions, that functional dependencies appear 
to interact OK with overlapping instances, but type families do not. I this 
impression is mistaken, and I'll try to explain why in this message, in the 
hope of exposing any flaws in my reasoning.

We can't permit overlap for type families because it is unsound to do so (ie 
you can break "well typed programs don't go wrong"). But if it's unsound for 
type families, it would not be surprising if it was unsound for fundeps too.  
(I don't think anyone has done a soundness proof for fundeps + local 
constraints + overlapping instances, have they?)  And indeed I think it is.

So the short summary of this message is: if it works for fundeps it works for 
type families, and vice versa.  (NB this equivalence is not true about GHC's 
current implementation, however.   GHC doesn't support the combination of 
fundeps and local constraints at all.)

Such an equivalence doesn't argue against fundeps; I'm only suggesting the that 
the two really are very closely equivalent.   I much prefer type families from 
a programming-style point of view, but that's a subjective opinion.

Simon


Imagine a system "FDL" that has functional dependencies and local type 
constraints.  The big deal about this is that you get to exploit type 
equalities in *given* constraints.  Consider Oleg's example, cut down a bit:

class C a b | a -> b
instance C Int Bool
newtype N2 a = N2 (forall b. C a b => b)

t2 :: N2 Int
t2 = N2 True

We end up type-checking (True :: forall b. C Int b => b).   From the functional 
dependency we know that (b~Bool), so the function should typecheck.  GHC 
rejects this program; FDL would not.

But making use of these extra equalities in "given" constraints is quite 
tricky.  To see why look first at Example 1:

module X where
   class C a b | a -> b

   data T a where
 MkT :: C a b => b -> T a


module M1 where
  import X
  instance C Int Char where ...
  f :: Char -> T Int
  f c = MkT c

module M2 where
  import X
  instance C Int Bool
  g :: T Int -> Bool
  g (MkT x) = x

module Bad where
  import M1
  import M2
  bad :: Char -> Bool
  bad = g . f

This program is unsound: it lets you cast an Int to a Bool; result is a 
seg-fault.

You may say that the problem is the inconsistent functional dependencies in M1 
and M2.  But GHC won't spot that.  For type families, to avoid this we 
"eagerly" check for conflicts in type-family instances.  In this case the 
conflict would be reported when compiling module Bad, because that is the first 
time when both instances are visible together.

So any FDL system should also make this eager check for conflicts.

What about overlap?  Here's Example 2:

{-# LANGUAGE IncoherentInstances #-}
module Bad where
  import X
  -- Overlapping instances
  instance C Int Bool -- Instance 1
  instance C a [a]   -- Instance 2

  f :: Char -> T Int
  f c = MkT c   -- Uses Instance 1

  g :: T a -> a
  g (MkT x) = x-- Uses Instance 2

  bad :: Char -> Int
  bad = g . f

Again, a seg fault if it typechecks.  But will it?  When typechecking 'g', we 
get a constraint (C a ?), where 'a' is a skolem constant.  Without 
IncoherentInstances GHC would reject the program on the grounds that it does 
not know what instance to choose.  But *with* IncoherentInstances it would 
probably go through, which is unsound.  So IncoherentInstances has moved from 
causing varying dynamic behaviour to causing seg faults.

Very well, so FDL must get rid of IncoherentInstances altogether, at least for 
classes that have functional dependencies (or that have superclasses that do).

But at the moment GHC makes an exception for *existentials*.  Consider Example 
3:

  class C a b | a -> b

  -- Overlapping instances
  instance C Int Bool -- Instance 1
  instance C a [a]   -- Instance 2

  data T where
MkT :: C a b => a -> b -> T

  f :: Bool -> T
  f x = MkT (3::Int) x  -- Uses Instance 1

  g :: T -> T
  g (MkT n x) = MkT n (reverse x)   -- Uses Instance 2

  bad :: Bool -> T
  bad = g . f

In the pattern match for MkT in g we have the constraint (C a b), where 'a' is 
existentially bound.   So under GHC's current rules it'll choose the (C a [a]) 
instance, and conclude that (b ~ [a]).  So it's ok to reverse x.  But it isn't; 
see function bad!

So to avoid unsoundness we must not choose a particular instance from an 
overlapping set unless we know, absolutely positively, that the other cases 
cannot match.

(GHC's exception for existentials was introduced in response to user demand. 
Usually, overlapping instances are somehow semantically coherent, and with an 
existential we are *never* going to learn more about the instantiating type, so 
choosing the best available seems like a good thing to do.)

But even nuking IncoherentInstances altogether is not enough.  Consider this 
variant of Example 3, call it Example 4:
 module M where
  class C a

RE: [Haskell-cafe] checking types with type families

2010-07-07 Thread Simon Peyton-Jones
Martin Sulzmann, Jeremy 
Wazny,
 Peter J. 
Stuckey:
 A Framework for Extended Algebraic Data Types. FLOPS 
2006:
 47-64

describes such a system, fully implemented in Chameleon, but this
system is no longer maintained.

Type families and Fundeps are equivalent in expressive power and it's
not too hard to show how to encode one in terms of the other.
Local constraints are an orthogonal extension. In terms of type inference,
type families + local constraints and fundeps + local constraints pose the same
challenges.

Probably, Simon is refrerring to the 'unresolved' issue of providing a System F 
style translation for fundeps + local constraints.

Apologies, Martin, you are quite right.  Indeed, you were the first to teach me 
about implication constraints, which are the key to combining local constraints 
and functional dependencies.  Chameleon implements such a system, using (I 
believe) the Constraint Handling Rule framework to solve the resulting 
constraints.

However as you mention we could not figure out a good way to combine this 
approach to constraint solving with evidence generation, although it seems that 
in principle it should be possible. As you say

Well, the point is that System FC
is geared toward type families. The two possible solutions are (a) either
consider fundeps as syntactic sugar for type families (doesn't quite work once
you throw in overlapping instances), (b) design a variant System FC_fundep
which has built-in support for fundeps.

Why is FC is geared towards type families?  It's not an accidental bias; it's 
more that I  know how to do (a) and I don't know how to do (b).

I'll write separately about the issue of overlap

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


RE: [Haskell-cafe] Re: checking types with type families

2010-07-07 Thread Simon Peyton-Jones
|  >>   -- Does this typecheck?
|  >>   f :: C a b => T a -> Bool
|  >>   f T1 = True
|  >>   f T2 = op 3
|  >
|  >> The function f "should" typecheck because inside the T2 branch we know
|  >> that (a~Int), and hence by the fundep (b~Bool).
|  
|  Perhaps I'm confused, but there seems to be no link between
|  the call 'op 3' and 'a' in this example. While the 'desugaring'
|  introduces just such a connection.

You're right, I made a mistake here.  Sorry!  I hope you could see what I was 
after though.  I've written a long email about fundeps and overlap that should 
clarify further.

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


Re: [Haskell-cafe] Multidimensional Matrices in Haskell

2010-07-07 Thread John Lato
Hello,

There are a lot of options.  The "array" package, which is included
with GHC, provides both mutable and immutable arrays of arbitrary
dimensions.  A quick scan of hackage shows ArrayRef, ix-shapable, and
judy as alternatives, among others.

Immutable arrays can be pure, but all mutable array interfaces will
require a monad of some type.  I usually think ST-based mutability is
easiest to work with.

John

> From: Mihai Maruseac 
>
> Hi,
>
> A friend of mine wanted to do some Cellular Automata experiments in
> Haskell and was asking me what packages/libraries are there for
> multidimensional matrices. I'm interested in both immutable and
> mutable ones but I don't want them to be trapped inside a monad of any
> kind.
>
> Any hints?
>
> --
> MM
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Don Stewart
joerg.rudnick:
> Hi Chris,
>
>
> these are good questions -- actually, you might have mentioned Takusen, too.
>
> Clearly, HDBC is the largest of these projects, and there are lots of  
> things well done there.
>
> Takusen has an interesting approach, and I would like to see a  
> discussion here about the practical outcomes, as I have done no testing 
> yet.

It has been used in production at a number of places, including Galois.

 
> I myself quite a time ago had an opportunity to do a Haskell job with a  
> PostgreSQL backend for a client, where I tried out all three and got  
> hsql running easiest. A maintainer was vacant, so I stepped in happily  
> -- doing refactorings, fixing problems at request, giving advice to 
> people.
>
> I can say that I am quite a little PostgreSQL centric and that I have a  
> GIS project in sight, for which I want to try to adapt hsql.

And you have to be wary about the license of HDBC (LGPL) if you want to
use the package in software you redistribute (though this is rarely the
case for database apps, I'm guessing). Satisfying the linking
requirements with GHC -O2 are non-trivial, even with -dynamic.

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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Michael Snoyman
On Wed, Jul 7, 2010 at 9:46 PM, Jonathan Daugherty wrote:

> > Anyway, the point remains, we need a single goto database library.
> >
> > Though the lack of response to this thread makes me think no one
> > particularly thinks this is a problem.
>
> This is an interesting problem.  For my part, I suspect the
> proliferation of high-level database libraries is going to continue.
> If you were to convince the present package maintainers to pitch in
> and build a Grand Database Library, inevitably someone would come
> along and build another one for whatever reason.  Also, I don't think
> the dust has settled on techniques for database access in Haskell in
> any case, even for RDBMSs in particular.
>
> For what it's worth, I would be happy to get persistent[1] behind a Grand
Database Library. Right now, the PostgreSQL backend[2] is built on HDBC
while the SQLite backend[3] includes a variant of the direct-sqlite
package[4]. Here's my two cents on why I didn't run with HDBC for both:

* I wanted the SQLite backend to be the default backend that anyone could
use, without library dependencies. It would be nice if HDBC-sqlite3 had an
option to build against the sqlite3 amalgamation instead of system
libraries. (In fact, it would be cool if that were the default, and system
libraries the option.)

* I'm not fond of the Convertible typeclass. In particular, it makes no
distinction between conversions which are guaranteed to succeed (Int ->
String) and conversions which might fail (String -> Int). As a result, the
fromSql function can easily throw a runtime error. (For that matter, toSql
could as well, but that is much less likely.)

* I would like to be able to explicitly finalize statements. I believe I've
gotten some exceptions in the past when trying to close a database
connection because some statements were not finalized, but I can't remember
the details right now.

* I don't like that the lazy versions of functions are the default, and you
have to add the ' for strict. It's too easy to make mistakes with the
results of a lazy database query. I would even go so far as to recommend
removing them entirely, but I think most people will not like that.

Overall, I think HDBC is a great library, but I have no experience with the
alternatives.

The idea of breaking things into low-level C bindings and higher-level stuff
on top is great.

Michael

[1] http://hackage.haskell.org/package/persistent
[2] http://hackage.haskell.org/package/persistent-postgresql
[3] http://hackage.haskell.org/package/persistent-sqlite
[4] http://hackage.haskell.org/package/direct-sqlite
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: Re: [Haskell-cafe] What is Haskell unsuitable for?

2010-07-07 Thread aditya siram
Haskell's FFI [1]  is really nice, so you could still write your
performance-critical parts in C.
-deech

[1] http://book.realworldhaskell.org/read/interfacing-with-c-the-ffi.html

On Wed, Jul 7, 2010 at 1:54 PM, Zura_  wrote:
>
> It is ironic, but after reading your paper - "Experience Report: Haskell in
> the Real World", I doubt I'll use Haskell for a performance critical
> systems. Laziness (and understanding it) is one factor, but there is also
> GC, which is a real hassle, especially in embedded/mobile systems for a near
> real-time applications.
> In short, when milliseconds matter I'd prefer to stick with GC-less language
> and with native binaries.
>
> Regards,
> Zura
>
>
> Curt Sampson-2 wrote:
>>
>> (Oh, and the trading system is running in production and making money
>> these days. There's no question in my mind that the project was a
>> success, and I'd do it in GHC again. Thanks to the Simons and many
>> others for the fantastic job they've done with that.)
>>
>
> --
> View this message in context: 
> http://old.nabble.com/What-is-Haskell-unsuitable-for--tp28897715p29099864.html
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: Re: [Haskell-cafe] What is Haskell unsuitable for?

2010-07-07 Thread Zura_

It is ironic, but after reading your paper - "Experience Report: Haskell in
the Real World", I doubt I'll use Haskell for a performance critical
systems. Laziness (and understanding it) is one factor, but there is also
GC, which is a real hassle, especially in embedded/mobile systems for a near
real-time applications.
In short, when milliseconds matter I'd prefer to stick with GC-less language
and with native binaries.

Regards,
Zura


Curt Sampson-2 wrote:
> 
> (Oh, and the trading system is running in production and making money
> these days. There's no question in my mind that the project was a
> success, and I'd do it in GHC again. Thanks to the Simons and many
> others for the fantastic job they've done with that.)
> 

-- 
View this message in context: 
http://old.nabble.com/What-is-Haskell-unsuitable-for--tp28897715p29099864.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread aditya siram
If there is no real difference the one that is better supported (with
tutorials, examples etc.) will dominate the other. I don't see a
reason to unify them. Let them duke it out :)

-deech

On Wed, Jul 7, 2010 at 1:46 PM, Jonathan Daugherty  wrote:
>> Anyway, the point remains, we need a single goto database library.
>>
>> Though the lack of response to this thread makes me think no one
>> particularly thinks this is a problem.
>
> This is an interesting problem.  For my part, I suspect the
> proliferation of high-level database libraries is going to continue.
> If you were to convince the present package maintainers to pitch in
> and build a Grand Database Library, inevitably someone would come
> along and build another one for whatever reason.  Also, I don't think
> the dust has settled on techniques for database access in Haskell in
> any case, even for RDBMSs in particular.
>
> Since I couldn't agree more that duplication of effort is a sad thing,
> I think a good place to start is for people to write database library
> binding-only packages that get used by higher-level libraries like
> HDBC and Takusen.  Such libraries should include memory management
> hooks specific to the sematics of the engine in question.  There are a
> couple of libraries for this on Hackage already, but they don't appear
> to be used by any of the high-level database abstraction libraries.
>
> Otherwise I'd ask: what qualifies as a "go-to" library?  Which users
> should it satisfy?  How accessible should it be?  Most answers I can
> think of lead me to believe enough people will be put off by it that
> other libraries will pop up. :)
>
> --
>  Jonathan Daugherty
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Jonathan Daugherty
> Anyway, the point remains, we need a single goto database library.
>
> Though the lack of response to this thread makes me think no one
> particularly thinks this is a problem.

This is an interesting problem.  For my part, I suspect the
proliferation of high-level database libraries is going to continue.
If you were to convince the present package maintainers to pitch in
and build a Grand Database Library, inevitably someone would come
along and build another one for whatever reason.  Also, I don't think
the dust has settled on techniques for database access in Haskell in
any case, even for RDBMSs in particular.

Since I couldn't agree more that duplication of effort is a sad thing,
I think a good place to start is for people to write database library
binding-only packages that get used by higher-level libraries like
HDBC and Takusen.  Such libraries should include memory management
hooks specific to the sematics of the engine in question.  There are a
couple of libraries for this on Hackage already, but they don't appear
to be used by any of the high-level database abstraction libraries.

Otherwise I'd ask: what qualifies as a "go-to" library?  Which users
should it satisfy?  How accessible should it be?  Most answers I can
think of lead me to believe enough people will be put off by it that
other libraries will pop up. :)

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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Jason Dagit
On Wed, Jul 7, 2010 at 10:44 AM, Christopher Done
wrote:

> I did try Takusen with PostgreSQL and it worked perfectly for me, too.
> The only reason I'm using HDBC is because there was already a
> HaskellDB HDBC driver. I was considering writing a Takusen driver for
> HaskellDB, in fact (if possible).
>
> Anyway, the point remains, we need a single goto database library. I
> don't know if Takusen's left-fold typeable way of doing things is
> different enough to disqualify it from The Great Merge or not. Though
> the lack of response to this thread makes me think no one particularly
> thinks this is a problem. Is it worth the effort having one very high
> quality stable library instead of three fairly okay
> not-really-that-different maybe-working libraries?
>

Let me list what I want from a database library:
1) BSD license
2) Maturity
3) ODBC and PostgreSQL backends (and possibly sqlite)
4) Integration tests for the rare cases where you use the library with a new
database engine

I used one of hsql or hdbc years ago on windows and it worked quite well at
the time, although I don't recall which one it was.  Then for years I didn't
need one, and recently I maintained/modified some code that used Takusen.

I found that Takusen is a nice library, but it lacks some polish and
maturity.  We found several "show stopper" level bugs but we were able to
work with the current maintainer to fix all of them.  The test suite that
Takusen has helped pinpoint some of the problems we had with Takusen.  To
the point, I would consider this a "must have" feature.

Combining HSQL and HDBC is going to require some relicensing to satisfy my
requirements above.  One of them is LGPL but I would like the result of
merging them to be BSD3.  I would also like to see comparative benchmarks
between Takusen and HSQL/HDBC.  I would also like confidence that utf8
encoding/decoding is handled correctly in the backends.

I have to wonder if the easiest way to merge the libraries would be to
separate the low level bits of the backends from the Haskell parts of the
libraries and put the backends into a BSD3 license package that the others
can depend on.

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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Michael Snoyman
FWIW, +1. Sorry for not speaking up sooner, I just don't have much to add:
of the three, I've only used HDBC.

Michael

On Wed, Jul 7, 2010 at 8:44 PM, Christopher Done
wrote:

> I did try Takusen with PostgreSQL and it worked perfectly for me, too.
> The only reason I'm using HDBC is because there was already a
> HaskellDB HDBC driver. I was considering writing a Takusen driver for
> HaskellDB, in fact (if possible).
>
> Anyway, the point remains, we need a single goto database library. I
> don't know if Takusen's left-fold typeable way of doing things is
> different enough to disqualify it from The Great Merge or not. Though
> the lack of response to this thread makes me think no one particularly
> thinks this is a problem. Is it worth the effort having one very high
> quality stable library instead of three fairly okay
> not-really-that-different maybe-working libraries?
>
> On 7 July 2010 19:29, Gregory Crosswhite 
> wrote:
> >  I've been using Takusen for all of my database needs, which most of the
> > time means interfacing to a PostgreSQL database, and it has worked out
> > pretty well in practice.  In fact, I experimented with hsql and HDBC a
> while
> > back and for some reason I can't remember they turned out to be less
> > convenient than Takusen so I changed the code I was working on back over
> to
> > Takusen.
> >
> > Cheers,
> > Greg
> >
> > On 7/7/10 2:17 AM, Nick Rudnick wrote:
> >>
> >> Hi Chris,
> >>
> >>
> >> these are good questions -- actually, you might have mentioned Takusen,
> >> too.
> >>
> >> Clearly, HDBC is the largest of these projects, and there are lots of
> >> things well done there.
> >>
> >> Takusen has an interesting approach, and I would like to see a
> discussion
> >> here about the practical outcomes, as I have done no testing yet.
> >>
> >> I myself quite a time ago had an opportunity to do a Haskell job with a
> >> PostgreSQL backend for a client, where I tried out all three and got
> hsql
> >> running easiest. A maintainer was vacant, so I stepped in happily --
> doing
> >> refactorings, fixing problems at request, giving advice to people.
> >>
> >> I can say that I am quite a little PostgreSQL centric and that I have a
> >> GIS project in sight, for which I want to try to adapt hsql.
> >>
> >> Cheers,
> >>
> >>   Nick
> >>
> >>
> >> Christopher Done wrote:
> >>>
> >>> One thing that would be nice is a unification of the general database
> >>> libraries hsql and HDBC. What is the difference between them? Why are
> >>> there two, and why are there sets of drivers for both (duplication of
> >>> effort?)? I've used both in the past but I can't discern a real big
> >>> difference (I used the hsql-sqlite library and the HDBC-postgresql
> >>> library, whichever worked...). It seems the best thing to do is either
> >>> actively merge them together and encourage the community to move from
> >>> one to the other -- judging from what I've read HDBC is more up to
> >>> date and newer than hsql -- or have some documentation with damn good
> >>> reasons to choose one or the other, because currently this is a
> >>> needless source of confusion and possible duplication of effort for
> >>> Haskell's database libraries.
> >>>
> >>> I wasn't going to post until I'd actually researched the difference
> >>> myself properly but I didn't get chance to have a look over the
> >>> weekend, but I thought I'd pose the question. Do people actually care
> >>> about this?
> >>> ___
> >>> Haskell-Cafe mailing list
> >>> Haskell-Cafe@haskell.org
> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >>>
> >>
> >> ___
> >> Haskell-Cafe mailing list
> >> Haskell-Cafe@haskell.org
> >> http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Christopher Done
I did try Takusen with PostgreSQL and it worked perfectly for me, too.
The only reason I'm using HDBC is because there was already a
HaskellDB HDBC driver. I was considering writing a Takusen driver for
HaskellDB, in fact (if possible).

Anyway, the point remains, we need a single goto database library. I
don't know if Takusen's left-fold typeable way of doing things is
different enough to disqualify it from The Great Merge or not. Though
the lack of response to this thread makes me think no one particularly
thinks this is a problem. Is it worth the effort having one very high
quality stable library instead of three fairly okay
not-really-that-different maybe-working libraries?

On 7 July 2010 19:29, Gregory Crosswhite  wrote:
>  I've been using Takusen for all of my database needs, which most of the
> time means interfacing to a PostgreSQL database, and it has worked out
> pretty well in practice.  In fact, I experimented with hsql and HDBC a while
> back and for some reason I can't remember they turned out to be less
> convenient than Takusen so I changed the code I was working on back over to
> Takusen.
>
> Cheers,
> Greg
>
> On 7/7/10 2:17 AM, Nick Rudnick wrote:
>>
>> Hi Chris,
>>
>>
>> these are good questions -- actually, you might have mentioned Takusen,
>> too.
>>
>> Clearly, HDBC is the largest of these projects, and there are lots of
>> things well done there.
>>
>> Takusen has an interesting approach, and I would like to see a discussion
>> here about the practical outcomes, as I have done no testing yet.
>>
>> I myself quite a time ago had an opportunity to do a Haskell job with a
>> PostgreSQL backend for a client, where I tried out all three and got hsql
>> running easiest. A maintainer was vacant, so I stepped in happily -- doing
>> refactorings, fixing problems at request, giving advice to people.
>>
>> I can say that I am quite a little PostgreSQL centric and that I have a
>> GIS project in sight, for which I want to try to adapt hsql.
>>
>> Cheers,
>>
>>   Nick
>>
>>
>> Christopher Done wrote:
>>>
>>> One thing that would be nice is a unification of the general database
>>> libraries hsql and HDBC. What is the difference between them? Why are
>>> there two, and why are there sets of drivers for both (duplication of
>>> effort?)? I've used both in the past but I can't discern a real big
>>> difference (I used the hsql-sqlite library and the HDBC-postgresql
>>> library, whichever worked...). It seems the best thing to do is either
>>> actively merge them together and encourage the community to move from
>>> one to the other -- judging from what I've read HDBC is more up to
>>> date and newer than hsql -- or have some documentation with damn good
>>> reasons to choose one or the other, because currently this is a
>>> needless source of confusion and possible duplication of effort for
>>> Haskell's database libraries.
>>>
>>> I wasn't going to post until I'd actually researched the difference
>>> myself properly but I didn't get chance to have a look over the
>>> weekend, but I thought I'd pose the question. Do people actually care
>>> about this?
>>> ___
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe@haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Adding new entry to list

2010-07-07 Thread Mrwibbly

Hi all I'm having a problem trying to add a new record to a list. I need to
be able to add a new record to the database. My code is below, I also need
to work out the total sales for everything in the Sales list.

As you can see, I've tried to do it but I can't seem to work it out.

type Title = String
type Artist = String
type Sold = Int
--type Record = (Title, (Artist, Sold))
type Sales = [(Title, Artist, Sold)]

testDatabase :: Sales
testDatabase = [("Kids", "MGMT", 3), ("This Charming Man", "The Smiths", 5),
("Gimme Shelter", "The Rolling Stones", 7)]

totalSales :: Sales -> Title -> Artist -> Sold
totalSales [] title artist = 0
--totalSales ((t,a,n):testDatabase) title artist = title artist

--addSale :: Sales -> Sales
--addSale (Title, Artist, sold) = (title, artist, sold + 1)

--newRecord :: String -> String -> Sales -> Sales
--newRecord testDatabase title artist = (title, artist) ++ testDatabase

--newRecordAction :: Sales -> IO()
--newRecordAction testDatabase = do
--putStrLn "Enter a new title: "
--title <- getLine
--putStrLn "Enter an artist: "
--artist <- getLine
--return $ newRecord title artist testDatabase

getTitle :: Sales -> Title
getTitle (title,_) = title

printNames :: Sales -> IO()
printNames testDatabase = mapM_ print testDatabase

mainLoop :: Sales -> IO()
mainLoop testDatabase = do
putStrLn "1 - Show all tracks in database"
putStrLn "2 - Exit"
putStrLn ""
putStrLn "Please select an option:"
input <- getLine
case read input of
1 -> do
putStrLn "--"
putStrLn "Show All Tracks"
putStrLn "--"
printNames testDatabase
putStrLn ""
mainLoop testDatabase
2 -> do
return ()


main :: IO()
main = mainLoop testDatabase

Thank you,

Jack
-- 
View this message in context: 
http://old.nabble.com/Adding-new-entry-to-list-tp29099032p29099032.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Gregory Crosswhite
 I've been using Takusen for all of my database needs, which most of 
the time means interfacing to a PostgreSQL database, and it has worked 
out pretty well in practice.  In fact, I experimented with hsql and HDBC 
a while back and for some reason I can't remember they turned out to be 
less convenient than Takusen so I changed the code I was working on back 
over to Takusen.


Cheers,
Greg

On 7/7/10 2:17 AM, Nick Rudnick wrote:

Hi Chris,


these are good questions -- actually, you might have mentioned 
Takusen, too.


Clearly, HDBC is the largest of these projects, and there are lots of 
things well done there.


Takusen has an interesting approach, and I would like to see a 
discussion here about the practical outcomes, as I have done no 
testing yet.


I myself quite a time ago had an opportunity to do a Haskell job with 
a PostgreSQL backend for a client, where I tried out all three and got 
hsql running easiest. A maintainer was vacant, so I stepped in happily 
-- doing refactorings, fixing problems at request, giving advice to 
people.


I can say that I am quite a little PostgreSQL centric and that I have 
a GIS project in sight, for which I want to try to adapt hsql.


Cheers,

   Nick


Christopher Done wrote:

One thing that would be nice is a unification of the general database
libraries hsql and HDBC. What is the difference between them? Why are
there two, and why are there sets of drivers for both (duplication of
effort?)? I've used both in the past but I can't discern a real big
difference (I used the hsql-sqlite library and the HDBC-postgresql
library, whichever worked...). It seems the best thing to do is either
actively merge them together and encourage the community to move from
one to the other -- judging from what I've read HDBC is more up to
date and newer than hsql -- or have some documentation with damn good
reasons to choose one or the other, because currently this is a
needless source of confusion and possible duplication of effort for
Haskell's database libraries.

I wasn't going to post until I'd actually researched the difference
myself properly but I didn't get chance to have a look over the
weekend, but I thought I'd pose the question. Do people actually care
about this?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



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


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


[Haskell-cafe] ANN: HaRe-0.6.0.1

2010-07-07 Thread Chris BROWN
Dear Haskellers,

There were a few reported problems with building HaRe on Linux systems, so I 
have now uploaded HaRe, version 0.6.0.1. This version should fix all these 
problems.

I can confirm that I have tested this version on:

Ubuntu, version 10.04
Mac OS X version 10.6.4
and Cygwin.

I also confirm HaRe works with AquaMacs, Emacs 23.1.1 and GVim 7.2

Please let me know if there are any issues.

Kind regards,
Chris Brown (on behalf of the HaRe team).



On 7 Jul 2010, at 12:20, Chris BROWN wrote:

Dear Haskellers,

As part of our project on Refactoring Functional Programs

 http://www.cs.kent.ac.uk/projects/refactor-fp/

we are pleased to announce the availability of HaRe 0.6 on Hackage.

 http://hackage.haskell.org/package/HaRe-0.6

Please see the README.txt for build/use instructions and known issues,
and let us know about any problems, bugs, suggestions or additional
platforms you can confirm as working.


Happy Refactoring!

  The HaRe Team (Chris Brown, Huiqing Li, Simon Thompson)


Background:

  Refactoring is the process of changing the structure of programs
  without changing their functionality, i.e., refactorings are
  meaning-preserving program transformations that implement design
  changes. For more details about refactoring, about our project and
  for background on HaRe, see our project pages.

HaRe - the Haskell Refactorer:

  HaRe is our prototype tool supporting a collection of refactorings
  for Haskell 98 (see README.txt for known issues and limitations).

  It is implemented as a separate refactoring engine (on top of
  Programatica's Haskell frontend and Strafunski's generic traversal
  strategy library), with small scripting frontends that call this
  engine from either Vim or Emacs.



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


Re: [Haskell-cafe] Re: [Haskell] analogous functions in Sound.File.Sndfile

2010-07-07 Thread John Lato
> From: stefan kersten 
>
> following up on haskell-cafe ...
>
>
> i just noticed though that the lazy versions don't work correctly because they
> don't take closing the file handle into account properly. i think they should 
> be
> removed from the API, for incremental processing an iteratee interface would
> probably be more appropriate.

Incidentally I've been meaning to write an iteratee interface to
hsndfile for some time.  It would be an excellent fit, and it should
be quite simple to implement.  This would be a good small project for
someone interested in audio and iteratees.

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


Re: [Haskell-cafe] Multidimensional Matrices in Haskell

2010-07-07 Thread Casey Hawthorne
Doesn't mutable state have to be held in a monad?

If you want "mutable like behaviour" without a monad, you may want a
tree or some other data structure.

On Wed, 7 Jul 2010 17:08:48 +0300, you wrote:

>Hi,
>
>A friend of mine wanted to do some Cellular Automata experiments in
>Haskell and was asking me what packages/libraries are there for
>multidimensional matrices. I'm interested in both immutable and
>mutable ones but I don't want them to be trapped inside a monad of any
>kind.
>
>Any hints?
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Multidimensional Matrices in Haskell

2010-07-07 Thread Mihai Maruseac
Hi,

A friend of mine wanted to do some Cellular Automata experiments in
Haskell and was asking me what packages/libraries are there for
multidimensional matrices. I'm interested in both immutable and
mutable ones but I don't want them to be trapped inside a monad of any
kind.

Any hints?

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


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Yves Parès
Okay,
so I think that the better idea is to carry on with my low-level, imperative
binding, and then build a more functional on top of this.

Concerning the mutability of images, I notice that the problem with SFML is
that it handles Sprites in a way that is even more imperative than OpenGL
texture handling.


2010/7/7 Sebastian Sylvan 

>
>
> On Wed, Jul 7, 2010 at 2:24 PM, Yves Parès  wrote:
>
>> > 2010/7/7 Liam O'Connor 
>>
>> > Making an immutable API from a mutable one generally damages performance
>> (on von neumann architectures) somewhat, the goal is to minimize that
>> impact.
>>
>> In fact, I would like to determine if an EFFICIENT way to make images and
>> such immutable exists, or if it is impossible.
>>
>
> Both OpenGL and DirectX, while supporting updates to images, make it slow
> enough that any image data is effectively immutable. Each animation step a
> completely fresh frame buffer is created, without overwriting any of the
> inputs, by combining these immutable images in interesting ways.
>
> You're expected to combine multiple immutable data sources in the shader to
> produce the final output (which will be a different image from the inputs).
> Examples of data sources would be images, transformation matrices, colours
> etc.
>
> It's extremely rare to see people poke values individually into a mutable
> buffer (in fact, the capability of doing this on the GPU is very recent, and
> even then it's highly limited). You do a big purely functional transform
> from inputs to outputs instead. HLSL and GLSL may not look like functional
> languages, but they essentially are, in that each kernel runs independently
> with no shared mutable state, producing outputs from immutable inputs.
>
> So, if you want to do it on the CPU, I would mimic the way GPUs have been
> doing it for ages. Define what operations you want to perform in terms of
> the inputs, and then do them all "in bulk" to produce the output image. You
> don't want people to go in and arbitrarily set pixels to anything they want
> at any time they want.
>
>
> --
> Sebastian Sylvan
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] reading and playing music openAL

2010-07-07 Thread Henning Thielemann


On Tue, 6 Jul 2010, Maria Gabriela Valdes wrote:


Hi ! We have a question about about openAL. We would like to know if anybody 
knows how
to read a WAV file by chunks of a determined size, and after doing some 
processing with
a specific chunk send that same chunk back to the sound card so we can play the 
whole
WAV continiously (just like a music player).


If ALSA is allowed as solution, then you may try the 'duplex' example in:
   http://hackage.haskell.org/package/alsa-pcm-tests
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Sebastian Sylvan
On Wed, Jul 7, 2010 at 2:24 PM, Yves Parès  wrote:

> > 2010/7/7 Liam O'Connor 
>
> > Making an immutable API from a mutable one generally damages performance
> (on von neumann architectures) somewhat, the goal is to minimize that
> impact.
>
> In fact, I would like to determine if an EFFICIENT way to make images and
> such immutable exists, or if it is impossible.
>

Both OpenGL and DirectX, while supporting updates to images, make it slow
enough that any image data is effectively immutable. Each animation step a
completely fresh frame buffer is created, without overwriting any of the
inputs, by combining these immutable images in interesting ways.

You're expected to combine multiple immutable data sources in the shader to
produce the final output (which will be a different image from the inputs).
Examples of data sources would be images, transformation matrices, colours
etc.

It's extremely rare to see people poke values individually into a mutable
buffer (in fact, the capability of doing this on the GPU is very recent, and
even then it's highly limited). You do a big purely functional transform
from inputs to outputs instead. HLSL and GLSL may not look like functional
languages, but they essentially are, in that each kernel runs independently
with no shared mutable state, producing outputs from immutable inputs.

So, if you want to do it on the CPU, I would mimic the way GPUs have been
doing it for ages. Define what operations you want to perform in terms of
the inputs, and then do them all "in bulk" to produce the output image. You
don't want people to go in and arbitrarily set pixels to anything they want
at any time they want.


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


Re: [Haskell-cafe] finding the right mathematical model

2010-07-07 Thread John Lato
If you ignore the identity mappings (which all technically create
trivial loops), these mappings would form a directed acyclic graph
(DAG).  I would look at some of the graph libraries, e.g. fgl, to see
if they have anything appropriate.

John

> From: G?nther Schmidt 
> Hi list,
>
> the problem I have stems from the app I had developed. What my app does
> is to split the money a hospital receives for a case to the departments
> involved in a fair way.
>
> An additional requirement however was to allow the users of the app to
> re-map any revenue shares credited to certain departments to other
> departments. Such cases are sometimes due to politics within the
> hospital and also have more legitimate reasons, like saying the
> radiology should not receive shares for surgical procedures but those
> shares should be redirected to the "General surgery" department.
>
> The feature is already implemented, but I'm not pleased with it,
> especially since I did not develop a mathematical model for it.
>
> Details:
>
> It boils down to model mappings, or rather what sort of data structure
> would be suited for this kind of thing.
>
> Dept A is "mapped" to itself
>     A -> A
>
> Dept B is mapped to Dept C
>     B -> C
>
> Dept C is mapped to Dept C
>     C -> C
>
> Dept D is mapped to Dept A
>     D -> A
>
> It should not be possible to construct looping mappings, ie.
>
>   1. A -> B
>   2. B -> C
>   3. C -> A
>
> ..
>
>
> What sort of model would be suitable to describe this, some sort of matrix?
>
> Günther
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Yves Parès
> 2010/7/7 Liam O'Connor 
> Making an immutable API from a mutable one generally damages performance
(on von neumann architectures) somewhat, the goal is to minimize that
impact.

In fact, I would like to determine if an EFFICIENT way to make images and
such immutable exists, or if it is impossible.

I looked at graphics-drawingcombinators. It is nice, but it doesn't fully
answer to my problem since it just loads images and draws them. It provides
no ways to alter them, no problem of mutability, then.

> 2010/7/7 Chris Eidhof 
> Premature optimization is the root of all evil ;)

Yes, you are right, this is wise.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell] Re: [Haskell-cafe] ANN: HaRe-0.6, now on Hackage

2010-07-07 Thread Chris BROWN
Daniel, Ivan,



One comment on your .cabal file: it's usually preferred to write "base

= 3 && <5" rather than "base >= 3 && <= 4".

In particular if e.g. base-4.2.0.0 doesn't fall in the latter range.
I don't know how exactly Cabal interprets these bounds, but it's a
possibility since 4.2 > 4.0.



Thanks for the tip: we will get this into the next release of Cabal HaRe 0.6.1 
ASAP.

Any other comments or suggestions would be greatly appreciated.

Kind regards,
Chris.

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


[Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread Ertugrul Soeylemez
Yves Parès  wrote:

> > Fragmenting Hackage is bad.  But on the other hand I don't see why I
> > should stick with the inconvenient mtl.  Open source software is all
> > about choice, and as long as the mtl fails to provide the same
> > flexibility and convenience, I won't use it.  Combined with the fact
> > that fixing it would break existing packages, it appears like I
> > won't go back to the mtl ever.
>
> So tell me how you do when you have to use a package which relies on
> mtl's transformers?
> You re-develop the package?

So far this has never been a problem.  These packages always came along
with custom running and access functions.

If that wasn't the case, well, I would choose the ugly way through
qualified imports, but this has never happened to me:

  import qualified Control.Monad.Trans as MTL
  import MonadLib


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell] Re: [Haskell-cafe] ANN: HaRe-0.6, now on Hackage

2010-07-07 Thread Daniel Fischer
On Wednesday 07 July 2010 13:33:19, Ivan Lazar Miljenovic wrote:
> Chris BROWN  writes:
> > Dear Haskellers,
> >
> > As part of our project on Refactoring Functional Programs
> >
> >  http://www.cs.kent.ac.uk/projects/refactor-fp/
> >
> > we are pleased to announce the availability of HaRe 0.6 on Hackage.
> >
> >  http://hackage.haskell.org/package/HaRe-0.6
>
> Congratulations!
>
> One comment on your .cabal file: it's usually preferred to write "base
>
>   >= 3 && <5" rather than "base >= 3 && <= 4".

In particular if e.g. base-4.2.0.0 doesn't fall in the latter range.
I don't know how exactly Cabal interprets these bounds, but it's a 
possibility since 4.2 > 4.0.

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


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Chris Eidhof
I think it might influence performance, but it doesn't have to be that much. 
There are some optimization tricks you can apply to deal with this. Premature 
optimization is the root of all evil ;)

-chris

On 7 jul 2010, at 11:40, Yves Parès wrote:

> That's indeed an advice I've read [1].
> But wouldn't it damage the performances, since code will have to go through 
> an extra layer?
> 
> [1] http://blog.ezyang.com/2010/06/principles-of-ffi-api-design
> 
> 2010/7/7 Chris Eidhof 
> On 5 jul 2010, at 23:48, Yves Parès wrote:
> 
> > Hello,
> >
> > I don't know if some of you are familiar with the SFML library (stands for 
> > Simple and Fast Multimedia Library) --> http://sfml-dev.org
> > As SDL, SFML is a 2D graphics library, but conversely to SDL it provides a 
> > hardware-accelerated drawing, through OpenGL.
> > Well, I'm currently writing its Haskell binding, and I'm stuck with design 
> > issues.
> > What I'm heading to is a full IO binding, and that's what I'd like to avoid.
> 
> Have you considered writing a low-level binding and building a high-level 
> library on top of that?
> 
> -chris
> 

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


Re: [Haskell-cafe] ANN: HaRe-0.6, now on Hackage

2010-07-07 Thread Ivan Lazar Miljenovic
Chris BROWN  writes:

> Dear Haskellers,
>
> As part of our project on Refactoring Functional Programs
>
>  http://www.cs.kent.ac.uk/projects/refactor-fp/
>
> we are pleased to announce the availability of HaRe 0.6 on Hackage.
>
>  http://hackage.haskell.org/package/HaRe-0.6

Congratulations!

One comment on your .cabal file: it's usually preferred to write "base
  >= 3 && <5" rather than "base >= 3 && <= 4".

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: HaRe-0.6, now on Hackage

2010-07-07 Thread Chris BROWN
Dear Haskellers,

As part of our project on Refactoring Functional Programs

 http://www.cs.kent.ac.uk/projects/refactor-fp/

we are pleased to announce the availability of HaRe 0.6 on Hackage.

 http://hackage.haskell.org/package/HaRe-0.6

Please see the README.txt for build/use instructions and known issues,
and let us know about any problems, bugs, suggestions or additional
platforms you can confirm as working.


Happy Refactoring!

  The HaRe Team (Chris Brown, Huiqing Li, Simon Thompson)


Background:

  Refactoring is the process of changing the structure of programs
  without changing their functionality, i.e., refactorings are
  meaning-preserving program transformations that implement design
  changes. For more details about refactoring, about our project and
  for background on HaRe, see our project pages.

HaRe - the Haskell Refactorer:

  HaRe is our prototype tool supporting a collection of refactorings
  for Haskell 98 (see README.txt for known issues and limitations).

  It is implemented as a separate refactoring engine (on top of
  Programatica's Haskell frontend and Strafunski's generic traversal
  strategy library), with small scripting frontends that call this
  engine from either Vim or Emacs.

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


[Haskell-cafe] Re: [Haskell] analogous functions in Sound.File.Sndfile

2010-07-07 Thread stefan kersten
following up on haskell-cafe ...

On 07.07.10 04:07, Maria Gabriela Valdes wrote:
> Does anybody know what are the analogous functions and data types in the
> haskell library "Sound.File.Sndfile" of  the libsndfile library in C  ?

the decision may be debatable, but where it seemed appropriate the C identifiers
map to identifiers commonly used in haskell.

> data type : SNDFILE

Sound.File.Sndfile.Handle

> function: sf_open

Sound.File.Sndfile.openFile

> function : sf_read_short

the most lowlevel interface is the hGetBuf method of Sample; you have to
allocate buffer memory yourself. hGetBuffer returns a newly allocated instance
of Buffer; see the packages hsndfile-vector [1] and hsndfile-storablevector [2]
for instances and examples [3]. hGetContents returns the contents of the whole
file at once while hGetContentChunks returns a lazy list of buffers. readFile
and readFileChunks are just wrappers around openFile and hGetContents.

i just noticed though that the lazy versions don't work correctly because they
don't take closing the file handle into account properly. i think they should be
removed from the API, for incremental processing an iteratee interface would
probably be more appropriate.



[1] http://hackage.haskell.org/package/hsndfile-vector
[2] http://hackage.haskell.org/package/hsndfile-storablevector
[3]
http://hackage.haskell.org/packages/archive/hsndfile-vector/0.4.0/doc/html/src/Sound-File-Sndfile-Buffer-Vector-Examples.html#normalizeSoundFile
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Liam O'Connor
Making an immutable  API from a mutable one generally damages
performance (on von neumann architectures) somewhat, the goal is to
minimize that impact.

Cheers.
~Liam



On 7 July 2010 19:40, Yves Parès  wrote:
> That's indeed an advice I've read [1].
> But wouldn't it damage the performances, since code will have to go through
> an extra layer?
>
> [1] http://blog.ezyang.com/2010/06/principles-of-ffi-api-design
>
> 2010/7/7 Chris Eidhof 
>>
>> On 5 jul 2010, at 23:48, Yves Parès wrote:
>>
>> > Hello,
>> >
>> > I don't know if some of you are familiar with the SFML library (stands
>> > for Simple and Fast Multimedia Library) --> http://sfml-dev.org
>> > As SDL, SFML is a 2D graphics library, but conversely to SDL it provides
>> > a hardware-accelerated drawing, through OpenGL.
>> > Well, I'm currently writing its Haskell binding, and I'm stuck with
>> > design issues.
>> > What I'm heading to is a full IO binding, and that's what I'd like to
>> > avoid.
>>
>> Have you considered writing a low-level binding and building a high-level
>> library on top of that?
>>
>> -chris
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: finding the right mathematical model

2010-07-07 Thread Heinrich Apfelmus

Günther Schmidt wrote:

Hi list,

the problem I have stems from the app I had developed. What my app does 
is to split the money a hospital receives for a case to the departments 
involved in a fair way.


An additional requirement however was to allow the users of the app to 
re-map any revenue shares credited to certain departments to other 
departments. Such cases are sometimes due to politics within the 
hospital and also have more legitimate reasons, like saying the 
radiology should not receive shares for surgical procedures but those 
shares should be redirected to the "General surgery" department.


The feature is already implemented, but I'm not pleased with it, 
especially since I did not develop a mathematical model for it.


Details:

It boils down to model mappings, or rather what sort of data structure 
would be suited for this kind of thing.


Dept A is "mapped" to itself
A -> A

Dept B is mapped to Dept C
B -> C

Dept C is mapped to Dept C
C -> C

Dept D is mapped to Dept A
D -> A

It should not be possible to construct looping mappings, ie.

  1. A -> B
  2. B -> C
  3. C -> A

...


What sort of model would be suitable to describe this, some sort of matrix?


You probably want a graph where the nodes represent departments and 
edges represent the mappings. To implement graphs in Haskell, have a 
look at the functional graph library


  http://hackage.haskell.org/package/fgl

If that's too complicated for you and your graphs are really small, you 
can also use a toy implementation like


  type Graph = [(Node,   -- Department
[Node])  -- List of Departments it shares revenue to
   ]

To test whether a graph has cycles ("looping mapping"), you can use a 
depth-first search.



Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Yves Parès
That's indeed an advice I've read [1].
But wouldn't it damage the performances, since code will have to go through
an extra layer?

[1] http://blog.ezyang.com/2010/06/principles-of-ffi-api-design

2010/7/7 Chris Eidhof 

> On 5 jul 2010, at 23:48, Yves Parès wrote:
>
> > Hello,
> >
> > I don't know if some of you are familiar with the SFML library (stands
> for Simple and Fast Multimedia Library) --> http://sfml-dev.org
> > As SDL, SFML is a 2D graphics library, but conversely to SDL it provides
> a hardware-accelerated drawing, through OpenGL.
> > Well, I'm currently writing its Haskell binding, and I'm stuck with
> design issues.
> > What I'm heading to is a full IO binding, and that's what I'd like to
> avoid.
>
> Have you considered writing a low-level binding and building a high-level
> library on top of that?
>
> -chris
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Build problems on Hackage server

2010-07-07 Thread Ivan Lazar Miljenovic
Emil Axelsson  writes:

> Hello
>
> Last week I uploaded new versions of feldspar-language and
> feldspar-compiler. Both packages build just fine on our local machines
> with GHC 6.10 and 6.12.
>
> But Hackage reports the following build failure:
>
>> cabal: dependencies conflict: ghc-6.12.2 requires array ==0.3.0.1 however
>> array-0.3.0.1 was excluded because ghc-6.12.2 requires array
>> ==0.3.0.0

Wow... maybe hackage is being a bit silly and trying to use both
versions of containers? :s

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-07 Thread Chris Eidhof
On 5 jul 2010, at 23:48, Yves Parès wrote:

> Hello,
> 
> I don't know if some of you are familiar with the SFML library (stands for 
> Simple and Fast Multimedia Library) --> http://sfml-dev.org
> As SDL, SFML is a 2D graphics library, but conversely to SDL it provides a 
> hardware-accelerated drawing, through OpenGL.
> Well, I'm currently writing its Haskell binding, and I'm stuck with design 
> issues.
> What I'm heading to is a full IO binding, and that's what I'd like to avoid.

Have you considered writing a low-level binding and building a high-level 
library on top of that?

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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-07 Thread Nick Rudnick

Hi Chris,


these are good questions -- actually, you might have mentioned Takusen, too.

Clearly, HDBC is the largest of these projects, and there are lots of 
things well done there.


Takusen has an interesting approach, and I would like to see a 
discussion here about the practical outcomes, as I have done no testing yet.


I myself quite a time ago had an opportunity to do a Haskell job with a 
PostgreSQL backend for a client, where I tried out all three and got 
hsql running easiest. A maintainer was vacant, so I stepped in happily 
-- doing refactorings, fixing problems at request, giving advice to people.


I can say that I am quite a little PostgreSQL centric and that I have a 
GIS project in sight, for which I want to try to adapt hsql.


Cheers,

   Nick


Christopher Done wrote:

One thing that would be nice is a unification of the general database
libraries hsql and HDBC. What is the difference between them? Why are
there two, and why are there sets of drivers for both (duplication of
effort?)? I've used both in the past but I can't discern a real big
difference (I used the hsql-sqlite library and the HDBC-postgresql
library, whichever worked...). It seems the best thing to do is either
actively merge them together and encourage the community to move from
one to the other -- judging from what I've read HDBC is more up to
date and newer than hsql -- or have some documentation with damn good
reasons to choose one or the other, because currently this is a
needless source of confusion and possible duplication of effort for
Haskell's database libraries.

I wasn't going to post until I'd actually researched the difference
myself properly but I didn't get chance to have a look over the
weekend, but I thought I'd pose the question. Do people actually care
about this?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

  


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


Re: [Haskell-cafe] reading and playing music openAL

2010-07-07 Thread Patai Gergely
Hello,

> Hi ! We have a question about about openAL. We would like to know if anybody
> knows how to read a WAV file by chunks of a determined size, and after doing
> some processing with a specific chunk send that same chunk back to the sound
> card so we can play the whole WAV continiously (just like a music player).
The basic idea is that you have to define a source and repeatedly call
queueBuffers on it. I wrote an OpenAL version of the Hemkay module
player (example code without comments, with some horrible way to achieve
double buffering can be found at [1]), which can be compiled if you have
installed the hemkay-core package. Also, you might want to ask sound
related questions on the Haskell art list [2].

Gergely

[1] http://hpaste.org/fastcgi/hpaste.fcgi/view?id=27083
[2] http://lists.lurk.org/mailman/listinfo/haskell-art

-- 
http://www.fastmail.fm - Does exactly what it says on the tin

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


[Haskell-cafe] lambda calculus and equational logic

2010-07-07 Thread Patrick Browne
Hi,
In Haskell what roles are played by 1)lambda calculus and 2) equational
logic? Are these roles related?

Hopefully this question can be answered at a level suitable for this forum.

Thanks,
Pat

This message has been scanned for content and viruses by the DIT Information 
Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Debugging cause of indefinite thread blocking

2010-07-07 Thread Claus Reinke
I am making use of the Data.Array.Repa module to achieve data-parallelism. 
On running my program I get the error:


"thread blocked indefinitely on an MVar operation"


Haven't seen any responses yet, so here are some suggestions:


Two questions:
1. What could be some of the potential causes for the above error when the 
only use of parallelism is Repa arrays?


If you're sure the issue is in Repa, contact the Repa authors?

2. What are the best strategies for debugging he cause(s) of such an 
error?


If it is in your code, you could try replacing the Control.Concurrent
operations with variants that generate a helpful trace before calling
the originals. That approach was used in the Concurrent Haskell
Debugger: http://www.informatik.uni-kiel.de/~fhu/chd/

Google for "concurrent haskell debugger" to find related and
follow-on work on extensions of chd and alternative verification
approaches.

Newer GHCs have some internal runtime event logging features
(eg, link the code with -debug, then run with +RTS -Ds). See RTS
options in the GHC user manual (4.15.[67]).

Claus



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


[Haskell-cafe] Build problems on Hackage server

2010-07-07 Thread Emil Axelsson

Hello

Last week I uploaded new versions of feldspar-language and 
feldspar-compiler. Both packages build just fine on our local machines 
with GHC 6.10 and 6.12.


But Hackage reports the following build failure:


cabal: dependencies conflict: ghc-6.12.2 requires array ==0.3.0.1 however
array-0.3.0.1 was excluded because ghc-6.12.2 requires array ==0.3.0.0


Any idea of what might be causing this?

Thanks!

/ Emil

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


Re: [Haskell-cafe] Re: Transformers versus monadLib versus...

2010-07-07 Thread Yves Parès
>
> Fragmenting Hackage is bad.  But on the other hand I don't see why I
> should stick with the inconvenient mtl.  Open source software is all
> about choice, and as long as the mtl fails to provide the same
> flexibility and convenience, I won't use it.  Combined with the fact
> that fixing it would break existing packages, it appears like I won't go
> back to the mtl ever.
>

So tell me how you do when you have to use a package which relies on mtl's
transformers?
You re-develop the package?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is Haskell unsuitable for?

2010-07-07 Thread David Virebayre
On Tue, Jul 6, 2010 at 9:23 PM, Yves Parès  wrote:
>> I must have the same impediment. We should start a support group, that, or
>> give in and write a compiler. To add insult to injury,
>> I think it should be called "Turbo Haskell".
>
> That's true... I never noticed, because in French the two words get
> pronounced very differently.

Indeed. Sadly, I almost never get to speak about Haskell in French...
Except when I'm advocating it to my friends.

There's a majority of words I learned with haskell I have no idea what
their translation is in French. For others, the direct translation
sounds horrible "Haskell est un language fainéant".

I'm lucky I like English.

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