[Haskell-cafe] Fwd: Basic Parsec float & integer parsing question

Antoine Latter aslatter at gmail.com
Fri Jul 5 19:51:04 CEST 2013


Forwarding to the list.


---------- Forwarded message ----------
From: Fredrik Karlsson <dargosch at gmail.com>
Date: Fri, Jul 5, 2013 at 11:42 AM
Subject: [Haskell-cafe] Basic Parsec float & integer parsing question
To: haskell-cafe at haskell.org


Dear list,

Sorry for asking a simple parsec question, but both Parsec and Haskell
is new to me, so please be gentle :-)

I have this code:

------------------------------------------------------------------------------------------------
import Text.ParserCombinators.Parsec
import Text.Parsec.Token
import Text.ParserCombinators.Parsec.Char


data VariableLine = VariableLine String String deriving Show
data TierType = IntervalTier | PointTier deriving Show

data Tier = Tier TierType String Float Float Integer
data Label = Interval Float Float String
data LabelFile = LabelFile Float Float

symbol :: Parser Char
symbol = oneOf "!#$%&|*+-/:<=>?@^_~"

testString = "intervals [1]:\n    xmin = 0 \n    xmax =
0.028199999999999992 \n    text = \"\""
headTS1 = "File type = \"ooTextFile\"\nObject class = \"TextGrid\"\n\nxmin ="

header :: Parser LabelFile
header = do
headTS1
start <- float
string "\nxmax = "
end <- float
string "\ntiers? <exists>\nsize = "
integer
char '\n'
return $ LabelFile start end

------------------------------------------------------------------------------------------------

Loading it into ghci I get :

Prelude> :l parsectest.hs
[1 of 1] Compiling Main             ( parsectest.hs, interpreted )

parsectest.hs:21:9:
    Couldn't match type `[]'
                  with `Text.Parsec.Prim.ParsecT
                          String () Data.Functor.Identity.Identity'
    Expected type: Text.Parsec.Prim.ParsecT
                     String () Data.Functor.Identity.Identity Char
      Actual type: [Char]
    In a stmt of a 'do' block: headTS1
    In the expression:
      do { headTS1;
           start <- float;
           string
             "\
             \xmax = ";
           end <- float;
           .... }
    In an equation for `header':
        header
          = do { headTS1;
                 start <- float;
                 string
                   "\
                   \xmax = ";
                 .... }

parsectest.hs:22:18:
    Couldn't match expected type `Text.Parsec.Prim.ParsecT
                                    String ()
Data.Functor.Identity.Identity Float'
                with actual type `GenTokenParser s0 u0 m0
                                  -> Text.Parsec.Prim.ParsecT s0 u0 m0 Double'
    In a stmt of a 'do' block: start <- float
    In the expression:
      do { headTS1;
           start <- float;
           string
             "\
             \xmax = ";
           end <- float;
           .... }
    In an equation for `header':
        header
          = do { headTS1;
                 start <- float;
                 string
                   "\
                   \xmax = ";
                 .... }

parsectest.hs:24:16:
    Couldn't match expected type `Text.Parsec.Prim.ParsecT
                                    String ()
Data.Functor.Identity.Identity Float'
                with actual type `GenTokenParser s1 u1 m1
                                  -> Text.Parsec.Prim.ParsecT s1 u1 m1 Double'
    In a stmt of a 'do' block: end <- float
    In the expression:
      do { headTS1;
           start <- float;
           string
             "\
             \xmax = ";
           end <- float;
           .... }
    In an equation for `header':
        header
          = do { headTS1;
                 start <- float;
                 string
                   "\
                   \xmax = ";
                 .... }

parsectest.hs:26:9:
    Couldn't match expected type `Text.Parsec.Prim.ParsecT
                                    String () Data.Functor.Identity.Identity a0'
                with actual type `GenTokenParser s2 u2 m2
                                  -> Text.Parsec.Prim.ParsecT s2 u2 m2 Integer'
    In a stmt of a 'do' block: integer
    In the expression:
      do { headTS1;
           start <- float;
           string
             "\
             \xmax = ";
           end <- float;
           .... }
    In an equation for `header':
        header
          = do { headTS1;
                 start <- float;
                 string
                   "\
                   \xmax = ";
                 .... }
Failed, modules loaded: none.

I'm sure I'm doing something really stupid here, but I need help to
get through this problem. I've used the predefined "letter" parser at
other places in the code, so I can't understand why "float" and
"integer" does not work.

/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



More information about the Haskell-Cafe mailing list