[Haskell-cafe] Parsec error message not making any sense

David McBride toad3k at gmail.com
Wed Jul 10 15:39:17 CEST 2013


First, I want to say you'd have a lot better luck with these questions
by posting to stackoverflow.  This really isn't the right place for
it.

As for why your parser is not working, you need to realize that parsec
does not backtrack by default.  It does this to conserve memory (so it
doesn't have to save its location at every possible branch point).

When you go many1 (interval name), it will parse the five intervals
[n] lines, and then try to parse a 6th one.  Well it turns out the
next atom begins with an 'i' character.  When it hits the t afterword,
that was wrong, it was expecting "intervals [", not an i followed by a
t.  That error message is exactly right.  At that point it fails,
which is fine, it is supposed to fail, but it unfortunately does not
move its place in the text stream back up to the i, it stays at the
't' character, then tries to parse more item blocks starting there.

The fix is to change interval to: "interval tierName = try $ do".
That means if it fails anywhere in the interval block, it will move
the parser back to where it was when the try was hit and then try to
parse it in some other manner.

I think that the rest of your code is pretty good, but you will have
to fix a few more things to completely parse your file.

On Tue, Jul 9, 2013 at 4:23 PM, Fredrik Karlsson <dargosch at gmail.com> wrote:
> Hi,
>
> Sorry, that was a careless extraction of code - I should have made sure that
> it was complete.
> Please, have a look again. When downloading and running the gist
> (https://gist.github.com/dargosch/5955045) , I still get the error:
>
> Main> let testFile =
> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
> *Main> parseFromFile textgridfile testFile
> Left
> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
> (line 35, column 5):
> unexpected "t"
> expecting "intervals ["
>
> on the attached testfile. The "tier" parser works once, but then I get an
> error that I cant understand, given the input.
> How come the parser finds the "unexpected "t"" when the expected thing is
> what is in the input at that point?
>
> Thankful for any help I can get on this.
>
>
> On Tue, Jul 9, 2013 at 10:22 PM, Fredrik Karlsson <dargosch at gmail.com>
> wrote:
>>
>> Hi,
>>
>> Sorry, that was a careless extraction of code - I should have made sure
>> that it was complete.
>> Please, have a look again. When downloading and running the gist, I still
>> get the error:
>>
>> Main> let testFile =
>> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
>> *Main> parseFromFile textgridfile testFile
>> Left
>> "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
>> (line 35, column 5):
>> unexpected "t"
>> expecting "intervals ["
>>
>> on the attached testfile. The "tier" parser works once, but then I get an
>> error that I cant understand, given the input.
>> How come the parser finds the "unexpected "t"" when the expected thing is
>> what is in the input at that point?
>>
>> Thankful for any help I can get on this.
>>
>>
>> /Fredrik
>>
>>
>> On Tue, Jul 9, 2013 at 9:37 AM, Roman Cheplyaka <roma at ro-che.info> wrote:
>>>
>>> Please check your code.
>>>
>>> I had two problems with it: mixed tabs and spaces, and undefined
>>> 'quotedChar'. After defining quotedChar = anyChar, I get a different
>>> error message from yours:
>>>
>>>   *Main> parseFromFile textgridfile "testdata.TextGrid"
>>>   Left "testdata.TextGrid" (line 137, column 1):
>>>   unexpected end of input
>>>   expecting quote at end of cell
>>>
>>> Roman
>>>
>>> * Fredrik Karlsson <dargosch at gmail.com> [2013-07-09 08:07:24+0200]
>>> > Hi Roman,
>>> >
>>> > I'm using parsec-3.1.3
>>> >
>>> > I put the code in a gist here - sorry about that.
>>> >
>>> > https://gist.github.com/dargosch/5955045
>>> >
>>> > Fredrik
>>> >
>>> >
>>> >
>>> >
>>> > On Tue, Jul 9, 2013 at 12:08 AM, Roman Cheplyaka <roma at ro-che.info>
>>> > wrote:
>>> >
>>> > > Hi Fredrik,
>>> > >
>>> > > First, do you use the latest parsec version (3.1.3)? If not, can you
>>> > > try
>>> > > the same with 3.1.3?
>>> > >
>>> > > Second, please upload your code to hpaste.org or a similar service
>>> > > and
>>> > > give us the link. It's not much fun to extract code from an html
>>> > > email.
>>> > >
>>> > > Roman
>>> > >
>>> > > * Fredrik Karlsson <dargosch at gmail.com> [2013-07-08 23:54:17+0200]
>>> > > > Dear list,
>>> > > >
>>> > > > I have a Parsec parser that fails and gives the following error
>>> > > > message:
>>> > > >
>>> > > > *Main> parseFromFile textgridfile testFile
>>> > > > Left
>>> > > >
>>> > >
>>> > > "/Users/frkkan96/Documents/src/ume/umecore/testing/testdata/testdata.TextGrid"
>>> > > > (line 35, column 5):
>>> > > > unexpected "t"
>>> > > > expecting "intervals ["
>>> > > >
>>> > > > Now, this is perfectly understandable, but line 35, col 5 in the
>>> > > > file
>>> > > being
>>> > > > parsed looks like the supplies image - there is no 't' there.
>>> > > >
>>> > > > Any ideas on what is going on?
>>> > > >
>>> > > > The parser I am using is:
>>> > > >
>>> > > > data VariableLine = VariableLine String String deriving Show
>>> > > > data TierType = IntervalTier | PointTier deriving Show
>>> > > >
>>> > > > data Tier = Tier String deriving Show
>>> > > > data LabelFile = LabelFile Double Double deriving Show
>>> > > >
>>> > > > data Label = Label String TierType Double Double String deriving
>>> > > > Show
>>> > > >
>>> > > >
>>> > > > haskelldef = makeTokenParser haskellDef
>>> > > >
>>> > > >
>>> > > > textgridfile :: Parser (LabelFile, [[Label]])
>>> > > > textgridfile = do
>>> > > > h <- header
>>> > > > ll <- many1 tier
>>> > > > return $ (h,ll)
>>> > > >
>>> > > > header :: Parser LabelFile
>>> > > > header = do
>>> > > > string headTS1
>>> > > > start <- try (float haskelldef)
>>> > > > <|> (fmap fromInteger $ integer haskelldef )
>>> > > > string "xmax = "
>>> > > > end <- try (float haskelldef)
>>> > > > <|> (fmap fromInteger $ integer haskelldef )
>>> > > > string "tiers? <exists> \n"
>>> > > > string "size = "
>>> > > > integer haskelldef
>>> > > > string "item []:"
>>> > > > whiteSpace haskelldef
>>> > > > return $ LabelFile start end
>>> > > >
>>> > > > tier :: Parser [Label]
>>> > > > tier = do
>>> > > > whiteSpace haskelldef
>>> > > > string "item ["
>>> > > > integer haskelldef
>>> > > > string "]:"
>>> > > > whiteSpace haskelldef
>>> > > > try (string "class = \"IntervalTier\"")
>>> > > > <|> string "class = \"TextTier\""
>>> > > > whiteSpace haskelldef
>>> > > > string "name = "
>>> > > > char '"'
>>> > > > name <- many quotedChar
>>> > > > char '"' <?> "quote at end of cell"
>>> > > > whiteSpace haskelldef
>>> > > > string "xmin = "
>>> > > > try (float haskelldef) <|> (fmap fromInteger $ integer haskelldef )
>>> > > > whiteSpace haskelldef
>>> > > > string "xmax = "
>>> > > > try (float haskelldef) <|> (fmap fromInteger $ integer haskelldef )
>>> > > > string "intervals: size = " <|> string "points: size = "
>>> > > > integer haskelldef
>>> > > > whiteSpace haskelldef
>>> > > > labelList <- many1 (interval name)
>>> > > > return $ labelList
>>> > > > interval :: String -> Parser Label
>>> > > > interval tierName = do
>>> > > > whiteSpace haskelldef
>>> > > > string "intervals ["
>>> > > > integer haskelldef
>>> > > > string "]:"
>>> > > > whiteSpace haskelldef
>>> > > > string "xmin = "
>>> > > > start <- try (float haskelldef)
>>> > > > <|> (fmap fromInteger $ integer haskelldef )
>>> > > > whiteSpace haskelldef
>>> > > > string "xmax = "
>>> > > > end <- try (float haskelldef)
>>> > > > <|> (fmap fromInteger $ integer haskelldef )
>>> > > > whiteSpace haskelldef
>>> > > > string "text = "
>>> > > > char '"'
>>> > > > text <- many quotedChar
>>> > > > char '"' <?> "quote at end of cell"
>>> > > > return $ Label tierName IntervalTier start end text
>>> > > >
>>> > > > which fails on the attached input file.
>>> > > >
>>> > > > I can't see how 't' is found?? What am I doing wrong?
>>> > > >
>>> > > > /Fredrik
>>> > > >
>>> > > >
>>> > > >
>>> > > > --
>>> > > > "Life is like a trumpet - if you don't put anything into it, you
>>> > > > don't
>>> > > get
>>> > > > anything out of it."
>>> > >
>>> > >
>>> > >
>>> > > > _______________________________________________
>>> > > > Haskell-Cafe mailing list
>>> > > > Haskell-Cafe at haskell.org
>>> > > > http://www.haskell.org/mailman/listinfo/haskell-cafe
>>> > >
>>> > >
>>> >
>>> >
>>> > --
>>> > "Life is like a trumpet - if you don't put anything into it, you don't
>>> > get
>>> > anything out of it."
>>>
>>>
>>
>>
>>
>> --
>> "Life is like a trumpet - if you don't put anything into it, you don't get
>> anything out of it."
>
>
>
>
> --
> "Life is like a trumpet - if you don't put anything into it, you don't get
> anything out of it."
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list