雑記帳
Haskell でレイトレーシングのチュートリアルを追いかける その3 - アンチエイリアス
引き続きこのサイトのチュートリアルに則って、レイトレーシングによる画像の生成に挑戦。
進捗状況としては、ひとまず「section 7」まで完了。
進捗状況としては、ひとまず「section 7」まで完了。
コードの実行結果
ソースコード
{-# LANGUAGE TypeOperators #-}
module Main where
import Control.Lens
import System.Random
import Linear.Vector
import Linear.Metric
import Linear.V3
-- https://raytracing.github.io/books/RayTracingInOneWeekend.html section 7 + Torus with Haskell!! --
main :: IO ()
main = do
let
-- Image
aspect_ratio = 16.0 / 9
image_width = 256
image_height = round $ fromIntegral image_width / aspect_ratio
samples_per_pixel = 100
-- World
world = (([]
`add` RT_Torus{
centerOfTorus = V3 0 0 (-1),
majorRadius = 0.35,
minorRadius = 0.15,
orientationOfTorus = normalize $ V3 (-0.2) 1.2 1.9
})
`add` RT_Sphere{center = V3 0 (-10000.5) (-1), radius = 10000})
-- Camera
camera = Camera {
viewport_height = 2.0,
viewport_width = aspect_ratio * viewport_height camera,
focal_length = 1.0,
origin = zero,
horizontal = viewport_width camera *^ unit _x,
vertical = viewport_height camera *^ unit _y,
lower_left_corner =
origin camera - horizontal camera ^/2 - vertical camera ^/2
- focal_length camera *^ unit _z
}
-- Render
img_data <- return $ "P3\n" ++ show image_width ++ " " ++ show image_height ++ "\n255\n"
putStr $ img_data
foldr (>>) (return ()) $ (fmap $ ($) $ \((j, i), seed) ->
let
f h currentData gen =
if h < samples_per_pixel then
let
(randNum1, newGen1) = random gen :: (Double, StdGen)
(randNum2, newGen2) = random newGen1 :: (Double, StdGen)
u = (fromIntegral i + randNum1) / (fromIntegral image_width - 1.0)
v = (fromIntegral j + randNum2) / (fromIntegral image_height - 1.0)
r = get_ray camera (u, v)
pixcel_color = ray_color r world
in
f (succ h) (currentData + pixcel_color) newGen2
else
currentData
in
write_color (f 0 zero (mkStdGen seed)) samples_per_pixel) $
zip ((,) <$> [image_height - 1, image_height - 2 .. 0] <*> [0, 1 .. image_width - 1])
((randomRs (0, 536870912) (mkStdGen 21)) :: [Int])
---------------------
-- A Ray Data Type --
---------------------
data Ray = Ray {
orig :: V3 Double, -- Origin of this ray (As a position in 3D Euclidean space)
dir :: V3 Double -- Direction of this ray (As a direction vector in 3D Euclidean space)
} deriving (Show)
at' :: Ray -> Double -> V3 Double
at' r t = (orig r) + t *^ (dir r)
------------------------
-- A Camera Data Type --
------------------------
data Camera = Camera {
viewport_height :: Double,
viewport_width :: Double,
focal_length :: Double,
origin :: V3 Double,
horizontal :: V3 Double,
vertical :: V3 Double,
lower_left_corner :: V3 Double
} deriving (Show)
get_ray :: Camera -> (Double, Double) -> Ray
get_ray this (u, v) =
Ray {
orig = origin this,
dir = lower_left_corner this + u *^ horizontal this + v *^ vertical this - origin this
}
----------------------
-- A Hittable Class --
----------------------
type HittableData = (RT_Sphere + RT_Torus) + RT_Sphere -- Third RT_Sphere is just dummies
class Hittable a where
toSum :: a -> HittableData
hit :: a -> Ray -> Double -> Double -> Maybe HitRecord
instance (Hittable a, Hittable b) => Hittable (a + b) where
toSum = coPair(toSum, toSum)
hit = coPair(hit, hit)
add :: Hittable a => [HittableData] -> a -> [HittableData]
add list obj = (toSum obj) : list
data HitRecord = HitRecord {
p :: V3 Double,
normal :: V3 Double,
t :: Double,
front_face :: Bool
} deriving (Show)
set_face_normal :: HitRecord -> Ray -> V3 Double -> HitRecord
set_face_normal this r outward_normal =
HitRecord {
p = p this,
normal = if dir r `dot` outward_normal < 0 then outward_normal else -outward_normal,
t = t this,
front_face = (dir r `dot` outward_normal < 0)
}
hitSomething :: [HittableData] -> Ray -> Double -> Double -> Maybe HitRecord
hitSomething list r t_min t_max =
let
f (list', r', closest_so_far, currentRecord) =
case list' of
x:xs ->
let
temp = hit x r' t_min t_max
in
case temp of
Just a ->
f $ (xs, r', t a, temp)
Nothing ->
f $ (xs, r', closest_so_far, currentRecord)
[] ->
currentRecord
in
f $ (list, r, t_max, Nothing)
----------------------
-- Hittable Objects --
----------------------
-- Sphere
data RT_Sphere = RT_Sphere {
center :: V3 Double,
radius :: Double
} deriving (Show)
instance Hittable RT_Sphere where
toSum = Inj1 -: Inj1
hit obj r t_min t_max =
let
p0 = orig r
c1 = center obj
r1 = radius obj
oc = p0 - c1
a = quadrance (dir r)
half_b = oc `dot` dir r
c = quadrance oc - (radius obj) ^ 2
discriminant = half_b ^ 2 - a*c in
if discriminant > 0 then
let
root = sqrt discriminant
f k =
case k of
x:xs ->
if t_min < x && x < t_max then
return $ set_face_normal HitRecord {
p = at' r x,
normal = zero,
t = x,
front_face = False
} r ((at' r x - c1) ^/ r1)
else
f $ xs
[] ->
Nothing
in
f $ [(-half_b - root) / a, (-half_b + root) / a]
else
Nothing
-- Torus
data RT_Torus = RT_Torus {
centerOfTorus :: V3 Double,
majorRadius :: Double,
minorRadius :: Double,
orientationOfTorus :: V3 Double -- [BEWARB] this pseudo-vector must be normalized
} deriving (Show)
instance Hittable RT_Torus where
toSum = Inj2 -: Inj1
hit obj r t_min t_max =
let
p0 = orig r
c1 = centerOfTorus obj
r1 = majorRadius obj
r2 = minorRadius obj
n = orientationOfTorus obj
oc = p0 - c1
a = quadrance (dir r)
half_b = oc `dot` dir r
c = quadrance oc - (r1 + r2 + 0.01) ^ 2
discriminant = half_b ^ 2 - a*c in
if discriminant > 0 then
let
root = sqrt discriminant
s = newton's_method
50
(max 0 ((-half_b - root) / a), max 0 ((-half_b + root) / a))
(max 0 ((-half_b - root) / a), 0)
(findIntersection_forTorus obj r)
(findIntersection_forTorus' obj r)
in
s >>= (\k ->
let
x = at' r k - c1
in
return $ HitRecord {
p = c1 + x,
normal = (x - (r1 *^ (normalize $ x - (n `dot` x) *^ n))) ^/ r2,
t = k,
front_face = False
}
)
else
Nothing
findIntersection_forTorus :: RT_Torus -> Ray -> Double -> Double
findIntersection_forTorus obj r t =
(quadrance u + r1 ^2 - r2 ^ 2) ^ 2 - 4 * (r1 ^ 2) * (u `dot` (u - (n `dot` u) *^ n))
-- quadrance u - 2 * r1 * (sqrt $ u `dot` (u - (n `dot` u) *^ n)) + r1 ^2 - r2 ^ 2
where
a = dir r
u = at' r t - centerOfTorus obj
n = orientationOfTorus obj
r1 = majorRadius obj
r2 = minorRadius obj
findIntersection_forTorus' :: RT_Torus -> Ray -> Double -> Double
findIntersection_forTorus' obj r t =
4 * (a `dot` u) * (quadrance u + r1 ^ 2 - r2 ^ 2)
- 8 * (r1^2) * (u `dot` (a - (n `dot` a) *^ n))
-- 2 * (a `dot` u)
-- - 2 * r1 * (u `dot` (a - (n `dot` a) *^ n)) / (sqrt $ u `dot` (u - (n `dot` u) *^ n))
where
a = dir r
u = at' r t - centerOfTorus obj
n = orientationOfTorus obj
r1 = majorRadius obj
r2 = minorRadius obj
----------------------------------------
-- Computing the color of a given ray --
----------------------------------------
write_color :: RealFrac a => V3 a -> Int -> IO ()
write_color v samples_per_pixel =
let
v' = v ^/ fromIntegral samples_per_pixel
f = show.floor.(255.999*)
in
do
tmp <- return $ f(v' ^._x) ++ " " ++ f(v' ^._y) ++ " " ++ f(v' ^._z) ++ "\n"
putStr $ tmp
ray_color :: Ray -> [HittableData] -> V3 Double
ray_color r objects =
let
record = hitSomething objects r 0 infinity
in
case record of
Just a ->
0.5 *^ ((normal a) + (V3 1 1 1))
Nothing ->
let
unit_direction = normalize $ (dir r)
s = 0.5 * (unit_direction ^._y + 1.0)
in
lerp s (V3 0.5 0.7 1.0) (V3 1.0 1.0 1.0)
---------------
-- Utilities --
---------------
infinity :: RealFloat a => a
infinity = encodeFloat (floatRadix 0 - 1) (snd $ floatRange 0)
deg2rad :: Floating a => a -> a
deg2rad degrees = degrees * pi / 180
clamp :: (Ord a, Num a) => a -> a -> a -> a
clamp x y val = (max x).(min y) $ val
isInClosedInterval:: (Ord a, Fractional a) => (a, a) -> a -> Bool
isInClosedInterval (a, b) val = (a <= val && val <= b)
isInOpenInterval:: (Ord a, Fractional a) => (a, a) -> a -> Bool
isInOpenInterval (a, b) val = (a < val && val < b)
newton's_method :: (Ord a, Fractional a) => Int -> (a, a) -> (a, a) -> (a -> a) -> (a -> a) -> Maybe a
newton's_method depth interval (current, prev) f f' =
if (uncurry (/=)) interval && isInClosedInterval interval current && depth > 0 then
if abs(current - prev) < 1.0E-10 then
Just current
else
newton's_method (pred depth) interval (current - (f(current) / f'(current)), current) f f'
else
Nothing
-- Joke
derivativeOf :: (Floating a) => (a -> a) -> Int -> a -> a
derivativeOf f precision =
\x -> (f(x + dx) - f(x)) / dx
where dx = 0.1^precision
-- Diagrammatic-order composition
(-:) = flip (.)
-- Sum objects and injections
data (+) a b = Inj1 a | Inj2 b
instance (Show a, Show b) => Show (a + b) where
show = coPair(show -: (++ ";inj1"), show -: (++ ";inj2"))
coPair :: (a1 -> b, a2 -> b) -> (a1 + a2 -> b)
coPair (f, g) x = case x of
Inj1 x -> f x
Inj2 x -> g x
タグ一覧: