[Haskell-cafe] type signature of parsec functions and how to warp them up.
吴兴博
wuxb45 at gmail.com
Fri Jun 17 07:53:48 CEST 2011
It seems weird:
first ghci failed to load this file:
file: RunParse.hs
-------------------
module RunParse where
import System.IO
import Data.Functor.Identity (Identity)
----import Text.Parsec --------first, no this
line-------what about this line ???
import Text.Parsec.Prim (Parsec, parse, Stream)
runIOParse :: (Show a) => Parsec String () a -> String -> IO ()
runIOParse pa fn =
do
inh <- openFile fn ReadMode
outh <- openFile (fn ++ ".parseout") WriteMode
instr <- hGetContents inh
let result = case parse pa fn instr of
Right rs -> show rs
Left err -> "error"
hPutStr outh result
hClose inh
hClose outh
------------------
ghci tell me:
-----------------
RunParse.hs:13:23:
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 => Parsec String () a -> String -> IO ()
at Sim/Std/RunParse.hs:(8,1)-(18,15)
Possible fix:
add (Stream String Identity t0) to the context of
the type signature for
runIOParse :: Show a => Parsec String () a -> String -> IO ()
or add an instance declaration for (Stream String Identity t0)
In the expression: parse pa fn instr
In the expression:
case parse pa fn instr of {
Right rs -> show rs
Left err -> "error" }
In an equation for `result':
result
= case parse pa fn instr of {
Right rs -> show rs
Left err -> "error" }
------------------
I just add one line of import and ghci:
import Text.Parsec
then ghci loaded it succeed!
It seems I didn't uses any functions from this import.
what goes wrong?
2011/6/17 吴兴博 <wuxb45 at gmail.com>:
> 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.
--
----------------
吴兴博 Wu Xingbo
More information about the Haskell-Cafe
mailing list