[Haskell-cafe] type signature of parsec functions and how to warp them up.
吴兴博
wuxb45 at gmail.com
Fri Jun 17 07:26:09 CEST 2011
I have some different parsers of Parsec to use in a project, and I
want to make a warp function to make the testing easy.
here is some of my body of parser : they all has type of "parsecT ***"
stringSet :: ParsecT String u Identity [String]
intSet :: ParsecT String u Identity [Integer]
tupleSet :: ParsecT String u Identity [(String, String)]
all of the returned type are instance of 'Show'.
then I write these warp function:
------------------
import System.IO
import Data.Functor.Identity (Identity)
import Text.Parsec.Prim (ParsecT, runParserT, parse, Stream)
runIOParse :: (Show a) => ParsecT String u Identity a -> String -> IO ()
runIOParse pa fn =
do
inh <- openFile fn ReadMode
outh <- openFile (fn ++ ".parseout") WriteMode
instr <- hGetContents inh
let result = show $ parse pa fn instr
hPutStr outh result
hClose inh
hClose outh
-------------------
> :l RunParse.hs
-------------------
RunParse.hs:12:31:
Could not deduce (u ~ ())
from the context (Show a)
bound by the type signature for
runIOParse :: Show a =>
ParsecT String u Identity a -> String -> IO ()
at RunParse.hs:(7,1)-(15,15)
`u' is a rigid type variable bound by
the type signature for
runIOParse :: Show a =>
ParsecT String u Identity a -> String -> IO ()
at RunParse.hs:7:1
Expected type: Text.Parsec.Prim.Parsec String () a
Actual type: ParsecT String u Identity a
In the first argument of `parse', namely `pa'
In the second argument of `($)', namely `parse pa fn instr'
Failed, modules loaded: none.
-------------------
then I modify the type signature of 'runIOParse':
runIOParse :: (Show a) => ParsecT String () Identity a -> String -> IO ()
then load again
> :l RunParse.hs
-------------------
RunParse.hs:12:25:
Could not deduce (Stream String Identity t0)
arising from a use of `parse'
from the context (Show a)
bound by the type signature for
runIOParse :: Show a =>
ParsecT String () Identity a -> String -> IO ()
at RunParse.hs:(7,1)-(15,15)
Possible fix:
add (Stream String Identity t0) to the context of
the type signature for
runIOParse :: Show a =>
ParsecT String () Identity a -> String -> IO ()
or add an instance declaration for (Stream String Identity t0)
In the second argument of `($)', namely `parse pa fn instr'
In the expression: show $ parse pa fn instr
In an equation for `result': result = show $ parse pa fn instr
Failed, modules loaded: none.
-------------------
I also tried some 'possible fix' in the information, but it still
failed to pass the compiler.
Main Question:
**** How can I warp a parsec function interface for do the IO test
with different 'ParsecT String u Identity a'?
--
----------------
吴兴博 Wu Xingbo
More information about the Haskell-Cafe
mailing list