Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
DotNetBridge documentation
Last updated at 11:05 pm UTC on 24 July 2019
Info retrieved from the Wayback Machine (www.archive.org) relating to a dot net connection for Squeak. Appears last updated around 2005 but may still be of some value?

An example


Here is a basic example to show how code that uses the bridge looks. It starts a .NET virtual machine, creates and manipulates an ArrayList, and uses Collection protocol to get a copy where all the Strings are reversed.

	| dotNet list reversed |
	dotNet := DotNet startNew.
	
	list := dotNet ArrayList new.
	list add: 'Hello'.
	list add: 'World'.

	Transcript show: list count. "Prints <<2>>"
	
	reversed := list collect: [:each | each reversed].
	
	Transcript show: reversed asArray. "Prints #('elloH' 'dlroW')"
	dotNet exitDotNet.


We automatically convert Strings and SmallIntegers to .NET Strings and Int32s, and vice-versa. We do the same with nil and booleans. Doubles are passed to .NET with single-precision and back to Squeak with full double-precision when necessary.

We plan to add support for integers of different lengths and more complete support for floating-point numbers in the future.

Starting a .NET virtual machine


The bridge uses TCP sockets to communicate with a .NET virtual machine running in another process. The .NET VM is represented in Squeak as an instance of class DotNet.

To start a new .NET VM from Squeak, send #startNew to DotNet.

	dotNet := DotNet startNew.


The Squeak and .NET VMs will communicate on some unused port.

To stop the .NET VM, send #exitDotNet to the DotNet instance. (The bridge was ported from Ruby, where all objects respond to :exit and exit the running VM.)

	dotNet exitDotNet.


Basic usage: creating objects, accessing members


Creating .NET objects looks very similar to creating Squeak objects, except that the .NET classes are found under an instance of DotNet.

	dotNet ArrayList new. "An ArrayList"


You can use namespaces to get to the classes as well, but you don't need to use them except to resolve ambiguity. For example, .NET has both System.Reflection.Emit.Label and System.Windows.Forms.Label classes, so you can use namespaces to tell the bridge which one you want to use.

	dotNet System Collections ArrayList. "the ArrayList class"
	
	dotNet System Reflection Emit Label. "a class of Labels for reflection"
	
	dotNet loadLibrary: 'System.Windows.Forms'.
	dotNet System Windows Forms Label. "a class of Labels for display"


If a class reference is ambiguous, the bridge will select one of the classes.

	dotNet Label. "??? Probably a System.Reflection.Emit.Label"


Once you have a .NET object, you can send messages to it just as you would to a Squeak object. Access to its properties and fields works the same way.

	button := dotNet Button new.
	
	button width: 30.
	button height: 70.
	
	Transcript show: button height. "Prints <<70>gt;"
	
	button performClick. "Clicks the button"


Collection entries are accessed using #at: and #at:put:. Lists are zero-based, following .NET conventions.

	list := dotNet ArrayList new.
	list add: 'Hello'.
	
	list at: 0. "'Hello'"
	
	list
		at: 0
		put: 'World'.
	
	list at: 0. "'World'"


When sending a .NET message with more than one parameter, you should use the entire .NET message name as the first part of the selector. You can name subsequent parts any way you'd like: I have usually just used "with". (This follows a convention set by #Smalltalk, a Smalltalk compiler for .NET.)

	dotNet ArrayList
		repeat: 'a'
		with: 5. "An ArrayList with 'a', 'a', 'a', 'a', 'a'"


The bridge is case-insensitive, which lets you send .NET messages using case conventions closer to usual Squeak style. However, you can use .NET uppercase style if you like.

	list := dotNet ArrayList new.
	list Count. "0"
	list count. "0"


Case-insensitivity can create ambiguity between .NET methods, fields, and properties. If there is ambiguity, the bridge will select one of the members.

Collections


You can index many .NET collections using #at: and #at:put:.

	| list table |
	list := dotNet ArrayList new.
	list add: 'Hello'.
	
	list at: 0. "'Hello'"
	
	table := dotNet Hashtable new.
	table
		at: 'color'
		put: 'blue'.
	
	table at: color. "'blue'"


The bridge supports using Collection protocol on any object that responds to Count and integer Item indexing, as well as on .NET Arrays (which respond to Length).

	| colors |
	colors := dotNet ArrayList new.
	colors
		add: 'red';
		add: 'green';
		add: 'blue'.
	
	colors do: [:each | Transcript show: each]. "prints <<red\r\ngreen\r\nblue>>"

Creating .NET arrays


Creating .NET arrays looks similar to creating other .NET objects; you can send #Array to a .NET Type to get its Array type object.

	| array |
	array := dotNet Object Array new: 3.
	array
		at: 0
		put: 'one'.
	
	array at: 0. "'one'"
	array length. "3"

Automatic conversions


The bridge performs some automatic conversions between Squeak and .NET objects.

Squeak .NET
SmallInteger Int32
String String
true/false Boolean
nil null
Double (sent to .NET) Single
Double (received from .NET) Single or Double

In the future, we would like to add support for other kinds of integers and more complete conversion for floating-point numbers.

These conversions seem to make for smoother code, but are not without their drawbacks. In particular, there is currently no easy way to call .NET methods of automatically-converted classes.

Using .NET libraries


Core libraries are loaded when you start the bridge, but many libraries, such as Windows Forms, are not. The bridge has a convenience method for loading some kinds of libraries; you can also load them by using methods of the .NET Assembly class.

Use #loadLibrary: to load libraries that are in the path or Globabl Assembly Cache. If you want to load a library from somewhere else, use Assembly.LoadFrom. LoadFrom requires a ".dll" or ".exe" extension on its parameter, but #loadLibrary: does not.

	dotNet loadLibrary: 'System.Windows.Forms'.
	
	dotNet Assembly loadFrom: 'c:\specialAssemblies\restaurantSimulation.dll'.


(The Ruby version of this bridge has another convenience method for the second kind of libraries, :loadLibraryFrom; we plan to add that method to this bridge soon.)

Handling .NET events


You can add a Squeak event handler to a .NET event by passing a block alongside the "add" method of the event.

	| button |
	button click add: [:sender :args | Transcript show: 'Button clicked!'].
	
	button performClick. "prints <<Button clicked!>>"


The arguments to the block are optional. The following code would also have worked.

	button click add: [Transcript show: 'Button clicked!'].


We plan to add a way to remove event handlers in the future.

More about delegates


You can use blocks to implement any .NET delegate in a similar way to how you would use them to implement event handlers. If you pass a block to a method that takes a delegate, the bridge will automatically create a delegate wrapper of the appropriate type for your block. (If you pass a block to a method that just takes Delegate, the bridge will create a ThreadStart.)

	| result |
	result := nil.
	(dotNet Thread new: [result := 'result from thread']) start.
As with event handler delegates, any arguments that the delegate might take are optional.


You can also create delegates of a particular type explicitly using #new on the delegate's type. (This is available starting with R4; in R3, you could use DotNet>>#makeDelegate.)

	| delegate |
	delegate = dotNet TypeFilter new: [:type :filterCriteria | type fullName = 'System.Collections.ArrayList'].
	
	delegate
		invoke: dotNet ArrayList
		with: nil. "true"
	
	delegate
		invoke: dotNet Hashtable
		with: nil. "false"

Exceptions


.NET exceptions are signalled in Squeak as instances of DotNetException. The bridge passes calls on DotNetException to .NET in the same way as for any other .NET object. #message contains the exception's message, and will work even if the rest of the bridge has exited. (This is particularly important during testing.)

	| list |
	[list := dotNet ArrayList new.
	list at: 1]
		on: DotNetException
		do: [:exception | Transcript show: exception getType fullName].

	"prints <<System.ArgumentOutOfRangeException>>"


Squeak exceptions can be handled even if they are raised from inside event handlers. However, the exceptions will unwind the stack back to before the call to .NET that preceded the exception. We are planning to make this behavior closer to regular Squeak exception handling in the future.

	| button |
	button := dotNet Button new.
	button click add: [:sender :args | self someMethodThatIsNotThere].
	
	[button performClick]
		on: MessageNotUnderstood
		do: [:exception | Transcript show: 'Got a MessageNotUnderstood'].
	
	"prints <<Got a MessageNotUnderstood>>"

More about types: static methods, Type objects


Calling static methods is similar to calling Squeak class methods.

	dotNet ArrayList
		repeat: 'a'
		with: 5.
	
	"an ArrayList with 'a', 'a', 'a', 'a', 'a'"


The "classes" retrieved from .NET can also be used as Type objects ...

	dotNet ArrayList fullName. "'System.Collections.ArrayList'"


... and Type objects can be used as .NET classes.

	(dotNet Type getType: 'System.Collections.ArrayList') new. "a new ArrayList"

Enumerated types


.NET enumerated type constants can be used as if they were static fields of the class.

	dotNet BindingFlags NonPublic.
	dotNet DockStyle Fill.


To combine multiple constants, you can use the Parse method of the .NET Enum class. We would like to add a more convenient syntax, probably involving the | operator, to the bridge.

	dotNet Enum
		parse: dotNet BindingFlags
		with: 'Public, NonPublic'.

Implementing interfaces


interfaces just by responding to the messages of the interface. (There's no need to declare that an object implements a particular interface.) For example, you can initialize ArrayLists by passing them an ICollection. If you want to use a Squeak Array to do so, you might implement ICollection as follows.

	Array>>#Count
		^self size
	
	Array>>CopyTo: targetArray with: startIndex
		self doWithIndex:
			[:each :i |
			targetArray
				at: startIndex + i
				put: each]
	
	Array>>#SyncRoot
		^self


You could then use Arrays to initialize ArrayLists.

	| list |
	list := dotNet ArrayList new: #(1 2 3).
	
	Transcript show: list Count. "prints <<3>>"
	Transcript show: (list at: 0). "prints <<1>>"
	Transcript show: (list at: 1). "prints <<2>>"
	Transcript show: (list at: 2). "prints <<3>>"


The methods above aren't all of ICollection. You don't have to implement all of the methods of an interface - the bridge will optimistically call the methods and signal MessageNotUnderstood if necessary. In the example above, ArrayList actually only uses Count, SyncRoot, and CopyTo - so there's no need to implement GetEnumerator and IsSynchronized. (Of course, it might or might not be wise to implement the full interface in a given situation anyway.)

Here's what the rest of the interface might look like.

	Array>>GetEnumerator
		^ArrayEnumerator new initialize: self
	
	Array>>#IsSynchronized
		^false
	
	ArrayEnumerator>>initialize: anArray
		array := anArray.
		index := -1.
	
	ArrayEnumerator>>Current
		^array at: index
	
	ArrayEnumerator>>MoveNext
		index := index + 1
	
	ArrayEnumerator>>Reset
		index := -1


Here are a few notes about the way the feature works.

  1. Unlike most names in the bridge, names of interface methods are case-sensitive - the Squeak method names must match the .NET method names exactly. We may relax this in a future release.
  2. Multiple-parameter methods follow similar naming conventions to those for sending messages to .NET - parts of the selector after the first must be called "with:".
  3. Properties are modeled as instance variable accessors would be. The selectors for a read-write Text property would be #Text and #Text:.
  4. The bridge automatically generates wrappers when you pass a Squeak object into a method that requires a certain interface. It does the same when you return an object from a method which has an interface for its return type (like GetEnumerator above).

There is at least one caveat about this feature: the bridge presently generates new wrappers each time it needs to, so object identity on the .NET side might be unreliable. We plan to firm this up in the future, at least for the case when you're using a Squeak object in the same interface role again and again.

Object identity


You can pass Squeak objects into .NET and get them back. The objects keep their identity on the .NET side.

	| list object table |
	list := dotNet ArrayList new.
	object := dotNet Object new.
	
	list add: object.
	
	list contains: object. "true"
	
	(list at: 0) == object. "true"


The bridge also uses the same proxy object each time you see a particular .NET object in Squeak.

	table := dotNet Hashtable new.
	list add: table.
	
	(list at: 1) == table. "true"


Known issues


.NET server processes left running
This is fixed in R4.

When a DotNet instance is let go without sending #exitDotNet to it, extra server processes (DotNetBridge.server.exe) can be left running. This might happen, for example, when trying out .NET code in a Workspace or when you exit the image with a live DotNet instance.

The bridge only creates one server process per instance of DotNet, rather than one for every DotNetObject, so things might not get too far out of hand.

We plan to fix this problem in two ways in the next release: send #exitDotNet during finalization and also to every live DotNet instance at image shutdown. This is safe to do yourself; you can also safely kill the .NET processes after shutting down.

Readme example missing a temporary variable
This is fixed in R4.

The example in the readme that comes with the SAR has a small problem: it's missing one temporary variable declaration. Of course, this is easy to remedy - the system will even add it for you after a warning.

DotNetObject is a Collection

DotNetObject extends one of the Collection classes in order to share its Collection protocol implementations, but this seems a bit suspicious to me. Maybe there is a better way.