cube draws. fixed double transpose-error.
This commit is contained in:
parent
563ea7c26d
commit
25196135b7
@ -1,5 +1,5 @@
|
|||||||
# camera: eye, center, up, fovy, width, height
|
# 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
|
# recursion depth
|
||||||
depth 1
|
depth 1
|
||||||
|
@ -89,6 +89,7 @@ initializeMeshes p = traverse (initializeMeshes' p)
|
|||||||
let filename = p </> (B8.unpack f) in
|
let filename = p </> (B8.unpack f) in
|
||||||
do
|
do
|
||||||
d <- lift $ B.readFile filename
|
d <- lift $ B.readFile filename
|
||||||
|
lift $ print filename
|
||||||
mesh <- hoistEither $ parseMesh s m d
|
mesh <- hoistEither $ parseMesh s m d
|
||||||
return mesh
|
return mesh
|
||||||
initializeMeshes' _ a = return a
|
initializeMeshes' _ a = return a
|
||||||
@ -119,4 +120,4 @@ main = do
|
|||||||
v3ToPixel :: Int -> Vector (V3 Word8) -> Int -> Int -> PixelRGB8
|
v3ToPixel :: Int -> Vector (V3 Word8) -> Int -> Int -> PixelRGB8
|
||||||
v3ToPixel w vec x y = PixelRGB8 r g b
|
v3ToPixel w vec x y = PixelRGB8 r g b
|
||||||
where
|
where
|
||||||
V3 r g b = vec ! (x*w+y)
|
V3 r g b = vec ! (y*w+x)
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings, BangPatterns #-}
|
||||||
module Scene.Parser (parseScene, parseMesh) where
|
module Scene.Parser (parseScene, parseMesh) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
@ -201,12 +201,12 @@ parseMesh' s m = do
|
|||||||
skipSpace
|
skipSpace
|
||||||
_ <- decimal --ignored in our OFF-Files
|
_ <- decimal --ignored in our OFF-Files
|
||||||
skipSpace
|
skipSpace
|
||||||
verts <- D.trace (show v ++ " verts") $ A8.count v parseVector
|
! verts <- D.trace (show v ++ " verts") $ A8.count v parseVector
|
||||||
faces <- D.trace (show f ++ " faces") $ A8.count f parseTriangle
|
! faces <- D.trace (show f ++ " faces") $ A8.count f parseTriangle
|
||||||
-- whatever should be parsed afterwards in OFF..
|
-- whatever should be parsed afterwards in OFF..
|
||||||
let
|
let
|
||||||
mv = IM.fromList $ P.zip [0..] verts
|
! mv = IM.fromList $ P.zip [0..] verts
|
||||||
mf = IM.fromList $ P.zip [0..] faces
|
! mf = IM.fromList $ P.zip [0..] faces
|
||||||
mfn = normal mv <$> mf
|
mfn = normal mv <$> mf
|
||||||
normal :: IntMap (V3 Float) -> V3 Int -> V3 Float
|
normal :: IntMap (V3 Float) -> V3 Int -> V3 Float
|
||||||
normal verts (V3 v1 v2 v3) = normalize $ cross (verts ! v2 - verts ! v1)
|
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!
|
--TODO: weight sum with opening-angle!
|
||||||
where
|
where
|
||||||
fs = keys $ IM.filter (\(V3 a b c) -> P.any (==i) [a,b,c]) faces
|
fs = keys $ IM.filter (\(V3 a b c) -> P.any (==i) [a,b,c]) faces
|
||||||
bounds = f b
|
! bounds = f b
|
||||||
where
|
where
|
||||||
f ((V3 a b c),(V3 x y z)) = BoundingBox
|
f ((V3 a b c),(V3 x y z)) = BoundingBox
|
||||||
{ boundX = (a,x)
|
{ boundX = (a,x)
|
||||||
@ -227,7 +227,7 @@ parseMesh' s m = do
|
|||||||
b = F.foldl' minmax (V3 (-infty) (-infty) (-infty), V3 infty infty infty) mv
|
b = F.foldl' minmax (V3 (-infty) (-infty) (-infty), V3 infty infty infty) mv
|
||||||
minmax (maxin,minin) vec = (max <$> maxin <*> vec, min <$> minin <*> vec)
|
minmax (maxin,minin) vec = (max <$> maxin <*> vec, min <$> minin <*> vec)
|
||||||
infty = 9999999999999 :: Float
|
infty = 9999999999999 :: Float
|
||||||
return $ D.trace ("verts: "++show verts++"\nfaces:"++show faces) (OpI Mesh
|
return $ OpI Mesh
|
||||||
{ meshShading = s
|
{ meshShading = s
|
||||||
, meshMaterial = m
|
, meshMaterial = m
|
||||||
, meshVertices = mv
|
, meshVertices = mv
|
||||||
@ -235,7 +235,7 @@ parseMesh' s m = do
|
|||||||
, meshNormals = mn
|
, meshNormals = mn
|
||||||
, meshFaceNormals = mfn
|
, meshFaceNormals = mfn
|
||||||
, meshBounds = bounds
|
, meshBounds = bounds
|
||||||
})
|
}
|
||||||
|
|
||||||
parseTriangle :: Parser (V3 Int)
|
parseTriangle :: Parser (V3 Int)
|
||||||
parseTriangle = do
|
parseTriangle = do
|
||||||
|
@ -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
|
(V3 cr cg cb) = getColorFromRay (sceneRecursions s) ray s
|
||||||
|
|
||||||
ray@(Ray co _) = camRay x y (sceneCamera s)
|
ray@(Ray co _) = camRay x y (sceneCamera s)
|
||||||
y = fromIntegral $ h - (index `mod` w) - 1
|
y = fromIntegral $ h - (index `div` w) - 1
|
||||||
x = fromIntegral $ index `div` w
|
x = fromIntegral $ index `mod` w
|
||||||
ci = floor . (clamp 0 255) . (*255)
|
ci = floor . (clamp 0 255) . (*255)
|
||||||
--wrong format:
|
--wrong format:
|
||||||
--Ray (eye cam) $ rotCam x y w h (center cam - eye cam) (up cam) (fovy cam)
|
--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) =
|
hitsFlat verts norm f (V3 w1 w2 w3) =
|
||||||
if det == 0 || t < epsilon || not det2
|
if det == 0 || t < epsilon || not det2
|
||||||
then Nothing
|
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
|
where
|
||||||
! det = dot rd' (norm IM.! f) --do we hit the plane
|
! det = dot rd' (norm IM.! f) --do we hit the plane
|
||||||
rd' = normalize rd
|
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
|
pos = ro + t *^ rd' --where do we hit the plane
|
||||||
v1 = (verts IM.! w2) - (verts IM.! w1)
|
v1 = (verts IM.! w2) - (verts IM.! w1)
|
||||||
v2 = (verts IM.! w3) - (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))
|
det2v = det2m !* (pos - (verts IM.! w1))
|
||||||
-- fromJust is justified as we only make a base-change and all 3
|
-- fromJust is justified as we only make a base-change and all 3
|
||||||
-- vectors are linear independent.
|
-- vectors are linear independent.
|
||||||
det2 = det2v ^. _x > 0 && det2v ^. _y > 0
|
det2 = det2v ^. _x >= 0 && det2v ^. _y >= 0
|
||||||
&& det2v ^. _x + det2v ^. _y < 1
|
&& det2v ^. _x + det2v ^. _y <= 1
|
||||||
--hitsPhong :: IntMap (V3 Float) -> IntMap (V3 Float) -> V3 Int -> Maybe Collision
|
--hitsPhong :: IntMap (V3 Float) -> IntMap (V3 Float) -> V3 Int -> Maybe Collision
|
||||||
|
|
||||||
-- deprecated - wrong calculation of rays.
|
-- deprecated - wrong calculation of rays.
|
||||||
|
Loading…
Reference in New Issue
Block a user