-
Notifications
You must be signed in to change notification settings - Fork 1
Home
Martín Dias edited this page May 7, 2025
·
12 revisions
Welcome to the PharoSDL3 wiki!
The following snippet should serve to generate again the bindings using CIG:
(For the record: SDL v3.2.10; Pharo 12; CIG on this commit).
lib := CigCLibraryGenerator new.
lib
prefix: 'S3';
packageName: 'SDL3';
libraryName: 'SDL3'.
lib
cIncludePath: './';
cIncludePath: './SDL';
cIncludePath: '/usr/include'.
{'_Bool'. #bool.
'const _Bool'. #bool.
'signed char'. #char.
'wchar_t'. #int.
} pairsDo: [ :a :b |
CigType typeMap at: a put: b ].
lib import: '/usr/include/stdint.h'.
lib import: './SDL/include/SDL3/SDL_assert.h'.
lib import: './SDL/include/SDL3/SDL_platform_defines.h'.
lib import: './SDL/include/SDL3/SDL_stdinc.h'.
lib import: './SDL/include/SDL3/SDL_properties.h'.
lib import: './SDL/include/SDL3/SDL_error.h'.
"basic utils (generally need only SDL_stdinc and SDL_error)"
lib import: './SDL/include/SDL3/SDL_version.h'.
lib import: './SDL/include/SDL3/SDL_init.h'.
lib import: './SDL/include/SDL3/SDL_time.h'.
lib import: './SDL/include/SDL3/SDL_timer.h'.
lib import: './SDL/include/SDL3/SDL_clipboard.h'.
lib import: './SDL/include/SDL3/SDL_cpuinfo.h'.
lib import: './SDL/include/SDL3/SDL_filesystem.h'.
lib import: './SDL/include/SDL3/SDL_misc.h'.
"video stuff"
lib import: './SDL/include/SDL3/SDL_endian.h'.
lib import: './SDL/include/SDL3/SDL_pixels.h'.
lib import: './SDL/include/SDL3/SDL_rect.h'.
lib import: './SDL/include/SDL3/SDL_blendmode.h'.
lib import: './SDL/include/SDL3/SDL_iostream.h'.
lib import: './SDL/include/SDL3/SDL_surface.h'.
lib import: './SDL/include/SDL3/SDL_video.h'.
lib import: './SDL/include/SDL3/SDL_render.h'.
lib import: './SDL/include/SDL3/SDL_gpu.h'.
"utils that need video"
lib import: './SDL/include/SDL3/SDL_dialog.h'.
lib import: './SDL/include/SDL3/SDL_messagebox.h'.
"input and events stuff"
lib import: './SDL/include/SDL3/SDL_sensor.h'.
lib import: './SDL/include/SDL3/SDL_mouse.h'.
lib import: './SDL/include/SDL3/SDL_touch.h'.
lib import: './SDL/include/SDL3/SDL_pen.h'.
lib import: './SDL/include/SDL3/SDL_scancode.h'.
lib import: './SDL/include/SDL3/SDL_keycode.h'.
lib import: './SDL/include/SDL3/SDL_keyboard.h'.
lib import: './SDL/include/SDL3/SDL_atomic.h'.
lib import: './SDL/include/SDL3/SDL_thread.h'.
lib import: './SDL/include/SDL3/SDL_mutex.h'.
lib import: './SDL/include/SDL3/SDL_audio.h'.
lib import: './SDL/include/SDL3/SDL_camera.h'.
lib import: './SDL/include/SDL3/SDL_power.h'.
lib import: './SDL/include/SDL3/SDL_guid.h'.
lib import: './SDL/include/SDL3/SDL_joystick.h'.
lib import: './SDL/include/SDL3/SDL_events.h'.
"other features"
lib import: './SDL/include/SDL3/SDL_asyncio.h'.
lib import: './SDL/include/SDL3/SDL_loadso.h'.
lib import: './SDL/include/SDL3/SDL_locale.h'.
lib import: './SDL/include/SDL3/SDL_platform.h'.
lib import: './SDL/include/SDL3/SDL_system.h'.
lib import: './SDL/include/SDL3/SDL_tray.h'.
"Generation signals an error, but the main work is done anyway:"
lib generate.
"After the error:"
S3SDL3Typedef initialize. "There was a problem with the order of variables in the generated #initialize... run it again."
"(Anyway, we must manually sort the lines of this method to allow the right initialization on load)"
"Delete unneeded code"
S3SDL_DUMMY_ENUM removeFromSystem.
S3SDL_alignment_test removeFromSystem.
(LibSDL3 >> #SDL_COMPILE_TIME_ASSERT) removeFromSystem.
(LibSDL3 >> #SDL_COMPILE_TIME_ASSERT:) removeFromSystem.
"Re-try struct initialization. The result should be empty:"
Array streamContents: [ :stream |
S3Structure allSubclassesDo: [ :each |
[each rebuildFieldAccessors] onErrorDo: [
stream nextPut: each ] ] ].
"Alternative to S3Enumeration class >> initialize"
S3Enumeration allSubclassesDo: #initializeEnumeration.
"Create S3SDLMappedEvent and make all events subclass of it with:"
evts := S3Structure subclasses select: [ :each | each name endsWith: 'Event' ].
evts := evts copyWithout: S3SDLMappedEvent.
evts do: [ :e | e superclass: S3SDLMappedEvent ]
Method rename post-processing script (pair-programmed with @tesonep, applied in https://github.com/pharo-graphics/PharoSDL3/commit/06b717f77afada9ecf6325af6e75ff4ef530846a):
prefixRules := {
'SDL_GL_' -> 'gl'.
'SDL_EGL_' -> 'egl'.
'SDL_GPU' -> 'gpu'.
'SDL_GUID' -> 'guid'.
'SDL_Create' -> 'new'.
'SDL_' -> '' }.
"First pass, fix prefixes"
renames := LibSDL3 selectors sorted
select: [ :each | prefixRules anySatisfy: [ :rule | each beginsWith: rule key ] ]
thenCollect: [ :oldSelector |
| newSelector rule newSelector |
rule := prefixRules detect: [ :rule | oldSelector beginsWith: rule key ].
newSelector := oldSelector allButFirst: rule key size.
newSelector := rule value, newSelector.
oldSelector -> newSelector ].
"Convert underscores to CamelCase"
renames withIndexDo: [ :assoc :index |
| newSelector |
newSelector := assoc value.
(assoc value includes: $_) ifTrue: [
newSelector :=
String streamContents: [ :writeStream | | readStream |
readStream := newSelector readStream.
[ readStream atEnd ] whileFalse: [
writeStream nextPutAll: (readStream upTo: $_) capitalized ] ].
renames
at: index
put: assoc key -> newSelector ] ].
"Make first letter lowercase"
renames withIndexDo: [ :assoc :index |
| newSelector |
newSelector := assoc value.
newSelector at: 1 put: (newSelector first asLowercase).
renames
at: index
put: assoc key -> newSelector ].
"model := (RBNamespace onEnvironment: (RBPackageEnvironment packageNames: #('SDL3' 'SDL3-Own' 'SDL3-Tests'))).
renames do: [ :assoc |
| changes |
changes :=
(ReRenameMethodRefactoring new
model: model;
renameMethod: assoc key
in: LibSDL3
to: assoc value
permutation: (1 to: assoc key numArgs);
renameChanges) changes.
changes do: #execute ] displayingProgress: [ :each | each asString ].
"
env := RBPackageEnvironment packageNames: #('SDL3' 'SDL3-Own' 'SDL3-Tests').
model := RBNamespace onEnvironment: env.
allChanges := renames flatCollect: [ :assoc |
| changes |
changes := (ReRenameMethodRefactoring new
model: model;
renameMethod: assoc key
in: LibSDL3
to: assoc value
permutation: (1 to: assoc key numArgs);
renameChanges) changes ].
allChanges do: #generateChanges.
It was executed in Pharo 12 with this patch in RBMethod
:
refersToSymbol: aSymbol
| searcher |
searcher := self parserTreeSearcher.
searcher
matches: aSymbol printString do: [ :node :answer | true ];
matches: '`#literal' do: [ :node :answer |
answer or: [
(node parent isMessage and: [(node parent selector beginsWith: 'ffiCall') not]) and: [
self literal: node value containsReferenceTo: aSymbol ] ] ].
aSymbol isValidSelector ifTrue: [
searcher
matches: '`@object '
, (self parseTreeSearcherClass buildSelectorString: aSymbol)
do: [ :node :answer | true ] ].
^ searcher executeTree: self parseTree initialAnswer: false
The enumerations were renamed with the following script (this commit and 3 extra classes afterwards):
(S3Enumeration allSubclasses sorted: [:a :b | a name < b name])
select: [ :enumClass | enumClass classSide includesSelector: #enumDecl ]
thenDo: [ :enumClass |
| renames env model allChanges |
renames := enumClass enumDeclToCamelCaseDictionary.
"Apply rename refactorings"
env := RBPackageEnvironment packageNames: #('SDL3' 'SDL3-Own' 'SDL3-Tests' 'SDL3-Image').
env := env & (RBSelectorEnvironment new addMethod: (enumClass classSide >> #enumDecl); yourself) not.
model := RBNamespace onEnvironment: env.
allChanges := OrderedCollection new.
renames keysAndValuesDo: [ :oldName :newName |
allChanges addAll: (ReRenameMethodRefactoring new
model: model;
renameMethod: oldName
in: enumClass classSide
to: newName
permutation: #();
renameChanges) changes ].
allChanges := allChanges reject: [ :e |
e class = RBAddMethodChange and: [
"e protocol ~= #'accessing enum'"
(e selector beginsWith: 'enumDecl') and: [
e changeClassName = enumClass name ] ] ].
allChanges do: #generateChanges ]
The following script renames the classes (see commit and next).
#(
'S3SDL_'
'S3SDL3'
'S3SDL'
'S3'
) do: [ :oldPrefix |
| renames |
renames := Smalltalk allClassesAndTraits
select: [ :each | each name beginsWith: oldPrefix ]
thenCollect: [ :each |
| newName |
"Remove old prefix"
newName := each name withoutPrefix: oldPrefix.
"Convert underscores to CamelCase"
newName := String streamContents: [ :writeStream | | readStream |
readStream := newName readStream.
[ readStream atEnd ] whileFalse: [
writeStream nextPutAll: (readStream upTo: $_) capitalized ] ].
"Add the new prefix"
newName := 'SDL3', newName.
each -> newName ].
renames do: [ :each |
(ReRenameClassRefactoring rename: each key name to: each value)
execute ]
]
This script renamed all struct methods that had underscores to camelCased (commit 34a7aac10):
SDL3Structure allSubclasses do: [ :structClass |
| renames env model allChanges |
renames := OrderedDictionary new.
structClass selectors
select: [:selector | selector includes: $_ ]
thenCollect: [ :selector |
| newName |
newName := String streamContents: [ :writeStream | | readStream |
readStream := selector readStream.
[ readStream atEnd ] whileFalse: [
writeStream nextPutAll: (readStream upTo: $_) capitalized ] ].
newName := newName uncapitalized.
renames add: selector -> newName ].
"Apply rename refactorings"
env := RBPackageEnvironment packageNames: #('SDL3' 'SDL3-Own' 'SDL3-Tests' 'SDL3-Image').
model := RBNamespace onEnvironment: env.
allChanges := OrderedCollection new.
renames keysAndValuesDo: [ :oldName :newName |
allChanges addAll: (ReRenameMethodRefactoring new
model: model;
renameMethod: oldName
in: structClass
to: newName
permutation: (1 to: oldName numArgs);
renameChanges) changes ].
allChanges := allChanges reject: [ :e |
e class = RBAddMethodChange and: [
(e changeClassName = #LibSDL3) or: [
(e selector = #fieldsDesc) ] ] ].
allChanges do: #generateChanges ]