first commit

This commit is contained in:
Jeena Paradies 2011-04-19 11:37:05 +02:00
commit 063194f8be
349 changed files with 36508 additions and 0 deletions

BIN
tester/.DS_Store vendored Normal file

Binary file not shown.

BIN
tester/Grade Executable file

Binary file not shown.

BIN
tester/Grade.hi Normal file

Binary file not shown.

125
tester/Grade.hs Normal file
View file

@ -0,0 +1,125 @@
module Grade where
import RunCommand
import KompTest
import Data.List
import Data.Maybe
import System.Directory
import System.Environment
import System.Exit
import System.IO
import System.Process
import System.FilePath
import System.Posix.Files
import Control.Exception
import Control.Monad
import System.Console.GetOpt
cmd c = do
putStrLn c
(out,err,code) <- runCommandStrWait c ""
putStrLn out
putStrLn err
makeAbsolute p = do
c <- getCurrentDirectory
return (c </> p)
maybeBuild _ [] = return ()
maybeBuild groupPath0 ((tarOpt,subm) : _) = do
cmd $ "tar -C "++groupPath0 ++" -"++ tarOpt++"xvf "++ show (groupPath0 </> subm)
cmd $ "make -C " ++ show (groupPath0 </> "src")
testAll compiler bs exts [testSuitePath00, groupPath0] = do
allFiles <- getDirectoryContents groupPath0
let submissions = [(opts, s) |
(opts, suff) <- [("z", ".tar.gz"), ("j", ".tar.bz2"), ("j", ".tar.bzip2"), ("", ".tar")],
s <- filter (suff `isSuffixOf`) allFiles]
maybeBuild groupPath0 submissions
let testSuitePath0 = groupPath0 </> "graderTestSuite"
cmd $ "rm -r " ++ testSuitePath0
cmd $ "cp -R " ++ testSuitePath00 </> "testsuite" ++ " " ++ testSuitePath0
let exePath0 = groupPath0 </> compiler
exePath <- makeAbsolute exePath0
groupPath <- makeAbsolute groupPath0
testSuitePath <- makeAbsolute testSuitePath0
curDir <- getCurrentDirectory
let exeDir = takeDirectory exePath
putStrLn $ "Running tests for " ++ exePath
let libpath = groupPath </> "lib"
let testProg = if null bs then Nothing
else case bs of
"JVM" : _ -> Just testJVM
"LLVM" : _ -> Just testLLVM
"x86" : _ -> Just testx86
b : _ -> error ("Unknown backend: " ++ b)
setCurrentDirectory exeDir
summary <- forM (testSpecs testProg exts libpath) $ \(points, name, tests) -> do
putStrLn $ name ++ "..."
results <- forM tests $ \(good, p, testFunction) -> do
testFiles <- getTestFilesForPath (testSuitePath </> p)
putStrLn $ p ++ "..."
rs <- testFunction exePath good testFiles
report p rs
return (p, rs)
putStrLn $ "Passed suites: " ++ (concat $ intersperse ", " $ [p | (p,rs) <- results, and rs])
let tally = concat (map snd results)
return (name, if and tally then points else (0 :: Int), tally)
setCurrentDirectory curDir
putStrLn $ "Summary:\n" ++ unlines (map summaryLine summary)
putStrLn $ "Credits total: " ++ show (sum [x | (_,x,_) <- summary])
padl n s = replicate (n - length s) ' ' ++ s
summaryLine (name, points, tests) =
padl 2 (show points) ++ " " ++ name ++ " " ++ "(" ++ show (length (filter id tests)) ++ "/" ++ show (length tests) ++ ")"
testSpecs testProg exts libpath =
(0, "Compiling core programs", [(True, "good",testCompilation), (False, "bad", testCompilation)]) :
map (\x -> (0,"Compiling extension " ++ x,[(True,"extensions/"++x,testCompilation)])) exts ++
case testProg of
Nothing -> []
Just backEnd ->
(0, "Running core programs", [(True, "good",backEnd libpath)]) :
map (\x -> (6,"Running extension " ++ x,[(True,"extensions/"++x,backEnd libpath)])) exts
testBack back cmd good fs = if good then test cmd fs back else return []
testJVM classpath = testBack (jvmBackend classpath)
testLLVM libpath = testBack (llvmBackend libpath)
testx86 libpath = testBack (x86Backend libpath)
data Flag = SearchScript String
| Extension String
| Back String
deriving (Eq,Ord)
flags =
[Option "s" ["search-compiler"] (ReqArg SearchScript "<compiler>") "search for the specified compiler",
Option "x" ["extension"] (ReqArg Extension "<extension>") "specify extensions to test",
Option "b" ["backend"] (ReqArg Back "<backend>") "specify backend"]
main = do
argv <- getArgs
case getOpt Permute flags argv of
(opts,args,[]) -> do
let searchList0 = [s | SearchScript s <- opts]
compiler = if null searchList0 then "jlc" else head searchList0
exts = [e | Extension e <- opts]
bs = [b | Back b <- opts]
testAll compiler bs exts args
(_,_,errs) -> do
hPutStrLn stderr (concat errs ++ usageInfo "" flags)
exitWith (ExitFailure 1)
where defaultSearchList = []

BIN
tester/Grade.o Normal file

Binary file not shown.

BIN
tester/KompTest.hi Normal file

Binary file not shown.

299
tester/KompTest.hs Normal file
View file

@ -0,0 +1,299 @@
-- {-# LANGUAGE NamedFieldPuns, ScopedTypeVariables #-}
-- GHC needs -threaded
module KompTest where
import Control.Monad
import Data.List
import Data.Maybe
import System
import System.Directory
import System.Environment
import System.Exit
import System.IO
import System.FilePath
import Data.Char
import RunCommand
data Backend = Backend {
name :: String,
objFile :: FilePath -> FilePath,
run :: String -> FilePath -> FilePath -> FilePath -> IO Bool
}
--
-- * Error reporting and output checking
--
reportErrorColor :: Color
-> String -- ^ command that failed
-> String -- ^ how it failed
-> FilePath -- ^ source file
-> String -- ^ given input
-> String -- ^ stdout output
-> String -- ^ stderr output
-> IO ()
reportErrorColor col c m f i o e =
do
putStrLn $ color col $ c ++ " failed: " ++ m
putStrLn $ "For source file " ++ f ++ ":"
-- prFile f
when (not (null i)) $ do
putStrLn "Given this input:"
putStrLn $ color blue $ i
when (not (null o)) $ do
putStrLn "It printed this to standard output:"
putStrLn $ color blue $ o
when (not (null e)) $ do
putStrLn "It printed this to standard error:"
putStrLn $ color blue $ e
reportError :: String -- ^ command that failed
-> String -- ^ how it failed
-> FilePath -- ^ source file
-> String -- ^ given input
-> String -- ^ stdout output
-> String -- ^ stderr output
-> IO ()
reportError = reportErrorColor red
data ErrorReport = ErrorReport {
repErr :: String,
repSeverity :: Severity,
repCmd :: String,
repStdIn :: String,
repStdOut :: String,
repStdErr :: String
}
data Severity = SWarning | SError | SInfo
defRep = ErrorReport {
repErr = "OK",
repSeverity = SInfo,
repCmd = "",
repStdIn = "",
repStdOut = "",
repStdErr = ""
}
rep ?! msg = rep { repErr = msg, repSeverity = SError }
rep ?? msg = rep { repErr = msg, repSeverity = SWarning }
report0 er = case repSeverity er of
SInfo -> return True
_ -> do reportError (repCmd er) (repErr er) (repCmd er) (repStdIn er) (repStdOut er) (repStdErr er)
return False
report1 Nothing = return True
report1 (Just rep) = report0 rep >> return False
prFile :: FilePath -> IO ()
prFile f = do
putStrLn $ "---------------- begin " ++ f ++ " ------------------"
s <- readFile f
putStrLn $ color green s
putStrLn $ "----------------- end " ++ f ++ " -------------------"
-- | Report how many tests passed.
report :: String -> [Bool] -> IO ()
report n rs =
do let (p,t) = (length (filter id rs), length rs)
putStrLn $ n ++ ": passed " ++ show p ++ " of " ++ show t ++ " tests"
--
-- * Generic running
--
runProg :: String -- ^ command
-> FilePath -- ^ source file (for error reporting)
-> FilePath -- ^ known input file
-> FilePath -- ^ known output file
-> IO Bool
runProg c f i o =
do
fe <- doesFileExist i
input <- if fe then readFile i else return ""
output <- readFile o
(out,err,s) <- runCommandStrWait c input
case s of
ExitFailure x -> do
reportError c ("with status " ++ show x) f input out err
return False
ExitSuccess ->
do
if not (null err) then
do
reportError c "Printed something to standard error" f input out err
return False
else if output /= out then
do
putStrLn $ color red $ c ++ " produced the wrong output:"
putStrLn $ "For source file " ++ f ++ ":"
prFile f
when (not (null input)) $ do
putStrLn "Given this input:"
putStrLn $ color blue $ input
putStrLn "It printed this to standard output:"
putStrLn $ color blue $ out
putStrLn "It should have printed this:"
putStrLn $ color blue $ output
return False
else do
putStrLn "output ok"
return True
testProg :: FilePath -- ^ executable
-> Backend
-> FilePath -- ^ test file
-> IO Bool
testProg cmd b f = do
putStr $ "Testing " ++ takeFileName f ++ ": "
hFlush stdout
let n = dropExtension f
o = n ++ ".output"
let c = objFile b f
ofe <- doesFileExist o
if ofe then run b c f (n ++ ".input") o
else do
putStrLn $ color blue $ "skipping: " ++ o ++ " not found"
return True
test :: FilePath -> [FilePath] -> Backend -> IO [Bool]
test c fs b =
do putStrLn $ color green $ "Backend: " ++ name b
mapM (testProg c b) fs
--
-- * Compilation
--
testCompilation :: FilePath -> Bool -> [FilePath] -> IO [Bool]
testCompilation c good fs =
do x <- doesFileExist c
forM fs $ \t -> report0 =<< do
if x then testCompilationProg c good t
else return $ defRep {repCmd = c} ?! ("compiler " ++ c ++ " not found")
testCompilationProg :: FilePath -> Bool -> FilePath -> IO ErrorReport
testCompilationProg path good f =
do let c = path ++ " " ++ f
putStrLn $ takeFileName path ++ " " ++ takeFileName f ++ "..."
(out,err,_) <- runCommandStrWait c ""
let rep = defRep {repCmd = f, repStdOut = out, repStdErr = err}
lns <- return $ lines err
return $ case filter (not . null) lns of
msgs | isOk msgs -> if good then rep else rep ?! "passed BAD program"
| isError msgs -> if good then rep ?! "failed OK program" else rep
_ -> rep ?! "invalid output"
where isOk (s:_) | "OK" `isSuffixOf` tu s || "OK" `isPrefixOf` tu s = True
isOk _ = False
isError (s:_) | "ERROR" `isSuffixOf` tu s || "ERROR" `isPrefixOf` tu s = True
isError ("Syntax Error, trying to recover and continue parse...":"ERROR":_) = True
isError _ = False
tu = map toUpper
--
-- * JVM back-end
--
objFileJVM f = dropExtension f
runJVM :: String -- libpath
-> String -- ^ Java class file
-> FilePath -- ^ source file (for error reporting)
-> FilePath -- ^ known input file
-> FilePath -- ^ known output file
-> IO Bool
runJVM libPath classFile src inp outp = do
let dir = takeDirectory classFile
d0 <- System.Directory.getCurrentDirectory
setCurrentDirectory dir
result <- runProg ("java -cp .:" ++ libPath ++ " " ++ takeBaseName classFile) src inp outp
setCurrentDirectory d0
return result
jvmBackend libpath = Backend { name = "JVM", objFile = objFileJVM,
run = runJVM libpath }
--
-- * LLVM back-end
--
objFileLLVM f = dropExtension f <.> "bc"
runLLVM :: String -- libpath
-> String -- ^ LLVM bitcode file
-> FilePath -- ^ source file (for error reporting)
-> FilePath -- ^ known input file
-> FilePath -- ^ known output file
-> IO Bool
runLLVM libPath bcFile src inp outp = do
let dir = takeDirectory bcFile
d0 <- System.Directory.getCurrentDirectory
setCurrentDirectory dir
system ("rm a.out")
system ("llvm-ld " ++ bcFile ++ " " ++ libPath ++"/runtime.bc")
result <- runProg "./a.out" src inp outp
setCurrentDirectory d0
return result
llvmBackend libpath = Backend { name = "LLVM", objFile = objFileLLVM,
run = runLLVM libpath }
--
-- * x86 back-end
--
objFilex86 f = dropExtension f <.> "o"
runx86 libPath oFile src inp outp = do
let dir = takeDirectory oFile
d0 <- System.Directory.getCurrentDirectory
setCurrentDirectory dir
system ("rm a.out")
system ("gcc -m32 " ++ oFile ++ " " ++ libPath ++"/runtime.o")
result <- runProg "./a.out" src inp outp
setCurrentDirectory d0
return result
x86Backend libpath = Backend { name = "x86", objFile = objFilex86,
run = runx86 libpath }
getTestFilesForPath :: String -> IO [String]
getTestFilesForPath f = do
d <- doesDirectoryExist f
if d then jlFiles f else do
d' <- doesFileExist f
if d' then return [f]
else error $ "Not a file or directory: " ++ f
-- | Get all .jl files in the given directory.
jlFiles :: FilePath -> IO [FilePath]
jlFiles d = do fs <- getDirectoryContents d
return $ map (d </>) $ sort $ filter ((".jl" ==) . takeExtension) fs
--
-- * Terminal output colors
--
type Color = Int
color :: Color -> String -> String
color c s = fgcol c ++ s ++ normal
highlight = "\ESC[7m"
bold = "\ESC[1m"
underline = "\ESC[4m"
normal = "\ESC[0m"
fgcol col = "\ESC[0" ++ show (30+col) ++ "m"
bgcol col = "\ESC[0" ++ show (40+col) ++ "m"
red, green, blue :: Color
red = 1
green = 2
blue = 4

BIN
tester/KompTest.o Normal file

Binary file not shown.

9
tester/Makefile Normal file
View file

@ -0,0 +1,9 @@
all: Grade
tests.tgz:
tar -czvf $@ `find examples -name "*.jl" -or -name "*.output"`
%: %.hs *.hs
ghc -main-is $* -threaded --make $<
clean:
rm *.{hi,o} Grade

82
tester/README.txt Normal file
View file

@ -0,0 +1,82 @@
The Javalette test programs are in (subdirectories of) directory examples.
This directory contains a test driver (Grade.hs, RunCommand.hs and KompTest.hs) that
can be used to run the tests for your project.
Prerequisites
----------
We expect that you are using a Unix-like system (including Linux and
Mac OS X) and have the Haskell compiler ghc in your path.
You will then just have to do
make
in this directory to compile the test program. This gives the executable program
Grade in this same directory.
Running the tests
-----------------
Assume that your submission directory is dir and that your
compiler is called jlc. Assume also that dir/lib
contains the runtime support file (Runtime.class for submission A,
runtime.bc and/or runtime.o for submission B). For submission A,
also jasmin.jar should be in dir/lib.
The test driver takes a number of options and two directories as
command line arguments. The possible options are
-s <name> The name of your compiler (in directory dir) is <name> (default is "jlc")
-b JVM Target files are JVM .class files
-b LLVM Target files are LLVM .bc files
-b x86 Target files are x86 .o files
-x <extension> Implemented extensions (only for submission B).
The first of the two path arguments specifies where to find the
directory examples which contains the testsuite (it is in this
directory). The second specifies your submission directory.
Thus, from this directory you may run
./Grade . dir
to compile all the basic javalette programs. The test driver will not
attempt to run the good programs, so you may do the above
already when you have the parser working, and then when you
have the typechecker working.
To also run the good programs, you must specify the backend as
indicated above, i.e. for submission A
./Grade -b JVM . dir
The test driver will report its activities in compiling the test
programs and running the good ones. If your compiler is correct,
output will end as follows:
Summary:
0 Compiling core programs (48/48)
0 Running core programs (22/22)
Credits total: 0
All 48 test programs were compiled and gave correct indication OK or
ERROR to stderr. The 22 correct programs were run and gave correct output.
Preparing a submission
-------------------
Your submission must be structured as specified in Appendix A of the
project description. We suggest that, after having prepared your tar
ball, you place it in an empty directory dir1 and run
./Grade -b JVM . dir1
from this directory. The grading program, when it finds a tar ball in
the submission directory, starts by extracting and building your
compiler, before running the test suite. This is how we test your
submission, so you can check whether building and testing succeeds
before you submit. Note that if the tester does not succeed on your
submission, we will reject it without further checks, and you will
anyhow have to redo the submission according to specification.

BIN
tester/RunCommand.hi Normal file

Binary file not shown.

70
tester/RunCommand.hs Normal file
View file

@ -0,0 +1,70 @@
module RunCommand (runCommandStrWait) where
import System.Process
import System.Exit
import System.IO
import Control.Concurrent
import Control.Concurrent.Chan
import Data.Either
type Pipe = Chan (Either Char ())
pipeGetContents :: Pipe -> IO String
pipeGetContents p =
do
s <- getChanContents p
return $ map fromLeft $ takeWhile isLeft s
pipeWrite :: Pipe -> String -> IO ()
pipeWrite p s = writeList2Chan p (map Left s)
-- close the pipe for writing
pipeClose :: Pipe -> IO ()
pipeClose p = writeChan p (Right ())
--
-- * Either utilities
--
isLeft :: Either a b -> Bool
isLeft = either (const True) (const False)
fromLeft :: Either a b -> a
fromLeft = either id (error "fromLeft: Right")
--
-- * Various versions of runCommand
--
runCommandChan :: String -- ^ command
-> IO (Pipe,Pipe,Pipe,ProcessHandle) -- ^ stdin, stdout, stderr, process
runCommandChan c =
do
inC <- newChan
outC <- newChan
errC <- newChan
(pin,pout,perr,p) <- runInteractiveCommand c
forkIO (pipeGetContents inC >>= hPutStr pin >> hClose pin)
forkIO (hGetContents pout >>= pipeWrite outC >> pipeClose outC)
forkIO (hGetContents perr >>= pipeWrite errC >> pipeClose errC)
return (inC,outC,errC,p)
runCommandStr :: String -- ^ command
-> String -- ^ stdin data
-> IO (String,String,ProcessHandle) -- ^ stdout, stderr, process
runCommandStr c inStr =
do
(inC,outC,errC,p) <- runCommandChan c
forkIO (pipeWrite inC inStr >> pipeClose inC)
out <- pipeGetContents outC
err <- pipeGetContents errC
return (out,err,p)
runCommandStrWait :: String -- ^ command
-> String -- ^ stdin data
-> IO (String,String,ExitCode) -- ^ stdout, stderr, process exit status
runCommandStrWait c inStr =
do
(out,err,p) <- runCommandStr c inStr
s <- waitForProcess p
return (out,err,s)

BIN
tester/RunCommand.o Normal file

Binary file not shown.

View file

@ -0,0 +1 @@
/*

View file

@ -0,0 +1 @@
a

View file

@ -0,0 +1,3 @@
int f(int x, int x) {
return x;
}

View file

@ -0,0 +1,4 @@
int main)( {
return 0;
return 1;
}

View file

@ -0,0 +1 @@
foo() {}

View file

@ -0,0 +1,4 @@
int main() {
x = 14;
return 0 ;
}

View file

@ -0,0 +1,5 @@
int main() {
int x;
int x;
return 0 ;
}

View file

@ -0,0 +1,4 @@
int main() {
if (false)
return 0;
}

View file

@ -0,0 +1,5 @@
int main() {
int x;
x = true;
return 1;
}

View file

@ -0,0 +1,6 @@
int main() {
if (true)
return;
;
return 1;
}

View file

@ -0,0 +1,3 @@
int main() {
return true;
}

View file

@ -0,0 +1,6 @@
int main() {
int i = foo(true);
return 0 ;
}
int foo(boolean b) { b = true; }

View file

@ -0,0 +1,5 @@
int main() {
double x ;
x = 2 * 3.14 ;
return 0 ;
}

View file

@ -0,0 +1,6 @@
// passing doubles to printInt().
int main() {
printInt(1.0);
return 0 ;
}

View file

@ -0,0 +1,6 @@
// passing integers to printDouble().
int main() {
printDouble(1);
return 0 ;
}

View file

@ -0,0 +1,11 @@
// 0 instead of 1 argument
int main() {
int x = foo();
return 0 ;
}
int foo(int y) {
return y;
}

View file

@ -0,0 +1,11 @@
// 1 instead of 2 arguments
int main() {
int x = foo(1);
return 0 ;
}
int foo(int y,int z) {
return y;
}

View file

@ -0,0 +1,11 @@
// 2 instead of 1 arguments
int main() {
int x = foo(1,2);
return 0 ;
}
int foo(int y) {
return y;
}

View file

@ -0,0 +1,8 @@
// Compare double with boolean.
int main() {
if (2.0 == true) {
printString("foo");
}
return 0 ;
}

View file

@ -0,0 +1,6 @@
/* Testing that main must return. */
/* All functions should return a value of their value type. This is not a valid Javalette program: */
int main() {
}

View file

@ -0,0 +1,6 @@
// Assigning double to int variable.
int main () {
int x = 1.0;
return 0 ;
}

View file

@ -0,0 +1,6 @@
// Assigning int to double variable.
int main () {
double x = 1;
return 0 ;
}

View file

@ -0,0 +1,4 @@
int main() {
if (false)
return 0;
}

View file

@ -0,0 +1,8 @@
int main() {
return f(3);
}
int f(int x) {
if (x<0)
return x;
}

View file

@ -0,0 +1,7 @@
// Assigning double to int variable.
int main () {
int x;
x = 1.0;
return 0 ;
}

View file

@ -0,0 +1,7 @@
// Assigning int to double variable.
int main () {
double x;
x = 1;
return 0 ;
}

View file

@ -0,0 +1,16 @@
int main() {
int[] a = new int[10];
int j=0;
while (j<a.length) {
a[j] = j;
j++;
}
for (int x : a)
printInt(x);
int x = 45;
printInt(x);
return 0;
}

View file

@ -0,0 +1,11 @@
0
1
2
3
4
5
6
7
8
9
45

View file

@ -0,0 +1,46 @@
int [] doubleArray (int [] a){
int [] res = new int [a . length];
int i = 0 ;
for (int n : a){
res [i] = 2 * n ;
i ++ ;
}
return res ;
}
void shiftLeft (int [] a){
int x = a [0];
int i = 0 ;
while (i < a.length - 1){
a [i] = a [i + 1];
i ++ ;
}
a[a.length - 1]= x ;
return;
}
int scalProd(int[] a, int[] b) {
int res = 0;
int i = 0;
while (i < a.length) {
res = res + a[i] * b[i];
i++;
}
return res;
}
int main () {
int [] a = new int [5];
int i = 0 ;
while (i < a.length){
a [i]= i ;
i ++ ;
}
shiftLeft (a);
int [] b = doubleArray (a);
for (int x : a)printInt (x);
for (int x : b)printInt (x);
printInt(scalProd(a,b));
return 0 ;
}

View file

@ -0,0 +1,11 @@
1
2
3
4
0
2
4
6
8
0
60

View file

@ -0,0 +1,35 @@
int main() {
double[] vector = new double[4];
double[][] matrix = new double[3][4];
int i=0;
while (i<matrix.length) {
int j=0;
while (j<matrix[0].length) {
matrix[i][j] = 5.0;
j++;
}
i++;
}
i=0;
while (i<vector.length-1) {
vector[i] = 3.0;
i++;
}
matrix[0] = vector;
int j = 0;
while (j<vector.length) {
matrix[1][j] = vector[j]+1.0;
j++;
}
for (double[] x : matrix)
for (double y : x)
printDouble(y);
return 0 ;
}

View file

@ -0,0 +1,12 @@
3.0
3.0
3.0
0.0
4.0
4.0
4.0
1.0
5.0
5.0
5.0
5.0

View file

@ -0,0 +1,19 @@
int main () {
Counter c;
c = new Counter;
c.incr();
c.incr();
c.incr();
int x = c.value();
printInt(x);
return 0;
}
class Counter {
int val;
void incr () {val++; return;}
int value () {return val;}
}

View file

@ -0,0 +1 @@
3

View file

@ -0,0 +1,50 @@
class Node {
int elem;
Node next;
void setElem(int c) { elem = c; }
void setNext(Node n) { next = n; }
int getElem() { return elem; }
Node getNext() { return next; }
}
class Stack {
Node head;
void push(int c) {
Node newHead = new Node;
newHead.setElem(c);
newHead.setNext(head);
head = newHead;
}
boolean isEmpty() {
return head==(Node)null;
}
int top() {
return head.getElem();
}
void pop() {
head = head.getNext();
}
}
int main() {
Stack s = new Stack;
int i= 0;
while (i<10) {
s.push(i);
i++;
}
while (!s.isEmpty()) {
printInt(s.top());
s.pop();
}
return 0;
}

View file

@ -0,0 +1,10 @@
9
8
7
6
5
4
3
2
1
0

View file

@ -0,0 +1,62 @@
class Point2 {
int x;
int y;
void move (int dx, int dy) {
x = x + dx;
y = y + dy;
}
int getX () { return x; }
int getY () { return y; }
}
class Point3 extends Point2 {
int z;
void moveZ (int dz) {
z = z + dz;
}
int getZ () { return z; }
}
class Point4 extends Point3 {
int w;
void moveW (int dw) {
w = w + dw;
}
int getW () { return w; }
}
int main () {
Point2 p = new Point3;
Point3 q = new Point3;
Point4 r = new Point4;
q.move(2,4);
q.moveZ(7);
p = q;
p.move(3,5);
r.move(1,3);
r.moveZ(6);
r.moveW(2);
printInt(p.getX());
printInt(p.getY());
printInt(q.getZ());
printInt(r.getW());
return 0;
}

View file

@ -0,0 +1,4 @@
5
9
7
2

View file

@ -0,0 +1,61 @@
class Node {
int elem;
Node next;
void setElem (int e) { elem = e; }
void setNext (Node n) { next = n; }
int getElem () { return elem; }
Node getNext () { return next; }
}
class IntQueue {
Node front;
Node rear;
boolean isEmpty () { return front == (Node)null; }
void insert (int x) {
Node last = new Node;
last.setElem(x);
if (self.isEmpty())
front = last;
else
rear.setNext(last);
rear = last;
}
int first () { return front.getElem(); }
void rmFirst () {
front = front.getNext();
}
int size () {
Node n = front;
int res = 0;
while (n != (Node)null) {
n = n.getNext();
res++;
}
return res;
}
}
int f (int x) {
return x*x + 3;
}
int main () {
IntQueue q = new IntQueue;
q.insert(f(3));
q.insert(5);
q.insert(7);
printInt(q.first());
q.rmFirst();
printInt(q.size());
return 0;
}

View file

@ -0,0 +1,2 @@
12
2

View file

@ -0,0 +1,82 @@
class Node {
Shape elem;
Node next;
void setElem(Shape c) { elem = c; }
void setNext(Node n) { next = n; }
Shape getElem() { return elem; }
Node getNext() { return next; }
}
class Stack {
Node head;
void push(Shape c) {
Node newHead = new Node;
newHead.setElem(c);
newHead.setNext(head);
head = newHead;
}
boolean isEmpty() {
return head==(Node)null;
}
Shape top() {
return head.getElem();
}
void pop() {
head = head.getNext();
}
}
class Shape {
void tell () {
printString("I'm a shape");
}
void tellAgain() {
printString("I'm just a shape");
}
}
class Rectangle extends Shape {
void tellAgain() {
printString("I'm really a rectangle");
}
}
class Circle extends Shape {
void tellAgain() {
printString("I'm really a circle");
}
}
class Square extends Rectangle {
void tellAgain() {
printString("I'm really a square");
}
}
int main() {
Stack stk = new Stack;
Shape s = new Shape;
stk.push(s);
s = new Rectangle;
stk.push(s);
s = new Square;
stk.push(s);
s = new Circle;
stk.push(s);
while (!stk.isEmpty()) {
s = stk.top();
s.tell();
s.tellAgain();
stk.pop();
}
return 0;
}

View file

@ -0,0 +1,8 @@
I'm a shape
I'm really a circle
I'm a shape
I'm really a square
I'm a shape
I'm really a rectangle
I'm a shape
I'm just a shape

View file

@ -0,0 +1,48 @@
typedef struct Node *list;
struct Node {
int elem;
list next;
};
int main() {
printInt(length(fromTo(1,50)));
printInt(length2(fromTo(1,100)));
return 0;
}
int head (list xs) {
return xs -> elem;
}
list cons (int x, list xs) {
list n;
n = new Node;
n->elem = x;
n->next = xs;
return n;
}
int length (list xs) {
if (xs==(list)null)
return 0;
else
return 1 + length (xs->next);
}
list fromTo (int m, int n) {
if (m>n)
return (list)null;
else
return cons (m,fromTo (m+1,n));
}
int length2 (list xs) {
int res = 0;
while (xs != (list)null) {
res++;
xs = xs->next;
}
return res;
}

View file

@ -0,0 +1,2 @@
50
100

View file

@ -0,0 +1,78 @@
struct Node {
tree left;
int val;
tree right;
};
typedef struct Node *tree;
struct Header {
tree elems;
};
typedef struct Header *intset;
void insert (int x, intset s) {
s->elems = insertTree(x,s->elems);
return;
}
boolean isElem(int x, intset s) {
return isElemTree (x,s->elems);
}
tree insertTree(int x,tree t) {
if (t==(tree)null) {
tree n1;
n1 = new Node;
n1->left = (tree)null;
n1->val = x;
n1->right = (tree)null;
return n1;
}
else if (x < t->val)
t->left = insertTree (x,t->left);
else if (x > t->val)
t->right = insertTree (x,t->right);
return t;
}
boolean isElemTree(int x,tree t) {
if (t==(tree)null)
return false;
else if (x==t->val)
return true;
else if (x < t->val)
return isElemTree (x, t->left);
else
return isElemTree(x, t->right);
}
void printElem(int n, intset s) {
if (isElem(n,s))
printString("Elem!");
else
printString("Not elem!");
return;
}
int main () {
intset s;
s = new Header;
s->elems = (tree)null;
int x = 3;
int i = 0;
while (i<100) {
x = (x * 37) % 100;
i++;
insert(x, s);
}
printElem(23,s);
printElem(24,s);
printElem(25,s);
return 0;
}

View file

@ -0,0 +1,3 @@
Elem!
Not elem!
Not elem!

View file

@ -0,0 +1,73 @@
int main() {
printInt(fac(10));
printInt(rfac(10));
printInt(mfac(10));
printInt(ifac(10));
double r ; // just to test blocks
{
int n = 10;
int r = 1;
while (n>0) {
r = r * n;
n--;
}
printInt(r);
}
printDouble(dfac(10.0));
printString ("hello */");
printString ("/* world") ;
return 0 ;
}
int fac(int a) {
int r;
int n;
r = 1;
n = a;
while (n > 0) {
r = r * n;
n = n - 1;
}
return r;
}
int rfac(int n) {
if (n == 0)
return 1;
else
return n * rfac(n-1);
}
int mfac(int n) {
if (n == 0)
return 1;
else
return n * nfac(n-1);
}
int nfac(int n) {
if (n != 0)
return mfac(n-1) * n;
else
return 1;
}
double dfac(double n) {
if (n == 0.0)
return 1.0;
else
return n * dfac(n-1.0);
}
int ifac(int n) { return ifac2f(1,n); }
int ifac2f(int l, int h) {
if (l == h)
return l;
if (l > h)
return 1;
int m;
m = (l + h) / 2;
return ifac2f(l,m) * ifac2f(m+1,h);
}

View file

@ -0,0 +1,8 @@
3628800
3628800
3628800
3628800
3628800
3628800.0
hello */
/* world

View file

@ -0,0 +1,12 @@
/* void expression as statement */
int main() {
foo();
return 0 ;
}
void foo() {
printString("foo");
return;
}

View file

@ -0,0 +1 @@
foo

View file

@ -0,0 +1,23 @@
// Testing the return checker
int f () {
if (true)
return 0;
else
{}
}
int g () {
if (false)
{}
else
return 0;
}
void p () {}
int main() {
p();
return 0;
}

View file

View file

@ -0,0 +1,7 @@
/* allow comparing booleans. */
int main() {
if (true == true) { printInt(42); }
return 0 ;
}

View file

@ -0,0 +1 @@
42

View file

@ -0,0 +1,14 @@
/* usage of variable initialized in both branches. */
int main () {
int x;
int y = 56;
if (y + 45 <= 2) {
x = 1;
} else {
x = 2;
}
printInt(x);
return 0 ;
}

View file

@ -0,0 +1 @@
2

View file

@ -0,0 +1,11 @@
// Declaration of multiple variables of the same type in one statement:
int main () {
int x, y;
x = 45;
y = -36;
printInt(x);
printInt(y);
return 0 ;
}

View file

@ -0,0 +1,2 @@
45
-36

View file

@ -0,0 +1,8 @@
// declaration and initialization in same statement
int main() {
int x = 7;
printInt(x);
return 0 ;
}

View file

@ -0,0 +1 @@
7

View file

@ -0,0 +1,11 @@
// multiple variables of the same type declared
// and possibly initialized in the same statement
int main() {
int x, y = 7;
x = -1234234;
printInt(x);
printInt(y);
return 0 ;
}

View file

@ -0,0 +1,2 @@
-1234234
7

View file

@ -0,0 +1,13 @@
// Calling functions which take zero parameters
int main() {
int x = foo();
printInt(x);
return 0 ;
}
int foo() {
return 10;
}

View file

@ -0,0 +1 @@
10

View file

@ -0,0 +1,19 @@
// count function parameters as initialized
int main() {
printInt(fac(5));
return 0 ;
}
int fac (int a) {
int r;
int n;
r = 1;
n = a;
while (n > 0)
{
r = r * n;
n = n - 1;
}
return r;
}

View file

@ -0,0 +1 @@
120

View file

@ -0,0 +1,6 @@
/* Test pushing -1. */
int main() {
printInt(-1);
return 0 ;
}

View file

@ -0,0 +1 @@
-1

View file

@ -0,0 +1,26 @@
/* Test arithmetic and comparisons. */
int main() {
int x = 56;
int y = -23;
printInt(x+y);
printInt(x-y);
printInt(x*y);
printInt(45/2);
printInt(78%3);
double z = -9.3;
double w = 5.1;
printBool(z+w > z-w);
printBool(z/w <= z*w);
return 0 ;
}
void printBool(boolean b) {
if (b) {
printString("true");
return;
} else {
printString("false");
return;
}
}

View file

@ -0,0 +1,7 @@
33
79
-1288
22
0
true
false

View file

@ -0,0 +1,33 @@
/* Test boolean operators. */
int main() {
printString("&&");
printBool(test(-1) && test(0));
printBool(test(-2) && test(1));
printBool(test(3) && test(-5));
printBool(test(234234) && test(21321));
printString("||");
printBool(test(-1) || test(0));
printBool(test(-2) || test(1));
printBool(test(3) || test(-5));
printBool(test(234234) || test(21321));
printString("!");
printBool(true);
printBool(false);
return 0 ;
}
void printBool(boolean b) {
if (!b) {
printString("false");
} else {
printString("true");
}
return;
}
boolean test(int i) {
printInt(i);
return i > 0;
}

View file

@ -0,0 +1,25 @@
&&
-1
false
-2
false
3
-5
false
234234
21321
true
||
-1
0
false
-2
1
true
3
true
234234
true
!
true
false

View file

@ -0,0 +1,17 @@
/* Fibonacci. */
int main () {
int lo,hi,mx ;
lo = 1 ;
hi = lo ;
mx = 5000000 ;
printInt(lo) ;
while (hi < mx) {
printInt(hi) ;
hi = lo + hi ;
lo = hi - lo ;
}
return 0 ;
}

View file

@ -0,0 +1,33 @@
1
1
2
3
5
8
13
21
34
55
89
144
233
377
610
987
1597
2584
4181
6765
10946
17711
28657
46368
75025
121393
196418
317811
514229
832040
1346269
2178309
3524578

View file

@ -0,0 +1,16 @@
/* parity of positive integers by recursion */
int main () {
printInt(ev(17)) ;
return 0 ;
}
int ev (int y) {
if (y > 0)
return ev (y-2) ;
else
if (y < 0)
return 0 ;
else
return 1 ;
}

View file

@ -0,0 +1 @@
0

View file

@ -0,0 +1,15 @@
/* parity of positive integers by loop */
int main () {
int y = 17;
while (y > 0)
y = y - 2;
if (y < 0) {
printInt(0);
return 0 ;
}
else {
printInt(1);
return 0 ;
}
}

View file

@ -0,0 +1 @@
0

View file

@ -0,0 +1,40 @@
/* Test boolean operators */
int main () {
int x = 4;
if (3 <= x && 4 != 2 && true) {
printBool(true);
} else {
printString("apa");
}
printBool(true == true || dontCallMe(1));
printBool(4.0 < -50.0 && dontCallMe(2));
printBool(4 == x && true == !false && true);
printBool(implies(false,false));
printBool(implies(false,true));
printBool(implies(true,false));
printBool(implies(true,true));
return 0 ;
}
boolean dontCallMe(int x) {
printInt(x);
return true;
}
void printBool(boolean b) {
if (b) {
printString("true");
} else {
printString("false");
}
return;
}
boolean implies(boolean x, boolean y) {
return !x || x == y;
}

View file

@ -0,0 +1,8 @@
true
true
false
true
true
true
false
true

View file

@ -0,0 +1,2 @@
-5673
42.5

View file

@ -0,0 +1,15 @@
/* test input */
int main() {
int x = readInt();
double y = readDouble();
printInt(x-5);
if (y > 42.0 || y < 43.0)
printString("yay!");
else
printString("nay!");
return 0 ;
}

View file

@ -0,0 +1,2 @@
-5678
yay!

Some files were not shown because too many files have changed in this diff Show more