Changed the Rain parser to use the CompState of the occam parser
This commit is contained in:
parent
eab08e7af2
commit
d2022defb0
21
RainParse.hs
21
RainParse.hs
|
@ -1,7 +1,6 @@
|
||||||
module RainParse where
|
module RainParse where
|
||||||
|
|
||||||
import qualified Text.ParserCombinators.Parsec.Token as P
|
import qualified Text.ParserCombinators.Parsec.Token as P
|
||||||
import Parse (tryXV)
|
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
@ -32,26 +31,12 @@ import Metadata
|
||||||
import Pass
|
import Pass
|
||||||
import Types
|
import Types
|
||||||
import Utils
|
import Utils
|
||||||
|
import qualified Parse
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
--Dummy:
|
type RainState = CompState
|
||||||
type RainState = Int
|
type RainParser = Parse.OccParser
|
||||||
|
|
||||||
type RainParser = GenParser Char RainState
|
|
||||||
|
|
||||||
|
|
||||||
emptyState:: RainState
|
|
||||||
emptyState = 0
|
|
||||||
|
|
||||||
{-
|
|
||||||
instance MonadState st (GenParser tok st) where
|
|
||||||
get = getState
|
|
||||||
put = setState
|
|
||||||
|
|
||||||
instance Die (GenParser tok st) where
|
|
||||||
die = fail
|
|
||||||
-}
|
|
||||||
|
|
||||||
rainStyle
|
rainStyle
|
||||||
= emptyDef
|
= emptyDef
|
||||||
|
|
|
@ -7,6 +7,7 @@ import Test.HUnit
|
||||||
import Metadata (Meta,emptyMeta)
|
import Metadata (Meta,emptyMeta)
|
||||||
import Prelude hiding (fail)
|
import Prelude hiding (fail)
|
||||||
import TestUtil
|
import TestUtil
|
||||||
|
import CompState
|
||||||
|
|
||||||
data ParseTest a = Show a => ExpPass (String, RP.RainParser a , (a -> Assertion)) | ExpFail (String, RP.RainParser a)
|
data ParseTest a = Show a => ExpPass (String, RP.RainParser a , (a -> Assertion)) | ExpFail (String, RP.RainParser a)
|
||||||
|
|
||||||
|
@ -20,7 +21,7 @@ fail x = ExpFail x
|
||||||
--Runs a parse test, given a tuple of: (source text, parser function, assert)
|
--Runs a parse test, given a tuple of: (source text, parser function, assert)
|
||||||
testParsePass :: Show a => (String, RP.RainParser a , (a -> Assertion)) -> Assertion
|
testParsePass :: Show a => (String, RP.RainParser a , (a -> Assertion)) -> Assertion
|
||||||
testParsePass (text,prod,test)
|
testParsePass (text,prod,test)
|
||||||
= case (runParser parser RP.emptyState "" text) of
|
= case (runParser parser emptyState "" text) of
|
||||||
Left error -> assertString (show error)
|
Left error -> assertString (show error)
|
||||||
Right result -> ((return result) >>= test)
|
Right result -> ((return result) >>= test)
|
||||||
where parser = do { p <- prod ; eof ; return p}
|
where parser = do { p <- prod ; eof ; return p}
|
||||||
|
@ -30,7 +31,7 @@ testParsePass (text,prod,test)
|
||||||
|
|
||||||
testParseFail :: Show a => (String, RP.RainParser a) -> Assertion
|
testParseFail :: Show a => (String, RP.RainParser a) -> Assertion
|
||||||
testParseFail (text,prod)
|
testParseFail (text,prod)
|
||||||
= case (runParser parser RP.emptyState "" text) of
|
= case (runParser parser emptyState "" text) of
|
||||||
Left error -> return ()
|
Left error -> return ()
|
||||||
Right result -> assertFailure ("Test was expected to fail:\n***BEGIN CODE***\n" ++ text ++ "\n*** END CODE ***\n")
|
Right result -> assertFailure ("Test was expected to fail:\n***BEGIN CODE***\n" ++ text ++ "\n*** END CODE ***\n")
|
||||||
where parser = do { p <- prod ; eof ; return p}
|
where parser = do { p <- prod ; eof ; return p}
|
||||||
|
|
Loading…
Reference in New Issue
Block a user