[Haskell-cafe] Re: The Opposite of $

2007-12-04 Thread Alan Hawkins
| is not defined in the prelude but can be defined as let (|) = flip ($) to make it the opposite of $ which means the syntax looks more like the Unix pipe '|' command eg. filter (\x- x 3 x 7) $ [1..10] ++ [5] [1..10] ++ [5] | filter (\x- x 3 x 7) res: [4,5,6] note that with the |

[Haskell-cafe] regexen no go with 6.8.1?

2007-12-04 Thread Jason Dusek
Is it just me, or are all the regex implementations broken with new change in lib layout for 6.8.1? Are fixes available in darcs? -- _jsn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Felipe Lessa
On Dec 4, 2007 1:28 AM, Don Stewart [EMAIL PROTECTED] wrote: -- How to display results instance Show Action where show MoveOutOfBounds= Sorry you can't move in that direction. show (MoveBadTerrain a) = case a of Wall - You

Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Dougal Stanton
On 04/12/2007, Felipe Lessa [EMAIL PROTECTED] wrote: I always thought show was meant for returning a String that could be used to recreate the original data if you copy-pasted it in your code or if you used read (i.e. read . show == id). Reading the documentation more carefully, I see that

[Haskell-cafe] Re: Nofib modifications

2007-12-04 Thread Simon Marlow
I'd do something like #if defined(__nhc98__) || defined(YHC) #define NO_MONOMORPHISM_RESTRICTION #endif #ifdef NO_MONOMORPHISM_RESTRICTION powers :: [[Integer]] #endif just to make it quite clear what's going on. (good comments would do just as well). Cheers, Simon Simon

[Haskell-cafe] Re: Leopard: ghc 6.8.1 and the case of the missing _environ

2007-12-04 Thread Simon Marlow
Joel Reymont wrote: Symptoms: You build 6.8.1 from source on Leopard (x86 in my case) and then junior:ghc-6.8.1 joelr$ ghci GHCi, version 6.8.1: http://www.haskell.org/ghc/ :? for help ghc-6.8.1: /usr/local/lib/ghc-6.8.1/lib/base-3.0.0.0/HSbase-3.0.0.0.o: unknown symbol `_environ' Loading

Re: [Haskell-cafe] Re: do

2007-12-04 Thread Luke Palmer
On Dec 4, 2007 11:39 AM, Jules Bean [EMAIL PROTECTED] wrote: Ben Franksen wrote: I don't buy this. As has been noted by others before, IO is a very special case, in that it can't be defined in Haskell itself, and there is no evaluation function runIO :: IO a - a. This is a straw man. Most

Re: [Haskell-cafe] Re: do

2007-12-04 Thread Jules Bean
Ben Franksen wrote: I don't buy this. As has been noted by others before, IO is a very special case, in that it can't be defined in Haskell itself, and there is no evaluation function runIO :: IO a - a. This is a straw man. Most monads will not have such a function: There is no function

Re: [Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-04 Thread Neil Bartlett
Hi Gwern, Shu-thing is great fun! I think Monadius isn't compiling because most of the source files are missing; you only have Main.hs in there. Regards Neil On 4 Dec 2007, at 01:53, [EMAIL PROTECTED] wrote: Hi everyone. With the permission of the authors, I'd like to announce the

Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread Kalman Noel
Ryan Ingram wrote: On 12/3/07, Kalman Noel [EMAIL PROTECTED] wrote: You're confusing sum and product types. I'm not so sure; it looks like they already have that type (Exp) and wants to use AlgExp to hold the folding functions used. Ah, I didn't catch that on the first read. I suppose Carlo

Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Henning Thielemann
On Tue, 4 Dec 2007, Dougal Stanton wrote: On 04/12/2007, Felipe Lessa [EMAIL PROTECTED] wrote: I always thought show was meant for returning a String that could be used to recreate the original data if you copy-pasted it in your code or if you used read (i.e. read . show == id). Reading

[Haskell-cafe] Re: [Haskell] IVars

2007-12-04 Thread Bertram Felgenhauer
[redirecting to haskell-cafe] Simon Peyton-Jones wrote: But since the read may block, it matters *when* you perform it. For example if you print Hello and then read the IVar, you'll block after printing; but if you read the IVar and then print, the print won't come out. If the operation was

Re: [Haskell-cafe] regexen no go with 6.8.1?

2007-12-04 Thread Duncan Coutts
On Tue, 2007-12-04 at 02:02 -0800, Jason Dusek wrote: Is it just me, or are all the regex implementations broken with new change in lib layout for 6.8.1? Are fixes available in darcs? Use these ones: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/regex-base-0.72.0.1

Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Jules Bean
Felipe Lessa wrote: On Dec 4, 2007 1:28 AM, Don Stewart [EMAIL PROTECTED] wrote: -- How to display results instance Show Action where show MoveOutOfBounds= Sorry you can't move in that direction. show (MoveBadTerrain a) = case a of

Re: [Haskell-cafe] An interesting monad: Prompt

2007-12-04 Thread Ryan Ingram
Ask and ye shall receive. A simple guess-a-number game in MonadPrompt follows. But before I get to that, I have some comments: Serializing the state at arbitrary places is hard; the Prompt contains a continuation function so unless you have a way to serialize closures it seems like you lose.

[Haskell-cafe] unification would give infinite type

2007-12-04 Thread Rafael
Hi... I give this error using hugs for the code: --- f = foldl (\x y - add x y) 0 [1,2,3] add x y = return (x + y) --- I try: f = foldl (\x y - counter x y) (return 0) [1,2,3] but it dont solve, and

Re: [Haskell-cafe] unification would give infinite type

2007-12-04 Thread Emil Axelsson
Hi, Depending on what you want, you should either remove 'return' or change to 'foldM' (from Control.Monad). If you choose the latter, you also need to add a type signature to f (because of the monomorphism restriction). / Emil On 2007-12-04 14:43, Rafael wrote: Hi... I give this error

Re: [Haskell-cafe] unification would give infinite type

2007-12-04 Thread Mattias Bengtsson
Rafael skrev: Hi... I give this error using hugs for the code: --- f = foldl (\x y - add x y) 0 [1,2,3] add x y = return (x + y) --- I try: f = foldl (\x y - counter x y) (return 0) [1,2,3] but it

Re: [Haskell-cafe] Array copying

2007-12-04 Thread Jules Bean
Andrew Coppin wrote: Andrew Coppin wrote: copy :: Word32 - IOUArray Word32 Bool - Word32 - IO (IOUArray Word32 Bool) copy p grid size = do let size' = size * p grid' - newArray (1,size') False mapM_ (\n - do b - readArray grid n if b then mapM_ (\x - writeArray grid' (n

[Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Steffen Mazanek
Hello, I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance instance Arbitrary [Stmt] (mainly to restrict the size of the list). In quickcheck an instance Arbitrary of lists is already defined. Which parameters do I have to give

Re: [Haskell-cafe] unification would give infinite type

2007-12-04 Thread Rafael
Hi Emil, I'm beginning in monad area... I don't know about monomorphis restriction, but foldM works, a lot of thanks... Matias tnks too, i'm conscious about return in the monadic chain. thnks. On Dec 4, 2007 12:00 PM, Emil Axelsson [EMAIL PROTECTED] wrote: Hi, Depending on what you

[Haskell-cafe] Re: Haskell interface file (.hi) format?

2007-12-04 Thread Simon Marlow
Stefan O'Rear wrote: On Sun, Dec 02, 2007 at 05:45:48AM +0100, Tomasz Zielonka wrote: On Fri, Nov 30, 2007 at 08:55:51AM +, Neil Mitchell wrote: Hi Prelude :b Control.Concurrent.MVar module 'Control.Concurrent.MVar' is not interpreted :b now defaults to :breakpoint, you want :browse

Re: [Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Isaac Dupree
Steffen Mazanek wrote: Hello, I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance instance Arbitrary [Stmt] (mainly to restrict the size of the list). you don't always need to use instances. for example, I have (where

Re: [Haskell-cafe] Advice for clean code.

2007-12-04 Thread Don Stewart
jules: Felipe Lessa wrote: On Dec 4, 2007 1:28 AM, Don Stewart [EMAIL PROTECTED] wrote: -- How to display results instance Show Action where show MoveOutOfBounds= Sorry you can't move in that direction. show (MoveBadTerrain a) = case a of

Re: [Haskell-cafe] An interesting monad: Prompt

2007-12-04 Thread Thomas Hartman
Thank you! I really appreciate your explanation, and I hope this will enable me to do some interesting and usefull stuff, in addition to firming up my understanding of some of the more advanced haskell type system features. MACID is a sort of RDBMS replacement used as a backend by the HAppS web

[Haskell-cafe] isSpace

2007-12-04 Thread Ryan Bloor
hi I am having trouble with a function that is supposed to eliminate spaces from the start of a String and return the resulting string. I reckon a dropWhile could be used but the isSpace bit is causing me problems... words :: String - String words a = case dropWhile isSpace a of

Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread Carlo Vivari
Brent Yorgey wrote: One comment: it looks like (add exp1 exp2), (and exp1 exp2) and so on above are not correct. The second argument of foldExp is a value of type Exp, so you are pattern-matching on the constructors of Exp, and constructors are always uppercase. Perhaps Exp has

Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-04 Thread Steven Fodstad
Dan Piponi wrote: Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer? If not, does anyone have any recommendations for how to do it efficiently. There are some obvious things that come to mind but which might involve

Re: [Haskell-cafe] isSpace

2007-12-04 Thread Brent Yorgey
On Dec 4, 2007 12:13 PM, Ryan Bloor [EMAIL PROTECTED] wrote: hi I am having trouble with a function that is supposed to eliminate spaces from the start of a String and return the resulting string. I reckon a dropWhile could be used but the isSpace bit is causing me problems... You need to

Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-04 Thread David Benbennick
On Dec 4, 2007 9:21 AM, Steven Fodstad [EMAIL PROTECTED] wrote: For the index, how about this: truncate . (/(log 2)) . log . fromIntegral That will not work. It will convert the Integer to Double, which will overflow if the Integer is very large.

[Haskell-cafe] isSpace

2007-12-04 Thread Ryan Bloor
HI I will try and explain it better. I am meaning to write a function that takes a string, apple and eliminates the spaces at the start ONLY. called removeSpace :: String - String I decided to use the function 'dropWhile' and another one 'isSpace' in the 'removeSpace'

Re: [Haskell-cafe] isSpace

2007-12-04 Thread Brent Yorgey
On Dec 4, 2007 1:29 PM, Ryan Bloor [EMAIL PROTECTED] wrote: HI I will try and explain it better. I am meaning to write a function that takes a string, apple and eliminates the spaces at the start ONLY. called removeSpace :: String - String I decided to use the function

Re: [Haskell-cafe] ANN: Shu-thing 1.0 and Monadius 0.9

2007-12-04 Thread gwern0
On 2007.12.04 12:12:04 +, Neil Bartlett [EMAIL PROTECTED] scribbled 2.2K characters: Hi Gwern, Shu-thing is great fun! I think Monadius isn't compiling because most of the source files are missing; you only have Main.hs in there. Regards Neil Oh - you're absolutely right. For some

Re: [Haskell-cafe] isSpace

2007-12-04 Thread Thomas Hartman
look at the examples of dropWhile usage you got from the first result when you get when you google on dropWhile. t. 2007/12/4, Ryan Bloor [EMAIL PROTECTED]: HI I will try and explain it better. I am meaning to write a function that takes a string, apple and eliminates the spaces at

[Haskell-cafe] Re: Nofib modifications

2007-12-04 Thread Neil Mitchell
Hi I'd do something like #if defined(__nhc98__) || defined(YHC) #define NO_MONOMORPHISM_RESTRICTION #endif #ifdef NO_MONOMORPHISM_RESTRICTION powers :: [[Integer]] #endif just to make it quite clear what's going on. (good comments would do just as well). I'd rather avoid CPP, as

Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Dan Piponi
On Dec 3, 2007 10:05 PM, David Benbennick [EMAIL PROTECTED] wrote: Could you please post your code here when you're done? I'd be interested to see the final result. This is just experimental code I'm playing with in order to implement exact real arithmetic, so there'll never be a final result

Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread David Menendez
On Dec 3, 2007 12:18 PM, Carlo Vivari [EMAIL PROTECTED] wrote: Hi! I'm a begginer in haskell and I have a problem with an exercise, I expect someone could help me: In one hand I have a declaration of an algebra data, like this: data AlgExp a = AlgExp { litI :: Int - a, litB :: Bool -

Re: [Haskell-cafe] foild function for expressions

2007-12-04 Thread Carlo Vivari
Yes,as I said before to other of you the exp data type was also declared in the exercise (my fault not to say it), and look as this: data Exp = LitI Int |LitB Bool |Add Exp Exp |And Exp Exp |If Exp Exp Exp -- View this message

Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Don Stewart
dpiponi: On Dec 3, 2007 10:05 PM, David Benbennick [EMAIL PROTECTED] wrote: Could you please post your code here when you're done? I'd be interested to see the final result. This is just experimental code I'm playing with in order to implement exact real arithmetic, so there'll never

[Haskell-cafe] Re: [Haskell] IVar

2007-12-04 Thread Isaac Dupree
A pure readIVar would be just like lazy I/O, with similar drawbacks. With readIVar, the effect that lets you observe the evaluation order is writeIVar; with hGetContents it is hClose. Conclusion: it's probably no worse than lazy I/O. Actually, it's considerably better. +: implementation

[Haskell-cafe] NY Functional Programmers Network: F# Talk by Don Syme, Monday De cember 10th at 7pm

2007-12-04 Thread Mansell, Howard
Credit Suisse will be hosting a talk by Don Syme from Microsoft Research on Monday December 10th. He will talk about F# and Microsoft's plans for it. This talk is arranged by the New York Functional Programmers Network, a group of individuals in the New York area who are interested in

[Haskell-cafe] RFI: Link errors with random pkg on 6.8.1

2007-12-04 Thread Jim Stuttard
Hi, Getting same error in 2 diff. apps * built with ghc-6.8.1. * random-1.0.0.0 also built with 6.8.1 * random-1.0.0.0 is registered # HAppS -6.8.1/lib/random-1.0.0.0/HSrandom-1.0.0.0.o: unknown symbol `oldzmtimezm1zi0zi0zi0_SystemziTime_a99_info' ghc-6.8.1: unable to load package

Re: [Haskell-cafe] Looking for smallest power of 2 = Integer

2007-12-04 Thread Conal Elliott
Whatever the answer is, I expect it's relevant to Data.IntSet, which uses big-endian patricia trees. - Conal On Dec 3, 2007 8:36 PM, Dan Piponi [EMAIL PROTECTED] wrote: Is there anything in any of the interfaces to Integer that will allow me to quickly find the highest bit set in an Integer?

[Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Neil Mitchell
Hi server text | Just xs - parse text = let x | field1 `elem` xs = error ... do one thing ... | field2 `elem` xs = error ... do something else ... in x server _ = error ... invalid request ... This now has the wrong semantics - before if parse text returned Just []

Re: [Haskell-cafe] Re: [Haskell] IVar

2007-12-04 Thread Conal Elliott
main = do --irrelevant x - newIVar let y = last [1..] print test --was irrelevant writeIVar x 3 print y Exactly. The termination concern doesn't seem to have to do with readIVar. On Dec 4, 2007 11:56 AM, Isaac Dupree [EMAIL PROTECTED] wrote: A pure readIVar would be

[Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Paulo J. Matos
Hello all, As you might have possibly read in some previous blog posts: http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11 we (the FPSIG group) defined: data BTree a = Leaf a | Branch (BTree a) a (BTree a) and a function that

Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread David Benbennick
On Dec 4, 2007 11:51 AM, Don Stewart [EMAIL PROTECTED] wrote: Awesome. We can use this in Data.Bits, if you've got some QuickChecks for it. Hear hear. But is there any way to just make the compiler use fastTestBit in place of testBit :: (Bits a) = a - Int - Bool when a = Integer? (That is,

Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Don Stewart
dbenbenn: On Dec 4, 2007 11:51 AM, Don Stewart [EMAIL PROTECTED] wrote: Awesome. We can use this in Data.Bits, if you've got some QuickChecks for it. Hear hear. But is there any way to just make the compiler use fastTestBit in place of testBit :: (Bits a) = a - Int - Bool when a =

Re: [Haskell-cafe] ghc overlapping instances

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 03:36:20PM +0100, Steffen Mazanek wrote: Hello, I want to quickcheck a property on a datatype representing programs (=[Stmt]) and need to define a specific instance instance Arbitrary [Stmt] (mainly to restrict the size of the list). In quickcheck an instance

[Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Roberto Zunino
Neil Mitchell wrote: server text | Just xs - parse text = let x | field1 `elem` xs = error ... do one thing ... | field2 `elem` xs = error ... do something else ... in x server _ = error ... invalid request ... This now has the wrong semantics - before if parse

Re: [Haskell-cafe] isSpace

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 05:13:19PM +, Ryan Bloor wrote: hi I am having trouble with a function that is supposed to eliminate spaces from the start of a String and return the resulting string. I reckon a dropWhile could be used but the isSpace bit is causing me problems... words ::

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Neil Mitchell
Hi findAllPath :: (a - Bool) - (BTree a) - [[a]] findAllPath pred = g where g (Leaf l) | pred l = [[l]] g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred lf) ++ (findAllPath pred rt) g _ = [] without even using maybe. However, 2 questions

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Roberto Zunino
Neil Mitchell wrote: is there any automated way to know when a function is strict in its arguments? Yes, strictness analysis is a very well studied subject - ...and is undecidable, in general. ;-) Zun. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 09:41:36PM +, Paulo J. Matos wrote: Hello all, As you might have possibly read in some previous blog posts: http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11 we (the FPSIG group) defined: data BTree a = Leaf a

[Haskell-cafe] when I am rebuilding a package that has package dependencies

2007-12-04 Thread Galchin Vasili
Hello, Which document discusses how to first build all dependencies and then finally the target package? I prefer to read relevant documentation so I get fully up to speed rather than take up bandwidth on this newsgroup asking one question at a time. Regards, Vasya

Re: [Haskell-cafe] Looking for largest power of 2 = Integer

2007-12-04 Thread Dan Piponi
There's a bit of work required to make this code good enough for general consumption, and I don't know much about Haskell internals. (1) What is the official way to find the size of a word? A quick look at 6.8.1's base/GHC/Num.lhs reveals that it uses a #defined symbol. (2) Is it safe to assume

[Haskell-cafe] Re: Looking for smallest power of 2 = Integer

2007-12-04 Thread ChrisK
Sterling Clover wrote: Actually, I suspect GHC's strictness analyzer will give you reasonable performance with even the naive version, but fancier ideas are at http://graphics.stanford.edu/~seander/bithacks.html#IntegerLog If given an 'n' you are looking for the (2^x) such that 2^x = n

[Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-04 Thread gwern0
Hey everyone; recently I've been toying around with various methods of writing a shell and reading the academic literature on such things. The best prior art on the subject seems to be the ESTHER shell (see http://citeseer.ist.psu.edu/689593.html, http://citeseer.ist.psu.edu/744494.html,

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Ryan Ingram
Is there a reason why strictness is defined as f _|_ = _|_ instead of, for example, forall x :: Exception. f (throw x) = throw x where an exception thrown from pure code is observable in IO. In the second case we need to prove that the argument is evaluated at some point, which is also

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 03:07:01PM -0800, Ryan Ingram wrote: Is there a reason why strictness is defined as f _|_ = _|_ instead of, for example, forall x :: Exception. f (throw x) = throw x where an exception thrown from pure code is observable in IO. In the second case we need to

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Ryan Ingram
On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote: Is there a reason why 2 + 2 is defined as 4 instead of, for example, 5? Wow. That wasn't really necessary. 4 has a clear meaning (the number after the number after the number after the number after zero) which is equivalent to 2 + 2. I'm

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Lennart Augustsson
I don't even understand what your notation means. But apart from that, there are good reasons to define strictness denotationally instead of operationally. Remember that _|_ is not only exceptions, but also non-termination. For instance, the following function is strict without using its

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 03:35:28PM -0800, Ryan Ingram wrote: On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote: Is there a reason why 2 + 2 is defined as 4 instead of, for example, 5? Wow. That wasn't really necessary. 4 has a clear meaning (the number after the number after the

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread John Meacham
On Tue, Dec 04, 2007 at 03:35:28PM -0800, Ryan Ingram wrote: On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote: Well, one usually says something like f is strict in its 2nd argument which on casual reading tends to make me think that it has something to do with the argument. By the actual

[Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-04 Thread Aaron Denney
On 2007-12-04, Paulo J. Matos [EMAIL PROTECTED] wrote: Hello all, As you might have possibly read in some previous blog posts: http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10 http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11 we (the FPSIG group) defined: data BTree a = Leaf a

Re: [Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Nicolas Frisby
It seems there is previous background here that I am unaware of. I'll chime in anyway. What you describe as the wrong semantics seems to me to be the more appropriate. I am inferring that your expected behavior is explained such that the first server match ought to fail (and fall through to the

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Ryan Ingram
On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote: When you see an expression of the form: f a you generally want to evaluate a before applying; but if a is _|_, this will only give the correct result if f a = _|_. Merely 'guaranteed to evaluate' misses out on some common cases, for

Re: [Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Iavor Diatchki
Hello everyone, Just to clarify, the intended semantics of my example was that it should behave as if we were to duplicate the common prefix: server text | Just xs - parse text, field1 `elem` xs = ... do one thing ... | Just xs - parse text, field2 `elem` xs = ... do something else ...

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Stefan O'Rear
On Tue, Dec 04, 2007 at 07:43:36PM -0800, Ryan Ingram wrote: On 12/4/07, Stefan O'Rear [EMAIL PROTECTED] wrote: When you see an expression of the form: f a you generally want to evaluate a before applying; but if a is _|_, this will only give the correct result if f a = _|_. Merely

[Haskell-cafe] a positive challenge for the Haskell effort .....

2007-12-04 Thread Galchin Vasili
http://code.enthought.com/enthon/ .. how do Haskell libraries/packages stack up against this challenge? Kind regards, Vasya ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] building HUnit and other packages on Windows cygwin ...

2007-12-04 Thread Galchin Vasili
Hello, I believe that HUnit has absolutely not other package dependencies. When I do a runhaskell Setup.hs build, I get the following error message: gcc: installation problem, cannot exec `cc1': No such file or directory. I am not sure what cc1 is? A pass/phase of the gnu gcc compiler? Kind

[Haskell-cafe] Expert systems

2007-12-04 Thread Joel Reymont
Is there an expert system implemented in Haskell, or a library perhaps? A CLIPS/RETE implementation? The main stumbling point, from my perspective, is how to implement a knowledge base and check whether patterns with a certain shape have been asserted. It's much easier to do this in a