"ray tracing in one weekend"

General FreeBASIC programming questions.
Post Reply
dafhi
Posts: 1641
Joined: Jun 04, 2005 9:51

"ray tracing in one weekend"

Post by dafhi »

I'm progressing through the course by the same name.

Jan 31 -
updated Main() for quick image scale
scatter function 3 params (from 4)
dielectric material

Code: Select all

/' -- "Main.bas" - 2020 Jan 31 - by dafhi --

  - differences from Peter Shirley's version
  color function
  "attenuation = albedo" commented out in materials (found by accident that it still works)
  small optimization to random_in_unit_sphere

'/

/' -- "fb 1337 h4x.bas" - 2020 Jan 28 - by dafhi -- '/

#undef int
#define def   #define

def int     as Integer
def sng     as single
def dbl     as double
def ac      as const

def decl    declare
def func    function
def prop    property
def virt    virtual
def op      operator
def ctor    constructor
def ret     return
def float   single
def By      ByRef
def abst    abstract
' -------- fb 1337 h4x


#ifndef piBy4
const   Tau = 8*atn(1)
const   piBy4 = 4*atn(1)
#EndIf

def tReal float

def tVector3 vec3
def v3 vec3

const as float EPS=1e-6
const as float INF=1e9f

' D.J.Peters vector class b/c already done.
' I will likely attempt a translation Ray Tracing In One Weekend's vector class later.

type v3
  declare constructor (sX as tReal=0, _
                       sY as tReal=0, _
                       sZ as tReal=0)
  declare constructor (p as tReal ptr)
  declare constructor (o as v3)

  declare operator    cast as tReal ptr
  declare const operator    [](index as integer) byref as tReal

  decl sub            make_unit_vector
  declare prop        unit_v as v3
  declare prop        perp as v3
  declare property    squared_length as tReal
  declare property    length as tReal
  declare function    cross( as v3 ) as v3
  declare function    dot( as v3 ) as float
  declare sub         Zero
  union
    as tReal x,r
  end union
  union
    as tReal y,g
  end union
  union
    as tReal z,b
  end union

end type

constructor v3(fX as tReal, _
                     fY as tReal, _
                     fZ as tReal)
  x=fX : y=fY : z=fZ
end constructor

constructor v3(p as tReal ptr)
  if p then
    x=p[0] : y=p[1] : z=p[2]
  else
    x=0 : y=0 : z=0
  end if
end constructor

constructor v3(o as v3)
  x=o.x : y=o.y : z=o.z
end constructor

operator v3.cast as tReal ptr
  operator = @x
end operator

const operator v3.[](index as integer) byref as tReal
  return cptr(tReal ptr,@x)[index]
end operator

operator -(r ac v3) as v3
  operator = v3(-r.x,-r.y,-r.z)
end operator

operator +(l ac v3,r ac v3) as v3
  operator = v3(l.x+r.x, l.y+r.y, l.z+r.z)
end operator

operator -(l ac v3,r ac v3) as v3
  operator = v3(l.x-r.x, l.y-r.y, l.z-r.z)
end operator

operator *(l ac v3,r ac tReal) as v3
  operator = v3(l.x*r, l.y*r, l.z*r)
end operator

operator *(l ac tReal,r ac v3) as v3
  operator = v3(l*r.x, l*r.y, l*r.z)
end operator

operator *(l ac v3,r ac v3) as v3
  return type(l.x*r.x, l.y*r.y, l.z*r.z)
end operator

func dot(byref v1 ac v3, byref v2 ac v3) ac float
    ret v1.x*v2.x + v1.y*v2.y + v1.z*v2.z
end func

func v3.dot( r as v3 ) as float
  ret x*r.x+y*r.y+z*r.z
end func

function v3.cross(r as v3) as v3
  dim as single xx=y*r.z - z*r.y
  dim as single yy=z*r.x - x*r.z
  dim as single zz=x*r.y - y*r.x
  return v3(y*r.z - z*r.y, z*r.x - x*r.z, x*r.y - y*r.x)
End function

#include "crt.bi"

#define rABS   fabs
const as tReal REAL_EPSILON = 0.000001

operator /(l ac v3,r as tReal) ac v3
  if rABS(r) < REAL_EPSILON then
    operator = l
  else
    r=1/r
    operator = l*r
  end if
end operator

#define rSQR   sqrt

sub v3.make_unit_vector
  dim as float s = x*x+y*y+z*z
  if s<>0 then s = 1/s: x*=s:y*=s:z*=s
End Sub

prop v3.unit_v as v3
  dim as tReal s = x*x+y*y+z*z
  if s > REAL_EPSILON then s=1/sqr(s): return v3(x*s,y*s,z*s)
  return this
end prop

prop v3.squared_length as tReal
  return x*x+y*y+z*z
end prop

prop v3.length as tReal
  return sqr(x*x+y*y+z*z)
end prop

prop v3.perp as v3'(in sng) as v3
  if y=0 then return type(0, 1, 0)
  #if 1
    if z*z+x*x = 0 then return v3(1,0,0)
    return type(z, 0, -x)
  #else
    var s=z*z+x*x: if s=0 then return type(in,0,0)
    s=in/sqr(s):  return type(z*s, 0, -x*s)
  #EndIf
End prop
' --------- vec3

/' -- ray.bas (FreeBASIC) - 2020 Jan 28 - by dafhi
 
  "Ray Tracing In One Weekend"  '/

'#include "vec3 z.bas"

type ray
  decl      ctor
  decl      ctor( ac vec3, ac vec3 )
  decl const func point_at_parameter( as float) ac vec3
 
  as vec3 origin, direction
End Type

ctor ray
end ctor

ctor ray( a ac vec3, b ac vec3 )
  origin=a: direction=b
end ctor

const func ray.point_at_parameter(t as float) ac vec3
  ret origin + t*direction
end func
' ------ ray

/' -- "hittable.bas" - 2020 Jan 28 - by dafhi -- '/

'#include once "ray.bas"

type ref_mat as material '' forward reference

type hit_record
  as float  t
  as vec3   p
  as vec3         normal
  as ref_mat ptr  mat_ptr
End Type


type material extends object
  decl virt func scatter( as ray, as hit_record, as ray ) as boolean
  'decl virt func scatter( as ray, as hit_record, as vec3, as ray ) as boolean
  as vec3 albedo
  
  int uid = 0
End Type

virt func material.scatter( r as ray, rec as hit_record, scattered as ray) as boolean
'virt func material.scatter( r as ray, rec as hit_record, attenuation as vec3, scattered as ray) as boolean
  return false
end func


type hittable extends object
    declare virtual function hit(ac ray, sng, sng, as hit_record) ac boolean
End Type

virtual function hittable.hit(r ac ray, t_min sng, t_max sng, rec as hit_record) ac boolean
    return false
end func
' ------ hittable

/' -- "sphere.bas" - 2020 Jan 28 - by dafhi -- '/

'#include once "hittable.bas"

type sphere extends hittable
    decl      ctor
    decl      ctor(as vec3, as float, as material ptr)
   
    declare virt func hit( By ac ray, sng, sng, By as hit_record) ac boolean
   
    decl prop radius(as float)
    decl prop radius as float
   
    as vec3   center
    as float  rad, r2
    as material ptr mat_ptr
End Type

ctor sphere
end ctor

ctor sphere(cen as vec3, r as float, pmat as material ptr)
  center = cen: radius = r:  mat_ptr = pmat
end ctor

prop sphere.radius(in as float)
  rad = in: r2 = in*in
end prop

prop sphere.radius as float
  return rad
end prop

virt func sphere.hit( By r ac ray, t_min sng, t_max sng, By rec as hit_record) ac boolean
    var oc = r.origin - center
    var a = dot(r.direction, r.direction) '' dot
    var b = dot(oc, r.direction)
    var c = dot(oc, oc) - r2
    var disc = b*b - a*c
    if disc > 0 then
       
        #macro dupl()
      if temp < t_max andalso temp > t_min then
        rec.t = temp
        rec.p = r.point_at_parameter(rec.t)
        rec.normal = (rec.p - center) / rad
        rec.mat_ptr = mat_ptr
        ret true
      EndIf
      #endmacro
     
      var temp = (-b - rsqr(disc))/a
      dupl()
     
      temp = (-b + rsqr(disc))/a
      dupl()
    EndIf
    ret false
end func
' ------- sphere

/' --  material.bas - 2020 Jan 28 - by dafhi -- '/

'#include once "hittable.bas"

func reflect( v ac v3, n ac v3 ) as vec3
  ret v - 2*dot(v,n)*n
end func

func refract( v as v3, n ac v3, ni_over_nt as float, refracted as v3 ) as boolean
  var uv = v.unit_v
  dim as float dt = dot(uv, n)
  dim as float disc = 1 - ni_over_nt*ni_over_nt*(1-dt*dt)
  if disc > 0 then
    refracted = ni_over_nt*(uv - n*dt) - n*sqrt(disc)
    return true
  EndIf
  return false
end func

'' slight optimization
function random_in_unit_sphere as v3
  static as vec3 p
  do
    p = vec3(rnd-.5,rnd-.5,rnd-.5)
  Loop while p.squared_length >= .5
  return 2*p
end function

function rodriguez_rot( ray_d as v3, norm as v3, angle as float ) as v3
  var dlen=norm.x*norm.x+norm.y*norm.y+norm.z*norm.z
  if dlen < .0001 then
    norm.x=0:norm.y=-1:norm.z=0
  else
    dlen = -1/sqr(dlen): norm.x*=dlen: norm.y*=dlen: norm.z*=dlen
  endif
  dim as float cosa = cos(angle), sina = sin(angle)
  with ray_d
    return (1-cosa)*(norm.x*.x+norm.y*.y+norm.z*.z)*norm + cosa*ray_d + _
      sina*type(norm.y*.z-norm.z*.y, norm.z*.x-norm.x*.z, norm.x*.y-norm.y*.x)
  end with
End Function

function fuzzy_norm( byval ray_d as v3, surf_n as v3, k as float) as v3
    static as v3 vtemp

    ray_d = ray_d.unit_v
    dim sng cosa = -surf_n.dot(ray_d)
    
    vtemp = rodriguez_rot( surf_n, _
      surf_n.cross(ray_d), acos(cosa) * k / 2 )
    
    const a = sqr(2)

    return (vtemp * a + random_in_unit_sphere * k).unit_v
End Function


'' diffuse
type lambertian extends material
  decl ctor(as v3)
  decl func scatter( as ray, as hit_record, as ray) as boolean
  'decl func scatter( as ray, as hit_record, as v3, as ray) as boolean
End Type

ctor lambertian(a as v3)
  albedo = a
  uid = 1
end ctor

func lambertian.scatter( r as ray, rec as hit_record, scattered as ray) as boolean
'func lambertian.scatter( r as ray, rec as hit_record, attenuation as v3, scattered as ray) as boolean
 
  scattered = ray(rec.p, rec.normal + random_in_unit_sphere)
  'attenuation = albedo
  return true
end func


''
type metal extends material
  decl ctor(ac v3, sng = 1)
  decl func scatter( as ray, as hit_record, as ray) as boolean
  'decl func scatter( as ray, as hit_record, as v3, as ray) as boolean
 
  as float fuzz
End Type

ctor metal(a ac v3, f sng)
  albedo = a
  fuzz = f
  uid = 2
end ctor

func metal.scatter( r as ray, rec as hit_record, scattered as ray) as boolean
'func metal.scatter( r as ray, rec as hit_record, attenuation as v3, scattered as ray) as boolean
 
  '' All-metal/lambertian solution?
  dim as v3 reflected = reflect( r.direction, fuzzy_norm( r.direction, rec.normal, fuzz ) )
  scattered = ray(rec.p, reflected)
  'attenuation = albedo
 
  return dot(scattered.direction, rec.normal) > 0
end func


''
type dielectric extends material
  decl ctor(ac v3=v3(1,1,1), sng = 1, sng = 0)
  decl virt func scatter( as ray, as hit_record, as ray) as boolean
  'decl virt func scatter( as ray, as hit_record, as v3, as ray) as boolean
 
  as float  r_i
  as float  fuzz
End Type

ctor dielectric(a ac v3, ri sng, f sng)
  albedo = a
  fuzz = f
  r_i = ri
  uid = 3 '' dbg
end ctor

func dielectric.scatter( r as ray, rec as hit_record, scattered as ray) as boolean
'func dielectric.scatter( r as ray, rec as hit_record, attenuation as v3, scattered as ray) as boolean
  
  static as v3 outward_normal, reflected, refracted
  reflected = reflect( r.direction, rec.normal )'fuzzy_norm( r.direction, rec.normal, fuzz ) )
  dim as float ni_over_nt
  
  if dot(r.direction, rec.normal) > 0 then
    outward_normal = -rec.normal
    ni_over_nt = r_i
  else
    outward_normal = rec.normal
    ni_over_nt = 1 / r_i
  EndIf
  
  if refract(r.direction, _
      fuzzy_norm( r.direction, outward_normal, fuzz ), _
      ni_over_nt, refracted) then
    scattered = ray(rec.p, refracted)
  else
    scattered = ray(rec.p, reflected)
    return false
  EndIf
  return true
  'attenuation = albedo
  
  return dot(scattered.direction, rec.normal) > 0
end func
' ------- material

/' -- "hitablelist.bas" - 2020 Jan 28 - by dafhi -- '/

'#include once "material.bas"

type hittable_list extends hittable
  decl ctor
  decl ctor( as hittable ptr ptr, int)
  decl virt func hit( By ac ray, sng, sng, By as hit_record) ac boolean
  as hittable ptr ptr list
  int list_size
End Type

ctor hittable_list
end ctor

ctor hittable_list(l as hittable ptr ptr, n int)
  list = l: list_size = n
end ctor

virt func hittable_list.hit( By r ac ray, t_min sng, t_max sng, By rec as hit_record) ac boolean
  dim as hit_record temp_rec
  var hit_anything = false
  var closest_so_far = t_max '' make double?
  for i int = 0 to list_size-1
    if list[i]->hit(r, t_min, closest_so_far, temp_rec) then
      hit_anything = true
      closest_so_far = temp_rec.t
      rec = temp_rec
    EndIf
  Next
  ret hit_anything
end func
' ------- hittablelist

/' -- camera.bas - 2020 Jan 28 - by dafhi -- '/

'#include once "ray.bas"

type camera
  decl ctor (as vec3 = v3(-2,-1,-1), as vec3 = v3(4,0,0), as vec3 = v3(0,2,0), as vec3 = v3(0,0,0))
  decl func get_ray(as float, as float) as ray
  as vec3 origin
  as vec3 lower_left_corner
  as vec3 horizontal
  as vec3 vertical
End Type

ctor camera( llc as vec3, h as vec3, v as vec3, o as vec3 )
  lower_left_corner = llc
  horizontal = h
  vertical = v
  origin = o
end ctor

func camera.get_ray(u as float, v as float) as ray
  ret ray( _
    origin, _
    lower_left_corner + u*horizontal + v*vertical - origin)
end func
' ------ camera

func sky( ray_d as vec3 ) as vec3
  var t = .5 * ( ray_d.unit_v.y + 1 )
  ret (1 - t) * vec3(1, 1, 1) + t * vec3( .5, .7, 1 )
end func

#undef color

func color( byref r as ray, world as hittable ptr, depth int ) as vec3
 
  '' different from Peter Shirley's
 
  var rec = hit_record
  if world->hit(r, EPS, INF, rec) then
    var attenuation = rec.mat_ptr->albedo
    dim as ray scattered
    if depth < 50 andalso rec.mat_ptr->scatter( r, rec, scattered) then
    'if depth < 50 andalso rec.mat_ptr->scatter( r, rec, attenuation, scattered) then
      return attenuation*color( scattered, world, depth+1 )
    else
      return attenuation
    endif
  EndIf
  ret sky( r.direction )
end func


function c255(in sng) int  '2020 Jan 22
  return iif( in<0, 0, iif( in>=1, 255, sqr(in)*256-.5 ) )
end function

#macro show_pixel( _col )
  var ir = c255( _col[0] )
  var ig = c255( _col[1] )
  var ib = c255( _col[2] )
  pset (i,ny-1-j), rgb( ir, ig, ib )
#EndMacro
 

sub main
  dim as string kstr
  
  var scale = 2.4
  var   nx = 200 * scale
  var   ny = 150 * scale
  var   ns = 11 '' samples
  
  const                 borderless = 8
  screenres nx, ny, 32', borderless
  
  dim as hittable ptr ptr list = new hittable ptr[4]
  list[0] = new sphere( vec3(0,0,-1), .5, new metal(vec3(.1,.2,.5), .2))
  list[1] = new sphere( vec3(0,-100.5,-1), 100, new metal(vec3(.8,.8,.0), .2))
  list[2] = new sphere( vec3(1,0,-1),.5, new metal(vec3(.8,.6,.2), .1))
  list[3] = new sphere( vec3(-1,0,-1),.5, new dielectric(vec3(.8,.8,.8), 1.5, .01)) '' fuzz
  
  dim as hittable ptr world = new hittable_list( list, 4 )
  dim as camera cam = camera( vec3( -nx/(100*scale), -ny/(100*scale), -1), vec3(nx/(50*scale),0,0), vec3(0,ny/(50*scale),0) )
  'cam.origin.y += .1
  #if 1
    for j int = 0 to ny-1
      for i int = 0 to nx - 1
        var col = vec3(0,0,0)
        for s int = 0 to ns-1
          dim sng u = (i + rnd-.5)/nx
          dim sng v = (j + rnd-.5)/ny
          var r = cam.get_ray(u, v)
          col += color(r, world, 0)
        Next
        col /= ns
        show_pixel( col )
      next
      if j mod 2=0 then kstr=inkey: sleep 1 '' small rest every N scanlines
      if kstr<>"" then exit for
    Next
  #elseif 1
 
  #EndIf
  
  if kstr=chr(27) then exit sub
  sleep
End Sub

main
Post Reply