[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

test[sqlite] index

SwikiCodeRobot @> #testSqliteIndex

"Check Sqlite is actually included in the image"
(Smalltalk includesKey: #LibSqlite3) ifFalse: [
	^self print: 'Missing LibSqlite3 implementation'
].

[	self print: 'Using libsqlite3 version ', LibSqlite3 current version
] on: Error do: [:ex|
	self print: 'Error using libsqlite3 ', ex toString stream nextLine.
	^self reject: '[sqlite]'; abortPage
].

self print: 'Ok - LibSqlite3 API installed and working'.
self abortPage.



"Inject code for SqLite3 API"
(Smalltalk includesKey: #LibSqlite3) ifTrue: [
	^self abortPage
].


"Implementing LibSqlite3..."
FFIDynamicLibrary
	subclass: #LibSqlite3
	category: #LibSqlite3 !

! LibSqlite3 class methodsFor: #spec !
specLiteral
	" Private - Returns the specification literal of library file. "

	^#(
	#(sqlite3_libversion #(string #()))
	#(sqlite3_open #(int #( #(fName string) #(sqlite sqlite3PtrPtr) )))
	#(sqlite3_close #(int #(#(sqlite sqlite3Ptr))))
	#(sqlite3_changes #(int #(#(sqlite sqlite3Ptr))))
	#(sqlite3_exec #(int #(#(sqlite sqlite3Ptr) #(string string) #(callback sqlite3_exec_callback) #(voidPtr 'void *') #(stringPtr stringPtr))))
)! !

! LibSqlite3 class methodsFor: #builders !
stMessageHeader: msgHeader
	" Private - Return a message header string with nice smalltalk looking. "

	| result |
	result := super stMessageHeader: msgHeader.
	(result indexOf: #sqlite3_) = 1 ifTrue: [
		^result copyFrom: #sqlite3_ size + 1 to: result size
	].
	^result! !

! LibSqlite3 class methodsFor: #spec !
sqlite3Types
	" Private - Returns the sqlite types array. "

	| pool type ref |
	pool := PoolDictionary new.
	type := #sqlite3. ref := #void.  
	3 timesRepeat: [
		pool at: type put: ref.
		type := type ,#Ptr.
		ref := S8Ref refType: ref.  
	].
	^pool! !

! LibSqlite3 class methodsFor: #spec !
validFFITypeFor: selector
	" Private - Validate the type selector and returns the FFI type for selector. "

	| sqlite3 sqlite3Ptr |
	selector = #stringPtr ifTrue: [ ^S8Ref refType: #string ].
	selector = #sqlite3_exec_callback ifTrue: [ ^#pointer ].
	(selector includes: #sqlite) ifFalse: [ ^super validFFITypeFor: selector ].
	^self sqlite3Types at: selector
		ifAbsent: [ self error: 'Invalid FFI type for argument ',selector ]! !

! LibSqlite3 class methodsFor: #builders !
buildSpec: specs
	" Build spec method. "

	^'' "ignored - we resolve spec dynamically"! !

! LibSqlite3 class methodsFor: #spec !
spec
	" Return the specification of the library functions. "

	^self specFromLiteral: self specLiteral! ! 

! LibSqlite3 methodsFor: #accessing !
version
	" Returns the version string. "

	^self libversion! !

! LibSqlite3 methodsFor: #exec !
exec: sqlite string: string

	^self handle
		#sqlite3_exec: sqlite string: string
		callback: nil json voidPtr: nil json
		stringPtr: nil json ! !


"Generate bindings"
LibSqlite3 buildFromLiteral