Rain: tidied up the tests for the constant folding pass
This commit is contained in:
parent
01f763373d
commit
e35873f01c
|
@ -118,6 +118,17 @@ intLiteral n = A.Literal emptyMeta A.Int $ A.IntLiteral emptyMeta (show n)
|
||||||
intLiteralPattern :: Integer -> Pattern
|
intLiteralPattern :: Integer -> Pattern
|
||||||
intLiteralPattern = (stopCaringPattern emptyMeta) . mkPattern . intLiteral
|
intLiteralPattern = (stopCaringPattern emptyMeta) . mkPattern . intLiteral
|
||||||
|
|
||||||
|
|
||||||
|
-- | Creates an integer literal 'A.Expression' with the given integer.
|
||||||
|
int64Literal :: Integer -> A.Expression
|
||||||
|
int64Literal n = A.Literal emptyMeta A.Int64 $ A.IntLiteral emptyMeta (show n)
|
||||||
|
|
||||||
|
-- | Creates a 'Pattern' to match an 'A.Expression' instance.
|
||||||
|
-- @'assertPatternMatch' ('intLiteralPattern' x) ('intLiteral' x)@ will always succeed.
|
||||||
|
-- All meta tags are ignored.
|
||||||
|
int64LiteralPattern :: Integer -> Pattern
|
||||||
|
int64LiteralPattern = (stopCaringPattern emptyMeta) . mkPattern . int64Literal
|
||||||
|
|
||||||
-- | Creates a pair of variable lists, given a pair of variable-name lists as input.
|
-- | Creates a pair of variable lists, given a pair of variable-name lists as input.
|
||||||
makeNamesWR :: ([String],[String]) -> ([A.Variable],[A.Variable])
|
makeNamesWR :: ([String],[String]) -> ([A.Variable],[A.Variable])
|
||||||
makeNamesWR (x,y) = (map variable x,map variable y)
|
makeNamesWR (x,y) = (map variable x,map variable y)
|
||||||
|
|
|
@ -18,16 +18,39 @@ with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module RainTypesTest where
|
module RainTypesTest where
|
||||||
|
|
||||||
import Test.HUnit
|
import Test.HUnit hiding (State)
|
||||||
import TestUtil
|
import TestUtil
|
||||||
import RainTypes
|
import RainTypes
|
||||||
import TreeUtil
|
import TreeUtil
|
||||||
|
import qualified AST as A
|
||||||
|
import CompState
|
||||||
|
import Control.Monad.State
|
||||||
|
|
||||||
constantFoldTest :: Test
|
constantFoldTest :: Test
|
||||||
constantFoldTest = TestList
|
constantFoldTest = TestList
|
||||||
[
|
[
|
||||||
TestCase $ assertPatternMatch "constantFoldTest 0" (buildExprPattern $ Var "x") (buildExpr $ Var "x")
|
foldVar 0 $ Var "x"
|
||||||
|
,foldVar 1 $ Dy (Var "x") A.Plus (lit 0)
|
||||||
|
|
||||||
|
,foldCon 100 (lit 2) (Dy (lit 1) A.Plus (lit 1))
|
||||||
|
,foldCon 101 (lit 65537) (Dy (lit 2) A.Plus (lit 65535))
|
||||||
|
,foldCon 102 (lit (- two63)) (Dy (lit $ two63 - 1) A.Plus (lit 1))
|
||||||
]
|
]
|
||||||
|
where
|
||||||
|
two63 :: Integer
|
||||||
|
two63 = 9223372036854775808
|
||||||
|
|
||||||
|
foldVar :: Int -> ExprHelper -> Test
|
||||||
|
foldVar n e = testPass ("constantFoldTest " ++ show n) (buildExprPattern e) (constantFoldPass $ buildExpr e) state
|
||||||
|
|
||||||
|
foldCon :: Int -> ExprHelper -> ExprHelper -> Test
|
||||||
|
foldCon n exp orig = testPass ("constantFoldTest " ++ show n) (buildExprPattern exp) (constantFoldPass $ buildExpr orig) state
|
||||||
|
|
||||||
|
state :: State CompState ()
|
||||||
|
state = return ()
|
||||||
|
|
||||||
|
lit :: Integer -> ExprHelper
|
||||||
|
lit n = Lit $ int64Literal n
|
||||||
|
|
||||||
tests :: Test
|
tests :: Test
|
||||||
tests = TestList
|
tests = TestList
|
||||||
|
|
Loading…
Reference in New Issue
Block a user