[Haskell-beginners] Parse error in pattern
Daniel Fischer
daniel.is.fischer at web.de
Fri Feb 26 16:57:03 EST 2010
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...
More information about the Beginners
mailing list