Removed the export of "m" in TestUtils, instead moving the definition to each module that uses it (less confusing that way)

This commit is contained in:
Neil Brown 2008-02-24 18:55:44 +00:00
parent 5d9e2d8e33
commit 74f3cb7fc2
8 changed files with 32 additions and 18 deletions

View File

@ -26,11 +26,15 @@ import Test.HUnit hiding (State)
import qualified AST as A import qualified AST as A
import BackendPasses import BackendPasses
import Metadata
import Pattern import Pattern
import TagAST import TagAST
import TestUtils import TestUtils
import TreeUtils import TreeUtils
m :: Meta
m = emptyMeta
-- | Test WaitUntil guard (should be unchanged) -- | Test WaitUntil guard (should be unchanged)
testTransformWaitFor0 :: Test testTransformWaitFor0 :: Test
testTransformWaitFor0 = TestCase $ testPass "testTransformWaitFor0" orig (transformWaitFor orig) (return ()) testTransformWaitFor0 = TestCase $ testPass "testTransformWaitFor0" orig (transformWaitFor orig) (return ())

View File

@ -38,7 +38,7 @@ import Omega
import ShowCode import ShowCode
import TestFramework import TestFramework
import TestHarness import TestHarness
import TestUtils hiding (m) import TestUtils
import UsageCheckUtils hiding (Var) import UsageCheckUtils hiding (Var)
import Utils import Utils

View File

@ -51,6 +51,8 @@ tvC = Var $ vC
tvD = Var $ vD tvD = Var $ vD
tvL = Var $ vL tvL = Var $ vL
m = emptyMeta
--These are all shorthand for some useful "building block" processes --These are all shorthand for some useful "building block" processes
--The syntax is roughly: <variable list>_eq_<variable list> --The syntax is roughly: <variable list>_eq_<variable list>
--where a variable may be <letter> or <letter'subscript> --where a variable may be <letter> or <letter'subscript>

View File

@ -50,7 +50,7 @@ import Test.QuickCheck
import qualified AST as A import qualified AST as A
import CompState import CompState
import Errors import Errors
import Metadata (Meta,emptyMeta) import Metadata (emptyMeta)
import Pass import Pass
import Pattern import Pattern
import PrettyShow import PrettyShow
@ -116,12 +116,6 @@ timeTask label (low,med,high) test level
let mean = average times let mean = average times
return (label, mean, Just $ average (map (\x -> (x - mean) * (x - mean)) times)) return (label, mean, Just $ average (map (\x -> (x - mean) * (x - mean)) times))
-- | An abbreviation for using 'emptyMeta'. TODO: This should really be removed (and all uses of it replaced with 'emptyMeta') for clarity.
m :: Meta
m = emptyMeta
-- | Creates a 'A.Name' object with the given 'String' as 'A.nameName', and 'A.nameType' as 'A.VariableName'. -- | Creates a 'A.Name' object with the given 'String' as 'A.nameName', and 'A.nameType' as 'A.VariableName'.
simpleName :: String -> A.Name simpleName :: String -> A.Name
simpleName s = A.Name { A.nameName = s , A.nameMeta = emptyMeta , A.nameType = A.VariableName } simpleName s = A.Name { A.nameName = s , A.nameMeta = emptyMeta , A.nameType = A.VariableName }
@ -423,29 +417,29 @@ data ExprHelper =
| EHTrue | EHTrue
buildExprPattern :: ExprHelper -> Pattern buildExprPattern :: ExprHelper -> Pattern
buildExprPattern = (stopCaringPattern m) . mkPattern . buildExpr buildExprPattern = (stopCaringPattern emptyMeta) . mkPattern . buildExpr
buildExpr :: ExprHelper -> A.Expression buildExpr :: ExprHelper -> A.Expression
buildExpr (Dy lhs op rhs) = A.Dyadic m op (buildExpr lhs) (buildExpr rhs) buildExpr (Dy lhs op rhs) = A.Dyadic emptyMeta op (buildExpr lhs) (buildExpr rhs)
buildExpr (Mon op rhs) = A.Monadic m op (buildExpr rhs) buildExpr (Mon op rhs) = A.Monadic emptyMeta op (buildExpr rhs)
buildExpr (Cast ty rhs) = A.Conversion m A.DefaultConversion ty (buildExpr rhs) buildExpr (Cast ty rhs) = A.Conversion emptyMeta A.DefaultConversion ty (buildExpr rhs)
buildExpr (Var n) = A.ExprVariable m $ variable n buildExpr (Var n) = A.ExprVariable emptyMeta $ variable n
buildExpr (DirVar dir n) = A.ExprVariable m $ (A.DirectedVariable m dir $ variable n) buildExpr (DirVar dir n) = A.ExprVariable emptyMeta $ (A.DirectedVariable emptyMeta dir $ variable n)
buildExpr (Lit e) = e buildExpr (Lit e) = e
buildExpr EHTrue = A.True m buildExpr EHTrue = A.True emptyMeta
-- | A simple definition of a variable -- | A simple definition of a variable
simpleDef :: String -> A.SpecType -> A.NameDef simpleDef :: String -> A.SpecType -> A.NameDef
simpleDef n sp = A.NameDef {A.ndMeta = m, A.ndName = n, A.ndOrigName = n, A.ndNameType = A.VariableName, simpleDef n sp = A.NameDef {A.ndMeta = emptyMeta, A.ndName = n, A.ndOrigName = n, A.ndNameType = A.VariableName,
A.ndType = sp, A.ndAbbrevMode = A.Original, A.ndPlacement = A.Unplaced} A.ndType = sp, A.ndAbbrevMode = A.Original, A.ndPlacement = A.Unplaced}
-- | A simple definition of a declared variable -- | A simple definition of a declared variable
simpleDefDecl :: String -> A.Type -> A.NameDef simpleDefDecl :: String -> A.Type -> A.NameDef
simpleDefDecl n t = simpleDef n (A.Declaration m t Nothing) simpleDefDecl n t = simpleDef n (A.Declaration emptyMeta t Nothing)
-- | A simple definition of a declared variable -- | A simple definition of a declared variable
simpleDefDeclInit :: String -> A.Type -> Maybe A.Expression -> A.NameDef simpleDefDeclInit :: String -> A.Type -> Maybe A.Expression -> A.NameDef
simpleDefDeclInit n t init = simpleDef n (A.Declaration m t init) simpleDefDeclInit n t init = simpleDef n (A.Declaration emptyMeta t init)
-- | A pattern that will match simpleDef, with a different abbreviation mode -- | A pattern that will match simpleDef, with a different abbreviation mode
simpleDefPattern :: String -> A.AbbrevMode -> Pattern -> Pattern simpleDefPattern :: String -> A.AbbrevMode -> Pattern -> Pattern

View File

@ -63,6 +63,9 @@ fail x = ExpFail x
pat :: Data a => a -> Pattern pat :: Data a => a -> Pattern
pat = (stopCaringPattern emptyMeta) . mkPattern pat = (stopCaringPattern emptyMeta) . mkPattern
m :: Meta
m = emptyMeta
-- | Runs a parse test, given a tuple of: (source text, parser function, assertion) -- | Runs a parse test, given a tuple of: (source text, parser function, assertion)
-- There will be success if the parser succeeds, and the output succeeds against the given assertion. -- There will be success if the parser succeeds, and the output succeeds against the given assertion.
testParsePass :: Show a => (String, RP.RainParser a , (a -> Assertion)) -> Assertion testParsePass :: Show a => (String, RP.RainParser a , (a -> Assertion)) -> Assertion

View File

@ -38,6 +38,7 @@ import Test.HUnit hiding (State)
import qualified AST as A import qualified AST as A
import CompState import CompState
import Errors import Errors
import Metadata
import Pattern import Pattern
import RainPasses import RainPasses
import RainTypes import RainTypes
@ -45,6 +46,9 @@ import TagAST
import TestUtils import TestUtils
import TreeUtils import TreeUtils
m :: Meta
m = emptyMeta
-- | A helper function that returns a simple A.Structured A.Process item (A.Only m $ A.Skip m). -- | A helper function that returns a simple A.Structured A.Process item (A.Only m $ A.Skip m).
skipP :: A.Structured A.Process skipP :: A.Structured A.Process
skipP = A.Only m (A.Skip m) skipP = A.Only m (A.Skip m)

View File

@ -28,6 +28,7 @@ import Test.HUnit hiding (State)
import qualified AST as A import qualified AST as A
import CompState import CompState
import Errors import Errors
import Metadata
import Pass import Pass
import Pattern import Pattern
import RainTypes import RainTypes
@ -37,6 +38,9 @@ import TreeUtils
import Types import Types
import Utils import Utils
m :: Meta
m = emptyMeta
-- | Tests that constants in expressions are folded properly. TODO these tests could do with a lot of expanding. -- | Tests that constants in expressions are folded properly. TODO these tests could do with a lot of expanding.
-- It may even be easiest to use QuickCheck for the testing. -- It may even be easiest to use QuickCheck for the testing.
constantFoldTest :: Test constantFoldTest :: Test

View File

@ -34,6 +34,9 @@ import TagAST
import TestUtils import TestUtils
import TreeUtils import TreeUtils
m :: Meta
m = emptyMeta
-- | A handy typed version of Nothing for use with A.Declaration -- | A handy typed version of Nothing for use with A.Declaration
noInit :: Maybe A.Expression noInit :: Maybe A.Expression
noInit = Nothing noInit = Nothing