diff --git a/scenes/cube/cube.sce b/scenes/cube/cube.sce index 0d9c958..99bf355 100644 --- a/scenes/cube/cube.sce +++ b/scenes/cube/cube.sce @@ -1,5 +1,5 @@ # camera: eye, center, up, fovy, width, height -camera 5 2 5 0 0 0 0 1 0 45 50 50 +camera 5 2 5 0 0 0 0 1 0 45 500 500 # recursion depth depth 1 diff --git a/src/Main.hs b/src/Main.hs index e8c58e6..4dd1a07 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -89,6 +89,7 @@ initializeMeshes p = traverse (initializeMeshes' p) let filename = p (B8.unpack f) in do d <- lift $ B.readFile filename + lift $ print filename mesh <- hoistEither $ parseMesh s m d return mesh initializeMeshes' _ a = return a @@ -119,4 +120,4 @@ main = do v3ToPixel :: Int -> Vector (V3 Word8) -> Int -> Int -> PixelRGB8 v3ToPixel w vec x y = PixelRGB8 r g b where - V3 r g b = vec ! (x*w+y) + V3 r g b = vec ! (y*w+x) diff --git a/src/Scene/Parser.hs b/src/Scene/Parser.hs index 2b15f8d..0dc858d 100644 --- a/src/Scene/Parser.hs +++ b/src/Scene/Parser.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE OverloadedStrings, BangPatterns #-} module Scene.Parser (parseScene, parseMesh) where import Control.Applicative @@ -201,12 +201,12 @@ parseMesh' s m = do skipSpace _ <- decimal --ignored in our OFF-Files skipSpace - verts <- D.trace (show v ++ " verts") $ A8.count v parseVector - faces <- D.trace (show f ++ " faces") $ A8.count f parseTriangle + ! verts <- D.trace (show v ++ " verts") $ A8.count v parseVector + ! faces <- D.trace (show f ++ " faces") $ A8.count f parseTriangle -- whatever should be parsed afterwards in OFF.. let - mv = IM.fromList $ P.zip [0..] verts - mf = IM.fromList $ P.zip [0..] faces + ! mv = IM.fromList $ P.zip [0..] verts + ! mf = IM.fromList $ P.zip [0..] faces mfn = normal mv <$> mf normal :: IntMap (V3 Float) -> V3 Int -> V3 Float normal verts (V3 v1 v2 v3) = normalize $ cross (verts ! v2 - verts ! v1) @@ -217,7 +217,7 @@ parseMesh' s m = do --TODO: weight sum with opening-angle! where fs = keys $ IM.filter (\(V3 a b c) -> P.any (==i) [a,b,c]) faces - bounds = f b + ! bounds = f b where f ((V3 a b c),(V3 x y z)) = BoundingBox { boundX = (a,x) @@ -227,7 +227,7 @@ parseMesh' s m = do b = F.foldl' minmax (V3 (-infty) (-infty) (-infty), V3 infty infty infty) mv minmax (maxin,minin) vec = (max <$> maxin <*> vec, min <$> minin <*> vec) infty = 9999999999999 :: Float - return $ D.trace ("verts: "++show verts++"\nfaces:"++show faces) (OpI Mesh + return $ OpI Mesh { meshShading = s , meshMaterial = m , meshVertices = mv @@ -235,7 +235,7 @@ parseMesh' s m = do , meshNormals = mn , meshFaceNormals = mfn , meshBounds = bounds - }) + } parseTriangle :: Parser (V3 Int) parseTriangle = do diff --git a/src/Scene/Renderer.hs b/src/Scene/Renderer.hs index ce1777b..bf9ac2d 100644 --- a/src/Scene/Renderer.hs +++ b/src/Scene/Renderer.hs @@ -39,8 +39,8 @@ render w h s index = V3 (ci cr) (ci cg) (ci cb) (V3 cr cg cb) = getColorFromRay (sceneRecursions s) ray s ray@(Ray co _) = camRay x y (sceneCamera s) - y = fromIntegral $ h - (index `mod` w) - 1 - x = fromIntegral $ index `div` w + y = fromIntegral $ h - (index `div` w) - 1 + x = fromIntegral $ index `mod` w ci = floor . (clamp 0 255) . (*255) --wrong format: --Ray (eye cam) $ rotCam x y w h (center cam - eye cam) (up cam) (fovy cam) @@ -152,7 +152,7 @@ intersect (Ray ro rd) m@(M (Mesh s _ v f vn fn b)) = case catMaybes . elems $ po hitsFlat verts norm f (V3 w1 w2 w3) = if det == 0 || t < epsilon || not det2 then Nothing - else D.trace (show t ++ "\t" ++ show pos) (Just $ Collision pos (norm IM.! f) t m) + else Just $ Collision pos (norm IM.! f) t m where ! det = dot rd' (norm IM.! f) --do we hit the plane rd' = normalize rd @@ -160,12 +160,12 @@ intersect (Ray ro rd) m@(M (Mesh s _ v f vn fn b)) = case catMaybes . elems $ po pos = ro + t *^ rd' --where do we hit the plane v1 = (verts IM.! w2) - (verts IM.! w1) v2 = (verts IM.! w3) - (verts IM.! w1) - det2m = fromJust $ inv33 $ V3 v1 v2 (norm IM.! f) -- base-change-matrix into triangle-coordinates + det2m = fromJust $ inv33 $ transpose $ V3 v1 v2 (norm IM.! f) -- base-change-matrix into triangle-coordinates det2v = det2m !* (pos - (verts IM.! w1)) -- fromJust is justified as we only make a base-change and all 3 -- vectors are linear independent. - det2 = det2v ^. _x > 0 && det2v ^. _y > 0 - && det2v ^. _x + det2v ^. _y < 1 + det2 = det2v ^. _x >= 0 && det2v ^. _y >= 0 + && det2v ^. _x + det2v ^. _y <= 1 --hitsPhong :: IntMap (V3 Float) -> IntMap (V3 Float) -> V3 Int -> Maybe Collision -- deprecated - wrong calculation of rays.