Skip to content

Commit

Permalink
I am adding support for mesh gradients to Athens. Mesh gradients can …
Browse files Browse the repository at this point in the history
…be used to simulate gradients that cannot be implemented directly or efficiently through linear gradients and/or radial gradients such a gouraud shaded triangle, a coons patch, or a conical gradient.
  • Loading branch information
ronsaldo committed Oct 22, 2020
1 parent 84268b1 commit d8d323c
Show file tree
Hide file tree
Showing 13 changed files with 458 additions and 0 deletions.
6 changes: 6 additions & 0 deletions src/Athens-Cairo/AthensAbstractMeshPaintPatch.extension.st
@@ -0,0 +1,6 @@
Extension { #name : #AthensAbstractMeshPaintPatch }

{ #category : #'*Athens-Cairo' }
AthensAbstractMeshPaintPatch >> addToCairoMeshGradientPaint: meshGradientPaint [
self subclassResponsibility
]
102 changes: 102 additions & 0 deletions src/Athens-Cairo/AthensCairoMeshGradientPaint.class.st
@@ -0,0 +1,102 @@
"
I represent a mesh gradient in the Cairo backend.
"
Class {
#name : #AthensCairoMeshGradientPaint,
#superclass : #AthensCairoPatternPaint,
#pools : [
'AthensCairoDefinitions'
],
#category : #'Athens-Cairo-Paints'
}

{ #category : #paints }
AthensCairoMeshGradientPaint class >> createMeshGradientWithPatches: aListOfMeshPatches [
| paint |
paint := self primCreateMesh.

"note, we do #initialize here because instance was created by primitive"
paint initialize; populatePatches: aListOfMeshPatches.
^ paint
]

{ #category : #paints }
AthensCairoMeshGradientPaint class >> primCreateMesh [
^ self ffiCall: #(AthensCairoMeshGradientPaint cairo_pattern_create_mesh () )

]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> beginPatch [
^ self ffiCall:#( void cairo_mesh_pattern_begin_patch ( cairo_pattern_t self ))

]

{ #category : #accessing }
AthensCairoMeshGradientPaint >> colors: aSequenceOfColors [
aSequenceOfColors doWithIndex: [ :color :index |
self setCorner: index - 1 color: color
]
]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> curveVia: pt1 and: lastControlPoint to: endPoint [
self curveViaX: pt1 x Y: pt1 y viaX: lastControlPoint x Y: lastControlPoint y toX: endPoint x Y: endPoint y
]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> curveViaX: x1 Y: y1 viaX: x2 Y: y2 toX: x3 Y: y3 [
^ self ffiCall: #(void cairo_mesh_pattern_curve_to(cairo_pattern_t self,
double x1,
double y1,
double x2,
double y2,
double x3,
double y3))


]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> endPatch [
^ self ffiCall:#( void cairo_mesh_pattern_end_patch ( cairo_pattern_t self ))

]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> lineTo: aPoint [
self lineToX: aPoint x asFloat Y: aPoint y asFloat
]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> lineToX: x Y: y [
^ self ffiCall:#( void cairo_mesh_pattern_line_to ( cairo_pattern_t self, double x, double y ))

]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> moveTo: aPoint [
self moveToX: aPoint x asFloat Y: aPoint y asFloat
]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> moveToX: x Y: y [
^ self ffiCall:#( void cairo_mesh_pattern_move_to ( cairo_pattern_t self, double x, double y ))

]

{ #category : #private }
AthensCairoMeshGradientPaint >> populatePatches: aListOfMeshPatches [
aListOfMeshPatches do: [ :each | each addToCairoMeshGradientPaint: self ]
]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> setCorner: corner_num color: color [
self setCorner: corner_num r: color red g: color green b: color blue a: color alpha
]

{ #category : #'mesh pattern commands' }
AthensCairoMeshGradientPaint >> setCorner: corner_num r: red g: green b: blue a: alpha [
^ self ffiCall:#( void cairo_mesh_pattern_set_corner_color_rgba ( cairo_pattern_t self, uint corner_num, double red, double green, double blue, double alpha ))

]
5 changes: 5 additions & 0 deletions src/Athens-Cairo/AthensCairoSurface.class.st
Expand Up @@ -464,6 +464,11 @@ AthensCairoSurface >> createLinearGradient: aColorRamp start: aStartPoint stop:

]

{ #category : #paints }
AthensCairoSurface >> createMeshGradientWithPatches: aListOfMeshPatches [
^ AthensCairoMeshGradientPaint createMeshGradientWithPatches: aListOfMeshPatches
]

{ #category : #creation }
AthensCairoSurface >> createPath: aPathCreatingBlock [
^ builder createPath: aPathCreatingBlock
Expand Down
17 changes: 17 additions & 0 deletions src/Athens-Cairo/CoonsPaintPatch.extension.st
@@ -0,0 +1,17 @@
Extension { #name : #CoonsPaintPatch }

{ #category : #'*Athens-Cairo' }
CoonsPaintPatch >> addToCairoMeshGradientPaint: meshGradientPaint [
meshGradientPaint
beginPatch;
moveTo: (controlPoints at: 1);
curveVia: (controlPoints at: 2) and: (controlPoints at: 3) to: (controlPoints at: 4);
curveVia: (controlPoints at: 5) and: (controlPoints at: 6) to: (controlPoints at: 7);
curveVia: (controlPoints at: 8) and: (controlPoints at: 9) to: (controlPoints at: 10);
curveVia: (controlPoints at: 11) and: (controlPoints at: 12) to: (controlPoints at: 1);
setCorner: 0 color: colors first;
setCorner: 1 color: colors second;
setCorner: 2 color: colors third;
setCorner: 3 color: colors fourth;
endPatch
]
10 changes: 10 additions & 0 deletions src/Athens-Cairo/GenericPaintPatch.extension.st
@@ -0,0 +1,10 @@
Extension { #name : #GenericPaintPatch }

{ #category : #'*Athens-Cairo' }
GenericPaintPatch >> addToCairoMeshGradientPaint: meshGradientPaint [
meshGradientPaint beginPatch.
[
buildBlock value: meshGradientPaint
] ensure: [ meshGradientPaint endPatch ].

]
14 changes: 14 additions & 0 deletions src/Athens-Cairo/TrianglePaintPatch.extension.st
@@ -0,0 +1,14 @@
Extension { #name : #TrianglePaintPatch }

{ #category : #'*Athens-Cairo' }
TrianglePaintPatch >> addToCairoMeshGradientPaint: meshGradientPaint [
meshGradientPaint
beginPatch;
moveTo: controlPoints first;
lineTo: controlPoints second;
lineTo: controlPoints third;
setCorner: 0 color: colors first;
setCorner: 1 color: colors second;
setCorner: 2 color: colors third;
endPatch
]
37 changes: 37 additions & 0 deletions src/Athens-Core/AthensAbstractMeshPaintPatch.class.st
@@ -0,0 +1,37 @@
"
I am a patch in a mesh gradient.
"
Class {
#name : #AthensAbstractMeshPaintPatch,
#superclass : #Object,
#instVars : [
'controlPoints',
'colors'
],
#category : #'Athens-Core-Paints'
}

{ #category : #constructor }
AthensAbstractMeshPaintPatch class >> controlPoints: controlPoints colors: colors [
^ self new controlPoints: controlPoints; colors: colors; yourself
]

{ #category : #accessing }
AthensAbstractMeshPaintPatch >> colors [
^ colors
]

{ #category : #accessing }
AthensAbstractMeshPaintPatch >> colors: anObject [
colors := anObject
]

{ #category : #accessing }
AthensAbstractMeshPaintPatch >> controlPoints [
^ controlPoints
]

{ #category : #accessing }
AthensAbstractMeshPaintPatch >> controlPoints: anObject [
controlPoints := anObject
]
5 changes: 5 additions & 0 deletions src/Athens-Core/AthensSurface.class.st
Expand Up @@ -87,6 +87,11 @@ AthensSurface >> createLinearGradient: colorRamp start: pt1 stop: pt2 [
self shouldNotImplement
]

{ #category : #paints }
AthensSurface >> createMeshGradientWithPatches: aListOfMeshPatches [
self subclassResponsibility.
]

{ #category : #paths }
AthensSurface >> createPath: aPathBuilder [
"Create a path from provided path builder instance"
Expand Down
8 changes: 8 additions & 0 deletions src/Athens-Core/CoonsPaintPatch.class.st
@@ -0,0 +1,8 @@
"
I am patch that performs bilinear interpolation along four curved vertices. I can be used for simulating more complex gradients such as conical gradients.
"
Class {
#name : #CoonsPaintPatch,
#superclass : #AthensAbstractMeshPaintPatch,
#category : #'Athens-Core-Paints'
}
21 changes: 21 additions & 0 deletions src/Athens-Core/GenericPaintPatch.class.st
@@ -0,0 +1,21 @@
"
I am a generic patch whose content is built through path building style commands. I have rough correspondence to SVG mesh gradient paths.
"
Class {
#name : #GenericPaintPatch,
#superclass : #AthensAbstractMeshPaintPatch,
#instVars : [
'buildBlock'
],
#category : #'Athens-Core-Paints'
}

{ #category : #accessing }
GenericPaintPatch >> buildBlock [
^ buildBlock
]

{ #category : #accessing }
GenericPaintPatch >> buildBlock: anObject [
buildBlock := anObject
]
87 changes: 87 additions & 0 deletions src/Athens-Core/MeshGradientPaint.class.st
@@ -0,0 +1,87 @@
"
I am a gradient that is defined by the composition of multiple patches.
"
Class {
#name : #MeshGradientPaint,
#superclass : #AthensAbstractPaint,
#instVars : [
'patches'
],
#category : #'Athens-Core-Paints'
}

{ #category : #adding }
MeshGradientPaint >> addCircleSliceCenter: center radius: radius startAngle: sliceStartAngle endAngle: sliceEndAngle colors: colors [
| sliceStartPoint sliceEndPoint f sliceControlPoint1 sliceControlPoint2 sliceCenter |
sliceStartPoint := Point r: radius theta: sliceStartAngle.
sliceEndPoint := Point r: radius theta: sliceEndAngle.

"Circle subdivision algorithm from: https://blogs.igalia.com/dpino/2020/06/11/renderization-of-conic-gradients/ [October, 2020]"
f := ( ((sliceEndAngle - sliceStartAngle) / 4) tan) * 4 / 3.
sliceControlPoint1 := (sliceStartPoint x - (f * sliceStartPoint y)) @ (sliceStartPoint y + (f * sliceStartPoint x)).
sliceControlPoint2 := (sliceEndPoint x + (f * sliceEndPoint y)) @ (sliceEndPoint y - (f * sliceEndPoint x)).

"Transform the control points to the actual center."
sliceCenter := center.
sliceStartPoint := sliceStartPoint + center.
sliceControlPoint1 := sliceControlPoint1 + center.
sliceControlPoint2 := sliceControlPoint2 + center.
sliceEndPoint := sliceEndPoint + center.

self
buildPatchWith: [ :patchBuilder |
patchBuilder
moveTo: sliceCenter;
lineTo: sliceStartPoint;
curveVia: sliceControlPoint1 and: sliceControlPoint2 to: sliceEndPoint;
lineTo: sliceCenter;
colors: colors
].

]

{ #category : #adding }
MeshGradientPaint >> addCoonsPatchWithPoints: controlPoints colors: colors [
self assert: controlPoints size = 12.
self assert: colors size = 4.
^ self addPatch: (CoonsPaintPatch controlPoints: controlPoints colors: colors)
]

{ #category : #adding }
MeshGradientPaint >> addPatch: patch [
patches add: patch
]

{ #category : #adding }
MeshGradientPaint >> addTriangleWithPoints: controlPoints colors: colors [
self assert: controlPoints size = 3.
self assert: colors size = 3.
^ self addPatch: (TrianglePaintPatch controlPoints: controlPoints colors: colors)
]

{ #category : #converting }
MeshGradientPaint >> asAthensPaintOn: aCanvas [
^ aCanvas surface
createMeshGradientWithPatches: patches
]

{ #category : #adding }
MeshGradientPaint >> buildPatchWith: aBlock [
^ self addPatch: (GenericPaintPatch new buildBlock: aBlock)
]

{ #category : #initialization }
MeshGradientPaint >> initialize [
super initialize.
patches := OrderedCollection new.
]

{ #category : #accessing }
MeshGradientPaint >> patches [
^ patches
]

{ #category : #accessing }
MeshGradientPaint >> patches: aListOfPatches [
patches := aListOfPatches copy
]
8 changes: 8 additions & 0 deletions src/Athens-Core/TrianglePaintPatch.class.st
@@ -0,0 +1,8 @@
"
I am a patch that interpolates linearly the colors defined along the three vertices of triangle. I am equivalent to Gouraud shading.
"
Class {
#name : #TrianglePaintPatch,
#superclass : #AthensAbstractMeshPaintPatch,
#category : #'Athens-Core-Paints'
}

0 comments on commit d8d323c

Please sign in to comment.