Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke
If the convention for modifying package versions of form x.y.z is: - increment z for bugfixes/changes that don't alter the interface - increment y for changes that consist solely of additions to the interface, parts of the interface may be marked as deprecated - increment x for changes that inclu

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke
1. Document the version numbering policy. agreed. just making everybody's interpretation explicit has already exposed subtle differences, so documenting common ground will help. We should have done this earlier, but we didn't. The proposed policy, for the sake of completeness is: x.y where:

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke
- if you provide a 'base' configuration that pulls in the stuff that used to be in base, the package will work I don't know of a way to do that. The name of the package is baked into the object files at compile time, so you can't use the same compiled module in more than one package. i've

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-16 Thread Claus Reinke
Be happy: we're about 15 years ahead of the lisp guys. 'cabal install xmonad' works, for example. - not on windows (and since it is popular, it will seduce more good haskellers not to bother with windows compatibility.. :-( - from xmonad.cabal (version 0.3, from hackage): build-depends:

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-15 Thread Claus Reinke
However, I'd like to separate it from Cabal. Cabal provides mechanism not policy, regarding version numbers. but the examples in the cabal docs should reflect the standard interpretation of version numbers. of course, i have absolutely no idea how to write stable packages under this interpr

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-15 Thread Claus Reinke
> but the name that is everywhere does not stand for what the new version > provides! any place that is currently referring to 'base' will have to be > inspected to check whether it will or will not work with the reduced > base package. and any place that is known to work with the new > base packa

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-15 Thread Claus Reinke
You need a way to specify "foo > 1.2 && foo < 2", which is a suggestion that was tossed around here recently. but what does such a version range say? that i haven't tested any versions outside the range (because they didn't exist when i wrote my package)? or that i have, and know that later v

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-15 Thread Claus Reinke
but calling "split-base" "base" goes directly against all basic assumptions of all packages depending on "base". The new base will have a new version number. There is no expectation of compatibility when the major version is bumped; but we do have an informal convention that minor version bum

Re: [Haskell-cafe] On the verge of ... giving up!

2007-10-14 Thread Claus Reinke
most widely-used programs (ex: web browsers, word processors, email programs, data bases, IDEs) tend to be 90% IO and 10% (or less) computation. This can make Haskell quite unweildy for solving these types of problems. On the otherhand, writing something like a compiler (which requires a small

Re: [Haskell-cafe] New slogan for haskell.org

2007-10-08 Thread Claus Reinke
since this doesn't seem to want to go away:-) 1. reverse psychology approach if you have reached this page following rumours of a language others told you every serious programmer would have to learn, the ministry of programming would like to reassure you that there is no such lang

[Haskell-cafe] getting more out of ghci [longish]

2007-09-25 Thread Claus Reinke
== intro no, i'm not talking about using a nice frontend to ghci, with added functionality, although the haskell modes for emacs and vim, and other such gui/ide/editor efforts, are well worth looking into!-) also, i'm not going to talk about the eagerly anticipated ghci debugger. what i am goi

Re: [Haskell-cafe] Re: Very crazy

2007-09-25 Thread Claus Reinke
This is why I found it so surprising - and annoying - that you can't use a 2-argument function in a point-free expression. For example, "zipWith (*)" expects two arguments, and yet sum . zipWith (*) fails to type-check. You just instead write \xs ys -> sum $ zipWith(*) xs ys which works as

Re: [Haskell-cafe] RE: simple function: stack overflow in hugsvsnonein ghc

2007-09-25 Thread Claus Reinke
return (replicate 100 'a') >>= \x->print $ spant (const True) x ERROR - Garbage collection fails to reclaim sufficient space i.e. as the function unfold, the thunk representing the second term builds up on the heap. (not sure why it works for an infinite list, hugs must drop the reference

Re: [Haskell-cafe] RE: simple function: stack overflow in hugsvsnonein ghc

2007-09-24 Thread Claus Reinke
return (replicate 100 'a') >>= \x->print $ spant (const True) x ERROR - Garbage collection fails to reclaim sufficient space i.e. as the function unfold, the thunk representing the second term builds up on the heap. true. i've often wanted a copy pseudo-function that would avoid updatin

Re: [Haskell-cafe] RE: simple function: stack overflow in hugs vsnonein ghc

2007-09-24 Thread Claus Reinke
afraid not the given example is too strict, the requirement is to generate the matched portion lazilly, and return the tail (unconsumed portion). ah yes, without optimisations, Prelude.span builds up stack, while the continuation-based alternative i mentioned is too strict for some uses. In p

Re: [Haskell-cafe] PROPOSAL: Rename haskell@ to haskell-announce@

2007-09-24 Thread Claus Reinke
in other words, people were meant to subscribe either to haskell or to haskell+haskell-cafe, and posting to haskell was meant to be a flag able to raise a topic briefly over the general din in haskell-cafe. Do people think that is working? i don't think it is working anymore. haskell-cafe w

Re: [Haskell-cafe] RE: simple function: stack overflow in hugs vs nonein ghc

2007-09-24 Thread Claus Reinke
return (repeat 'a') >>= \ x -> print $ span (const True) x with hugs you will get a stack error, in ghc it executes in constant space, i.e. indefinitely. In essenece the above example does exactly the same as my ealier code. this thread might be relevant: http://www.haskell.org/pipermail/hug

Re: [Haskell-cafe] PROPOSAL: Rename haskell@ to haskell-announce@

2007-09-24 Thread Claus Reinke
[cc-ed to haskell@, as this discussion is about [EMAIL PROTECTED] There are four things sent to the haskell list@ 1) Calls for papers 2) Annoucements 3) Oleg's stuff (which are really announcements of a library or technique) 4) Off topic stuff I'm initially only proposing to mop up category 4,

Re: [Haskell-cafe] Win32 Open GL / Glut Applications

2007-09-21 Thread Claus Reinke
> http://www.haskell.org/HOpenGL/ First, the bad news: The HOpenGL site is outdated. Look at [1] and note the date of the most recent release: September 9, *2003*. [1] http://www.haskell.org/HOpenGL/releases.html try http://www.haskell.org/haskellwiki/Opengl ? [Sven: could there please be a l

Re: [Haskell-cafe] Library Process (was Building "productionstable" software in Haskell)

2007-09-18 Thread Claus Reinke
I thought the master plan was that less would come with the compiler / interpreter and the user would install packages using cabal. Ideally, yes. I think a useful model would be GNU/Linux, where there is the Linux kernel, developed by core hackers, and then there are "distributions", which pack

Re: [Haskell-cafe] How can I stop GHCi from calling "show" for IOactions?

2007-09-18 Thread Claus Reinke
| It seems that GHCi outputs the contents of the variable you've created | when there's only one of them. Indeed, that is documented behaviour (first bullet here: http://www.haskell.org/ghc/docs/latest/html/users_guide/ch03s04.html#ghci-stmts ) Perhaps it's confusing behaviour? If so do suggest

Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Claus Reinke
PS: And, no, you won't be able to set breakpoints in type-level programs... but will i be able to lift type-level programs to the kind level? :-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haske

Re: [Haskell-cafe] Installation of GLUT package

2007-09-09 Thread Claus Reinke
>> Loading package OpenGL-2.2.1 ... linking ... done. >> Loading package GLUT-2.1.1 ... linking ... done. > > The above message was after you have installed GLUT-2.0, but GHC was > still loading GLUT-2.1.1. The later errors were caused by your forced > copy of 2.0 lib over the default 2.1.1. I no

Re: [Haskell-cafe] can't build haxml under ghc 6.7, says HughesPJis hidden... but ghc-pkg doesn't say it's hidden...

2007-08-10 Thread Claus Reinke
For now, we just edit .cabal files when transporting code between GHC versions... Just for information, the HaXml darcs repo has recently adopted the solution of containing two .cabal files, one for ghc-6.6.x, and the other for the split-base packages (>=ghc-6.7). The only difference is the bui

Re: [Haskell-cafe] Pure functional GUI (was "a regressive view of support for imperativeprogramming in Haskell")

2007-08-08 Thread Claus Reinke
FranTk, Haggis, Fudgets, Object I/O for Haskell, Gadgets, Pictures, HTk, Haskell Tk, HToolkit, Gtk+HS, Gtk2Hs, wxHaskell, FunctionalForms, .. and no, that list is not exhaustive by any means (you can find abstracts for some of these in old haskell community reports, but a lot of functional gui l

Re: Re[6]: [Haskell-cafe] Re: monad subexpressions

2007-08-04 Thread Claus Reinke
I think that defining lifted versions of every function is dangerous, especially in a widely-used library. Monadic code will start to look pure, and before long someone will be using let expressions and where blocks to share monadic computations rather than using do blocks to share the *results*

Re: Re[8]: [Haskell-cafe] Re: monad subexpressions

2007-08-04 Thread Claus Reinke
so, there could be a library defining lhs ==: rhs = putMVar <$> lhs <*> rhs ouch! since putMVar is already impure, there's a join missing: lhs ==: rhs = putMVar <$> lhs <*> rhs and in your application code, you could write newEmptyMVar ==: putStrLn "hi there" .. rant deleted

Re: Re[6]: [Haskell-cafe] Re: monad subexpressions

2007-08-04 Thread Claus Reinke
i know that it may be trsanslated to everything including pure assembler. what i'm missing in current Haskell is USEFUL SYNTAX for these expressions. adding tons of liftM and ap can't make me happy but the point is that you have a standard set of operations when working at that level, including

Re: Re[4]: [Haskell-cafe] Re: monad subexpressions

2007-08-04 Thread Claus Reinke
can you give translation you mean? i don't have anything against combinators, they just need to be easy to use, don't forcing me to think where i should put one, as i don't think with lazy code and C imperative code. and they shouldn't clatter the code, too. just try to write complex expression us

Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke
mytransaction = foo `liftM` r xvar0 `ap` r xvar1 .. where r = readTVar I really find it difficult to articulate why this isn't acceptable, because it seems so obvious to me! It's short yes, but I really don't think it's very clear... if it is any consolation, i don't use that style myself

Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke
I'll dig for it later if you like. The essence of the matter was a bunch of functions that looked something like this: foo = do b' <- readTVar b c' <- readTVar c d' <- readTvar d return (b' + c' / d') In other words, a string of readTVar statements, followed by one com

Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke
mytransaction = do { x0 <- readTVar xvar0 x1 <- readTVar xvar1 : xn <- readTVar xvarn return $ foo x0 x1 .. xn } Versus mytransaction = return $ foo $(readTVar xvar0) $(readTVar xvar1) .. $(readTVar xvarn) ah, a concrete example. but isn't that the typical use case for ap? mytransaction

Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Claus Reinke
to illustrate why some of us are concerned about this extension, a few examples might help. consider: f (g (<- mx)) does this stand for (a) mx >>= \x-> f (g x) (b) f (mx >>= \x-> (g x)) (c) none of the above, because there's no do (d) something else entirely if (a/b), does the

Re: Re[2]: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke
can you please rewrite *p++=*q++ in haskell? do { w p =<< r q; i p; i q } how about *Object.File.Line.CurPtr++ = *AnotherObject.File.Line.CurPtr++ ? ;) what's the difference?-) let p = Object.File.Line.CurPtr let q = AnotherObject.File.Line.CurPtr do { w p =<< r q; i p; i q }

Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Claus Reinke
can you please rewrite *p++=*q++ in haskell? assuming these operations i :: V a -> IO (V a) -- incr var addr, return old addr r :: V a -> IO a -- read var w :: V a -> a -> IO () -- write var value and this unfolded translation do { qv <- r q; w p qv; i p; i q } assuming

Re: [Haskell-cafe] monad subexpressions

2007-08-03 Thread Claus Reinke
I've heard Simon (Peyton-Jones) twice now mention the desire to be able to embed a monadic subexpression into a monad. That would be http://article.gmane.org/gmane.comp.lang.haskell.prime/2267 .. Thoughts? what is the problem you're trying to solve, and is it worth the complication in synta

Re: FW: RE [Haskell-cafe] Monad Description For Imperative Programmer

2007-08-01 Thread Claus Reinke
a Monad is a type constructor with two operations, implementing a standard interface and following a few simple rules. the Monad type class tells you the interface (what operations you've got, and their types), the Monad laws tell you what all types implementing that interface should have in comm

Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Requestforfeedback

2007-07-29 Thread Claus Reinke
Oh! I had assumed that it was already considered rude to expose a non-exhaustive function to the outside world: you mean, as in: head, tail, fromJust, ..?-) whether exposing or using those is considered rude or not, the type system has nothing to tell us about their not handling some inputs,

Re: [Haskell-cafe] Re: [Haskell] View patterns in GHC: Request forfeedback

2007-07-25 Thread Claus Reinke
Hi Dan, No, of course not. All I meant to say is that sometimes you want a total view, and that a total view should be given a type that says as much. The latter says this better than the former. On the other hand, there are lots of circumstances in which you want a partial view, and I think

[Haskell-cafe] Re: [Haskell] Re: View patterns in GHC: Request for feedback

2007-07-24 Thread Claus Reinke
unit :: Typ -> Maybe () arrow :: Type -> Maybe (Typ,Typ) size :: Typ -> Integer size (unit -> ()) = 1 size (arrow -> (t1,t2)) = size t1 + size t2 Though I guess you would not object to: size (unit -> Just ()) = 1 size (arrow -> Just (t1,t2)) = size t1 + size t2 ? actually, i m

Re: [Haskell-cafe] Equational Reasoning goes wrong

2007-07-22 Thread Claus Reinke
Haskell is known for its power at equational reasoning - being able to treat a program like a set of theorems. when you're trying to do equational reasoning, you better make sure that you're reasoning with equations. as others have pointed out some of the more interesting relations between prog

Re: [Haskell-cafe] gui libs? no thanks, i'm just browsing.. ;-)

2007-07-21 Thread Claus Reinke
That is all true. ABI compatibility would be nice. But I don't see how to combine with GHC's other goals. Notably, we frequently add new information to interface files, and it would be a major constraint not to be able to do so. that is the bit i never quite understood: if newer formats just

Re: [Haskell-cafe] gui libs? no thanks, i'm just browsing.. ;-)

2007-07-19 Thread Claus Reinke
the idea is well known: build your app as a server, and put an ajax-based gui in front of it, even if server and browser run on the same machine. A more desktopy alternative: http://www.gtk-server.org/ that looks promising. does that mean one could have the best of both worlds - gtk2hs were av

Re: [Haskell-cafe] gui libs? no thanks, i'm just browsing.. ;-)

2007-07-19 Thread Claus Reinke
| You're right, that's annoying. It's particularly a problem for Windows | GHC users who expect pre-built binaries, since GHC currently requires | all libs to be rebuilt with each new minor GHC version. Are you sure? We try hard not to change interface-file format or calling conventions between

Re: [Haskell-cafe] gui libs? no [...] - bug report

2007-07-19 Thread Claus Reinke
as Marc pointed out, there was a problem with my javascript use that showed up as an event error in firefox. Miguel has suggested how to remove that issue. i've also added commands to set the colour explicitly, and to move to the origin after translation, so that firefox now draws whole squares

[Haskell-cafe] gui libs? no thanks, i'm just browsing.. ;-)

2007-07-18 Thread Claus Reinke
gui libs are wonderful, but haskell sometimes has too few and sometimes has too many. and those we have do not work with every haskell implementation. and when they do work (usually with ghc, these days), they need to be rebuilt whenever ghc is updated, even if the gui lib hasn't changed at all

Re: [Haskell-cafe] Re: Haskell shootout game

2007-07-16 Thread Claus Reinke
There are lots of "robot battle" games out there, like but none in Haskell, of course. do the icfp contests count? not even limited to haskell, and there were several tasks that look related, including: http://alliance.seas.upenn.edu/~plclub/cgi-bin/contest/ants.html http://icfpc.plt-scheme.o

Re: [Haskell-cafe] Indentation Creep

2007-07-16 Thread Claus Reinke
as Thomas pointed out off-list, the transformation sequence as given is not type-preserving. i even documented that problem in my email, because i thought the type was dodgy, but forgot to track it down before posting. so here are the changes. a good demonstration that "does it still compile?

Re: [Haskell-cafe] Indentation Creep

2007-07-15 Thread Claus Reinke
Everyone's suggestions show that in order to advance to a level 3 Haskell Mage[*], I need to spend a chunk of time learning to grok monad transformers. let's see whether we can get from the initial version to the suggested final version without any magic, in a somewhat long sequence of minor r

Re: [Haskell-cafe] Maintaining the community

2007-07-15 Thread Claus Reinke
This is a bit tangental, but... One problem I sometimes have is not knowing the status of things. E.g., you read about Associated Types, and then you go "hey, is this implemented now? is it being implemented soon? etc." (Don't all rush in and tell me about ATs - I'm only picking it as an exam

Re: [Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-14 Thread Claus Reinke
I've already sent an email to the haskell.org admin requesting that /HOpenGL be made publically unviewable. Stefan in the interim, there's now a bare-bones wiki page: http://www.haskell.org/haskellwiki/Opengl quite dreary, but at least visitors will no longer thing that the binding should

Re: [Haskell-cafe] List of authors happy to have work moved totheHaskell wiki

2007-07-14 Thread Claus Reinke
(sorry if you already know this, just want to clarify. All AIUI, IANAL, etc) neither am i!-) If you publish something under licence A, you still remain the copyright holder, and can later also publish it under licence B. You can also publish it combined with other material under licence B. y

Re: [Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-14 Thread Claus Reinke
Can someone post either a simple Hopengl example or a link to one please? (Something that displays a triangle or two, preferably rotatign slowly, ideally rotating when you move the mouse). in addition to HOpenGL, check out the GLUT binding as well (same mailing list): http://darcs.haskell.or

Re: [Haskell-cafe] Haskell & monads for newbies

2007-07-14 Thread Claus Reinke
Yeah, the laws confused me for a while as well. Hint to guys writing Haskell documentation, we're not all doing CS phD you know ;-) We just want to get things done ;-) teachers and tutorials making a fuss about some concept is the surest way to guarantee that learners will find that concept

Re: [Haskell-cafe] List of authors happy to have work moved to theHaskell wiki

2007-07-14 Thread Claus Reinke
I've created a page to track contributors who are happy to have their work moved to the Haskell wiki, and thus explicitly licensed under the `simple permissive license'. http://haskell.org/haskellwiki/Haskell_Cafe_migration Hi Don, i'm all for using mailinglist postings to improve the wik

Re: [Haskell-cafe] Indentation Creep

2007-07-13 Thread Claus Reinke
is there Haskellmagic that I still need to learn? one bit of magic, coming right up!-) of course, we haskellers are the lazy types, and if none of that helps, some Monad often does. in ghci or hugs, try ':browse Data.Maybe' and ':info Maybe'. in particular, 'case . of Nothing -> . ; Just . -

Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Claus Reinke
Perhaps those of you who have found good, free NNTP servers would care to share these well kept secrets? have you tried gmane.org? http://gmane.org/about.php http://news.gmane.org/search.php?match=haskell (there's nntp://news.gmane.org/ and http://news.gmane.org/ among others) claus

Re: [Haskell-cafe] Maintaining the community

2007-07-13 Thread Claus Reinke
As we sit here riding the Haskell wave: http://www.cse.unsw.edu.au/~dons/tmp/cafe.png with nearly 2000 (!) people reading haskell-cafe@, perhaps its time to think some more about how to build and maintain this lovely Haskell community we have. my replies to some of the issues raised in thi

Re: [Haskell-cafe] Looking for final year project - using Haskell, or another functional language

2007-07-12 Thread Claus Reinke
Building on what Hugh was getting at, beyond better opengl bindings, i'm curious: just what do you think is missing in haskell's opengl binding? just be sure to ignore http://www.haskell.org/HOpenGL/ , which should be moved to the wiki or to /dev/null. instead, look at the implementation, ma

Re: [Haskell-cafe] unresolved overloading

2007-07-12 Thread Claus Reinke
g x = [2] ++ [3,5..truncate(sqrt x)] p n= fp n (g n) fp n [ ]= True fp n (x:xs) = if (mod n x) == 0 then False else fp n xs ERROR - Unresolved overloading *** Type : (RealFrac a, Floating a, Integral a) => Bool *** Expression : p 103 I know why, ther

Re: [Haskell-cafe] Strange results when trying to create large Boolarrays.

2007-07-12 Thread Claus Reinke
I'd really like to have errors on overflow, at least as an option, even if it is costly in terms of performance. Is there a Trac ticket or something for this? as far as safety aspects are concerned, you might consider adding yourself to http://hackage.haskell.org/trac/ghc/ticket/1380 ? althoug

Re: [Haskell-cafe] embedding Haskell: problematic polymorphism

2007-07-11 Thread Claus Reinke
Say I have 3 boxes: Box 1: [1,2,5,3]:: [Float] Box 2: reverse :: [a] -> [a] Box 3: putStrLn . show :: (Show b) => b -> IO () I wonder, is it possible to create these boxes separately at runtime (each box being compiled/loaded separately with hsplugins), then connect them t

Re: [Haskell-cafe] In-place modification

2007-07-11 Thread Claus Reinke
... still talking about "In-place modification" ? yes. in the time-honoured tradition of demonstrating concepts by means of meta-circular arguments. ;-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/h

Re: [Haskell-cafe] reading existential types

2007-07-09 Thread Claus Reinke
which is the important hint! the parser used for 'read' depends on the return type, but the existential type _hides_ the internal type which would be needed to select a read parser. forall e . (MyClass e, Show e, Read e) => MT (e,Int) the 'Read' there ensures that we only inject types that

Re: [Haskell-cafe] reading existential types

2007-07-09 Thread Claus Reinke
I'd like to be able to use MT to build a list like: [MT (T1a,1), MT (T1b,3)] And I'd like to read str with: read $ show str Substituting return (m) with return (MT m) leads to error messages like: Ambiguous type variable `e' in the constraints which is the important hint! the parser used for

Re: [Haskell-cafe] A very nontrivial parser

2007-07-07 Thread Claus Reinke
Now take decodeRLEb and feed it's output to some nontrivial parser, and then feed the remainder of the input, unmodified, into another parser: so the code as posted didn't exhibit a full use case. that specification is still a bit vague. assuming that p1: decodeRLE, p2: nontrivial parser, and

Re: [Haskell-cafe] Re: Playing with delimited continuations

2007-07-07 Thread Claus Reinke
Anyhow, thanks for the input, and the pointers to the papers and such (and writing so many of them in the first place. :) Incidentally, I really enjoyed your "Delimited continuations in operating systems" paper. Reading that one really made things click for me as to how delimited continuations c

Re: [Haskell-cafe] update on SoC projects?

2007-07-06 Thread Claus Reinke
there still seem to be only three entries for status reports (of 9 projects) on that page. have the other projects been abandoned? since the existing reports are fairly terse, it isn't always easy to guess what is going on (eg, why would parts of hackage web depend on things like debian, sdl, x11

Re: [Haskell-cafe] A very nontrivial parser [Source code]

2007-07-06 Thread Claus Reinke
source code is always useful, as it is concrete. but some comments about purpose and important aspects would help, too, lest we optimise away the parts you're most interested in. as it stands, i must assume that 'decodeRLEb' is the purpose of the exercise, and it isn't clear to me why that requir

Re: [Haskell-cafe] Parsers are monadic?

2007-07-05 Thread Claus Reinke
(b) i like my combinator grammars to be reversible, so that a single grammar specification can be used for both parsing and unparsing/pretty-printing. that means i have to define the details myself anyway. the latest such experiment is not necessarily the simplest variant, for in

Re: [Haskell-cafe] folds with escapes

2007-07-05 Thread Claus Reinke
Can you do dropWhile in terms of foldr? I don't see how. If you are really keen, you might want to try altering the "working backwards with tuples" version into one which is properly lazy (many people who read the paper pointed out the omission). you might want to mention the story of the p

Re: [Haskell-cafe] Parsers are monadic?

2007-07-04 Thread Claus Reinke
(b) i like my combinator grammars to be reversible, so that a single grammar specification can be used for both parsing and unparsing/pretty-printing. that means i have to define the details myself anyway. Oh cool - this is something I have wanted for a long time. Anything released

Re: [Haskell-cafe] Sparse documentation

2007-07-04 Thread Claus Reinke
Simon, if the less-talented among us (like me) want to contribute to GHC's docs -- and especially documenting the libraries -- what's the best way to go about this? I'm not too comfortable with the notion of just going into GHC's guts and Haddocking the comments, contributing patches willy-nilly

Re: [Haskell-cafe] Sparse documentation

2007-07-03 Thread Claus Reinke
the references have not been updated, it seems. but once you've used the name "Mark P Jones", mentioned next to the link, to google for a current url for his publications page, you'll (a) find a treasure-trove of haskell papers http://web.cecs.pdx.edu/~mpj/ (b) be able to submit a fix for t

Re: [Haskell-cafe] Re: Parsers are monadic?

2007-07-02 Thread Claus Reinke
class Monad m => MonadError e m | m -> e where throwError :: e -> m a catchError :: m a -> (e -> m a) -> m a .. power of TwoCont? I mean, it still seems like there's an operation missing that supplies new left and right continuations at once. i guess, instead of one DiMonad with two sets

Re: [Haskell-cafe] Parsers are monadic?

2007-07-02 Thread Claus Reinke
contrary to monadic parsers, those continuation-based parsers had *two* continuations, one for success, one for failure. and that seemed to be a very natural match for the problem. Two-continuations is a monad too, right? yes, but my problem is not about giving them a monadic interface, but ab

Re: [Haskell-cafe] Parsers are monadic?

2007-07-01 Thread Claus Reinke
When you pretend you've never heard of monads or arrows, and write down the types what do you get? this question made me wonder whether i could still recall how i used to write parsers before i heard of monads or arrows. it is difficult not to fall back into the pattern of state transformer mo

Re: [Haskell-cafe] Re: Parsers are monadic?

2007-06-30 Thread Claus Reinke
First post. I'm a newbie, been using Haskell for about a week and love it. Anyway, this is something I don't understand. Parsers are monadic. I can see this if the parser is reading from an input stream but if there's just a block of text can't you just have the parser call itself recursively feed

Re: [Haskell-cafe] avoiding command window with wxHaskell on Windows?

2007-06-30 Thread Claus Reinke
For the application I'm building, besides being able to launch it as above, I want also to be able to "invoke" it (normally from a command line). A program so invoked can interact with its invoker, and the invoker awaits the program's completion and gets its termination status. From what Esa

Re: [Haskell-cafe] Parsers are monadic?

2007-06-30 Thread Claus Reinke
Have you used Parsec? i read about it when it came out, but i've always defined my own combinators. in case you wonder, there are two reasons for this: (a) the approximation of parsers as monads is close enough that a simple type Parser m a = StateT String m a gives us the basic com

Re: [Haskell-cafe] Parsers are monadic?

2007-06-30 Thread Claus Reinke
The standard, naïve approach to monadic parsing is very nice, but inefficient. So *please read* some material based on Hutton&Meijer approach, but don't stay there, read something more modern, since we thereby seem to have left the phase of simple answers to simple questions;-) i'd like to raise

Fw: [Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Claus Reinke
i just noticed that i forgot to copy this message to the list.. - Original Message - From: "Claus Reinke" <[EMAIL PROTECTED]> To: "apfelmus" <[EMAIL PROTECTED]> Sent: Monday, June 25, 2007 12:20 PM Subject: Re: [Haskell-cafe] Re: Best idiom for avoid

Re: [Haskell-cafe] Re: Best idiom for avoiding Defaulting warningswith ghc -Wall -Werror ??

2007-06-25 Thread Claus Reinke
if you have a strongly and dynamically typed language, you can embed strongly and statically typed languages into it. by default, that means you get more type-checks than necessary and type-errors later than you'd wish, but you still get them. Are you sure this is true in a meaningful way? You

Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Claus Reinke
Now I've got a situation I can't figure out how to resolve. I want to have a set of actions which are executed sequentially, but which, before I even start to execute the first one, have been inspected for legality and/or plausibility. Consider this kind of sequence: do x <- performActionA y

Re: [Haskell-cafe] Haskell version of ray tracer code ismuchslowerthan the original ML

2007-06-24 Thread Claus Reinke
also try replacing that (foldl' intersect') with (foldr (flip intersect'))! OK, next question: Given that I'm using all the results from intersect', why is the lazy version better than the strict one? Is ghc managing to do some loop fusion? haskell tends to prefer foldr where mls prefer foldl,

Re: [Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-24 Thread Claus Reinke
True enough, in a sense, a dynamically typed language is like a statically typed language with only one type (probably several by distinguishing function types) and many incomplete pattern matches. So, you can embed a dynamically typed language into a strongly typed language without loosing stati

Re: [Haskell-cafe] Haskell version of ray tracer code is muchslowerthan the original ML

2007-06-23 Thread Claus Reinke
http://www.kantaka.co.uk/darcs/ray try making ray_sphere and intersect' local to intersect, then drop their constant ray parameter. saves me 25%. claus also try replacing that (foldl' intersect') with (foldr (flip intersect'))! using a recent ghc head instead of ghc-6.6.1 also seems to make a

Re: [Haskell-cafe] Haskell version of ray tracer code is much slowerthan the original ML

2007-06-22 Thread Claus Reinke
http://www.kantaka.co.uk/darcs/ray try making ray_sphere and intersect' local to intersect, then drop their constant ray parameter. saves me 25%. claus ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haske

Re: [Haskell-cafe] Re: Haskell version of ray tracer code is muchslower than the original ML

2007-06-22 Thread Claus Reinke
on second thought, user-defined profiles are a two-edged sword, negating the documentation advantages of in-source flags. better to handle that in the editor/ide. but predefined flag profiles would still seem to make sense? there is something wrong about this wealth of options. it is great that

Re: [Haskell-cafe] Re: Haskell version of ray tracer code is much slower than the original ML

2007-06-22 Thread Claus Reinke
-fvia-C -fexcess-precision -optc-mfpmath=sse2 is there, or should there be a way to define -O "profiles" for ghc? so that -O would refer to the standard profile, -Ofp would refer to the combination above as a floating point optiimisation profile, other profiles might include things like -funbo

Re: [Haskell-cafe] "Graphical Haskell"

2007-06-22 Thread Claus Reinke
Since nobody gave an answer on this topic, I guess it is insane to do it in Haskell (at least for a newbie)? :) not necessarily; we're all waiting for your first release?-) I would like to create a program that allows you to create such flow graphs, and then let GHC generate the code and do ty

Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-22 Thread Claus Reinke
Most languages, even Java, have a reflection capability to dynamically inspect an object. _Even_ Java? That's a strange point of view considering how much money went into this technology. they didn't take reflection seriously at first, initially providing only a half-baked feature set; that st

Re: [Haskell-cafe] Re: Orthogonal Persistence in Haskell

2007-06-21 Thread Claus Reinke
with orthogonal persistence, everything a program touches might persist, but usually, programs talk about the data being persistet (?), not about whether that data is currently temporary or in long-term storage. if you want to move such data between processes or storage areas, you move the referen

Re: [Haskell-cafe] Useful IDE features -

2007-06-20 Thread Claus Reinke
in practice, overloading introduces overhead that might hamper performance. You mean overloading in general, so using type classes? Is this comparable to the Java/C#/C++ overhead with virtual methods, so one extra level of indirection before the function gets called? Or is it much worse? usual

[Haskell-cafe] Re: Orthogonal Persistence in Haskell

2007-06-20 Thread Claus Reinke
Prevayler is an efficient and very simple way of providing application state persistency. Essentially: - all the state is kept in memory, in native language data structures - whenever a write transaction is performed the system automatically serialises a description of the transaction so that

Re: [Haskell-cafe] Useful IDE features -

2007-06-19 Thread Claus Reinke
That looks nice, just unfortunate you need to cast to ::Float in homer2?Age::Float. I don't see why this is needed, but I must say I don't understand your code completely yet, working on that :) that annotation is not needed if you keep the functional dependency (which just states that record ty

Re: [Haskell-cafe] Useful IDE features - "implement instance"

2007-06-19 Thread Claus Reinke
Just another wild idea which I might find useful, but is more like refactoring, is to convert the fields of a record to get/set type-classes, and refactor all usages of those fields. you could use a preprocessor (DrIFT, Data.Derive) to derive the instances, but you need to share the class decla

Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-18 Thread Claus Reinke
hi titto, I actually knew about Croquet but I thought of it mostly as an "open-source second life" because of its emphasys on shared 3D worlds but you are quite right, it might also be useful for cooperative software development. the first corporation betting its money on croquet is Qwaq:

Re: [Haskell-cafe] To yi or not to yi, is this really the question? A plea for a cooperative, ubiquitous, distributed integrated development system.

2007-06-18 Thread Claus Reinke
Having just presented a case for the possible rationality of the irrational decision of creating an Emacs-like IDE in Haskell, I wonder if we should not be even more irrational and contemplate the possibility of using Haskell to create a radically different kind of IDE.. New technologies are ofte

Re: [Haskell-cafe] Useful IDE features - "implement instance"

2007-06-18 Thread Claus Reinke
Another feature which would be cool for an IDE is: "implement instance". So you automatically get to see all the functions of a type class you need to implement. Using C#/Java, this is used all over the place. sounds potentially useful, but perhaps not quite as useful as one might expect: if you

<    1   2   3   4   5   6   >