Skip to content

Commit

Permalink
add support for OpenGL blitting of Cairo surfaces
Browse files Browse the repository at this point in the history
2008-05-30  Paolo Bonzini  <bonzini@gnu.org>

	* examples/CairoBlit.st: Hack together OpenGL support here.

packages/cairo:
2008-05-30  Paolo Bonzini  <bonzini@gnu.org>

	* CairoContext.st: Add #operator and #operator:.
	* CairoFuncs.st: Add cairo_{get,set}_operator.
	* CairoSurface.st: Add #free.

packages/opengl:
2008-05-30  Paolo Bonzini  <bonzini@gnu.org>

	* OpenGL.st: Add glPushAttrib, glPopAttrib, glBlendFunc,
	glTexSubImage1D, glTexSubImage2D.

packages/sdl:
2008-05-30  Paolo Bonzini  <bonzini@gnu.org>

	* libsdl/Display.st: Add #shutdown.  Move SdlGLDisplay...
	* libsdl_gl/Display.st: ... here.
	* cairo/CairoSDL.st: Add OpenGL support.
  • Loading branch information
bonzini committed May 30, 2008
1 parent 6fc44a7 commit 1940cf6
Show file tree
Hide file tree
Showing 17 changed files with 351 additions and 75 deletions.
4 changes: 4 additions & 0 deletions ChangeLog
@@ -1,3 +1,7 @@
2008-05-30 Paolo Bonzini <bonzini@gnu.org>

* examples/CairoBlit.st: Hack together OpenGL support here.

2008-05-30 Paolo Bonzini <bonzini@gnu.org>

* kernel/CObject.st: Fix CByte.
Expand Down
2 changes: 2 additions & 0 deletions configure.ac
Expand Up @@ -416,6 +416,8 @@ GST_PACKAGE_ENABLE([LibSDL], [sdl/libsdl],
AM_CONDITIONAL([HAVE_COCOA], [test $gst_cv_sdl_uses_cocoa = yes])],
[gst_cv_sdl],
[Makefile], [sdl.la])
GST_PACKAGE_ENABLE([LibSDL_GL], [sdl/libsdl_gl], [],
[gst_cv_sdl gst_cv_opengl_libs])
GST_PACKAGE_ENABLE([CairoSDL], [sdl/cairo],
[],
[ac_cv_lib_cairo_cairo_save gst_cv_sdl])
Expand Down
26 changes: 21 additions & 5 deletions examples/CairoBlit.st
Expand Up @@ -30,6 +30,7 @@


PackageLoader fileInPackage: #CairoSDL.
PackageLoader fileInPackage: #'LibSDL_GL'.

SDL.SdlEventHandler subclass: BlitDemo [
<import: SDL>
Expand All @@ -43,26 +44,40 @@ SDL.SdlEventHandler subclass: BlitDemo [
]

run [
SdlDisplay current: SdlGLDisplay new.
SdlDisplay current eventSource handler: self; startEventLoop.
Processor activeProcess terminateOnQuit.
self winningDirectAccess.
SdlDisplay current isGLDisplay ifFalse: [ self winningDirectAccess ].
self blitStuff.
]

randomColorComponent [
^ ((Random between: 0 and: 255) / 255) asFloat
]

transparentFill: surface [
"Just an example that would allow showing other OpenGL stuff behind
the Cairo graphics."
surface withContextDo: [ :context |
context
operator: #source;
sourceRed: 0 green: 0 blue: 0 alpha: 0;
paint;
operator: #over ].
]

blitStuff [
| maxw maxh x y w h startTime count surface |
| maxw maxh x y w h startTime count surface frameRects |
startTime := Time millisecondClock.
surface := Cairo.CairoSdlSurface on: SdlDisplay current.
count := 0.
maxw := SdlDisplay current extent x.
maxh := SdlDisplay current extent y.
frameRects := SdlDisplay current isGLDisplay ifTrue: [1] ifFalse: [100].
SdlDisplay current isGLDisplay ifTrue: [ self transparentFill: surface ].
[
surface withContextDo: [ :context |
100 timesRepeat: [
frameRects timesRepeat: [
x := Random between: 0 and: maxw.
y := Random between: 0 and: maxh.
w := Random between: 0 and: maxw - x.
Expand All @@ -74,10 +89,11 @@ SDL.SdlEventHandler subclass: BlitDemo [
blue: self randomColorComponent;
fill: [ context rectangle: (x@y extent: w@h)]]].

Transcript << count << ' frames, '
count \\ 100 == 0 ifTrue: [
Transcript << count << ' frames, '
<< (count / ((Time millisecondClock - startTime) / 1000.0))
<< ' fps'; nl.
Processor yield.
Processor yield ].
] repeat.
]

Expand Down
12 changes: 12 additions & 0 deletions packages/cairo/CairoContext.st
Expand Up @@ -692,6 +692,12 @@ CairoContextProvider subclass: CairoContext [
^self class lookupLineJoinValue: (Cairo getLineJoin: context).
]

operator [
"Set how cairo will composite the destination, source and mask."
<category: 'accessing'>
^self class lookupOperatorValue: (Cairo getOperator: context).
]

miterLimit [
"Answer the miter limit of the cairo context, i.e. the ratio between
miter length and line width above which a #miter line join is
Expand Down Expand Up @@ -732,6 +738,12 @@ CairoContextProvider subclass: CairoContext [
Cairo setLineJoin: context lineJoin: (self class lookupLineJoin: aSymbol).
]

operator: aSymbol [
"Set how cairo will composite the destination, source and mask."
<category: 'accessing'>
Cairo setOperator: context operator: (self class lookupOperator: aSymbol).
]

miterLimit: aNumber [
"Answer the miter limit of the cairo context, i.e. the ratio between
miter length and line width above which a #miter line join is
Expand Down
8 changes: 8 additions & 0 deletions packages/cairo/CairoFuncs.st
Expand Up @@ -355,6 +355,10 @@ CairoContext.'>
<cCall: 'cairo_get_line_width' returning: #double args: #(#cObject )>
]

Cairo class >> getOperator: cr [
<cCall: 'cairo_get_operator' returning: #int args: #(#cObject )>
]

Cairo class >> setSource: cr source: source [
<cCall: 'cairo_set_source' returning: #void args: #(#cObject #cObject )>
]
Expand Down Expand Up @@ -391,6 +395,10 @@ CairoContext.'>
<cCall: 'cairo_set_line_width' returning: #void args: #(#cObject #double )>
]

Cairo class >> setOperator: cr operator: lineJoin [
<cCall: 'cairo_set_operator' returning: #void args: #(#cObject #int )>
]

Cairo class >> showText: cr utf8: utf8 [
<cCall: 'cairo_show_text' returning: #void args: #(#cObject #string )>
]
Expand Down
5 changes: 5 additions & 0 deletions packages/cairo/CairoSurface.st
Expand Up @@ -73,6 +73,11 @@ CairoContextProvider subclass: CairoSurface [
]

finalize [
<category: 'private-finalization'>
self free
]

free [
<category: 'private-finalization'>
surface ifNil: [ ^self ].
Cairo surfaceDestroy: surface.
Expand Down
6 changes: 6 additions & 0 deletions packages/cairo/ChangeLog
@@ -1,3 +1,9 @@
2008-05-30 Paolo Bonzini <bonzini@gnu.org>

* CairoContext.st: Add #operator and #operator:.
* CairoFuncs.st: Add cairo_{get,set}_operator.
* CairoSurface.st: Add #free.

2008-05-06 Paolo Bonzini <bonzini@gnu.org>

* CairoContext.st: Use GCed CStructs.
Expand Down
5 changes: 5 additions & 0 deletions packages/opengl/ChangeLog
@@ -1,3 +1,8 @@
2008-05-30 Paolo Bonzini <bonzini@gnu.org>

* OpenGL.st: Add glPushAttrib, glPopAttrib, glBlendFunc,
glTexSubImage1D, glTexSubImage2D.

2008-05-20 Paolo Bonzini <bonzini@gnu.org>

* gstGlu.c: Fix pasto.
Expand Down
34 changes: 32 additions & 2 deletions packages/opengl/OpenGL.st
Expand Up @@ -198,6 +198,18 @@ See OpenGL programming guide for more informations.'>

]

glPushAttrib: aProperty [
<category: 'GL'>
<cCall: 'glPushAttrib' returning: #void args: #( #int )>

]

glPopAttrib [
<category: 'GL'>
<cCall: 'glPopAttrib' returning: #void args: #( #void )>

]

glEnable: aProperty [
<category: 'GL'>
<cCall: 'glEnable' returning: #void args: #( #int )>
Expand Down Expand Up @@ -246,6 +258,12 @@ See OpenGL programming guide for more informations.'>

]

glBlendFunc: sfactor dfactor: dfactor [
<category: 'GL'>
<cCall: 'glBlendFunc' returning: #void args: #(#int #int)>

]

glBegin: type [
<category: 'GL'>
<cCall: 'glBegin' returning: #void args: #(#int)>
Expand Down Expand Up @@ -556,13 +574,25 @@ See OpenGL programming guide for more informations.'>

glTexImage1D: target level: level internalFormat: internalFormat width: aWidht border: aBorder format: aFormat type: aType pixels: pixels [
<category: 'Textures'>
<cCall: 'glTexImage1D' returning: #void args: #(#int #int #int #int #int #int #int #byteArray)>
<cCall: 'glTexImage1D' returning: #int args: #(#int #int #int #int #int #int #int #cObject)>

]

glTexImage2D: target level: level internalFormat: internalFormat width: aWidht height: aHeight border: aBorder format: aFormat type: aType pixels: pixels [
<category: 'Textures'>
<cCall: 'glTexImage2D' returning: #void args: #(#int #int #int #int #int #int #int #int #byteArray)>
<cCall: 'glTexImage2D' returning: #int args: #(#int #int #int #int #int #int #int #int #cObject)>

]

glTexSubImage1D: target level: level xoffset: xoffset yoffset: yoffset width: aWidht format: aFormat type: aType pixels: pixels [
<category: 'Textures'>
<cCall: 'glTexSubImage1D' returning: #int args: #(#int #int #int #int #int #int #int #cObject)>

]

glTexSubImage2D: target level: level xoffset: xoffset yoffset: yoffset width: aWidht height: aHeight format: aFormat type: aType pixels: pixels [
<category: 'Textures'>
<cCall: 'glTexSubImage2D' returning: #int args: #(#int #int #int #int #int #int #int #int #cObject)>

]

Expand Down
10 changes: 10 additions & 0 deletions packages/sdl/ChangeLog
@@ -0,0 +1,10 @@
2008-05-30 Paolo Bonzini <bonzini@gnu.org>

* libsdl/Display.st: Add #shutdown. Move SdlGLDisplay...
* libsdl_gl/Display.st: ... here.
* cairo/CairoSDL.st: Add OpenGL support.

2008-05-06 Paolo Bonzini <bonzini@gnu.org>

* libsdl/Display.st: Use GCed CStructs.

0 comments on commit 1940cf6

Please sign in to comment.