Object subclass: #AoBench instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Category-AoBench'! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! AoBench class instanceVariableNames: ''! !AoBench class methodsFor: 'benchmark' stamp: 'sumim 2/27/2009 00:47'! render "[AoBench render] timeToRun" | out scene width height nsubSamples naoSamples cnt rgb | width := 256. height := 256. nsubSamples := 2. naoSamples := 8. out := FileStream fileNamed: 'ao.ppm'. out nextPutAll: 'P6', String lf. out nextPutAll: width printString, ' ', height printString, String lf. out nextPutAll: '255', String lf; binary. scene := {Vec x: -2.0 y: 0.0 z: -3.5. Vec x: -0.5 y: 0.0 z: -3.0. Vec x: 1.0 y: 0.0 z: -2.2} collect: [:vec | Sphere center: vec radius: 0.5]. scene := scene copyWith: (Plane p: (Vec x: 0.0 y: -0.5 z: 0.0) n: (Vec x: 0.0 y: 1.0 z: 0.0)). cnt := 0. 0 to: height - 1 do: [:y | 0 to: width - 1 do: [:x | | rad | rad := Vec zero. 0 to: nsubSamples - 1 do: [:v | 0 to: nsubSamples - 1 do: [:u | | px py eye ray isect | cnt := cnt + 1. px := (x + (u / nsubSamples) - (width / 2.0)) / (width / 2.0). py := (y + (v / nsubSamples) - (height / 2.0)) negated / (height / 2.0). eye := (Vec x: px y: py z: -1.0) normalize. ray := Ray origin: Vec zero direction: eye. isect := Isect new. scene do: [:elem | elem intersectRay: ray isect: isect]. isect hit ifTrue: [ | col | col := isect ambientOcclusion: scene samples: naoSamples. rad := rad + col]]]. rgb := rad / nsubSamples squared. out nextPut: (self clamp: rgb x). out nextPut: (self clamp: rgb y). out nextPut: (self clamp: rgb z)]]. out close! ! !AoBench class methodsFor: 'utility methods' stamp: 'sumim 2/26/2009 20:05'! clamp: f | i | i := f * 255.5. i > 255.0 ifTrue: [i := 255.0]. i < 0.0 ifTrue: [i := 0.0]. ^i rounded! ! Object subclass: #Isect instanceVariableNames: 't hit p n' classVariableNames: '' poolDictionaries: '' category: 'Category-AoBench'! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:33'! hit ^hit! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:33'! hit: aBoolean hit := aBoolean! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:33'! n ^n! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:33'! n: aVec n := aVec! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:34'! p ^p! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:34'! p: aVec p := aVec! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:34'! t ^t! ! !Isect methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:34'! t: aFloat t := aFloat! ! !Isect methodsFor: 'initialization' stamp: 'sumim 2/26/2009 20:10'! initialize t := 1000000.0. hit := false. p := Vec zero. n := Vec zero! ! !Isect methodsFor: 'calculating' stamp: 'sumim 2/26/2009 21:22'! ambientOcclusion: scene samples: naoSamples | basis ntheta nphi eps occlution rand p1 | basis := Array new: 3. n orthoBasis: basis. ntheta := nphi := naoSamples. eps := 0.0001. occlution := 0.0. rand := Random new. p1 := p + (n * eps). nphi * ntheta timesRepeat: [ | r phi x y z rx ry rz raydir ray occIsect | r := rand next. phi := 2.0 * Float pi * rand next. x := phi cos * (1.0 - r) sqrt. y := phi sin * (1.0 - r) sqrt. z := r sqrt. rx := (x * basis first x) + (y * basis second x) + (z * basis third x). ry := (x * basis first y) + (y * basis second y) + (z * basis third y). rz := (x * basis first z) + (y * basis second z) + (z * basis third z). raydir := Vec x: rx y: ry z: rz. ray := Ray origin: p1 direction: raydir. occIsect := Isect new. scene do: [:elem | elem intersectRay: ray isect: occIsect]. occIsect hit ifTrue: [occlution := occlution + 1.0]]. occlution := (ntheta * nphi - occlution) / (ntheta * nphi). ^Vec x: occlution y: occlution z: occlution! ! Object subclass: #Plane instanceVariableNames: 'p n' classVariableNames: '' poolDictionaries: '' category: 'Category-AoBench'! !Plane methodsFor: 'private' stamp: 'sumim 2/26/2009 18:49'! setP: newP n: newN p := newP. n := newN! ! !Plane methodsFor: 'calculating' stamp: 'sumim 2/26/2009 21:02'! intersectRay: ray isect: isect | d v t | d := (p dot: n) negated. v := ray direction dot: n. v abs < 1.0e-17 ifTrue: [^false]. t := ((ray origin dot: n) + d) negated / v. (t > 0.0 and: [t < isect t]) ifTrue: [ isect hit: true. isect t: t. isect n: n. isect p: ray origin + (ray direction * t)]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Plane class instanceVariableNames: ''! !Plane class methodsFor: 'instance creation' stamp: 'sumim 2/26/2009 20:09'! p: p n: n ^self new setP: p n: n; yourself! ! Object subclass: #Ray instanceVariableNames: 'origin direction' classVariableNames: '' poolDictionaries: '' category: 'Category-AoBench'! !Ray methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:28'! direction ^direction! ! !Ray methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:28'! origin ^origin! ! !Ray methodsFor: 'private' stamp: 'sumim 2/26/2009 18:29'! setOrigin: newOri direction: newDir origin := newOri. direction := newDir! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Ray class instanceVariableNames: ''! !Ray class methodsFor: 'instance creation' stamp: 'sumim 2/26/2009 18:29'! origin: origin direction: direction ^self new setOrigin: origin direction: direction; yourself! ! Object subclass: #Sphere instanceVariableNames: 'center radius' classVariableNames: '' poolDictionaries: '' category: 'Category-AoBench'! !Sphere methodsFor: 'private' stamp: 'sumim 2/26/2009 18:20'! setCenter: newCenter radius: newRadius center := newCenter. radius := newRadius! ! !Sphere methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:21'! center ^center! ! !Sphere methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:21'! radius ^radius! ! !Sphere methodsFor: 'calculating' stamp: 'sumim 2/26/2009 20:14'! intersectRay: ray isect: isect | rs b c d | rs := ray origin - center. b := rs dot: ray direction. c := (rs dot: rs) - (radius * radius). d := b * b - c. d > 0.0 ifTrue: [ | t | t := b negated - d sqrt. (t > 0.0 and: [t < isect t]) ifTrue: [ isect t: t. isect hit: true. isect p: ray origin + (ray direction * t). isect n: (isect p - center) normalize]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Sphere class instanceVariableNames: ''! !Sphere class methodsFor: 'instance creation' stamp: 'sumim 2/26/2009 18:19'! center: center radius: radius ^self new setCenter: center radius: radius; yourself! ! Object subclass: #Vec instanceVariableNames: 'x y z' classVariableNames: '' poolDictionaries: '' category: 'Category-AoBench'! !Vec methodsFor: 'arithmetic' stamp: 'sumim 2/26/2009 20:14'! * n ^Vec x: x * n y: y * n z: z * n! ! !Vec methodsFor: 'arithmetic' stamp: 'sumim 2/26/2009 18:02'! + aVec ^Vec x: x + aVec x y: y + aVec y z: z + aVec z! ! !Vec methodsFor: 'arithmetic' stamp: 'sumim 2/26/2009 18:02'! - aVec ^Vec x: x - aVec x y: y - aVec y z: z - aVec z! ! !Vec methodsFor: 'arithmetic' stamp: 'sumim 2/26/2009 18:22'! / n ^Vec x: x / n y: y / n z: z / n! ! !Vec methodsFor: 'arithmetic' stamp: 'sumim 2/26/2009 20:10'! cross: aVec ^ Vec x: y * aVec z - (z * aVec y) y: z * aVec x - (x * aVec z) z: x * aVec y - (y * aVec x)! ! !Vec methodsFor: 'arithmetic' stamp: 'sumim 2/26/2009 20:15'! dot: aVec ^(x * aVec x) + (y * aVec y) + (z * aVec z)! ! !Vec methodsFor: 'private' stamp: 'sumim 2/26/2009 17:58'! setX: newX y: newY z: newZ x := newX. y := newY. z := newZ! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:25'! length ^(x squared + y squared + z squared) sqrt! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:11'! x ^x! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 20:11'! x: newX x := newX! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:11'! y ^y! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 20:11'! y: newY y := newY! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 18:11'! z ^z! ! !Vec methodsFor: 'accessing' stamp: 'sumim 2/26/2009 20:11'! z: newZ z := newZ! ! !Vec methodsFor: 'converting' stamp: 'sumim 2/26/2009 18:24'! normalize | length | length := self length. length > 1.0e-17 ifTrue: [^self / length]. ^self! ! !Vec methodsFor: 'converting' stamp: 'sumim 2/26/2009 20:30'! orthoBasis: basis basis at: 3 put: self copy. basis at: 2 put: Vec zero. (x between: -0.6 and: 0.6) ifTrue: [basis second x: 1.0] ifFalse: [(y between: -0.6 and: 0.6) ifTrue: [basis second y: 1.0] ifFalse: [(z between: -0.6 and: 0.6) ifTrue: [basis second z: 1.0] ifFalse: [basis second x: 1.0]]]. basis at: 1 put: (basis second cross: basis third). basis at: 1 put: basis first normalize. basis at: 2 put: (basis third cross: basis first). basis at: 2 put: basis second normalize! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Vec class instanceVariableNames: ''! !Vec class methodsFor: 'instance creation' stamp: 'sumim 2/26/2009 17:57'! x: x y: y z: z ^self new setX: x y: y z: z; yourself! ! !Vec class methodsFor: 'instance creation' stamp: 'sumim 2/26/2009 20:09'! zero ^self x: 0.0 y: 0.0 z: 0.0! !