Re: [Haskell-cafe] Dynamically altering sort order

2009-05-03 Thread Denis Bueno
On Fri, Apr 24, 2009 at 19:49, Edward Kmett wrote: > On Fri, Apr 24, 2009 at 5:11 PM, Denis Bueno wrote: >> Is there an Ord instance that can be dynamically changed in this way? >> >> My first idea is something like this: >> >>    data CompareRecord = CR{ rCompare :: Record -> Record -> Ordering,

[Haskell-cafe] Combining computations

2009-05-03 Thread michael rice
If you look at this stuff long enough it almost begins to make sense. Maybe. ;-) I've been messing around with MonadPlus and I understand its usage with the Maybe and List monads. Since one use of Monads is combining computations, how can I combine a Maybe with a List? let m1 = Nothing let m2 =

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Daniel Fischer
Am Sonntag 03 Mai 2009 00:17:22 schrieb Achim Schneider: > Steve wrote: > > "It is useful to define gcd(0, 0) = 0 and lcm(0, 0) = 0 because then > > the natural numbers become a complete distributive lattice with gcd > > as meet and lcm as join operation. This extension of the definition > > is al

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Luke Palmer
On Sat, May 2, 2009 at 4:17 PM, Achim Schneider wrote: > Steve wrote: > > > "It is useful to define gcd(0, 0) = 0 and lcm(0, 0) = 0 because then > > the natural numbers become a complete distributive lattice with gcd > > as meet and lcm as join operation. This extension of the definition > > is

[Haskell-cafe] Combining computations

2009-05-03 Thread michael rice
I posted something similar about an hour ago but it seems to have gotten lost. Very strange. I've read that Monads can combine computations. Can a Maybe monad be combined with a List monad such that Nothing `mplus` [] ==> [] Just 1 `mplus` [] ==> [1] If not, can someone supply a simple exampl

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread Belka
Welcome to Haskell! =) > But now I don't know how to dynamically add new spells (new spells can be > created in my gameplay). Since I can't assign a new value to the `spells' > variable (Data.Map.insert returns a new map), I just don't know where to > go. Do distinguish *pure function* concept a

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Nathan Bloomfield
Having gcd(0,0) = 0 doesn't mean that 0 is not divisible by any other natural number. On the contrary, any natural trivially divides 0 since n*0 = 0. Perhaps the disagreement is over what is meant by "greatest". The "greatest" in gcd is not w.r.t. the canonical ordering on the naturals; rather w.r.

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tony Morris
michael rice wrote: > If you look at this stuff long enough it almost begins to make sense. > Maybe. ;-) > > I've been messing around with MonadPlus and I understand its usage > with the Maybe and List monads. Since one use of Monads is combining > computations, how can I combine a Maybe with a Lis

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread j.waldmann
don't think in terms of modifying state, think of it as computing new values from old values. I find that the payoff of learning to think ,like this is massive, as it's usually much easier to reason about. Indeed. [warning: what follows is a rant with a purpose:] The imperative/OO guys have

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Kalman Noel
michael rice schrieb: > let m1 = Just 1 > let m2 = [] > let m3 = m1 `mplus` m2 ==> [1] --if the Maybe is not Nothing, add it to the > list > > Or am I misunderstanding combining computations? You just got the type of mplus wrong: mplus :: (MonadPlus m) => m a -> m a -> m a Note that

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Luke Palmer
mplus requires both arguments to be in the same monad (the same type, even). Fortunately, the empty list behaves like Nothing, and a singleton list behaves like Just. So convert the Maybe before composing, using: maybeToList Nothing = [] maybeToList (Just x) = [x] (The maybeToList function can

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Luke Palmer
On Sun, May 3, 2009 at 4:41 AM, Luke Palmer wrote: > mplus requires both arguments to be in the same monad (the same type, > even). Fortunately, the empty list behaves like Nothing, and a singleton > list behaves like Just. So convert the Maybe before composing, using: > > maybeToList Nothing

Re: [Haskell-cafe] Decoupling OpenAL/ALUT packages from OpenGL

2009-05-03 Thread Sven Panne
Am Sonntag, 3. Mai 2009 00:56:00 schrieb Tillmann Vogt: > Sven Panne schrieb: > >* a tiny "ObjectName" package, consisting only of OpenGL's ObjectName > > class (In "Data.ObjectName"? I'm not very sure about a good place in the > > hierarchy here.) > > How about Data.GraphicsObjects ? [...] Th

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Felipe Lessa
I don't know if I understood your intentions, but let's go. The problem is that you're trying to combine different monads. We have mplus :: MonadPlus m => m a -> m a -> m a, so you never leave 'm', but you want mplus' :: ??? => n a -> m a -> m a where 'n' could be a different monad. In s

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Daniel Fischer
Am Sonntag 03 Mai 2009 05:26:22 schrieb michael rice: > I posted something similar about an hour ago but it seems to have gotten > lost. Very strange. > > I've read that Monads can combine computations. Can a Maybe monad be > combined with a List monad such that > > Nothing `mplus` [] ==> [] > Just

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tillmann Rendel
Hi, normally, one uses monads to express and combine computations in the same monad. However, you can convert between some monads, e.g. from Maybe to List: import Data.Maybe (maybeToList) > let m1 = Nothing > let m2 = [1] > let m3 = maybeToList m1 `mplus` m2 > let m1 = Just 1 >

Re: [Haskell-cafe] Array Binary IO & molecular simulation

2009-05-03 Thread Grigory Sarnitskiy
To sum up here is the example that can write two arrays in one file and then read this two arrays back. To restore written data it just reads the file into bytestring, then splits the bytestring into equal parts. The parts are decoded. I suppose the method is suitable for decoding files with unb

Re: [Haskell-cafe] ANN: Silkworm game

2009-05-03 Thread Sven Panne
Nice work! Two minor suggestions, apart from the the paths issue already discussed here: * Either include a license file in the source distribution or remove the corresponding line in the .cabal file. Cabal won't work if it is specified and missing. * List all your build dependencies dir

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread Martijn van Steenbergen
Hi Nicolas, Nicolas Martyanoff wrote: So now I'd want to use it for a small project of mine, a simple multiplayer roguelike based on telnet. I wrote a minimal server in C, and it took me a few hours. Now I'm thinking about doing the same in Haskell, and I'm in trouble. I don't know if this is

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread Eugene Kirpichov
To the original author: I must notice that this is not the most convincing use of purity. I personally would prefer to have a character's spell list be mutable because this corresponds better to the nature of the problem (in the problem domain it is nonsense to have two versions of a character and

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread michael rice
Thanks for all the help, everyone. I think this stuff is starting to come together. Michael --- On Sun, 5/3/09, Tillmann Rendel wrote: From: Tillmann Rendel Subject: Re: [Haskell-cafe] Combining computations To: "michael rice" Cc: haskell-cafe@haskell.org Date: Sunday, May 3, 2009, 7:33 AM

Re: [Haskell-cafe] Array Binary IO & molecular simulation

2009-05-03 Thread Grigory Sarnitskiy
To sum up here is the example that can write two arrays in one file and then read this two arrays back. To restore written data it just reads the file into bytestring, then splits the bytestring into equal parts. The parts are decoded. I suppose the method is suitable for decoding files with unboxe

[Haskell-cafe] StateT IO Action on `onKeyPress`

2009-05-03 Thread Andy Stewart
Hi all, I have a function named `keymapTest` need moand state WindowListT, and WindowListT is `type WindowListT = StateT WindowList IO`. when i add "(\event -> keymapTest winList event >> return False)" after `onKeyPress` for handle key press event, i got GHC error: Manatee.hs:57:58: Couldn'

[Haskell-cafe] Re: gcd

2009-05-03 Thread Achim Schneider
Nathan Bloomfield wrote: > The "greatest" in gcd is not w.r.t. the canonical ordering on the > naturals; rather w.r.t. the partial order given by the divides > relation. > This, to defend myself, was not how it was explained in high school. -- (c) this sig last receiving data processing entity.

[Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread Tobias Olausson
Hello! I have a program that is using ST.Strict, which works fine. However, the program needs to be extended, and to do that, lazy evaluation is needed. As a result of that, I have switched to ST.Lazy to be able to do stuff like foo y = do x <- something xs <- foo (y+1) return (x:xs)

[Haskell-cafe] Vector-like data structure

2009-05-03 Thread Krzysztof Skrzętnicki
Hi I'm looking for a data structure with following characteristics: 1. O(1) lookup 2. O(1) modification 3. amortized O(1) append 4. O(1) size query This roughly characterizes C++ vector<> class. I'm ready to implement it myself, but first I would like to ask if anyone knows package with similar d

[Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Daniel Carrera
Hi, I think the mail server may have been acting up earlier. I sent this to Haskell-beginners, but it more properly belongs here. I found something interesting. "General wisdom" is that Clean (or OCaml) is faster than Haskell. The claim is often followed by a link to the Debian shootout. But

Re: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Gwern Branwen
On Sun, May 3, 2009 at 2:24 PM, Daniel Carrera wrote: > Hi, > > I think the mail server may have been acting up earlier. I sent this to > Haskell-beginners, but it more properly belongs here. > > I found something interesting. "General wisdom" is that Clean (or OCaml) is > faster than Haskell. The

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Nathan Bloomfield
> This, to defend myself, was not how it was explained in high school. No worries. I didn't realize this myself until college; most nonspecialist teachers just don't know any better. Nor did, it appears, the original authors of the Haskell Prelude. :) BTW, this definition of gcd makes it possible

Re: [Haskell-cafe] using haskell for a project

2009-05-03 Thread Bulat Ziganshin
Hello Nicolas, Saturday, May 2, 2009, 9:17:55 PM, you wrote: > But now I don't know how to dynamically add new spells (new spells can be > created in my gameplay). Since I can't assign a new value to the `spells' > variable (Data.Map.insert returns a new map), I just don't know where to > go. we

Re: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Daniel Carrera
Gwern Branwen wrote: Perhaps it's just that no one has parallelized the Clean programs? Haskellers seem to care about the shootout programs much more than Cleaners do. I'm not sure about the second comment. I haven't seen the Haskell site mention the shootout, whereas web pages about Clean oft

[Haskell-cafe] Foldable for BNFC generated tree

2009-05-03 Thread Deniz Dogan
Hi I have a bunch of data types which are used to represent a JavaScript program. The data types and a lexer and a parser have all been generated using BNFC. So basically an entire JavaScript program is represented as a tree using these data types. Ideally I'd like to be able to "fold" over this

Re: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Bulat Ziganshin
Hello Daniel, Sunday, May 3, 2009, 10:24:52 PM, you wrote: > 32-bit sing core [1]: Lisp, Fortran :) this test measures speed of some programs, not "languages". results are depends mainly on bundled libraries and RTS. by no means it demonstrates speed of compiler-generated code of carefully-writ

Re: [Haskell-cafe] Vector-like data structure

2009-05-03 Thread Bulat Ziganshin
Hello Krzysztof, Sunday, May 3, 2009, 10:06:30 PM, you wrote: > This roughly characterizes C++ vector<> class. I'm ready to implement http://haskell.org/haskellwiki/Library/ArrayRef#Using_dynamic_.28resizable.29_arrays although this (mine) package is probably incompatible with current ghc versi

Re[2]: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Bulat Ziganshin
Hello Gwern, Sunday, May 3, 2009, 10:29:37 PM, you wrote: >> 32-bit quad-core [2]: Haskell, C# Mono, Lisp, Clean, Fortran. > I can't really read Clean, but it certainly looks as if it's making no > use of concurrency at all, while the Haskell one most certainly is. probably other languages goes

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread João Ferreira
Something that perhaps could be added is that leaving 0 `gcd` 0 undefined has two obvious annoying consequences: gcd is no longer idempotent (i.e. we don't have a `gcd` a = a, for all a), and it is no longer associative ((a `gcd` 0) `gcd` 0 is well-defined whilst a `gcd` (0 `gcd` 0) is not). (We

Re[2]: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Bulat Ziganshin
Hello Daniel, Sunday, May 3, 2009, 10:42:06 PM, you wrote: > I'm not sure about the second comment. I haven't seen the Haskell site > mention the shootout just search cafe archives ;) -- Best regards, Bulatmailto:bulat.zigans...@gmail.com

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Daniel Fischer
Am Sonntag 03 Mai 2009 18:16:38 schrieb Achim Schneider: > Nathan Bloomfield wrote: > > The "greatest" in gcd is not w.r.t. the canonical ordering on the > > naturals; rather w.r.t. the partial order given by the divides > > relation. Nitpick: it's not a partial order, but a preorder (2 | (-2), (

Re: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Daniel Carrera
Bulat Ziganshin wrote: 32-bit sing core [1]: Lisp, Fortran :) this test measures speed of some programs, not "languages". I know. But since I know that you know that too, I opted for brevity. "How can we benchmark a programming language? We can't - we benchmark programming language implemen

Re: [Haskell-cafe] Haskell vs Clean (speed comparison)

2009-05-03 Thread Thomas DuBuisson
> > I haven't seen the Haskell site mention the shootout, whereas web pages > about Clean often do. Well, there certainly has been significant efforts on the shootout in the Haskell community. There's wiki pages about it [1] and it comes up on the Haskell reddit and proggit frequently. With reg

Re: [Haskell-cafe] ANN: Silkworm game

2009-05-03 Thread Duane Johnson
So here's the thing to get it to run on Mac OS X, I have to build a "SilkwormGame.app" directory, with a "Resources" directory inside, along with a lot of other rubbish, just so that GLFW can create a Mac OS window that accepts mouse and keyboard input. This is the purpose of the Makef

Re: [Haskell-cafe] ANN: Silkworm game

2009-05-03 Thread Don Stewart
For the Mac, you might have to use mkbndl or one of the other native package builders for the Mac. -- Don duane.johnson: > So here's the thing to get it to run on Mac OS X, I have to build a > "SilkwormGame.app" directory, with a "Resources" directory inside, along > with a lot of other rub

Re: [Haskell-cafe] Vector-like data structure

2009-05-03 Thread Don Stewart
gtener: > Hi > > I'm looking for a data structure with following characteristics: > 1. O(1) lookup > 2. O(1) modification > 3. amortized O(1) append > 4. O(1) size query > > This roughly characterizes C++ vector<> class. I'm ready to implement > it myself, but first I would like to ask if anyone

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Claus Reinke
mplus' :: MonadPlus m => Maybe a -> m a -> m a mplus' m l = maybeToMonad m `mplus` l maybeToMonad :: Monad m => Maybe a -> m a maybeToMonad = maybe (fail "Nothing") return In general, however, this operation can't be done. For example, how would you write: mplus' :: IO a -> [a] -> [a] P

Re: [Haskell-cafe] gcd

2009-05-03 Thread Hans Aberg
On 2 May 2009, at 04:05, Steve wrote: Why is gcd 0 0 undefined? In math, one may define gcd(x, y) as a generator of the ideal generated by x and y in the ring of integers Z. The gcd(x, y) then always exists as the ring Z is a PID (principal ideal domain), i.e., all ideals can be generate

[Haskell-cafe] Research in functional programming

2009-05-03 Thread Louis Wasserman
Where might I find or submit a paper on functional data structures? Examples I've found so far include ICFP and the JFP , but Google hasn't found me anything else. Louis Wasserman wasserman.lo...@gmail.co

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Brandon S. Allbery KF8NH
On May 3, 2009, at 16:59 , Claus Reinke wrote: Perhaps the question should be: is there an interesting structure that would allow us to capture when this kind of merging Monads is possible? We can convert every 'Maybe a' to a '[] a', but the other way round is partial or loses information, so l

[Haskell-cafe] Getting WriterT log lazily

2009-05-03 Thread Magnus Therning
I've been playing around with (WriterT [Int] IO), trying to get the log out and map `print` over it... and do it lazily. However, I'm not really happy with what I have so far, since I've had to resort to `unsafePerformIO`. Any hints are welcome. What I have so far is: foo = let _te

Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-03 Thread Ryan Ingram
Cont with success and failure isn't Cont; it's something else (albeit similar) There's a great exposition of using something much like Cont to get success and failure "for free" here: http://www-ps.informatik.uni-kiel.de/~sebf/haskell/barefaced-pilferage-of-monadic-bind.lhs.html -- ryan On Sat

Re: [Haskell-cafe] Getting WriterT log lazily

2009-05-03 Thread Ryan Ingram
How about this: > type ActionLog v = Writer [IO v] > myTell :: v -> ActionLog v () > myTell a = tell [sleep 1 >> return a] > foo :: ActionLog Int () > foo = mapM_ myTell [1..10] > main = sequence_ results where >(_, vals) = runWriter foo >results = map (>>= print) vals -- ryan On Su

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tillmann Rendel
Claus Reinke wrote: mplus' :: MonadPlus m => Maybe a -> m a -> m a mplus' m l = maybeToMonad m `mplus` l maybeToMonad :: Monad m => Maybe a -> m a maybeToMonad = maybe (fail "Nothing") return In general, however, this operation can't be done. For example, how would you write: mplus' :: I

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread Ryan Ingram
So, I don't know what is causing your problem, but foo will not do what you want even with lazy ST. foo y = do x <- something xs <- foo (y+1) return (x:xs) Desugaring: foo y = something >>= \x -> foo (y+1) >>= \xs -> return (x:xs) = something >>= \x -> something >>= \x2 -> foo (y+2) >>=

Re: [Haskell-cafe] StateT IO Action on `onKeyPress`

2009-05-03 Thread Ryan Ingram
Hi Andy. The GTK bindings use IO for their callbacks, not any custom monad like your WindowListT. I suggest, instead of StateT s IO a, you use ReaderT (IORef s) IO a: putR :: s -> ReaderT (IORef s) IO () putR s = do r <- ask liftIO $ writeIORef r s getR :: ReaderT (IORef s) IO s getR =

[Haskell-cafe] converting IOException to Either in ErrorT

2009-05-03 Thread brian
I wrote this to make it a little nicer to catch IO exceptions and convert them to ErrorT failure: onExceptionThrowError :: (Error ce) => IO a -> (String -> ce) -> ErrorT ce IO a onExceptionThrowError a ce = liftIO (try a) >>= either (\(e :: IOException) -> throwError (

Re: [Haskell-cafe] ANN: Silkworm game

2009-05-03 Thread Daryoush Mehrtash
I noticed that Chipmunk also has a Ruby interface. Do you have any pro/con of implementing the game in Ruby vs Haskell? Thanks, Daryoush On Sat, May 2, 2009 at 12:00 PM, Duane Johnson wrote: > Reprinted from my blog post [1]: > > === > > The semester is over, my final project was a success (at

[Haskell-cafe] Re: Getting WriterT log lazily

2009-05-03 Thread Ertugrul Soeylemez
Hello Magnus, although your approach is a bit more pragmatic, I always prefer to use concurrency to implement predictable logging. This is a bit more code, but works much nicer and a lot more predictable: {-# LANGUAGE ExistentialQuantification #-} module Main where import Control.Concurr

Re: [Haskell-cafe] ANN: Silkworm game

2009-05-03 Thread Duane Johnson
I'm not too much of an expert in Haskell, but I did notice that building the game required keeping track of a lot of state information, which was not very intuitive in Haskell (although the OpenGL state info is rather intuitive). If I were to do it in Haskell again, I would try to learn mo

Re: [Haskell-cafe] ANN: Silkworm game

2009-05-03 Thread Felipe Lessa
On Sun, May 03, 2009 at 02:07:23PM +0200, Sven Panne wrote: > As a side note, I get a very bad feeling when Hipmunk gets compiled on my > x86_64 box: [...] > This can't be correct, but I'll probably have to take a look at that. Or is it > a know bug that Hipmunk ist not 64bit-clean? My machine is

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread Tobias Olausson
Would unsafeInterleaveST work just as unsafeInterleaveIO in the manner that it returns immediately, and then is computed lazily? The idea in the complete program is that one part representing the CPU will produce a list lazily, which will then be consumed lazily by another part of the program, whic

[Haskell-cafe] Re: StateT IO Action on `onKeyPress`

2009-05-03 Thread Andy Stewart
Ryan Ingram writes: Thank you very much! I try to use your solution to fix my problem. -- Andy > Hi Andy. > > The GTK bindings use IO for their callbacks, not any custom monad like > your WindowListT. > > I suggest, instead of StateT s IO a, you use ReaderT (IORef s) IO a: > > putR :: s -> Re

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread David Menendez
On Sun, May 3, 2009 at 6:11 PM, Ryan Ingram wrote: > So, I don't know what is causing your problem, but foo will not do > what you want even with lazy ST. That depends on what he wants to do. As long as nothing subsequent to the call to foo tries to read a reference, then foo is fine. For exampl

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-03 Thread David Menendez
On Sun, May 3, 2009 at 7:54 PM, Tobias Olausson wrote: > Would unsafeInterleaveST work just as unsafeInterleaveIO in the manner > that it returns immediately, and then is computed lazily? > The idea in the complete program is that one part representing > the CPU will produce a list lazily, which w

Re: [Haskell-cafe] converting IOException to Either in ErrorT

2009-05-03 Thread David Menendez
On Sun, May 3, 2009 at 6:36 PM, wrote: > I wrote this to make it a little nicer to catch IO exceptions and > convert them to ErrorT failure: > > onExceptionThrowError >  :: (Error ce) => >     IO a >  -> (String -> ce) >  -> ErrorT ce IO a > onExceptionThrowError a ce = >    liftIO (try a) >>= >