From: simonmar Date: Thu, 4 Jul 2002 10:42:32 +0000 (+0000) Subject: [project @ 2002-07-04 10:42:32 by simonmar] X-Git-Tag: nhc98-1-18-release~952 X-Git-Url: http://git.megacz.com/?a=commitdiff_plain;h=a0edfd924f34dc719d90e1564de800a318d918f8;p=haskell-directory.git [project @ 2002-07-04 10:42:32 by simonmar] Explicitly import the Prelude, and add a few types signatures to make these modules produce better documentation. --- diff --git a/Text/ParserCombinators/Parsec/Char.hs b/Text/ParserCombinators/Parsec/Char.hs index 5f06136..05f3ad0 100644 --- a/Text/ParserCombinators/Parsec/Char.hs +++ b/Text/ParserCombinators/Parsec/Char.hs @@ -23,6 +23,7 @@ module Text.ParserCombinators.Parsec.Char , satisfy ) where +import Prelude import Data.Char import Text.ParserCombinators.Parsec.Pos( updatePosChar, updatePosString ) import Text.ParserCombinators.Parsec.Prim @@ -64,4 +65,4 @@ satisfy f = tokenPrim (\c -> show [c]) (\c -> if f c then Just c else Nothing) string :: String -> CharParser st String -string s = tokens show updatePosString s \ No newline at end of file +string s = tokens show updatePosString s diff --git a/Text/ParserCombinators/Parsec/Error.hs b/Text/ParserCombinators/Parsec/Error.hs index b72b65e..abb3c69 100644 --- a/Text/ParserCombinators/Parsec/Error.hs +++ b/Text/ParserCombinators/Parsec/Error.hs @@ -26,6 +26,7 @@ module Text.ParserCombinators.Parsec.Error where +import Prelude import Data.List (nub,sortBy) import Text.ParserCombinators.Parsec.Pos @@ -43,15 +44,18 @@ messageToEnum msg Expect _ -> 2 Message _ -> 3 +messageCompare :: Message -> Message -> Ordering messageCompare msg1 msg2 = compare (messageToEnum msg1) (messageToEnum msg2) +messageString :: Message -> String messageString msg = case msg of SysUnExpect s -> s UnExpect s -> s Expect s -> s Message s -> s +messageEq :: Message -> Message -> Bool messageEq msg1 msg2 = (messageCompare msg1 msg2 == EQ) @@ -77,18 +81,23 @@ errorIsUnknown (ParseError pos msgs) ----------------------------------------------------------- -- Create parse errors ----------------------------------------------------------- +newErrorUnknown :: SourcePos -> ParseError newErrorUnknown pos = ParseError pos [] +newErrorMessage :: Message -> SourcePos -> ParseError newErrorMessage msg pos = ParseError pos [msg] +addErrorMessage :: Message -> ParseError -> ParseError addErrorMessage msg (ParseError pos msgs) = ParseError pos (msg:msgs) +setErrorPos :: SourcePos -> ParseError -> ParseError setErrorPos pos (ParseError _ msgs) = ParseError pos msgs +setErrorMessage :: Message -> ParseError -> ParseError setErrorMessage msg (ParseError pos msgs) = ParseError pos (msg:filter (not . messageEq msg) msgs) diff --git a/Text/ParserCombinators/Parsec/Prim.hs b/Text/ParserCombinators/Parsec/Prim.hs index 7ec06eb..4889717 100644 --- a/Text/ParserCombinators/Parsec/Prim.hs +++ b/Text/ParserCombinators/Parsec/Prim.hs @@ -39,6 +39,7 @@ module Text.ParserCombinators.Parsec.Prim , getParserState, setParserState ) where +import Prelude import Text.ParserCombinators.Parsec.Pos import Text.ParserCombinators.Parsec.Error import Control.Monad @@ -105,7 +106,10 @@ setInput input = do{ updateParserState (\(State _ pos user) -> State input ; return () } -getParserState = updateParserState id +getParserState :: GenParser tok st (State tok st) +getParserState = updateParserState id + +setParserState :: State tok st -> GenParser tok st (State tok st) setParserState st = updateParserState (const st) @@ -152,6 +156,7 @@ parseTest p input Right x -> print x +parse :: GenParser tok () a -> SourceName -> [tok] -> Either ParseError a parse p name input = runParser p () name input @@ -313,6 +318,7 @@ label :: GenParser tok st a -> String -> GenParser tok st a label p msg = labels p [msg] +labels :: GenParser tok st a -> [String] -> GenParser tok st a labels (Parser p) msgs = Parser (\state -> case (p state) of