First time haskell - parse error!

Hi, i am getting an error when trying to compile this part of my program, its my first time using haskell and as lovely as it is it didn't give me very much to go on in the error message! <code>score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"</code> when i try to compile it says: test.hs 63:29: parse error on input 'where' (its the line beginning with 'then') Anybody got any ideas whats going on? thanks! -- View this message in context: http://old.nabble.com/First-time-haskell---parse-error%21-tp27839657p2783965... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

2010/3/9 boblettoj
Hi, i am getting an error when trying to compile this part of my program, its my first time using haskell and as lovely as it is it didn't give me very much to go on in the error message!
<code>score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"</code>
when i try to compile it says: test.hs 63:29: parse error on input 'where' (its the line beginning with 'then') Anybody got any ideas whats going on? thanks! -- View this message in context: http://old.nabble.com/First-time-haskell---parse-error%21-tp27839657p2783965... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
You can't use `where' in the middle of an `if'. This should get rid of the parse error: score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) else "Bad Guess" where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) -- Deniz Dogan

Thats because you can't put a "where" in a "then" clause. Move the "where" stuff to the end of the function. On 09/03/10 19:04, boblettoj wrote:
Hi, i am getting an error when trying to compile this part of my program, its my first time using haskell and as lovely as it is it didn't give me very much to go on in the error message!
<code>score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"</code>
when i try to compile it says: test.hs 63:29: parse error on input 'where' (its the line beginning with 'then') Anybody got any ideas whats going on? thanks!

On 9 mrt 2010, at 20:04, boblettoj wrote:
Hi, i am getting an error when trying to compile this part of my program, its my first time using haskell and as lovely as it is it didn't give me very much to go on in the error message!
<code>score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"</code>
If you want to keep the definitions local to the expression you should write then let s1 = .. s2 = ... ... in (s1++s2++s3++s4) else ... Doaitse
when i try to compile it says: test.hs 63:29: parse error on input 'where' (its the line beginning with 'then') Anybody got any ideas whats going on? thanks! -- View this message in context: http://old.nabble.com/First-time-haskell---parse-error%21-tp27839657p2783965... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"S. Doaitse Swierstra"
then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g)
If you want to keep the definitions local to the expression you should write
..but I think it is better style to avoid this kind of one-off named values. I much prefer: then "Golds "++show (gold s g)++... For some reason, this is a style isse that doesn't get much attention, at least not in the non-functional language tradition, where temporary variables are scattered all over. So instead of doing: let ns y = not (isSpace y) f x = takeWhile ns x in map f We can use anonymous functions in place of the uninformatively named ones: map (\x -> takeWhile (\y -> not (isSpace y)) x) and use partial application toward point-free-ness: map (takeWhile (not . isSpace)) which IMO is a lot easier to read, taking up less screen and mind estate. Of course it's possible to overdo the point-free thing (commonly referred to as "pointless"), but I think it's great when you can eliminate gratuitous naming like this. -k -- If I haven't seen further, it is by standing in the footprints of giants

On Mar 10, 2010, at 8:47 AM, Ketil Malde wrote:
I think it is better style to avoid this kind of one-off named values. I much prefer:
then "Golds "++show (gold s g)++...
For some reason, this is a style isse that doesn't get much attention
At the end of the Section on function composition in the tutorial "Learn You a Haskell for Great Good" [1] there is a nice example demonstrating that sometimes it may be preferable to introduce names for readability: Quote: In the section about maps and filters, we solved a problem of finding the sum of all odd squares that are smaller than 10,000. Here's what the solution looks like when put into a function. oddSquareSum :: Integer oddSquareSum = sum (takeWhile (<10000) (filter odd (map (^2) [1..]))) Being such a fan of function composition, I would have probably written that like this: oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..] However, if there was a chance of someone else reading that code, I would have written it like this: oddSquareSum :: Integer oddSquareSum = let oddSquares = filter odd $ map (^2) [1..] belowLimit = takeWhile (<10000) oddSquares in sum belowLimit It wouldn't win any code golf competition, but someone reading the function will probably find it easier to read than a composition chain. End Quote. [1]: http://learnyouahaskell.com/higher-order-functions#composition -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Maybe it's just me, but I think composition chain is MUCH easier to read. When readning, I'd probably transform the last version to the previous one by hand, just to make it more comprehensible. Sebastian Fischer wrote:
On Mar 10, 2010, at 8:47 AM, Ketil Malde wrote:
I think it is better style to avoid this kind of one-off named values. I much prefer:
then "Golds "++show (gold s g)++...
For some reason, this is a style isse that doesn't get much attention
At the end of the Section on function composition in the tutorial "Learn You a Haskell for Great Good" [1] there is a nice example demonstrating that sometimes it may be preferable to introduce names for readability:
Quote: In the section about maps and filters, we solved a problem of finding the sum of all odd squares that are smaller than 10,000. Here's what the solution looks like when put into a function.
oddSquareSum :: Integer oddSquareSum = sum (takeWhile (<10000) (filter odd (map (^2) [1..]))) Being such a fan of function composition, I would have probably written that like this:
oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..] However, if there was a chance of someone else reading that code, I would have written it like this:
oddSquareSum :: Integer oddSquareSum = let oddSquares = filter odd $ map (^2) [1..] belowLimit = takeWhile (<10000) oddSquares in sum belowLimit It wouldn't win any code golf competition, but someone reading the function will probably find it easier to read than a composition chain.
End Quote.
[1]: http://learnyouahaskell.com/higher-order-functions#composition

Miguel Mitrofanov
Maybe it's just me, but I think composition chain is MUCH easier to read.
I definitely agree. [Cited from "Learn You a Haskell for Great Good"]
oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..]
oddSquareSum :: Integer oddSquareSum = let oddSquares = filter odd $ map (^2) [1..] belowLimit = takeWhile (<10000) oddSquares in sum belowLimit
To me, the first one is very clear, and exposes the function as what it is: a neat, linear pipeline of standard function applications. You don't have to be a very seasoned programmer to quickly identify this structure, or the components involved. Introducing names means that I need to keep the temporary definitions in my head, and I think "takeWhile (<10000)" is as clear as it can get. And while a name can be misleading (belowLimit is a boolean, no?) or flat out wrong, the definition has its semantics¹. Another, perhaps graver issue, is that the names obscure the linearity of the function. I now need to check that the temporary defintions don't recurse or perform other tricks.² Named values are just like comments, which IMO also should be kept to a bare minimum. A bit tongue in cheek: If you need a name to understand what a function does, or a comment to understand how it does it, then your code is too complicated. -k (who still doesn't name all his functions 'foo') ¹ Which are perhaps not-so-defined. Thanks for bringing it up. ² There are plenty of point-free examples that overload my mind -- I wonder if this might be when you start to linearize non-linear structures, composing dots and combinators and whatnot? -- If I haven't seen further, it is by standing in the footprints of giants

On 10 March 2010 11:21, Ketil Malde
[Cited from "Learn You a Haskell for Great Good"]
oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..]
To me, the first one is very clear, and exposes the function as what it is: a neat, linear pipeline of standard function applications. You don't have to be a very seasoned programmer to quickly identify this structure, or the components involved.
Named values are just like comments, which IMO also should be kept to a bare minimum. A bit tongue in cheek: If you need a name to understand what a function does, or a comment to understand how it does it, then your code is too complicated.
Tongue-in-cheek? It's completely ridiculous. That example above has six names in it. Try recursively replacing all the names in it with their definitions, until the only names left are built-in primitives. -- Colin Adams Preston, Lancashire, ENGLAND

Colin Adams
Named values are just like comments, which IMO also should be kept to a bare minimum. A bit tongue in cheek: If you need a name to understand what a function does, or a comment to understand how it does it, then your code is too complicated.
Tongue-in-cheek? It's completely ridiculous.
I'm not saying that you shouldn't name things - just that you shouldn't add names as a remedy for incomprehensible code. Especially when you can instead write clear code in the first place. E.g. I don't need a name for "\n -> n `mod` 2 == 1" to understand what it does. And especially in this case, naming otherwise clear code fragments just introduces a layer of indirection, which add more opportunities for errors and misunderstandings.
That example above has six names in it.
And they are named because they represent common idioms that are used all over the place, and so labeling and memorizing them improves clarity and reusability, and since they are from the standard library, I can expect them to be reasonably correct and efficient. Here's another one for you: never introduce names if it increases the size of your program. (Corrolary: don't name things that aren't referred to at least twice) -k -- If I haven't seen further, it is by standing in the footprints of giants

Am Mittwoch 10 März 2010 13:03:59 schrieb Ketil Malde:
never introduce names if it increases the size of your program. (Corrolary: don't name things that aren't referred to at least twice)
Objection! If the final result of your function is a combination of a handful or two of long (and convoluted (expressions with ++ lots of) parentheses (as well (as operators and) other stuff), please, please, pretty please with sugar and cream, give names to the parts to expose the overall structure of the result. Well, IMO, parts and intermediate results needn't even be so extreme to deserve a local name. Just stop and think for a moment before introducing a local name, "Does that help or hinder readability?". If you aren't sure, probably either is okay.

On Wed, 2010-03-10 at 13:03 +0100, Ketil Malde wrote:
Colin Adams
writes: Named values are just like comments, which IMO also should be kept to a bare minimum. A bit tongue in cheek: If you need a name to understand what a function does, or a comment to understand how it does it, then your code is too complicated.
Tongue-in-cheek? It's completely ridiculous.
I'm not saying that you shouldn't name things - just that you shouldn't add names as a remedy for incomprehensible code. Especially when you can instead write clear code in the first place.
E.g. I don't need a name for "\n -> n `mod` 2 == 1" to understand what it does.
And especially in this case, naming otherwise clear code fragments just introduces a layer of indirection, which add more opportunities for errors and misunderstandings.
Hmm - good for you if you understand. I had to read and think (ok. something like 0.03s but it appeared non-obvious - it seem strange but n `mod` k == 0 where k is constant would be obvious). If you write some very complicate expression . filter odd . other expression It is IMHO much clearer then: some very complicate expression . filter (\n -> n `mod` 2 == 1) . other expression
That example above has six names in it.
And they are named because they represent common idioms that are used all over the place, and so labeling and memorizing them improves clarity and reusability, and since they are from the standard library, I can expect them to be reasonably correct and efficient.
Here's another one for you: never introduce names if it increases the size of your program. (Corrolary: don't name things that aren't referred to at least twice)
-k
Well - my rule of thumb (for imperative programs): "If function is longer then 24 lines then it should be splitted into sub-functions [even if they are called only once]". Due to much more expressiveness and density of functional code the boundary is much lower. It is good to do because: - I can test function separately. I mane that if I have // Lots of code in function while (...) { ... // Here it prints the wrong value ... } // Lots of code I don't have idea if the problem is in loop or outside. If the loop is in smaller function I can test it separately. - it provides separation of possible different functions. Like: void main() { init(); while (Event *e = poolEvent ()) { processEvent (e); } cleanup(); } Now imagine that init have 15 lines, cleanup 10, poolEvent 10 and processEvent 30. We have 65-line mess which is unmaintainable ;) Ok - this is extrem example but still . - It clarifies the levels of abstraction. If I'm reading the code of server message processing I might just be interested in the general processing (it gets message, filter through antivirus etc.). The actual code of I/O, filtering would make it less clear even if they are called once and increase size of program. Regards

On Mar 10, 2010, at 12:21 PM, Ketil Malde wrote:
Introducing names means that I need to keep the temporary definitions in my head, and I think "takeWhile (<10000)" is as clear as it can get. And while a name can be misleading (belowLimit is a boolean, no?) or flat out wrong, the definition has its semantics¹.
I agree that composition chains are acceptable (and preferable) if they are clear. And I won't argue about wether the example from LYAHFGG is sufficiently clear in pointfree style (because I'm biased, to me it is certainly clear). I do not agree that introducing names locally for compositions is *always* a bad idea, even if used only once. (Choosing names that are "misleading or flat out wrong" is of course always a bad idea.)
Named values are just like comments
While you wanted to degrade named values by this statement I think it can serve as justification. A sensible comment for the example program might be -- computes the sum of all odd squares below a certain limit With the names in the rewritten example this comment is no longer necessary. I think only an average Haskell programmer understands the original pointfree program as quickly as this comment. Good names can help making comments less important. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Hello all Algorithmically oddSquareSum is a bit below par though...
oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..]
Why filter out the evens after generating them?
oos1 :: Integer oss1 = sum . takeWhile (<10000) $ map (^2) odds where odds = iterate (+2) 1
Best wishes
Stephen
On 10 March 2010 13:14, Sebastian Fischer
On Mar 10, 2010, at 12:21 PM, Ketil Malde wrote:
Introducing names means that I need to keep the temporary definitions in my head, and I think "takeWhile (<10000)" is as clear as it can get. And while a name can be misleading (belowLimit is a boolean, no?) or flat out wrong, the definition has its semantics¹.
I agree that composition chains are acceptable (and preferable) if they are clear. And I won't argue about wether the example from LYAHFGG is sufficiently clear in pointfree style (because I'm biased, to me it is certainly clear).
I do not agree that introducing names locally for compositions is *always* a bad idea, even if used only once. (Choosing names that are "misleading or flat out wrong" is of course always a bad idea.)
Named values are just like comments
While you wanted to degrade named values by this statement I think it can serve as justification. A sensible comment for the example program might be
-- computes the sum of all odd squares below a certain limit
With the names in the rewritten example this comment is no longer necessary. I think only an average Haskell programmer understands the original pointfree program as quickly as this comment.
Good names can help making comments less important.
Sebastian
-- Underestimating the novelty of the future is a time-honored tradition. (D.G.)
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Mittwoch 10 März 2010 14:53:32 schrieb Stephen Tetley:
Hello all
Algorithmically oddSquareSum is a bit below par though...
oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..]
Why filter out the evens after generating them?
oos1 :: Integer oss1 = sum . takeWhile (<10000) $ map (^2) odds where odds = iterate (+2) 1
Since we're now taking the code apart, oddSquareSum2 :: Integer oddSquareSum2 = sumOddSquaresBelow 10000 sumOddSquaresBelow bound = takeWhile (< bound) [x*x | x <- [1, 3 .. ]] (but you'd really want to use the power-sum formula).
Best wishes
Stephen

Stephen Tetley
oddSquareSum :: Integer oddSquareSum = sum . takeWhile (<10000) . filter odd . map (^2) $ [1..]
Why filter out the evens after generating them?
In other words: sum . takeWhile (<10000) . filter odd . map (^2) $ [1..] Since odd (x^2) => odd x: sum . takeWhile (<10000) . map (^2) $ [1,3..] Although it doesn't matter (more than a constant at any rate) for complexity, why generate values only to trim them later? Since x^2 < 10000 => x < 100: sum $ map (^2) [1,3..99] -k -- If I haven't seen further, it is by standing in the footprints of giants

Sebastian Fischer
I do not agree that introducing names locally for compositions is *always* a bad idea, even if used only once.
Well, of course I do that all the time too. :-)
(Choosing names that are "misleading or flat out wrong" is of course always a bad idea.)
Of course nobody actually does this on purpose, but like comments, names tend to bit-rot over time as code gets updated, but names or comments stay the same. Also, good names are harder than they sound: I don't think 'belowLimit' is a good name for 'takeWhile (<10000)', for instance. I certainly couldn't guess what it was for without looking at the implementation, which kind of defeats the purpose of names for improving code clarity, don't you think? And what's a good name for the associative monoid operator again?
Named values are just like comments
While you wanted to degrade named values by this statement I think it can serve as justification.
It does cut both ways, I suppose :-)
With the names in the rewritten example this comment is no longer necessary.
I'm not so sure - the names just try to put meaningful labels on the internals of 'oddSquareSum', while the comment refers to the whole function, and it can be picked up by haddock, so there are other considerations.
Good names can help making comments less important.
OTOH, comment can give you the best(?) of both worlds, both revealing the linear structure of the function, while still providing extra information: oddSquareSum :: Integer oddSquareSum = sum -- add together . takeWhile (<10000) -- until a value >10K is seen . filter odd -- all the odd . map (^2) -- squares of $ [1..] -- natural numbers -k -- If I haven't seen further, it is by standing in the footprints of giants

Good names can help making comments less important.
OTOH, comment can give you the best(?) of both worlds, both revealing the linear structure of the function, while still providing extra information:
oddSquareSum :: Integer oddSquareSum = sum -- add together . takeWhile (<10000) -- until a value >10K is seen . filter odd -- all the odd . map (^2) -- squares of $ [1..] -- natural numbers
-k
Hmm. My 0.03$ (to whole thread): 1. I prefer the concept of pipeline. - It gives me feeling that I'm not interested in the order of computation (map all values to square, then filter the odds) but rather with semi-parallel computation (which is really what is happening). Let syntax, being much more flexible, may give semi-imperative approach (although much more mixed). - I read that average human remembers up to 7-10 things in short term memory - why garbage it with variables? On the other hand more complex computation may require let/where and/or arrows helper functions. For example: filter (\x -> case x of Nil -> False; _ -> True) ... or filter (\x -> case x of Nil -> False _ -> True) ... is less clear then filter (not . isNil) ... where isNil Nil = True isNil _ = False 2. The comments in the above example are too verbose for my taste. It is like (in imperative program): x = x + 1; // add 1 to x Anyone having minimal knowledge about syntax will be able to deduce the comment directly from the line so why repeat it. However: c = ~c | (c && 0xFF000000); // Invert the color in ARGB Is meaningful comment. There is little information what the line does and it may happen that the operation must be done efficiently (inner loop). 3. While name should be meaningful (oddSquereSum is not - however it IMHO is permissible in let/where) if project have documentation and function is exported it should have documentation. While name is part of documentation it cannot replace it.

Ketil Malde wrote:
Also, good names are harder than they sound: I don't think 'belowLimit' is a good name for 'takeWhile (<10000)', for instance. I certainly couldn't guess what it was for without looking at the implementation, which kind of defeats the purpose of names for improving code clarity, don't you think?
I don't. I would not expect to understand the behavior of a piece of code just by reading its name. However, a good name can help you understand the purpose of the code while reading it, and after reading the code, you may link the name to the same concept as the original author did. This way, the original author can help you rediscover his understanding of the problem by structuring the code accordingly. But that means that names should not be introduced to break long expressions into short ones, but to point out structure. For example, the structure of the oddSquareSum example is a (.)-pipeline. We could highlight this fact by giving a name to each function in the pipeline. oddSquareSum = sum . belowLimit . onlyOdd . squareAll $ numbers where belowLimit = takeWhile (< 10000) onlyOdd = filter odd squareAll = map (^ 2) numbers = [1..] However, in this version of the code, we obfuscate an important aspect of the structure of the pipeline: It is a pipeline working on lists. I would like to make this more visible, e.g. like this: oddSquareSum = sum . takeWhile belowLimit . filter odd . map square $ numbers where belowLimit x = x < 10000 square x = x * x numbers = [1..] In this version, we see the structure of the code in the pipeline, and the details in the local definitions. Furthermore, I would expect a reader to be able to remember the meaning of the names after having read the definitions. Tillmann

Sebastian Fischer
(Choosing names that are "misleading or flat out wrong" is of course always a bad idea.)
foo = f . g . h where f x = ... g x = ... h x = ... Sometimes laziness is just the clearest option. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

On 09.03.2010 20:04, boblettoj wrote:
score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"
Apart from the parse error there is also a type error in your code: When the second argument is empty, you return false although you declared the function to return a String, not a boolean. Also you require the first argument to be a string containing exactly one character and the second argument to be a string containing zero or one characters. I'm not quite sure that's what you intend. If it is, you should consider changing the function so that it takes a Char and a Maybe Char, instead of two strings. HTH, Sebastian

On Tue, Mar 09, 2010 at 08:42:44PM +0100, Sebastian Hungerecker wrote:
On 09.03.2010 20:04, boblettoj wrote:
score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"
Apart from the parse error there is also a type error in your code: When the second argument is empty, you return false although you declared the function to return a String, not a boolean.
Not quite; data Bool = True | False, and the code uses a lowercase 'f' 'false'. Perhaps 'false' is defined as a String somewhere else? A bit odd, perhaps, but not necessarily a type error. -Brent

Seems like a good time to mention the Maybe monad looks like it would be a
good fit here.
score :: String -> String -> Maybe String
score s [] = Nothing
score s g =
if valid 4 g
then let s1 = "Golds "
s2 = show (gold s g)
s3 = ", Silvers "
s4 = show (silver s g)
in Just (s1 ++ s2 ++ s3 ++ s4)
else Just "Bad Guess"
-R. Kyle Murphy
--
Curiosity was framed, Ignorance killed the cat.
On Tue, Mar 9, 2010 at 17:42, Brent Yorgey
On Tue, Mar 09, 2010 at 08:42:44PM +0100, Sebastian Hungerecker wrote:
On 09.03.2010 20:04, boblettoj wrote:
score :: String -> String -> String score [s] [] = false score [s] [g] = if valid 4 g then (s1 ++ s2 ++ s3 ++ s4) where s1 = "Golds " s2 = show (gold s g) s3 = ", Silvers " s4 = show (silver s g) else "Bad Guess"
Apart from the parse error there is also a type error in your code: When the second argument is empty, you return false although you declared the function to return a String, not a boolean.
Not quite; data Bool = True | False, and the code uses a lowercase 'f' 'false'. Perhaps 'false' is defined as a String somewhere else? A bit odd, perhaps, but not necessarily a type error.
-Brent _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (17)
-
Achim Schneider
-
boblettoj
-
Brent Yorgey
-
Colin Adams
-
Daniel Fischer
-
Deniz Dogan
-
Ketil Malde
-
Kyle Murphy
-
Maciej Piechotka
-
Max Rabkin
-
Miguel Mitrofanov
-
Paul Johnson
-
S. Doaitse Swierstra
-
Sebastian Fischer
-
Sebastian Hungerecker
-
Stephen Tetley
-
Tillmann Rendel