Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
How do I programmatically create a block from a string?
Last updated at 12:20 pm UTC on 17 January 2006
On 29 December 2003, Nevin Pratt asked: How do I programmatically create a block from a string? The block's context would be the method that is creating the block. He got a lot of answers; each is listed separately below.

Ned Konz replied: Try this in a Workspace.
	model := nil.	"or set to Browser or Workspace, etc."
	stream := ReadWriteStream
				on: (String new: 100).
	stream nextPutAll: '[ 3 + 4 ]'.	"your code here in brackets"
	stream reset.
	(model respondsTo: #doItReceiver)
		ifTrue: [FakeClassPool adopt: model selectedClass.
			"Include model pool vars if any"
			rcvr := model doItReceiver.
			ctxt := model doItContext]
		ifFalse: [rcvr := ctxt := nil].
	result := [rcvr class evaluatorClass new
				evaluate: stream
				in: ctxt
				to: rcvr
				notifying: self
				ifFail: [FakeClassPool adopt: nil.
					^ #failedDoit]]
				on: OutOfScopeNotification
				do: [:ex | ex resume: true].
	FakeClassPool adopt: nil.

result value

(This code was also submitted as a change set CompileString-dtl.1.cs.gz by David Lewis- so it may end up in the image

Laurence Rozier noted: If temp vars don't matter, then Ned and Lex have provided examples. Also, you can use something like:
Compiler evaluate: '[myInstanceVar class] value' for: self logged: false
to access the instance variables of the object that's creating the block. If you intend for the block's code to access temporary variables declared in the method that created it, Workspace and Debugger provide two different approaches.

Question This does not look like something one does routinely. For what do you use it?
Answer Most apps don't but we all do it everyday - see ParagraphEditor evaluateSelection ...I use this type of thing all the time to add behaviors to instances with Morph Dynamic Behaviors which is on Squeak Map.

Daniel Altman suggested: Take a look at class side methods for BlockExpression class from the package "Logic Expression" which is available from SqueakMap.

Lex Spoon wrote: As a starting point, how about the simple Compiler evaluate?
	Compiler evaluate: '[:x | x + 1]'
By the way, if your ultimate goal is to programmatically create blocks out of chunks of code, then you can use blocks to hold the small chunks of code and then use "holey blocks" to combine them. For example, here is a holey block:
	[ Transcript show: 'at start'.
	  hole  value.
	  Transcript show: 'at end ].
This holey block (not a technical term :)) has a free variable named "hole" which can be filled in with different values. Here is a longer method that uses a holey block:
	createBlock:  hole1   with: hole2
		^[ Transcript show: 'at start'.
		  hole1 value.
		  Transcript show: 'in middle'.
		  hole2 value.
		  Transcript show: 'at end ].
Each call to the method will create a new block, and the holes of the block will be filled in with different chunks of code. hole1 and hole2 should themselves be blocks that have no arguments.

As a general warning, using strings to represent stuff tends to cause
extra difficulties compared to using objects that are richer. For example, you can have parse errors in strings at runtime, but the compiler will not let you have a parse error in a holey block. Furthermore, if you use a debugger while a holey block is running, you can trace where everything came from within the debugger; with strings, the debugger will be much less helpful.

So, unless you ultimate requirement involves strings, you probably want to use blocks instead, and you probably want to create larger blocks by using these "holey blocks".


And the best answer of all ;-) __ Nevin Pratt responded: I never got the "blocks from strings" code working inside of this Seaside context. It worked fine attached to a test method of a test class, and seemed to capture the context of the test method just fine, but for some reason I couldn't get it to work inside of Seaside, within the WARenderer instance context. Not sure exactly why (maybe it's the lose nut above the keyboard or something :-), but after that is when I realized that I really didn't need to get it working, because #perform: works just fine. So, chalk one up to embarrassment, for not seeing that solution sooner.