[additions to directory examples sydow@chalmers.se**20081111100156] { move ./examples/RandomGenerator.t ./lib/RandomGenerator.t hunk ./examples/HashTable.t 1 -module HashTable where - -struct Dictionary a b where - insert :: a -> b -> Action - lookup :: a -> Request (Maybe b) - -{- - -Wrong design; String should not have ONE hash function. -Better to give hash function as arg to hashDict. - -class Hashable a = - hash :: a -> Int -> Int - -- requirement: 0 <= hash a n < n - --} - -sequ [] = class result [] -sequ (x:xs) = class - y = new x - ys = new sequ xs - result (y:ys) - -hashDict hash dictT n = class - ds = new sequ (replicate n dictT) - - dict = array ds - - insert a b = action - (dict!(hash a n)).insert a b - - lookup a = request - (dict!(hash a n)).lookup a - - result Dictionary {..} - -{- -hashDict1 hash dictT n = do - ds <- sequence (replicate n dictT) - - dict = array ds - - insert a b = (dict!(hash a n)).insert a b - - lookup a = (dict!(hash a n)).lookup a - - result Dictionary {..} --} rmfile ./examples/HashTable.t hunk ./examples/MasterMind_descr.html 7 -MasterMind is a board game with two players; in this -case the user choses the secret and the program does the guessing. +MasterMind is a board game with two players; in this +case the user choses the secret and the program does the +guessing. Unfortunately, the board is not visualised. hunk ./examples/Primes.t 22 - tryFrom k = do + checkFrom k = do hunk ./examples/Primes.t 25 - count := count + 1 hunk ./examples/Primes.t 26 - if k < limit then tryFrom (k+1) + count := count + 1 + if k < limit then checkFrom (k+1) hunk ./examples/Primes.t 31 - tryFrom 3 - env.stdout.write (show (count+1)++"\n") + count := 1 + checkFrom 3 + env.stdout.write (show count++"\n") hunk ./examples/Primes_descr.html 63 +
+all elements are initialised to the value of the second argument). +
+procedure checkFrom. +
+ result action + primes!0 := 2 + count := 1 + forall k <- [3..limit] do + p <- isPrime k + if p then + count := count + 1 + primes!count := k + env.stdout.write (show (count+1)++"\n") + env.exit 0 ++The choice has negligible effect on efficiency (the tail recursive +checkFrom is transformed to iteration by the compiler), +but is merely a matter of taste. +
We end by noting two mathematical facts that the program relies +on: +
hunk ./examples/intro.html 44 -