Difference between revisions of "Haskell Quiz/Bytecode Compiler"

From HaskellWiki
Jump to navigation Jump to search
(added link to Craft of FP solution)
(+cat)
 
(10 intermediate revisions by 5 users not shown)
Line 1: Line 1:
 
==The Problem==
 
==The Problem==
   
  +
Create a bytecode compiler as described on this ruby quiz page: http://www.rubyquiz.com/quiz100.html
Create a bytecode compiler as described on the test page. The Ruby solution involves being run by a interpreter written in Ruby - but that wont' work for the Haskell solution. Anyone want to write the interpreter in Haskell to test the solutions? :)
 
   
  +
Use this tester by Michael Sloan:
* http://www.rubyquiz.com/quiz100.html
 
   
  +
<haskell>
  +
fromBytes n xs =
  +
let int16 = (fromIntegral ((fromIntegral int32) :: Int16)) :: Int
  +
int32 = byte xs
  +
byte xs = foldl (\accum byte -> (accum `shiftL` 8) .|. (byte)) (head xs) (take (n - 1) (tail xs))
  +
in
  +
if n == 2
  +
then int16
  +
else int32
  +
  +
interpret [] [] = error "no result produced"
  +
interpret (s1:s) [] = s1
  +
interpret s (o:xs) | o < 10 = interpret ((fromBytes (o*2) xs):s) (drop (o*2) xs)
  +
interpret (s1:s2:s) (o:xs)
  +
| o == 16 = interpret (s2:s1:s) xs
  +
| otherwise = interpret (((case o of 10 -> (+); 11 -> (-); 12 -> (*); 13 -> (^); 14 -> div; 15 -> mod) s2 s1):s) xs
  +
  +
test :: (String -> [Int]) -> IO ()
  +
test f = assert "2+5" 7 >> assert "2-1" 1 >> assert "2*12" 24 >> assert "2^3" 8 >> assert "5/2" 2 >> assert "15%4" 3 >>
  +
assert "2+2+2" 6 >> assert "2^8/4" 64 >> assert "3*11%3" 0 >>
  +
assert "2*(3+4)" 14 >> assert "(3/3)+(8-2)" 7 >> assert "(1+3)/(2/2)*(10-8)" 8 >> assert "(10%3)*(2+2)" 4 >>
  +
assert "(10/(2+3)*4)" 8 >> assert "5+((5*4)%(2+1))" 7 >> assert "-(2-3-5)" 6 >> assert "-1*-1" (1) >>
  +
assert "1*-1" (-1) >> assert "1*-1" (-1) >> assert "-1*1" (-1) >>
  +
assert "-1" (-1)
  +
where assert str val = print ((if (interpret [] $ f str) == val then "Passed: " else "Failed: ") ++ str)</haskell>
  +
  +
Or you can use the original Ruby test suite via this Ruby wrapper for your Haskell solution:
  +
  +
<code>
  +
class Compiler
  +
def Compiler.compile(arith)
  +
result = `runghc compiler.hs #{arith}`
  +
eval (result.strip.delete '"')
  +
end
  +
end
  +
</code>
  +
 
==Solutions==
 
==Solutions==
  +
  +
* [[Haskell Quiz/Bytecode Compiler/Solution Michael Sloan|Michael Sloan]]
   
 
* [[Haskell Quiz/Bytecode Compiler/Solution Justin Bailey|Justin Bailey]]
 
* [[Haskell Quiz/Bytecode Compiler/Solution Justin Bailey|Justin Bailey]]
   
  +
* [[Haskell Quiz/Bytecode Compiler/Solution Pepe Iborra |Pepe Iborra]]
* A (non-monadic) solution to this is a [http://www.cs.kent.ac.uk/people/staff/sjt/craft2e/Code/Parsing/Parsing.hs case study] in Chapter 17 of [http://www.cs.kent.ac.uk/people/staff/sjt/craft2e The Craft of Functional Programming] by Simon Thompson.
 
  +
  +
* [[Haskell Quiz/Bytecode Compiler/Solution Lennart Kolmodin| Lennart Kolmodin]]
  +
 
* A (non-monadic) solution to the parsing and eval part of this quiz is a [http://www.cs.kent.ac.uk/people/staff/sjt/craft2e/Code/Parsing/Parsing.hs case study] in Chapter 17 of [http://www.cs.kent.ac.uk/people/staff/sjt/craft2e The Craft of Functional Programming] by Simon Thompson.
  +
  +
[[Category:Haskell Quiz|Bytecode Compiler]]

Latest revision as of 10:35, 13 January 2007

The Problem

Create a bytecode compiler as described on this ruby quiz page: http://www.rubyquiz.com/quiz100.html

Use this tester by Michael Sloan:

fromBytes n xs =
  let int16 = (fromIntegral ((fromIntegral int32) :: Int16)) :: Int
      int32 = byte xs
      byte xs = foldl (\accum byte -> (accum `shiftL` 8) .|. (byte)) (head xs) (take (n - 1) (tail xs))
  in
    if n == 2
    then int16 
    else int32 

interpret [] [] = error "no result produced"
interpret (s1:s) [] = s1
interpret s (o:xs) | o < 10 = interpret ((fromBytes (o*2) xs):s) (drop (o*2) xs)
interpret (s1:s2:s) (o:xs)
  | o == 16 = interpret (s2:s1:s) xs
  | otherwise = interpret (((case o of 10 -> (+); 11 -> (-); 12 -> (*); 13 -> (^); 14 -> div; 15 -> mod) s2 s1):s) xs

test :: (String -> [Int]) -> IO ()
test f = assert "2+5" 7 >> assert "2-1" 1 >> assert "2*12" 24 >> assert "2^3" 8 >> assert "5/2" 2 >> assert "15%4" 3 >>
         assert "2+2+2" 6 >> assert "2^8/4" 64 >> assert "3*11%3" 0 >>
         assert "2*(3+4)" 14 >> assert "(3/3)+(8-2)" 7 >> assert "(1+3)/(2/2)*(10-8)" 8 >> assert "(10%3)*(2+2)" 4 >>
         assert "(10/(2+3)*4)" 8 >> assert "5+((5*4)%(2+1))" 7 >> assert "-(2-3-5)" 6 >> assert "-1*-1" (1) >>
         assert "1*-1" (-1) >> assert "1*-1" (-1) >> assert "-1*1" (-1) >>
         assert "-1" (-1)
  where assert str val = print ((if (interpret [] $ f str) == val then "Passed: " else "Failed: ") ++ str)

Or you can use the original Ruby test suite via this Ruby wrapper for your Haskell solution:

class Compiler 
 def Compiler.compile(arith)
   result = `runghc compiler.hs #{arith}`
   eval (result.strip.delete '"')
 end
end

Solutions