added bounding-box. corrected some errors..
This commit is contained in:
		@@ -14,7 +14,7 @@ ambience   0.2 0.2 0.2
 | 
			
		||||
light 5 20 0 1.0 1.0 1.0 25
 | 
			
		||||
 | 
			
		||||
# meshes: filename, shading, material (ambient, diffuse, specular, shininess)
 | 
			
		||||
mesh neutral.off   PHONG  0.2 0.2 0.2  0.9 0.9 0.4  1.0 1.0 1.0  30.0    0.0
 | 
			
		||||
mesh neutral.off   FLAT  0.2 0.2 0.2  0.9 0.9 0.4  1.0 1.0 1.0  30.0    0.0
 | 
			
		||||
mesh sad.off PHONG  0.2 0.2 0.2  0.9 0.5 0.1  1.0 1.0 1.0  30.0    0.0
 | 
			
		||||
mesh confused.off PHONG  0.2 0.2 0.2  0.9 0.2 0.2  1.0 1.0 1.0  30.0    0.0
 | 
			
		||||
mesh smile.off PHONG  0.2 0.2 0.2  0.2 0.2 0.7  1.0 1.0 1.0  30.0    0.0
 | 
			
		||||
 
 | 
			
		||||
@@ -108,6 +108,7 @@ main = do
 | 
			
		||||
            putStrLn $ "reading and parsing "++ show a
 | 
			
		||||
            !f <- B.readFile a
 | 
			
		||||
            r <- runEitherT $ validateAndParseScene f (dropFileName a)
 | 
			
		||||
            print r
 | 
			
		||||
            case r of
 | 
			
		||||
              Left error -> putStrLn $ "Error: " ++ error
 | 
			
		||||
              Right s -> do
 | 
			
		||||
 
 | 
			
		||||
@@ -57,25 +57,29 @@ parseObject = do
 | 
			
		||||
            "depth" -> do
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        d <- decimal
 | 
			
		||||
                        endOfLine
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        return $ OpR d
 | 
			
		||||
            "background" -> do
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        c <- parseVector
 | 
			
		||||
                        endOfLine
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        return $ OpB (Background c)
 | 
			
		||||
            "ambience" -> do
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        c <- parseVector
 | 
			
		||||
                        endOfLine
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        return $ OpA (Ambience c)
 | 
			
		||||
            "light" -> do
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        p <- parseVector
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        c <- parseVector
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        intensity <- double <|> return 0
 | 
			
		||||
                        skipSpace
 | 
			
		||||
                        i <- return $ if intensity == 0
 | 
			
		||||
                                         then Nothing
 | 
			
		||||
                                         else Just (fromRational . toRational $ intensity)
 | 
			
		||||
                        endOfLine
 | 
			
		||||
                        return $ OpL (Light p c i)
 | 
			
		||||
            "sphere" -> parseSphere
 | 
			
		||||
            "plane"  -> parsePlane
 | 
			
		||||
@@ -84,6 +88,7 @@ parseObject = do
 | 
			
		||||
 | 
			
		||||
parseCamera :: Parser ObjectParser
 | 
			
		||||
parseCamera = do
 | 
			
		||||
        skipSpace
 | 
			
		||||
        eye'      <- parseVector
 | 
			
		||||
        center'   <- parseVector
 | 
			
		||||
        up'       <- parseVector
 | 
			
		||||
@@ -93,7 +98,7 @@ parseCamera = do
 | 
			
		||||
        width'    <- decimal
 | 
			
		||||
        skipSpace
 | 
			
		||||
        height'   <- decimal
 | 
			
		||||
        endOfLine
 | 
			
		||||
        skipSpace
 | 
			
		||||
        let     xDir' = (normalize $ cross (center' ^-^ eye') up') ^* (im_width / w)
 | 
			
		||||
                yDir' = (normalize $ cross xDir' view) ^* (im_height / h)
 | 
			
		||||
                lowerLeft' = center' ^-^ (0.5 * w *^ xDir')
 | 
			
		||||
@@ -122,7 +127,6 @@ parsePlane = do
 | 
			
		||||
        c <- parseVector
 | 
			
		||||
        n <- parseVector
 | 
			
		||||
        m <- parseMaterial
 | 
			
		||||
        endOfLine
 | 
			
		||||
        return $ OpP Plane
 | 
			
		||||
               { planeCenter = c
 | 
			
		||||
               , planeNormal = normalize n
 | 
			
		||||
@@ -135,7 +139,6 @@ parseSphere = do
 | 
			
		||||
        skipSpace
 | 
			
		||||
        r <- double
 | 
			
		||||
        m <- parseMaterial
 | 
			
		||||
        endOfLine
 | 
			
		||||
        return $ OpS Sphere
 | 
			
		||||
               { sphereCenter = p
 | 
			
		||||
               , sphereRadius = (fromRational . toRational) r
 | 
			
		||||
@@ -179,6 +182,7 @@ parseRawMesh = do
 | 
			
		||||
        shading <- string "FLAT" <|> string "PHONG"
 | 
			
		||||
        skipSpace
 | 
			
		||||
        mat <- parseMaterial
 | 
			
		||||
        skipSpace
 | 
			
		||||
        let shading' = case shading of
 | 
			
		||||
                        "FLAT"  -> Flat
 | 
			
		||||
                        "PHONG" -> Phong
 | 
			
		||||
@@ -207,11 +211,11 @@ parseMesh' s m = do
 | 
			
		||||
            let
 | 
			
		||||
                ! mv = IM.fromList $ P.zip [0..] verts
 | 
			
		||||
                ! mf = IM.fromList $ P.zip [0..] faces
 | 
			
		||||
                mfn = normal mv <$> mf
 | 
			
		||||
                ! mfn = normal mv <$> mf
 | 
			
		||||
                normal :: IntMap (V3 Float) -> V3 Int -> V3 Float
 | 
			
		||||
                normal verts (V3 v1 v2 v3) = normalize $ cross (verts ! v2 - verts ! v1)
 | 
			
		||||
                                                               (verts ! v3 - verts ! v1)
 | 
			
		||||
                mn = IM.fromList $ P.zip [0..] $ vnormal mfn mf <$> [0..v]
 | 
			
		||||
                ! mn = IM.fromList $ P.zip [0..] $ vnormal mfn mf <$> [0..v]
 | 
			
		||||
                vnormal :: IntMap (V3 Float) -> IntMap (V3 Int) -> Int -> V3 Float
 | 
			
		||||
                vnormal norms faces i = normalize $ F.foldl' (+) (V3 0 0 0) $ (!) norms <$> fs
 | 
			
		||||
                                        --TODO: weight sum with opening-angle!
 | 
			
		||||
 
 | 
			
		||||
@@ -92,7 +92,7 @@ diffuseAndSpec (Collision pos n _ obj) s co (Light lpos color int) =
 | 
			
		||||
            ! lightdir = (lpos - pos)
 | 
			
		||||
            i = case int of
 | 
			
		||||
                    Nothing -> 1
 | 
			
		||||
                    Just a -> a
 | 
			
		||||
                    Just a -> 1 --a TODO: What is light-intensity and how does it relate to lighting?
 | 
			
		||||
 | 
			
		||||
clamp :: Ord a => a -> a -> a -> a
 | 
			
		||||
clamp min max x
 | 
			
		||||
@@ -140,14 +140,36 @@ intersect (Ray ro rd) p@(P (Plane pc pn _)) = if det == 0 || t < epsilon
 | 
			
		||||
                    ! det = dot rd' pn
 | 
			
		||||
                    t = (dot (pc - ro) pn)/det
 | 
			
		||||
                    rd' = normalize rd
 | 
			
		||||
intersect (Ray ro rd) m@(M (Mesh s _ v f vn fn b)) = case catMaybes . elems $ possHits of
 | 
			
		||||
intersect r@(Ray ro rd) m@(M (Mesh s _ v f vn fn b)) = case catMaybes . elems $ possHits of
 | 
			
		||||
                                [] -> Nothing
 | 
			
		||||
                                a  -> Just . P.head . L.sort $ a
 | 
			
		||||
                where
 | 
			
		||||
                    possHits = case s of
 | 
			
		||||
                    possHits = if inBounds b r then case s of
 | 
			
		||||
                        Flat -> hitsFlat v fn `IM.mapWithKey` f
 | 
			
		||||
                        --Phong -> hitsPhong v n <$> f
 | 
			
		||||
                        _ -> undefined
 | 
			
		||||
                        Phong -> IM.fromList [] --hitsPhong v n <$> f
 | 
			
		||||
                        else
 | 
			
		||||
                            IM.fromList []
 | 
			
		||||
                    inBounds :: BoundingBox -> Ray -> Bool
 | 
			
		||||
                    inBounds bound r = a < b
 | 
			
		||||
                        where
 | 
			
		||||
                           (a,b) = L.foldl' (\(a,b) (c,d) -> (min a c, max b d)) (0,infty)
 | 
			
		||||
                                   [ intersectBounds (boundX bound) r (V3 1 0 0)
 | 
			
		||||
                                   , intersectBounds (boundY bound) r (V3 0 1 0)
 | 
			
		||||
                                   , intersectBounds (boundZ bound) r (V3 0 0 1)]
 | 
			
		||||
                    intersectBounds :: (Float, Float) -> Ray -> V3 Float -> (Float,Float)
 | 
			
		||||
                    intersectBounds (min, max) (Ray ro rd) n = 
 | 
			
		||||
                        if det == 0 || tmin < epsilon
 | 
			
		||||
                            then if tmax < epsilon
 | 
			
		||||
                                 then (0,infty)
 | 
			
		||||
                                 else (tmin, tmax)
 | 
			
		||||
                            else (tmin, tmax)
 | 
			
		||||
                        where
 | 
			
		||||
                            ! det = dot rd' n
 | 
			
		||||
                            rd' = normalize rd
 | 
			
		||||
                            tmin = (dot ((min *^ n) - ro) n)/det
 | 
			
		||||
                            tmax = (dot ((max *^ n) - ro) n)/det
 | 
			
		||||
 | 
			
		||||
                    infty = 999999999999999999
 | 
			
		||||
                    hitsFlat :: IntMap (V3 Float) -> IntMap (V3 Float) -> Int -> V3 Int -> Maybe Collision
 | 
			
		||||
                    hitsFlat verts norm f (V3 w1 w2 w3) =
 | 
			
		||||
                        if det == 0 || t < epsilon || not det2
 | 
			
		||||
 
 | 
			
		||||
@@ -1,3 +1,4 @@
 | 
			
		||||
{-# LANGUAGE BangPatterns #-}
 | 
			
		||||
module Scene.Types where
 | 
			
		||||
 | 
			
		||||
import Linear (V3)
 | 
			
		||||
@@ -71,13 +72,13 @@ data UIMesh = UIMesh
 | 
			
		||||
                deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
data Mesh = Mesh
 | 
			
		||||
            { meshShading     :: Shading
 | 
			
		||||
            , meshMaterial    :: Material
 | 
			
		||||
            { meshShading     :: ! Shading
 | 
			
		||||
            , meshMaterial    :: ! Material
 | 
			
		||||
            , meshVertices    :: IntMap (V3 Float)
 | 
			
		||||
            , meshFaces       :: IntMap (V3 Int)
 | 
			
		||||
            , meshNormals     :: IntMap (V3 Float)
 | 
			
		||||
            , meshFaceNormals :: IntMap (V3 Float)
 | 
			
		||||
            , meshBounds      :: BoundingBox
 | 
			
		||||
            , meshBounds      :: ! BoundingBox
 | 
			
		||||
            }
 | 
			
		||||
            deriving (Show, Eq)
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user