Re: Functional design patterns (was: How to get functional software engineering experience?)

2002-05-15 Thread Kellom{ki Pertti
On Wed, May 15, 2002 at 08:13:22PM +0200, [EMAIL PROTECTED] wrote: > Yet another problem is that design patterns are all about design > and less about coding. Many challenges in functional programming are about > coding, and just about coding. This is something I've chatted about with a colleague

Re: State monads don't respect the monad laws in Haskell

2002-05-15 Thread Janis Voigtlaender
John Launchbury wrote: > > I watched with interest the discussion about the ravages of `seq`. > > In the old days, we protected uses of `seq` with a type class, to keep it at > bay. There was no function instance (so no problem with the state monads, or > lifting of functions in general), and th

Re: Newbie attempts to generate permutations

2002-05-15 Thread Mark Phillips
I've found out what was wrong. I should have written: perms (a:as) = concatMap (\b -> map ((:) (fst b)) (perms (snd b))) (del (a:as)) but I still don't understand why it had the error message it did. Ie, how did it infer the type of my lambda function to be "([a],[a]) -> [[a]]"? Cheers, Mark

Newbie attempts to generate permutations

2002-05-15 Thread Mark Phillips
Hi, I have recently started learning Haskell and, in writing a HUGS module to generate permutations, have been told I have an error but I don't understand why. The module is: module Arrange where -- -- perms :: [a] -> [[a]] perms [] = [[]] perms (a:as) = concatMap (\b -> fst b:perms (snd b)) (d

Re: Functional design patterns (was: How to get functional software engineering experience?)

2002-05-15 Thread Andrew J Bromage
G'day all. On Wed, May 15, 2002 at 08:13:22PM +0200, [EMAIL PROTECTED] wrote: > BTW, FP is older than OOP. So why are we so late :-) ? I know you meant it as an offhand remark, but I think there are two serious reasons why. The first one is that OOP and GUIs happened at around the same time an

Re: State monads don't respect the monad laws in Haskell

2002-05-15 Thread Ashley Yakeley
At 2002-05-15 09:48, John Launchbury wrote: >Will the next version of Haskell have something better. I hope so, but I >fear not. Rename it "unsafeSeq"? No puns please... But I think breaking Monad laws etc. is a different kind of unsafeness from usPIO etc. -- Ashley Yakeley, Seattle WA unsa

Re: How to get functional software engineering experience?

2002-05-15 Thread Andrew J Bromage
G'day all. On Wed, May 15, 2002 at 12:53:30PM +0100, Claus Reinke wrote: > Btw, I wouldn't subscribe to Andrew's opinion that "there isn't a lot of > functional (or even declarative) software engineering experience out > there.". Just to clarify: I meant to emphasise the _declarative_ part rath

Re: preprocessing printf/regex strings (like ocaml)

2002-05-15 Thread John Meacham
I wrote a printflike function which used existential types and a pretty simple class a while ago, although in retrospect i could have done it better with partial application (and pure haskell 98). http://homer.netmar.com/~john/computer/haskell/Format.hs John -- ---

Re: Functional design patterns (was: How to get functional software engineering experience?)

2002-05-15 Thread Lämmel
--- Joe English <[EMAIL PROTECTED]> wrote > ... there are plenty of FP design patterns > in common use, it's just that FP'ers don't usually use the term > "design patterns" to describe them. I'm thinking of things > like catamorphisms, anamorphisms (aka folds/unfolds), monads > and functors, "th

Re: preprocessing printf/regex strings (like ocaml)

2002-05-15 Thread Martin Norbäck
tis 2002-05-14 klockan 18.56 skrev anatoli: > Robert Ennals <[EMAIL PROTECTED]> wrote: > > Surely that problem only arises if one insists on encoding all the relevant > > information inside a string. > > This is pretty much the only option, because translators > and programmers are different peo

Re: Functional design patterns (was: How to get functional software engineering experience?)

2002-05-15 Thread Joe English
Ralf Laemmel wrote: > > Joost Visser and I, we worked out a few maybe not so obvious functional > programming pattern [...] > http://www.cs.vu.nl/Strafunski/dp-sf/ Neat! > I have the feeling that the FP community has a hard time getting started > with design patterns. I believe quite the

Functional design patterns (was: How to get functional software engineering experience?)

2002-05-15 Thread Ralf . Laemmel
Andrew J Bromage wrote: > On the other hand, it's an exciting time to do engineering in > declarative languages, because we can invent the design patterns and > discover what the good habits are as we go along. BTW, FP is older than OOP. So why are we so late :-) ? Joost Visser and I, we worked

Re: State monads don't respect the monad laws in Haskell

2002-05-15 Thread John Launchbury
I watched with interest the discussion about the ravages of `seq`. In the old days, we protected uses of `seq` with a type class, to keep it at bay. There was no function instance (so no problem with the state monads, or lifting of functions in general), and the type class prevented interference

Re: State monads don't respect the monad laws in Haskell

2002-05-15 Thread Jan-Willem Maessen
Dylan Thurston writes: > Do you ever use floating point addition? > > I rarely use floating point, but it is sometimes more useful than the > alternatives, as long as you bear in mind its limitations. Yep, floating point is by necessity a bit of a mess. On the other hand, I don't think we ought

Re: What does FP do well? (was How to get functional software engineering experience?)

2002-05-15 Thread Hal Daume III
On Wed, 15 May 2002, Karl-Filip Faxen wrote: > On the performance (or not) of high level code: I'm working on a > compiler with a strong emphasis on generating good code for I wish you luck! > It is going to be interesting to see how much this will give. I suspect > that part of the performan

Re: How to get functional software engineering experience?

2002-05-15 Thread Jeffrey Palmer
On Tuesday 14 May 2002 07:22 pm, Andrew J Bromage wrote: > On the other hand, it's an exciting time to do engineering in > declarative languages, because we can invent the design patterns and > discover what the good habits are as we go along. This is very interesting to me, as I have a great dea

Re: State monads don't respect the monad laws in Haskell

2002-05-15 Thread Dylan Thurston
On Tue, May 14, 2002 at 12:32:30PM -0400, Jan-Willem Maessen wrote: > Chalk me up as someone in favor of laws without exceptions. Do you ever use floating point addition? I rarely use floating point, but it is sometimes more useful than the alternatives, as long as you bear in mind its limitatio

Mathematics of Program Construction 2002 Call for Participation

2002-05-15 Thread mpc02
Call for Participation MPC 2002 - Sixth International Conference on MATHEMATICS OF PROGRAM CONSTRUCTION July 8 - 10, 2002 http://www.cs.ukc.ac.uk/events/conf/2002/mpc2002/ WCGP '02 - IFIP WG2.1 Working Conference on GENERIC PROGRAMMING July 11 - 12,

Re: What does FP do well? (was How to get functional software engineering experience?)

2002-05-15 Thread Karl-Filip Faxen
Hi! On the performance (or not) of high level code: I'm working on a compiler with a strong emphasis on generating good code for programs written in a fairly generic style. This work is very far from being completed, but some of the highlights of the compiler are: - Aggressive removal of highe

Re: What does FP do well? (was How to get functional software engineering experience?)

2002-05-15 Thread D. Tweed
On Wed, 15 May 2002, Scott Finnie wrote: > As a naive but interested newbie, I'm very keen to understand those > things that FP does well - and just as importantly, those things it > doesn't. (I'm coming at this from use in an industrial context). > Based on (_very_) limited experience so far, I

What does FP do well? (was How to get functional software engineering experience?)

2002-05-15 Thread Scott Finnie
Claus Reinke wrote: > The ground is better prepared than ever. It remains up to you to > decide whether you're confident enough to use FP, without needless > hype, and just for the many things you know it can do well. As a naive but interested newbie, I'm very keen to understand those things t

Re: How to get functional software engineering experience?

2002-05-15 Thread Claus Reinke
> > However, it appears that the only place (short of Ericsson) I can actually > > work on a complex functional system is in academia. Unfortunately, this is > > not an option, as I have no Ph.D., and going back to school is probably not > > realistic. The latter depends on your background. With