'From Squeak3.9 of 7 November 2006 [latest update: #7067] on 22 September 2007 at 3:25:28 am'! Object subclass: #Group instanceVariableNames: 'bound objs' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! Object subclass: #Hit instanceVariableNames: 'lambda normal' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! Object subclass: #Ray instanceVariableNames: 'orig dir' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! Object subclass: #RayBench instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! Object subclass: #Sphere instanceVariableNames: 'center radius' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! Array variableSubclass: #Vec instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! Object subclass: #Vec1 instanceVariableNames: 'x y z' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! FloatArray variableWordSubclass: #Vec2 instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Category-RayBench'! !Array methodsFor: 'converting' stamp: 'sumim 9/22/2007 02:27'! asVec ^RayBench vecClass newFrom: self! ! !Group methodsFor: 'private' stamp: 'sumim 9/20/2007 23:20'! setBound: aSphere bound := aSphere! ! !Group methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:16'! objs ^objs! ! !Group methodsFor: 'processing' stamp: 'sumim 9/20/2007 23:16'! intersectHit: hit ray: ray | len | len := bound raySphere: ray. len >= hit lambda ifTrue: [^hit]. ^objs inject: hit into: [:h :ss | ss intersectHit: h ray: ray]! ! !Group methodsFor: 'initialization' stamp: 'sumim 9/20/2007 23:18'! initialize objs := OrderedCollection new! ! !Group class methodsFor: 'instance creation' stamp: 'sumim 9/20/2007 23:19'! bound: aSphere ^self new setBound: aSphere; yourself! ! !Hit methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:39'! lambda ^lambda! ! !Hit methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:39'! normal ^normal! ! !Hit methodsFor: 'private' stamp: 'sumim 9/19/2007 12:42'! setLambda: l normal: n lambda := l. normal := n! ! !Hit class methodsFor: 'instance creation' stamp: 'sumim 9/19/2007 12:40'! lambda: l normal: n ^self new setLambda: l normal: n; yourself! ! !Ray methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:41'! dir ^dir! ! !Ray methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:41'! orig ^orig! ! !Ray methodsFor: 'private' stamp: 'sumim 9/19/2007 12:41'! setOrig: o dir: d orig := o. dir := d! ! !Ray class methodsFor: 'instance creation' stamp: 'sumim 9/19/2007 12:42'! orig: o dir: d ^self new setOrig: o dir: d; yourself! ! !RayBench class methodsFor: 'private' stamp: 'sumim 9/22/2007 01:56'! createLevel: level center: position radius: radius | sphere group factor | sphere := Sphere center: position radius: radius. level = 1 ifTrue: [^sphere]. group := Group bound: (Sphere center: position radius: 3.0 * radius). group objs add: sphere. factor := 3 * radius / 12 sqrt. #(-1 -1 -1 1 1 1 1 -1) pairsDo: [:dx :dz | | childPos | childPos := position + ({dx. 1. dz} * factor). group objs add: (self createLevel: level - 1 center: childPos radius: radius / 2.0)]. ^group! ! !RayBench class methodsFor: 'private' stamp: 'sumim 9/20/2007 23:57'! rayTraceLight: light ray: camRay scene: scene | hit refPos spGai spRay spHit delta infinity zeroVec | delta := 2.22045e-16 sqrt. infinity := Float infinity. zeroVec := #(0.0 0.0 0.0) asVec. hit := scene intersectHit: (Hit lambda: infinity normal: zeroVec) ray: camRay. hit lambda = infinity ifTrue: [^0]. refPos := camRay orig + (camRay dir * hit lambda) + (hit normal * delta). spGai := light dot: hit normal. spGai >= 0 ifTrue: [^0]. spRay := Ray orig: refPos dir: (light * -1). spHit := scene intersectHit: (Hit lambda: infinity normal: zeroVec) ray: spRay. ^spHit lambda = infinity ifTrue: [spGai negated] ifFalse: [0].! ! !RayBench class methodsFor: 'accessing' stamp: 'sumim 9/22/2007 03:00'! vecClass ^Vec1! ! !RayBench class methodsFor: 'example' stamp: 'sumim 9/22/2007 03:25'! pixelSize: px level: level "[self pixelSize: 64 level: 4] timeToRun milliSeconds" | scene out lf pxStr ss | ss := 4. scene := self createLevel: level center: #(0.0 -1.0 1.0) asVec radius: 1.0. out := FileStream fileNamed: 'image.pgm'. lf := String lf. pxStr := px printString. out nextPutAll: ('P5', lf, pxStr, ' ', pxStr, lf, '255', lf); binary. px - 1 to: 0 by: -1 do: [:y | 0 to: px - 1 do: [:x | | gain | gain := 0.0. 0 to: ss - 1 do: [:dx | 0 to: ss - 1 do: [:dy | | eye dir | dir := {x + (dx asFloat / ss) - (px / 2). y + (dy asFloat / ss) - (px / 2). px}. eye := Ray orig: #(0.0 0.0 -4.0) asVec dir: dir asVec unitise. gain := gain + (self rayTraceLight: #(-1.0 -3.0 2.0) asVec unitise ray: eye scene: scene)]]. out nextPut: (255 * gain / (ss * ss)) rounded]]. out close! ! !Sphere methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:43'! center ^center! ! !Sphere methodsFor: 'accessing' stamp: 'sumim 9/19/2007 12:43'! radius ^radius! ! !Sphere methodsFor: 'processing' stamp: 'sumim 9/20/2007 23:15'! intersectHit: hit ray: ray | len vec | len := self raySphere: ray. len >= hit lambda ifTrue: [^hit]. vec := ray orig + (ray dir * len - center). ^Hit lambda: len normal: vec unitise! ! !Sphere methodsFor: 'processing' stamp: 'sumim 9/20/2007 22:52'! raySphere: ray | vec b det sqDet t2 t1 | vec := center - ray orig. b := vec dot: ray dir. det := b * b - (vec dot: vec) + (radius * radius). det < 0 ifTrue: [^Float infinity]. sqDet := det sqrt. t2 := b + sqDet. t2 < 0 ifTrue: [^Float infinity]. t1 := b - sqDet. ^t1 > 0 ifTrue: [t1] ifFalse: [t2]! ! !Sphere methodsFor: 'private' stamp: 'sumim 9/19/2007 12:26'! setCenter: c radius: r center := c. radius := r! ! !Sphere class methodsFor: 'instance creation' stamp: 'sumim 9/19/2007 12:44'! center: c radius: r ^self new setCenter: c radius: r; yourself! ! !Vec methodsFor: 'processing' stamp: 'sumim 9/22/2007 02:39'! dot: other ^(self * other) sum! ! !Vec methodsFor: 'processing' stamp: 'sumim 9/22/2007 02:39'! unitise ^self / (self dot: self) sqrt! ! !Vec1 methodsFor: 'accessing' stamp: 'sumim 9/22/2007 01:31'! x ^x! ! !Vec1 methodsFor: 'accessing' stamp: 'sumim 9/22/2007 01:31'! y ^y! ! !Vec1 methodsFor: 'accessing' stamp: 'sumim 9/22/2007 01:31'! z ^z! ! !Vec1 methodsFor: 'arithmetic' stamp: 'sumim 9/22/2007 01:54'! * scale ^self class x: x * scale y: y * scale z: z * scale! ! !Vec1 methodsFor: 'arithmetic' stamp: 'sumim 9/22/2007 02:31'! + other (other isKindOf: Array) ifTrue: [^self class x: x + other first y: y + other second z: z + other third]. ^self class x: x + other x y: y + other y z: z + other z! ! !Vec1 methodsFor: 'arithmetic' stamp: 'sumim 9/22/2007 01:55'! - other ^self class x: x - other x y: y - other y z: z - other z! ! !Vec1 methodsFor: 'arithmetic' stamp: 'sumim 9/22/2007 01:48'! dot: other ^(x * other x) + (y * other y) + (z * other z)! ! !Vec1 methodsFor: 'arithmetic' stamp: 'sumim 9/22/2007 03:01'! unitise ^self * (1 / (self dot: self) sqrt)! ! !Vec1 methodsFor: 'private' stamp: 'sumim 9/22/2007 01:40'! setX: newX y: newY z: newZ x := newX. y := newY. z := newZ! ! !Vec1 class methodsFor: 'instance creation' stamp: 'sumim 9/22/2007 01:36'! newFrom: array ^self x: array first y: array second z: array third! ! !Vec1 class methodsFor: 'instance creation' stamp: 'sumim 9/22/2007 01:36'! x: x y: y z: z ^self new setX: x y: y z: z; yourself! ! !Vec2 methodsFor: 'arithmetic' stamp: 'sumim 9/20/2007 21:37'! dot: other ^(super * other) sum! ! !Vec2 methodsFor: 'arithmetic' stamp: 'sumim 9/20/2007 21:41'! unitise ^self / (self dot: self) sqrt! !