Re: [Haskell-cafe] Open CV or alternate image processing library for Haskell on windows?

2011-05-16 Thread Antoine Latter
On Mon, May 16, 2011 at 10:47 PM, Gregory Guthrie wrote: > Below is the install result. It does claim that "You must install OpenCV > (development packages) prior to installing this package." > I don't' see any Haskell /cabal opencv package, so am not sure what this > means one has to do. The e

Re: [Haskell-cafe] Open CV or alternate image processing library for Haskell on windows?

2011-05-16 Thread Gregory Guthrie
Below is the install result. It does claim that "You must install OpenCV (development packages) prior to installing this package." I don't' see any Haskell /cabal opencv package, so am not sure what this means one has to do. I am not familiar enough with the Haskell install and make environment

Re: [Haskell-cafe] Inconsistent window updates with SDL library

2011-05-16 Thread Michael Serra
Oh, in case the code would be helpful.. ;) import Data.Set (toList, fromList, intersection, size) import Data.List ((\\)) import System.Random (randomRIO) import Data.Word (Word32) import Graphics.UI.SDL as SDL main = do SDL.init [InitVideo, InitTimer, InitEventthread] w <- setVideoMode 1440

[Haskell-cafe] Inconsistent window updates with SDL library

2011-05-16 Thread Michael Serra
Greetings Haskellers, I'm relatively new to the language and I'm writing a basic game of life simulation to try out the SDL bindings. The program updates the window with the next generation of cells each time you press 'n', and the problem I'm finding is that every so often the window stops upda

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Felipe Almeida Lessa
On Mon, May 16, 2011 at 8:40 PM, Gracjan Polak wrote: >  result <- runErrorT $ do >     lift $ print "was here" >     fail "msg" > >  (result = Left "msg") > > after a while the print statement may be removed: > >  result <- runErrorT $ do >     fail "msg" > >  (result = Left "msg") That seems pr

[Haskell-cafe] Haskell memory model (was iterIO-0.1)

2011-05-16 Thread dm-list-haskell-cafe
At Mon, 16 May 2011 22:31:14 +0100, Simon Marlow wrote: > > Good example - so it looks like we don't get full sequential consistency > on x86 (actually I'd been thinking only about write ordering and > forgetting that reads could be reordered around writes). > > But that's bad because it means

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Gracjan Polak
Daniel Fischer googlemail.com> writes: > > On Monday 16 May 2011 23:41:44, Gracjan Polak wrote: > > Thanks Daniel, Yves and Edward for explanation. Two things come to my > > mind now. > > > > 1. It should be unified. > > The (Either e) Monad instance was recently changed after people have long

Re: [Haskell-cafe] Exception for NaN

2011-05-16 Thread Daniel Fischer
On Tuesday 17 May 2011 00:22:02, Alexey Khudyakov wrote: > On 16.05.2011 22:51, Casey McCann wrote: > > How so? Equality on floating point values other than NaN works just > > fine and behaves as expected. It's just that they violate all sorts of > > algebraic laws when arithmetic is involved so se

Re: [Haskell-cafe] Exception for NaN

2011-05-16 Thread Richard O'Keefe
On 16/05/2011, at 7:39 PM, Ketil Malde wrote: > I'm not intimately familiar with IEEE 754, but in any case we'd be in > good company: R typically lets you select to sort NaNs as greater or > less than any other values, and sorts non-NaN values correctly also in > the presence of NaNs, I think. >

Re: [Haskell-cafe] Exception for NaN

2011-05-16 Thread Alexey Khudyakov
On 16.05.2011 22:51, Casey McCann wrote: How so? Equality on floating point values other than NaN works just fine and behaves as expected. It's just that they violate all sorts of algebraic laws when arithmetic is involved so sequences of operations that should be equivalent aren't, in ways that

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Daniel Fischer
On Monday 16 May 2011 23:41:44, Gracjan Polak wrote: > Thanks Daniel, Yves and Edward for explanation. Two things come to my > mind now. > > 1. It should be unified. The (Either e) Monad instance was recently changed after people have long complained that there shouldn't be an (Error e) constrai

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Antoine Latter
On Mon, May 16, 2011 at 4:41 PM, Gracjan Polak wrote: > > Thanks Daniel, Yves and Edward for explanation. Two things come to my mind > now. > > 1. It should be unified. Why? Because conceptually: > > runIdentity (runErrorT (fail "msg")) :: Either String Int > Left "msg" > > and > > fail "msg" ::

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Gracjan Polak
Thanks Daniel, Yves and Edward for explanation. Two things come to my mind now. 1. It should be unified. Why? Because conceptually: runIdentity (runErrorT (fail "msg")) :: Either String Int Left "msg" and fail "msg" :: Either String Int *** Exception: msg Should be the same as Identity monad

Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-16 Thread Simon Marlow
On 16/05/11 20:31, dm-list-haskell-c...@scs.stanford.edu wrote: At Mon, 16 May 2011 10:56:02 +0100, Simon Marlow wrote: Yes, it's not actually documented as far as I know, and we should fix that. But if you think about it, sequential consistency is really the only sensible policy: suppose one

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Daniel Fischer
On Monday 16 May 2011 23:05:22, Yves Parès wrote: > Probably because in the instance of Monad Either, fail has not been > overloaded, and still has its default implementation: > fail = error Right. It used to be different in mtl-1.*, when there was an instance Error e => Monad (Either e) where

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Daniel Fischer
On Monday 16 May 2011 22:26:18, I wrote: > On Monday 16 May 2011 20:49:35, austin seipp wrote: > > As you can see, with the foldr definition, GHC is able to fuse the > > iteration of the input list with the generation of the result - note > > the 'GHC.Base.++' call with the first argument being a l

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Edward Amsden
I suspect it is because the "fail" method for the 'Either' monad instance makes use of Haskell's error function, since the instance is defined generally and there is no way to override it for (Either String a). On May 16, 2011, Gracjan Polak wrote: > Control.Monad.Error Prelude> runErrorT (fail

Re: [Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Yves Parès
Probably because in the instance of Monad Either, fail has not been overloaded, and still has its default implementation: fail = error Whereas runErrorT explicitely catches the exception. 2011/5/16 Gracjan Polak > > Hi all, > > A why question: Why: > > Control.Monad.Error Prelude> runErrorT (fa

[Haskell-cafe] ErrorT vs Either

2011-05-16 Thread Gracjan Polak
Hi all, A why question: Why: Control.Monad.Error Prelude> runErrorT (fail "msg") :: IO (Either String Int) Left "msg" but Control.Monad.Error Prelude> (fail "msg") :: (Either String Int) *** Exception: msg ? -- Gracjan ___ Haskell-Cafe mailing

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Daniel Fischer
On Monday 16 May 2011 20:49:35, austin seipp wrote: > As you can see, with the foldr definition, GHC is able to fuse the > iteration of the input list with the generation of the result - note > the 'GHC.Base.++' call with the first argument being a list from > [x..x*2], and the second list to appen

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread austin seipp
You're both right indeed - I didn't look for the definition of concatMap in GHC.List. I thought it could be some behavior with the new inliner, so I defined concatMap in terms of foldr, put it in a seperate module, and then included it and used it in my test: Concatmap2.hs: module Concatmap2 (con

Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-16 Thread dm-list-haskell-cafe
At Tue, 17 May 2011 02:18:55 +1000, Bernie Pope wrote: > > http://augustss.blogspot.com/2011/04/ > ugly-memoization-heres-problem-that-i.html > > He says that "There's no guarantee about readIORef and writeIORef when doing > multi-threading.". But I was wondering if that was true, and if it were

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Daniel Fischer
On Monday 16 May 2011 20:49:35, austin seipp wrote: > Looking at the Core for an utterly trivial example (test x = concatMap > k x where k i = [i..i*2]), the foldr definition seems to cause a > little extra optimization rules to fire, but the result seems pretty > big. The definition using concatMa

Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-16 Thread dm-list-haskell-cafe
At Mon, 16 May 2011 10:56:02 +0100, Simon Marlow wrote: > > Yes, it's not actually documented as far as I know, and we should fix > that. But if you think about it, sequential consistency is really the > only sensible policy: suppose one processor creates a heap object and > writes a reference

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Felipe Almeida Lessa
On Mon, May 16, 2011 at 3:49 PM, austin seipp wrote: > I don't know why GHC doesn't have this rule by default, though. We can > at least rig it with a RULES pragma, however: > > $ cat concatmap.hs > module Main where > > {-# RULES > "concatMap/foldr" forall x k. concatMap k x = foldr ((++) . k) []

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread austin seipp
Looking at the Core for an utterly trivial example (test x = concatMap k x where k i = [i..i*2]), the foldr definition seems to cause a little extra optimization rules to fire, but the result seems pretty big. The definition using concatMap results in core like this: main_go2 = \ (ds_aqV :: [Int

Re: [Haskell-cafe] Exception for NaN

2011-05-16 Thread Casey McCann
On Mon, May 16, 2011 at 3:39 AM, Ketil Malde wrote: > I'm not intimately familiar with IEEE 754, but in any case we'd be in > good company: R typically lets you select to sort NaNs as greater or > less than any other values, and sorts non-NaN values correctly also in > the presence of NaNs, I thin

Re: [Haskell-cafe] Problems with high-level interface to LLVM

2011-05-16 Thread Henning Thielemann
Николай Кудасов wrote: Problem becomes much more complex when I want to add function calls into my language. Type class CallArgs has an instance CallArgs (IO a) (CodeGenFunction r (Value a)), which can't be given as a constraint in typed AST because of free variable r. For a long time I have h

Re: [Haskell-cafe] Open CV or alternate image processing library for Haskell on windows?

2011-05-16 Thread Casey McCann
On Mon, May 16, 2011 at 8:37 AM, Gregory Guthrie wrote: > I wanted to look into using Haskell for an introductory Image Processing > class, but the main package used for such things (OpenCV) does not appear to > be available for windows systems. > > Is there some other good option for image proc

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Andrew Coppin
On 16/05/2011 10:07 AM, Michael Vanier wrote: Usually in monad tutorials, the >>= operator for the list monad is defined as: m >>= k = concat (map k m) -- or concatMap k m but in the GHC sources it's defined as: m >>= k = foldr ((++) . k) [] m As far as I can tell, this definition is equivale

Re: [Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Don Stewart
You might want to read the Repa tutorial: http://www.haskell.org/haskellwiki/Numeric_Haskell:_A_Repa_Tutorial e.g. fromList (Z :. (3::Int)) [1,2,3] 2011/5/16 Grigory Sarnitskiy : >> There's fromIArray and fromList [1].  Does that answer your question? > > Huh, yes, thank you! But still

Re: [Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Grigory Sarnitskiy
> There's fromIArray and fromList [1].  Does that answer your question? Huh, yes, thank you! But still I don't get it. Neither arr1 = fromList 3 [1,2,3] :: Array DIM1 Int nor arr1 = fromList (1,3) [1,2,3] :: Array DIM1 Int works ___ Haskell-Cafe mai

Re: [Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Felipe Almeida Lessa
On Mon, May 16, 2011 at 1:33 PM, Grigory Sarnitskiy wrote: > Hello! > > I'm probing CUDA with Haskell, accelerate package to be exact. Sound stupid, > but I couldn't find how to actually construct an array, for example Vector > Float. > > There is quite a number of examples provided with the pac

[Haskell-cafe] Accelerate package (CUDA). How to actually create an array?

2011-05-16 Thread Grigory Sarnitskiy
Hello! I'm probing CUDA with Haskell, accelerate package to be exact. Sound stupid, but I couldn't find how to actually construct an array, for example Vector Float. There is quite a number of examples provided with the package, but they seem not simple enough for me just to start. __

Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-16 Thread Bernie Pope
On 16 May 2011 19:56, Simon Marlow wrote: > On 13/05/2011 21:12, Bernie Pope wrote: > Could you please point me to more information about the sequential >> consistency of IORefs? I was looking for something about this recently >> but couldn't find it. I don't see anything in the Haddock for Data.

Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Casey McCann
On Mon, May 16, 2011 at 8:10 AM, Robert Clausecker wrote: > I found out, that GHC implements typeclasses as an extra argument, a > record that stores all functions of the typeclass. So I was wondering, > is there a way (apart from using newtype) to pass a custom record as the > typeclass record, t

Re: [Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Ertugrul Soeylemez
Robert Clausecker wrote: > I found out, that GHC implements typeclasses as an extra argument, a > record that stores all functions of the typeclass. So I was wondering, > is there a way (apart from using newtype) to pass a custom record as > the typeclass record, to modify the behavior of the typ

[Haskell-cafe] Open CV or alternate image processing library for Haskell on windows?

2011-05-16 Thread Gregory Guthrie
I wanted to look into using Haskell for an introductory Image Processing class, but the main package used for such things (OpenCV) does not appear to be available for windows systems. Is there some other good option for image processing in Haskell, or has anyone ported openCV to a windows Leksa

[Haskell-cafe] Random thoughts about typeclasses

2011-05-16 Thread Robert Clausecker
Hello! I found out, that GHC implements typeclasses as an extra argument, a record that stores all functions of the typeclass. So I was wondering, is there a way (apart from using newtype) to pass a custom record as the typeclass record, to modify the behavior of the typeclass? I thought about som

Re: [Haskell-cafe] Impossible class instance?

2011-05-16 Thread Emil Axelsson
Ahh, never mind... I just realized there's no way to relate the `info` in the instance to the `info` in the class definition. Alright, I'll keep trying to make this work. Sorry for the noise! / Emil 2011-05-16 12:19, Emil Axelsson skrev: Hello! At the end of this message is a program with a

[Haskell-cafe] Impossible class instance?

2011-05-16 Thread Emil Axelsson
Hello! At the end of this message is a program with a simple expression type, and a class `ToExpr` that generalizes expressions to arbitrary Haskell types. Every node in `Expr` is annotated with some abstract information. The program raises the following type error: test.hs:13:5: Couldn'

Re: [Haskell-cafe] ANNOUNCE: iterIO-0.1 - iteratee-based IO with pipe operators

2011-05-16 Thread Simon Marlow
On 13/05/2011 21:12, Bernie Pope wrote: On 13 May 2011 19:06, Simon Marlow mailto:marlo...@gmail.com>> wrote: As far as memory consistency goes, we claim to provide sequential consistency for IORef and IOArray operations, but not for peeks and pokes. Hi Simon, Could you please poi

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Ivan Lazar Miljenovic
On 16 May 2011 19:07, Michael Vanier wrote: > Usually in monad tutorials, the >>= operator for the list monad is defined > as: > > m >>= k = concat (map k m)  -- or concatMap k m > > but in the GHC sources it's defined as: > > m  >>=  k  =  foldr  ((++)  .  k)  []  m > > As far as I can tell, this

Re: [Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Daniel Fischer
On Monday 16 May 2011 11:07:15, Michael Vanier wrote: > Usually in monad tutorials, the >>= operator for the list monad is > defined as: > > m >>= k = concat (map k m) -- or concatMap k m > > but in the GHC sources it's defined as: > > m >>= k = foldr ((++) . k) [] m > > As far as I c

[Haskell-cafe] >>= definition for list monad in ghc

2011-05-16 Thread Michael Vanier
Usually in monad tutorials, the >>= operator for the list monad is defined as: m >>= k = concat (map k m) -- or concatMap k m but in the GHC sources it's defined as: m >>= k = foldr ((++) . k) [] m As far as I can tell, this definition is equivalent to the previous one (correct me

[Haskell-cafe] flattenend multi-level programs, in diagram form

2011-05-16 Thread Adam Megacz
A few people have mentioned that the flattening process is easier to understand from example diagrams. Now it's possible to generate those diagrams automatically: http://www.cs.berkeley.edu/~megacz/garrows/flattening.examples/ - a ___ Haskell-Ca

Re: [Haskell-cafe] Exception for NaN

2011-05-16 Thread Ketil Malde
Casey McCann writes: > It would improve things in the sense of giving well-behaved instances > for Eq and Ord, yes. It would not improve things in the sense that it > would violate the IEEE floating point spec. I'm not intimately familiar with IEEE 754, but in any case we'd be in good company: R