Changed to a state monad for warnings, and added a runPassM function to remove duplicate code for running passes
This commit is contained in:
parent
f7f01a3333
commit
4ef1ff7196
6
Main.hs
6
Main.hs
|
@ -161,10 +161,10 @@ main = do
|
||||||
ModeFull -> evalStateT (compileFull fn fileStem) []
|
ModeFull -> evalStateT (compileFull fn fileStem) []
|
||||||
|
|
||||||
-- Run the compiler.
|
-- Run the compiler.
|
||||||
v <- runWriterT $ evalStateT (runErrorT operation) initState
|
v <- runPassM initState operation
|
||||||
case v of
|
case v of
|
||||||
(Left e, ws) -> showWarnings ws >> dieIO e
|
(Left e, _, ws) -> showWarnings ws >> dieIO e
|
||||||
(Right r, ws) -> showWarnings ws
|
(Right r, _, ws) -> showWarnings ws
|
||||||
|
|
||||||
removeFiles :: [FilePath] -> IO ()
|
removeFiles :: [FilePath] -> IO ()
|
||||||
removeFiles = mapM_ (\file -> catch (removeFile file) doNothing)
|
removeFiles = mapM_ (\file -> catch (removeFile file) doNothing)
|
||||||
|
|
|
@ -48,6 +48,7 @@ import GenerateC
|
||||||
import GenerateCBased
|
import GenerateCBased
|
||||||
import GenerateCPPCSP
|
import GenerateCPPCSP
|
||||||
import Metadata
|
import Metadata
|
||||||
|
import Pass
|
||||||
import TestUtils
|
import TestUtils
|
||||||
import Utils
|
import Utils
|
||||||
|
|
||||||
|
@ -109,7 +110,9 @@ evalCGen :: CGen () -> GenOps -> CompState -> IO (Either Errors.ErrorReport [Str
|
||||||
evalCGen act ops state = evalCGen' (runReaderT act ops) state
|
evalCGen act ops state = evalCGen' (runReaderT act ops) state
|
||||||
|
|
||||||
evalCGen' :: CGen' () -> CompState -> IO (Either Errors.ErrorReport [String])
|
evalCGen' :: CGen' () -> CompState -> IO (Either Errors.ErrorReport [String])
|
||||||
evalCGen' act state = runWriterT (evalStateT (runErrorT $ execStateT act (Left []) >>* (\(Left x) -> x)) state) >>* fst
|
evalCGen' act state = runPassM state pass >>* (\(x,_,_) -> x)
|
||||||
|
where
|
||||||
|
pass = execStateT act (Left []) >>* (\(Left x) -> x)
|
||||||
|
|
||||||
-- | Checks that running the test for the C and C++ backends produces the right output for each.
|
-- | Checks that running the test for the C and C++ backends produces the right output for each.
|
||||||
testBothS ::
|
testBothS ::
|
||||||
|
|
|
@ -111,9 +111,9 @@ testGetVarProc = TestList (map doTest tests)
|
||||||
doTest (index, r, w, u, proc)
|
doTest (index, r, w, u, proc)
|
||||||
= TestCase $ do result <- runPass (getVarProc proc) startState
|
= TestCase $ do result <- runPass (getVarProc proc) startState
|
||||||
case result of
|
case result of
|
||||||
Left err ->
|
(_, Left err) ->
|
||||||
testFailure $ name ++ " failed: " ++ show err
|
testFailure $ name ++ " failed: " ++ show err
|
||||||
Right (_, result) ->
|
(_, Right result) ->
|
||||||
assertEqual name (vars r w u) result
|
assertEqual name (vars r w u) result
|
||||||
where
|
where
|
||||||
name = "testGetVarProc" ++ show index
|
name = "testGetVarProc" ++ show index
|
||||||
|
|
|
@ -59,7 +59,7 @@ defaultState = emptyState {csUsageChecking = True}
|
||||||
-- | Tests if compiling the given source gives any errors.
|
-- | Tests if compiling the given source gives any errors.
|
||||||
-- If there are errors, they are returned. Upon success, Nothing is returned
|
-- If there are errors, they are returned. Upon success, Nothing is returned
|
||||||
testOccam :: String -> IO (Maybe String)
|
testOccam :: String -> IO (Maybe String)
|
||||||
testOccam source = do (result,_) <- runWriterT $ evalStateT (runErrorT compilation) defaultState
|
testOccam source = do (result,_,_) <- runPassM defaultState compilation
|
||||||
return $ case result of
|
return $ case result of
|
||||||
Left (_,err) -> Just err
|
Left (_,err) -> Just err
|
||||||
Right _ -> Nothing
|
Right _ -> Nothing
|
||||||
|
|
|
@ -495,7 +495,8 @@ runPass :: TestMonad m r =>
|
||||||
PassM b -- ^ The actual pass.
|
PassM b -- ^ The actual pass.
|
||||||
-> CompState -- ^ The state to use to run the pass.
|
-> CompState -- ^ The state to use to run the pass.
|
||||||
-> m (CompState, Either ErrorReport b) -- ^ The resultant state, and either an error or the successful outcome of the pass.
|
-> m (CompState, Either ErrorReport b) -- ^ The resultant state, and either an error or the successful outcome of the pass.
|
||||||
runPass actualPass startState = liftM (\((x,y),_) -> (y,x)) $ runIO (runWriterT $ runStateT (runErrorT actualPass) startState)
|
runPass actualPass startState = liftM (\(x,y,_) -> (y,x)) $
|
||||||
|
runIO (runPassM startState actualPass)
|
||||||
|
|
||||||
-- | A test that runs a given AST pass and checks that it succeeds.
|
-- | A test that runs a given AST pass and checks that it succeeds.
|
||||||
testPass ::
|
testPass ::
|
||||||
|
@ -585,7 +586,7 @@ testPassShouldFail testName actualPass startStateTrans =
|
||||||
do ret <- runPass actualPass (execState startStateTrans emptyState)
|
do ret <- runPass actualPass (execState startStateTrans emptyState)
|
||||||
case ret of
|
case ret of
|
||||||
(_,Left err) -> return ()
|
(_,Left err) -> return ()
|
||||||
Right (state, output) -> testFailure $ testName ++ " pass succeeded when expected to fail; output: " ++ pshow output
|
(state, Right output) -> testFailure $ testName ++ " pass succeeded when expected to fail; output: " ++ pshow output
|
||||||
|
|
||||||
--}}}
|
--}}}
|
||||||
--{{{ miscellaneous utilities
|
--{{{ miscellaneous utilities
|
||||||
|
|
|
@ -448,7 +448,9 @@ checkExpressionTest = TestList
|
||||||
if (e /= act) then pass' (10000 + n) t (mkPattern e) e else return ()
|
if (e /= act) then pass' (10000 + n) t (mkPattern e) e else return ()
|
||||||
where
|
where
|
||||||
errorOrType :: IO (Either ErrorReport A.Type)
|
errorOrType :: IO (Either ErrorReport A.Type)
|
||||||
errorOrType = ((runWriterT (evalStateT (runErrorT $ typeOfExpression e) (execState state emptyState))) :: IO (Either ErrorReport A.Type, [WarningReport])) >>* fst
|
errorOrType
|
||||||
|
= (flip runPassM (typeOfExpression e) (execState state emptyState))
|
||||||
|
>>* \(x,_,_) -> x
|
||||||
|
|
||||||
|
|
||||||
fail :: Int -> ExprHelper -> Test
|
fail :: Int -> ExprHelper -> Test
|
||||||
|
|
18
pass/Pass.hs
18
pass/Pass.hs
|
@ -37,8 +37,8 @@ import TreeUtils
|
||||||
import Utils
|
import Utils
|
||||||
|
|
||||||
-- | The monad in which AST-mangling passes operate.
|
-- | The monad in which AST-mangling passes operate.
|
||||||
type PassM = ErrorT ErrorReport (StateT CompState (WriterT [WarningReport] IO))
|
type PassM = ErrorT ErrorReport (StateT CompState (StateT [WarningReport] IO))
|
||||||
type PassMR = ErrorT ErrorReport (ReaderT CompState (WriterT [WarningReport] IO))
|
type PassMR = ErrorT ErrorReport (ReaderT CompState (StateT [WarningReport] IO))
|
||||||
|
|
||||||
instance Die PassM where
|
instance Die PassM where
|
||||||
dieReport = throwError
|
dieReport = throwError
|
||||||
|
@ -47,10 +47,10 @@ instance Die PassMR where
|
||||||
dieReport = throwError
|
dieReport = throwError
|
||||||
|
|
||||||
instance Warn PassM where
|
instance Warn PassM where
|
||||||
warnReport w = tell [w]
|
warnReport w = lift $ lift $ modify (++ [w])
|
||||||
|
|
||||||
instance Warn PassMR where
|
instance Warn PassMR where
|
||||||
warnReport w = tell [w]
|
warnReport w = lift $ lift $ modify (++ [w])
|
||||||
|
|
||||||
-- | The type of an AST-mangling pass.
|
-- | The type of an AST-mangling pass.
|
||||||
data Monad m => Pass_ m = Pass {
|
data Monad m => Pass_ m = Pass {
|
||||||
|
@ -85,10 +85,16 @@ instance Ord Property where
|
||||||
runPassR :: (A.AST -> PassMR A.AST) -> (A.AST -> PassM A.AST)
|
runPassR :: (A.AST -> PassMR A.AST) -> (A.AST -> PassM A.AST)
|
||||||
runPassR p t
|
runPassR p t
|
||||||
= do st <- get
|
= do st <- get
|
||||||
(r,w) <- liftIO $ runWriterT $ runReaderT (runErrorT (p t)) st
|
(r,w) <- liftIO $ flip runStateT [] $ runReaderT (runErrorT (p t)) st
|
||||||
case r of
|
case r of
|
||||||
Left err -> throwError err
|
Left err -> throwError err
|
||||||
Right result -> tell w >> return result
|
Right result -> mapM_ warnReport w >> return result
|
||||||
|
|
||||||
|
runPassM :: CompState -> PassM a -> IO (Either ErrorReport a, CompState, [WarningReport])
|
||||||
|
runPassM cs pass = liftM flatten $ flip runStateT [] $ flip runStateT cs $ runErrorT pass
|
||||||
|
where
|
||||||
|
flatten :: ((a, b),c) -> (a, b, c)
|
||||||
|
flatten ((x, y), z) = (x, y, z)
|
||||||
|
|
||||||
makePassesDep :: [(String, A.AST -> PassM A.AST, [Property], [Property])] -> [Pass]
|
makePassesDep :: [(String, A.AST -> PassM A.AST, [Property], [Property])] -> [Pass]
|
||||||
makePassesDep = map (\(s, p, pre, post) -> Pass p s (Set.fromList pre) (Set.fromList post) (const True))
|
makePassesDep = map (\(s, p, pre, post) -> Pass p s (Set.fromList pre) (Set.fromList post) (const True))
|
||||||
|
|
Loading…
Reference in New Issue
Block a user