source: sizechecking/branches/macs/tests/SizeTest.hs @ 24

Last change on this file since 24 was 24, checked in by gobi, 11 years ago

expressions

File size: 1.1 KB
RevLine 
[22]1{-# LANGUAGE NoMonomorphismRestriction #-}
2
3module Tests.SizeTest where
4
5import Size
6import Lambda
7import Ops
[24]8import Prelude ( ($), Int, (==), return, sequence, (>>=), and, (.), IO, Bool, String, const )
9import qualified Control.Monad
[22]10
11testEmpty1 :: (Size l) => l [Unsized]
[24]12testEmpty1 = list (lit 0) (lam $ const unsized)
[22]13
14testNil :: (Size l) => l [a]
[24]15testNil = list (lit 0) (lam $ const bottom)
[22]16
17testHead :: (Size l) => l ([a] -> a)
[24]18testHead = slam $ \s f -> f `app` (s - lit 1)
[22]19
20testTail :: (Size l) => l ([a] -> [a])
[24]21testTail = slam $ \s f -> list (s - lit 1) f
[22]22
23testCons :: Size l => l (a -> [a] -> [a])
24testCons = lam $ \x -> slam $ \s f ->
[24]25    list (s + lit 1) $ shift f s (lam $ const x)
26
27checkAst :: S a -> String -> IO Bool
28checkAst exp repr = ast exp >>= (\t -> return $ t "" == repr)
29
30tests :: [IO Bool]
31tests = [
32      checkAst testEmpty1 "List 0 (λa.U)"
33    , checkAst testNil "List 0 (λa.┮)"
34    , checkAst testHead "Λa,b.b (a-1)"
35    , checkAst testTail "Λa,b.List (a-1) b"
36    , checkAst testCons "λa.Λb,c.List (b+1) (Shift c b (λd.a))"
37    ]
38
39runTests :: IO Bool
40runTests = Control.Monad.liftM and $ sequence tests
Note: See TracBrowser for help on using the repository browser.