module Csg (difference, intersection) where import Vec import Solid import Data.List -- Constructive Solid Geometry -- (boolean operations for solids) -- todo: implement shadow tests data Difference = Difference SolidItem SolidItem deriving Show data Intersection = Intersection [SolidItem] deriving Show --Difference-- -- csg of object b subtracted from object a -- difference :: SolidItem -> SolidItem -> SolidItem difference a b = SolidItem $ Difference a b rayint_difference :: Difference -> Ray -> Flt -> Texture -> Rayint rayint_difference dif r d t = let Difference sa sb = dif Ray orig dir = r ria = rayint sa r d t in case ria of RayMiss -> RayMiss RayHit ad ap an at -> if inside sb orig then case rayint sb r d t of RayMiss -> RayMiss RayHit bd bp bn bt -> if bd < ad then if inside sa bp then RayHit bd bp (vinvert bn) bt else rayint_advance (SolidItem dif) r d t bd else rayint_advance (SolidItem dif) r d t bd else if inside sb ap then rayint_advance (SolidItem dif) r d t ad else RayHit ad ap an at --Intersection-- intersection :: [SolidItem] -> SolidItem intersection slds = SolidItem $ Intersection slds -- fixme: there's some numerical instability near edges rayint_intersection :: Intersection -> Ray -> Flt -> Texture -> Rayint rayint_intersection (Intersection slds) r d t = let (Ray orig dir) = r in if null slds || d < 0 then RayMiss else let s = head slds in case tail slds of [] -> rayint s r d t ss -> if inside s orig then case rayint s r d t of RayMiss -> rayint (Intersection ss) r d t RayHit sd sp sn st -> case rayint (Intersection ss) r sd t of RayMiss -> rayint_advance (SolidItem (Intersection slds)) r d t sd hit -> hit else case rayint s r d t of RayMiss -> RayMiss RayHit sd sp sn st -> if inside (Intersection ss) sp then RayHit sd sp sn st else rayint_advance (SolidItem (Intersection slds)) r d t sd inside_difference :: Difference -> Vec -> Bool inside_difference (Difference sa sb) pt = (inside sa pt) && (not $ inside sb pt) -- note: inside is True for an empty intersection. -- this is actually the preferred semantics in -- some cases, strange as it may seem. inside_intersection :: Intersection -> Vec -> Bool inside_intersection (Intersection slds) pt = foldl' (&&) True (map (\x -> inside x pt) slds) bound_difference :: Difference -> Bbox bound_difference (Difference sa sb) = bound sa bound_intersection :: Intersection -> Bbox bound_intersection (Intersection slds) = if null slds then empty_bbox else foldl' bboverlap everything_bbox (map bound slds) instance Solid Difference where rayint = rayint_difference inside = inside_difference bound = bound_difference instance Solid Intersection where rayint = rayint_intersection inside = inside_intersection bound = bound_intersection