I would appreciate any help in solving the compilation error below.  I copied some type info from hugs into the bottom of this message.
 
 
Type checking.........................................
ERROR "d:/hxslt/XpathLex.hs" (line 113): Type error in explicitly typed binding
*** Term           : readQuote
*** Type           : String -> Position -> LexerState a -> Maybe (Either Error XPathToken,([Char],Int,Int),([Char],([Char],Int,Int),a),Maybe c)
*** Does not match : String -> Position -> LexerState a -> (Maybe (Either Error b),Position,LexerState a,Maybe (Lexer (LexerState a) b))
 
Lexers>
 
readQuote::String -> Position ->  LexerState s -> (Maybe (Either Error t), -- err/tok?
         Position,      -- new pos
         LexerState s,       -- state
         Maybe (Lexer (LexerState s) t))     -- lexer?    
 
readQuote (quote:_)  pos st@(str,tpos,x
-- ERROR OCCURS ON THE NEXT Line

    =   let index = findIndex (\c -> quote == c) str
     err=Error FatalErr pos ["No closing quote (" ++ quote:")"]
 in
 Just (maybe (Left err,pos,st,Nothing) get_tok index)
     where
     get_tok ix=
      let (tokstr,rest) = splitAt ix str
   tk=StringToken pos LiteralTK tokstr
   newst=(rest,incPos tpos ix+1,x)
      in
    (Right tk, incPos pos ix+1, newst,Nothing)
 
 
 
Lexers> :info LexerState
-- type constructor
type LexerState a = ([Char],([Char],Int,Int),a)
 
Lexers> :type Position
ERROR: Undefined constructor function "Position"
Lexers> :info Position
-- type constructor
type Position = ([Char],Int,Int)
 
Lexers> :type Lexer
Lexer :: LexAction a b -> Cont a b -> Lexer a b
Lexers>
 
 
 
In order to keep our private email private, I suggest you install PGP freeware http://web.mit.edu/network/pgp.html

Reply via email to