module Camera where import Basics import Vectors import Objects import Data.Array import Trace import World cameraLooks vertical from to = Camera from n u v where n = normalized (to-from) u = normalized vertical * n v = u * n render :: World -> Camera -> Scal -> Scal -> Int -> Int -> Frame render world (Camera from n u v) fovx fovy width height = bitmap where bitmap = array ((0,0), (height-1, width-1)) $ do y <- [0..height-1] x <- [0..width-1] let fx = fromIntegral x fy = fromIntegral y let psi = fovx * (fx / floatWidth - 0.5) phi = fovy * (fy / floatHeight - 0.5) h = rotateMatrix psi v `mulVec` n direction = cos phi `scale` h + sin phi `scale` v return ((y, x), traceRay 0 world from (normalized direction) [] 1) floatWidth = fromIntegral width floatHeight = fromIntegral height