
Hello, I try to set up a verification on the number of arguments given to my program, but keep on getting "Parse error in pattern" Here is what my code looks like: main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (length (argsList) == 0) then do putStrLn $ "No filename given to the program.\n $ ProgramName file.sac" return () else sacFile1 <- openBinaryFile fileToOpen ReadMode ghci complains, and tells "Parse error in pattern", indicating the 'if' line number. Can you please help ? Thank you very much, Florian

It doesn't look like a complete piece of code so these comments aren't
backed up by running it through GHCi or anything.
On Fri, Feb 26, 2010 at 16:29, Florian Duret
Hello,
I try to set up a verification on the number of arguments given to my program, but keep on getting "Parse error in pattern" Here is what my code looks like: main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (length (argsList) == 0) then do putStrLn $ "No filename given to the program.\n $ ProgramName file.sac" return ()
I believe the 'do' here is unecessary.
else sacFile1 <- openBinaryFile fileToOpen ReadMode
Here you do need a 'do' though, I believe.
ghci complains, and tells "Parse error in pattern", indicating the 'if' line number. Can you please help ? Thank you very much, Florian _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus@therning.org http://therning.org/magnus identi.ca|twitter: magthe

Am Freitag 26 Februar 2010 17:37:30 schrieb Magnus Therning:
It doesn't look like a complete piece of code so these comments aren't backed up by running it through GHCi or anything.
On Fri, Feb 26, 2010 at 16:29, Florian Duret
wrote: Hello,
I try to set up a verification on the number of arguments given to my program, but keep on getting "Parse error in pattern" Here is what my code looks like: main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (length (argsList) == 0)
It's most likely harmless for argument lists (although there are other cases), but Don't Use if (length list == 0) Never. Jamais. Niemals. Use if (null list) length has to traverse the entire list, which may take a long time.
then do putStrLn $ "No filename given to the program.\n $ ProgramName file.sac" return ()
I believe the 'do' here is unecessary.
As soon as the unnecessary "return ()" is removed.
else sacFile1 <- openBinaryFile fileToOpen ReadMode
Here you do need a 'do' though, I believe.
Yes. If he binds the name sacFile1 to a value, there must come more statements after it, so the "do" is required. But it might also be wrong indentation, if the mail programme fiddled with that.
ghci complains, and tells "Parse error in pattern", indicating the 'if' line number.
Invoke ghci with $ ghci -ferror-spans file to see how far GHC thinks the erroneous pattern extends. From that, one can often deduce better what the problem is.
Can you please help ? Thank you very much, Florian

It seems that both your suggestions have worked ! Thank you very much. But I
still can't figure out what went wrong.
My initial goal was to keep the minimum inside the if ... then ... else
statement. Basically, if the list is empty, then stop. If not, then assign
the argument to sacFile1, and go on with the rest.
Here is what it looks like now:
module Main () where
import System.IO
import System.Environment(getArgs)
import Data.Char(intToDigit)
import SAC_Type
import SAC_IO
main :: IO()
main = do
-- On commence par ouvrir le fichier SAC en mode binaire
argsList <- getArgs
if (null argsList)
then
putStrLn $ "No filename given to the program.\n $ ProgramName
file.sac"
else do
sacFile1 <- openBinaryFile (head argsList) ReadMode
position <- hTell sacFile1
putStrLn $ "Position 1: " ++ [intToDigit( fromInteger (position)
)]
hSeek sacFile1 AbsoluteSeek 440
position2 <- hTell sacFile1
putStrLn $ "Position 2: " ++ [intToDigit( fromInteger (position2)
)]
-- A la fin, il faut evidemment le fermer
hClose sacFile1
Thank you, Danke, 谢谢, merci, etc...
2010/2/26 Daniel Fischer
Am Freitag 26 Februar 2010 17:37:30 schrieb Magnus Therning:
It doesn't look like a complete piece of code so these comments aren't backed up by running it through GHCi or anything.
On Fri, Feb 26, 2010 at 16:29, Florian Duret
wrote: Hello,
I try to set up a verification on the number of arguments given to my program, but keep on getting "Parse error in pattern" Here is what my code looks like: main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (length (argsList) == 0)
It's most likely harmless for argument lists (although there are other cases), but
Don't Use
if (length list == 0)
Never. Jamais. Niemals.
Use
if (null list)
length has to traverse the entire list, which may take a long time.
then do putStrLn $ "No filename given to the program.\n $ ProgramName file.sac" return ()
I believe the 'do' here is unecessary.
As soon as the unnecessary "return ()" is removed.
else sacFile1 <- openBinaryFile fileToOpen ReadMode
Here you do need a 'do' though, I believe.
Yes. If he binds the name sacFile1 to a value, there must come more statements after it, so the "do" is required.
But it might also be wrong indentation, if the mail programme fiddled with that.
ghci complains, and tells "Parse error in pattern", indicating the 'if' line number.
Invoke ghci with
$ ghci -ferror-spans file
to see how far GHC thinks the erroneous pattern extends. From that, one can often deduce better what the problem is.
Can you please help ? Thank you very much, Florian

Am Freitag 26 Februar 2010 18:34:35 schrieb Florian Duret:
It seems that both your suggestions have worked ! Thank you very much. But I still can't figure out what went wrong.
Did you change anything besides removing the "do" and "return ()" from the then-branch and insert the "do" in the else-branch? If not, you've been bitten by a somewhat less than obvious aspect of layout - although it's pretty clear with an explanation. A new layout-block isn't opened by a larger indentation, but by the keywords do, let, of and where. So, when you write ... = do xxx if blah then do foo bar else baz zap the "do" after the then opens a new layout-block inside the big do-block, since you didn't insert an explicit brace. The indentation level thereof is determined by the 'f' of "foo", bar is indented to the same level as foo, so it's a new expression in that same block. The else is indented less than the foo, so that ends the inner layout-block and we return to the layout-block of the big do-block. The indentation level thereof is determined by the first 'x', and the "if" is indented to the same level. The else, the baz and the zap are all indented further than the if, so they all belong to the if-expression (as intended). But since there's no "do" after the "else", all that is on one logical line, it's parsed as ... = do xxx if blah then do { foo; bar } else baz zap Not what was intended, but it parses just fine. Now you didn't have baz zap but baz <- bong zap and since we're still having only one logical line for the if-expression, the parser sees that as ... = do xxx if blah then do { foo; bar } else baz <- bong zap But the syntax is pattern <- expression so the parser tries to parse if blah then do { foo; bar } else baz as a pattern. But it doesn't conform to the pattern productions, hence the parse error.
My initial goal was to keep the minimum inside the if ... then ... else statement. Basically, if the list is empty, then stop. If not, then assign the argument to sacFile1, and go on with the rest.
It would be cleanest to have realWork :: FileName -> IO () realWork file = do sacFile1 <- openBinaryFile file ReadMode ... main :: IO () main = do argList <- getArgs case argList of [] -> putStrLn "No filename ..." (f:_) -> realWork f or if null argList then putStrLn "..." else realWork (head argList) , je pense.
Here is what it looks like now: module Main () where
import System.IO import System.Environment(getArgs) import Data.Char(intToDigit)
import SAC_Type import SAC_IO
main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (null argsList) then putStrLn $ "No filename given to the program.\n $ ProgramName file.sac" else do sacFile1 <- openBinaryFile (head argsList) ReadMode
position <- hTell sacFile1 putStrLn $ "Position 1: " ++ [intToDigit( fromInteger (position) )]
hSeek sacFile1 AbsoluteSeek 440 position2 <- hTell sacFile1 putStrLn $ "Position 2: " ++ [intToDigit( fromInteger (position2) )]
I don't think that's what you really want: Prelude Data.Char> intToDigit 440 *** Exception: Char.intToDigit: not a digit 440 perhaps you wanted putStrLn $ "Position 2: " ++ show position2 ?
-- A la fin, il faut evidemment le fermer hClose sacFile1
Thank you, Danke, 谢谢, merci, etc...

Thank you Daniel, this helps a lot !
As you can guess, I come from the imperative world, but want to discover
functionnal languages (thanks to xmonad).
Thank you very much for your explainations. I think I will fall in that trap
again, but next time, I should be able to fix it myself. I still don't
understand exactly what lies behind, but start to get the picture. I didn't
change anything besides the position of the 'do' and the deletion of the
'return ()'.
I will modify the code with the realWork function as you suggested. I looks
much nicer.
As of the last problem, with the intToDigit function. I already knew about
the bug. I actually knew it wouldn't work since it is takes only argument
from 0 to 15... Well, that was lazy from me. I just wanted to write the
statement so that I don't forget it.
Danke sehr.
2010/2/26 Daniel Fischer
Am Freitag 26 Februar 2010 18:34:35 schrieb Florian Duret:
It seems that both your suggestions have worked ! Thank you very much. But I still can't figure out what went wrong.
Did you change anything besides removing the "do" and "return ()" from the then-branch and insert the "do" in the else-branch? If not, you've been bitten by a somewhat less than obvious aspect of layout - although it's pretty clear with an explanation. A new layout-block isn't opened by a larger indentation, but by the keywords do, let, of and where. So, when you write
... = do xxx if blah then do foo bar else baz zap
the "do" after the then opens a new layout-block inside the big do-block, since you didn't insert an explicit brace. The indentation level thereof is determined by the 'f' of "foo", bar is indented to the same level as foo, so it's a new expression in that same block. The else is indented less than the foo, so that ends the inner layout-block and we return to the layout-block of the big do-block. The indentation level thereof is determined by the first 'x', and the "if" is indented to the same level. The else, the baz and the zap are all indented further than the if, so they all belong to the if-expression (as intended). But since there's no "do" after the "else", all that is on one logical line, it's parsed as
... = do xxx if blah then do { foo; bar } else baz zap
Not what was intended, but it parses just fine.
Now you didn't have
baz zap
but
baz <- bong zap
and since we're still having only one logical line for the if-expression, the parser sees that as
... = do xxx if blah then do { foo; bar } else baz <- bong zap
But the syntax is
pattern <- expression
so the parser tries to parse
if blah then do { foo; bar } else baz
as a pattern. But it doesn't conform to the pattern productions, hence the parse error.
My initial goal was to keep the minimum inside the if ... then ... else statement. Basically, if the list is empty, then stop. If not, then assign the argument to sacFile1, and go on with the rest.
It would be cleanest to have
realWork :: FileName -> IO () realWork file = do sacFile1 <- openBinaryFile file ReadMode ...
main :: IO () main = do argList <- getArgs case argList of [] -> putStrLn "No filename ..." (f:_) -> realWork f
or
if null argList then putStrLn "..." else realWork (head argList)
, je pense.
Here is what it looks like now: module Main () where
import System.IO import System.Environment(getArgs) import Data.Char(intToDigit)
import SAC_Type import SAC_IO
main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (null argsList) then putStrLn $ "No filename given to the program.\n $ ProgramName file.sac" else do sacFile1 <- openBinaryFile (head argsList) ReadMode
position <- hTell sacFile1 putStrLn $ "Position 1: " ++ [intToDigit( fromInteger (position) )]
hSeek sacFile1 AbsoluteSeek 440 position2 <- hTell sacFile1 putStrLn $ "Position 2: " ++ [intToDigit( fromInteger (position2) )]
I don't think that's what you really want:
Prelude Data.Char> intToDigit 440 *** Exception: Char.intToDigit: not a digit 440
perhaps you wanted
putStrLn $ "Position 2: " ++ show position2
?
-- A la fin, il faut evidemment le fermer hClose sacFile1
Thank you, Danke, 谢谢, merci, etc...

On Fri, Feb 26, 2010 at 5:12 PM, Daniel Fischer
Am Freitag 26 Februar 2010 17:37:30 schrieb Magnus Therning:
It doesn't look like a complete piece of code so these comments aren't backed up by running it through GHCi or anything.
On Fri, Feb 26, 2010 at 16:29, Florian Duret
wrote: Hello,
I try to set up a verification on the number of arguments given to my program, but keep on getting "Parse error in pattern" Here is what my code looks like: main :: IO() main = do -- On commence par ouvrir le fichier SAC en mode binaire argsList <- getArgs if (length (argsList) == 0)
It's most likely harmless for argument lists (although there are other cases), but
Don't Use
if (length list == 0)
Never. Jamais. Niemals.
Use
if (null list)
length has to traverse the entire list, which may take a long time.
While the advice here is sound 90% of the time, it's evidence of falling into the trap of underestimating lazyness. If 0 and length list are both of type Nat, the first will be exactly as fast as the second. Bob

Am Samstag 27 Februar 2010 15:41:29 schrieb Tom Davie:
While the advice here is sound 90% of the time, it's evidence of falling into the trap of underestimating lazyness. If 0 and length list are both of type Nat, the first will be exactly as fast as the second.
Bob
As it is, we have length :: [a] -> Int Of course, an implementation with a lazy Int type is thinkable, but for the time being, it's a pretty safe bet that Int comparisons need complete evaluation of the arguments. (In GHC, you can use rewrite rules to avoid it, but if you think of that, you wouldn't write "length xs == k" unless you really mean it in the first place.) Most of the uses of "length xs == k" are due to the fact that people are used to strict list-like structures carrying their length with them and not to singly linked lazy lists of unknown length, I believe. So I'd say the advice is sound 100% of the time, though often the lists are so short that it's not a big deal. Thus the advice may be important less than 25% of the time. Now, genericLength is a different case. "genericLength xs == k" is a dangerous thing if used at strict types, but perfectly fine for lazy naturals. P.S.: Tom, I'm curious, why do you sign as Bob?
participants (4)
-
Daniel Fischer
-
Florian Duret
-
Magnus Therning
-
Tom Davie