ghci reports "The last statement in a 'do' construct must be an expression" error

Hi Heres my code snippet. It reports that my error is in line 9 right after the main definition. All functions that i call work under normal circumstances. Thanks module Benchmark where import ReadCSV import Operators import Data.Time.Clock (diffUTCTime, getCurrentTime) main = do xs <- readCSV "dataconvert/lineitem.tbl" '|' start <- getCurrentTime let pnp = projection [5] xs let snp = selection (\x -> (x!!0) > (Int 17000)) pnp end <- getCurrentTime putStrLn $ show (end `diffUTCTime` start) start2 <- getCurrentTime let pp = pProjection [5] xs let sp = pSelection (\x -> (x!!0) > (Int 17000)) pp end2 <- getCurrentTime putStrLn $ show (end2 `diffUTCTime` start2) return xs

Am Dienstag 16 Juni 2009 22:35:17 schrieb Nico Rolle:
Hi
Heres my code snippet. It reports that my error is in line 9 right after the main definition. All functions that i call work under normal circumstances. Thanks
Must be the indentation, probably the xs is indented further than the following line (though that's not the case for the code copy-pasted from the mail to an editor). But note that this will most likely print out 0 twice. The let pnp = ... bindings don't cause any computation to occur. To measure the time the computations take, you must force them to occur between the two calls to getCurrentTime.
module Benchmark where
import ReadCSV import Operators import Data.Time.Clock (diffUTCTime, getCurrentTime)
main = do xs <- readCSV "dataconvert/lineitem.tbl" '|' start <- getCurrentTime let pnp = projection [5] xs let snp = selection (\x -> (x!!0) > (Int 17000)) pnp end <- getCurrentTime putStrLn $ show (end `diffUTCTime` start) start2 <- getCurrentTime let pp = pProjection [5] xs let sp = pSelection (\x -> (x!!0) > (Int 17000)) pp end2 <- getCurrentTime putStrLn $ show (end2 `diffUTCTime` start2) return xs

Hi, This is more of a philosophical question then anything else. Recently I posted a question (see " exercise 3.10 in YAHT") and now Rolle is encountering what appears to be the same error (see "hci reports "The last statement in a 'do' construct must be an expression" error"). In both cases the responses have been something on the order of "must be the indentation". So...my questions are: (1) what was the driving force behind using white-space to denote code blocks? From a beginners perspective (especially coming from a strong C / C++ background) this seems to add to the learning curve for the language, and can add a good deal of frustration. (2) I know using layout is optional -- we can curly braces and semicolons (not sure what this method is called correctly), but in the books and sources that I have looked at this seems to be mentioned in passing, so I'm guessing "good haskell format" is to use layout. And if this is true, is there any reason for this? better performance? easier parsing? (3) Finally, is there a book or online reference that uses curly braces and semicolons from the start -- maybe introducing the concept of layout after all the language syntax is firmly grounded? George. PS -- For those of you that answered my first post, I sort-of solved my problem. From your conviction that there was not an error in the function (even though this is where the compiler was claiming it to be), I moved stuff around in the source file while not touching the function itself and the error disappeared. Not a satisfactory solution I know, but for now it will do till I get the syntax of Haskell down. Thanks for everyone's help. George

Am Mittwoch 17 Juni 2009 01:41:01 schrieb George Huber:
Hi,
This is more of a philosophical question then anything else.
Recently I posted a question (see " exercise 3.10 in YAHT") and now Rolle is encountering what appears to be the same error (see "hci reports "The last statement in a 'do' construct must be an expression" error"). In both cases the responses have been something on the order of "must be the indentation".
So...my questions are:
(1) what was the driving force behind using white-space to denote code blocks? From a beginners perspective (especially coming from a strong C / C++ background) this seems to add to the learning curve for the language, and can add a good deal of frustration.
Readability. Properly indented code is far easier to read, braces and semicolons are then only clutter.
(2) I know using layout is optional -- we can curly braces and semicolons (not sure what this method is called correctly), but in the books and sources that I have looked at this seems to be mentioned in passing, so I'm guessing "good haskell format" is to use layout. And if this is true, is there any reason for this? better performance? easier parsing?
It's only easier to parse for humans, it's harder to write a parser for the layout rule. But humans are considered more important.
(3) Finally, is there a book or online reference that uses curly braces and semicolons from the start -- maybe introducing the concept of layout after all the language syntax is firmly grounded?
I know none.
George.
PS -- For those of you that answered my first post, I sort-of solved my problem. From your conviction that there was not an error in the function (even though this is where the compiler was claiming it to be), I moved stuff around in the source file while not touching the function itself and the error disappeared. Not a satisfactory solution I know, but for now it will do till I get the syntax of Haskell down. Thanks for everyone's help.
Read http://haskell.org/onlinereport/lexemes.html#sect2.7 and http://haskell.org/onlinereport/syntax-iso.html#sect9.3 for an explanation of the layout rule.
George

On Wed, Jun 17, 2009 at 12:41 AM, George Huber
(1) what was the driving force behind using white-space to denote code blocks? From a beginners perspective (especially coming from a strong C / C++ background) this seems to add to the learning curve for the language, and can add a good deal of frustration.
I only really know two languages that use significant whitespace in this way, Python and Haskell. I learnt Python first, and had basically the same thoughts as you do. It felt weird, even though I always made sure to indent my C/C++ code to make it more readable. It took some time, but by now I love it, and consider it a positive point of both languages. IMO the people behind Haskell had a better understanding of the off-side rule though, so there are less strangeness in Haskell indentation. By now I find that my indentation practices are leaking into other languages, e.g. from a distance my OCaml code looks similar to my Haskell code. You may be right that it adds to the learning curve, but I consider it well worth it in the long run. /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

(1) what was the driving force behind using white-space to denote code blocks? From a beginners perspective (especially coming from a strong C / C++ background) this seems to add to the learning curve for the language, and can add a good deal of frustration.
This seems to be personal. Most people in the list seems to find layout easier to write and read (although we could make a case that those who don't just leave Haskell). I wasn't able to write anything in Haskell until I read the Haskell 98 report and learned how to use braces and semicolons (and this was my last attempt before just leaving the language). After you learn it, using layout becomes a lot easier, and the whole language makes a lot more sense. If you wan't to start a page in Haskell wiki with a reference to layout-free Haskell syntax I would be happy to contribute. Best, Maurício

Am Donnerstag 18 Juni 2009 16:43:06 schrieb Maurício:
If you want to start a page in Haskell wiki with a reference to layout-free Haskell syntax I would be happy to contribute.
Best, Maurício
Since you have some experience with it, why don't you start the page to lead newbies from C++-land in? You hopefully remember a few things that were especially hard to learn for you, that could probably help a lot.

If you want to start a page in Haskell wiki with a reference to layout-free Haskell syntax I would be happy to contribute.
Since you have some experience with it, why don't you start the page to lead newbies from C++-land in? You hopefully remember a few things that were especially hard to learn for you, that could probably help a lot.
I tought about that, but you're the first one to actually agree with me about that :) Now I would not like to start something I know I won't take care of, since I do take care of other stuff. But I can add stuff if somebody else does. Note that it would be great if instead of just a layout free reference we had a full common language version of the technical Haskell 98 specification. If you are learning Haskell, doing that can be really great as a learning tool: http://haskell.org/onlinereport Many words and explanations seen there are important to understand today version of Haskell, and most are not well explained by tutorials. You won't find about "kinds" in most tutorials, for instance, and they are really important. Here is a small reference (improvised, not checked, and 'classes' and their instances are important and missing): * How to write modules. Today, all Haskell compilers needs you to write only one module per file: module Name.OtherName (export_list) where { declarations separate by ';' } declarations may be imports (and those come first than all others): import ModuleName.SubModule qualified as W ; import OtherModule ; etc. export_list lists all names you want to be seen by other modules that import Name.OtherName. (This requires further details.) If you are writing module Main, which all applications are required to have, you need to export at least 'main'. * 'do' notation do { x ; y'<- y ; z' <- z y' ; a } expands to x >> y >>= \y' -> z y' >>= \z' -> a Also, using layout, do a <- x let b = a y b z expands to do {a <- x ; let {b = a} in do {y b >> z}} and then to x >>= \a -> let {b=a} in y b >> z * Using '::' You can declare types for names using :: like: a :: IO () b :: Integer (Needs a lot of further details.) These appear in declarations list of modules: module Bla (ble) where { import SomeModule ; ble :: Integer ; ble = 3 } * Using 'data' You can declare data types as: data DataName = Constructor1 Integer | Cons2 String | Cons3 Integer String DataName * Using '=' and pattern matching A somewhat general usage of '=' can be seen as (using that data type from previous item): f :: SomeType -> DataName -> Bool ; f (Constructor a b) c = case c of { Constructor1 i | h i -> True | True -> False where { h :: Integer -> Bool ; h = (>= 10) } ; Cons2 s | matches s -> True | otherwise -> False ; Cons3 j _ = j >= k } where { k :: Integer ; k = 5 } * Using 'let' and 'where' 'let' is different from 'where'. You can do: a = (let {b=5} in b + b) + (let {b=6;c=7} in b + c) but not a = (b + b where {b=5}) etc. (WRONG!!) 'where' is part of '=': a = b 9 where {b :: Integer -> String ; b 10 = "Equals ten." ; b _ = "Does not equal ten."} * Lazy evaluation: b :: Integer -> String ; b 10 = "Ten" ; b 9 = "Nine" ; func :: (Integer -> String) -> String ; func f = "Prefix" ++ f 8 Here, 'take 2 (func b)' (or 'take 2 $ func b') would evaluate to "Pr" dispite 'b 8' beeing undefined, because 'f 8' is not necessary to evaluate just the first two characters of that string. Hope this gives you some help, and contains only a few errors. Best, Maurício

On Sat, Jun 20, 2009 at 11:44:09AM -0400, George Huber wrote:
Maurício wrote:
Also, using layout,
do a <- x let b = a y b z
expands to
do {a <- x ; let {b = a} in do {y b >> z}}
I'm curious as to where the second `do' came from?
Well, the above translation isn't quite correct, the second 'do' wouldn't come until later. The point is that 'do { let x = y; foo }' translates to 'let x = y in do { foo }'. So do a <- x let b = a y b z gets translated as follows: do { a <- x ; let b = a ; y b ; z } (that's just inserting braces and semicolons using layout), and then x >>= \a -> do { let b = a ; y b ; z } x >>= \a -> let b = a in do { y b ; z } x >>= \a -> let b = a in yb >> do { z } x >>= \a -> let b = a in yb >> z -Brent

do a <- x let b = a y b z
expands to
do {a <- x ; let {b = a} in do {y b >> z}}
I'm curious as to where the second `do' came from?
Well, the above translation isn't quite correct, the second 'do' wouldn't come until later. The point is that 'do { let x = y; foo }' translates to 'let x = y in do { foo }'.
Exatly, I should have checked better that example. I just thought it worth to show how 'let' translates in a 'do' expression, because it caused me a lot of trouble when I learned Haskell. Since I had read that 'do' expressions are supposed to chain (Monad m) => (m a) elements, I assumed from this use of 'let' that: (WARNING: WRONG ASSUMPTIONS!) * 'let a = b' has type (Monad m) => (m x), x the type of a and b. * Since 'let' is used in let expressions and also in do expressions, either Haskell allows redefinition of reserved keywords or 'let' is not a reserved keyword and there's some way in Haskell to define constructs like 'let ... in ...' using more basic primitives. * Haskell has some kind of overloading allowing one word to be used in unrelated contexts. That's of course completely nonsense, but I would be happy if I could avoid others from running into this kind of misunderstanding. Best, Maurício

it really was an indentation error
i configured my editor to expand tabs into spaces but somehow he did a real
tab on line 9 and 10
thank you
2009/6/16 Daniel Fischer
Am Dienstag 16 Juni 2009 22:35:17 schrieb Nico Rolle:
Hi
Heres my code snippet. It reports that my error is in line 9 right after the main definition. All functions that i call work under normal circumstances. Thanks
Must be the indentation, probably the xs is indented further than the following line (though that's not the case for the code copy-pasted from the mail to an editor).
But note that this will most likely print out 0 twice. The let pnp = ... bindings don't cause any computation to occur. To measure the time the computations take, you must force them to occur between the two calls to getCurrentTime.
module Benchmark where
import ReadCSV import Operators import Data.Time.Clock (diffUTCTime, getCurrentTime)
main = do xs <- readCSV "dataconvert/lineitem.tbl" '|' start <- getCurrentTime let pnp = projection [5] xs let snp = selection (\x -> (x!!0) > (Int 17000)) pnp end <- getCurrentTime putStrLn $ show (end `diffUTCTime` start) start2 <- getCurrentTime let pp = pProjection [5] xs let sp = pSelection (\x -> (x!!0) > (Int 17000)) pp end2 <- getCurrentTime putStrLn $ show (end2 `diffUTCTime` start2) return xs
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (7)
-
Brent Yorgey
-
Daniel Fischer
-
George Huber
-
Magnus Therning
-
Maurício
-
Nico Rolle
-
Nico Rolle