
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."

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
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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
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
[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@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."

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
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
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
[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@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."
participants (2)
-
Fredrik Karlsson
-
Roman Cheplyaka