for VisualWorks 7.7 with Jun780
| aBlock | aBlock := [3 + 4]. ^aBlock
==> BlockClosure [] in UndefinedObject>>unboundMethod
| aString anObject aBlock | aString := '[self + 4]'. anObject := 3. aBlock := Kernel.Compiler evaluate: aString for: anObject logged: false. ^aBlock
==> BlockClosure [] in SmallInteger>>unboundMethod
| aString anObject aContext aNamespace aMethod aBlock |
aString := '[self + 4]'.
anObject := 3.
aContext := thisContext.
aNamespace := Smalltalk.Core.
aMethod := Kernel.Compiler new
compile: aString
in: aContext
allowReceiver: true
class: anObject class
environment: aNamespace
noPattern: true
notifying: nil
ifFail: [^nil].
aBlock := anObject performMethod: aMethod with: aContext.
^aBlock
==> BlockClosure [] in SmallInteger>>unboundMethodwith:
| aBlock | aBlock := [3 + 4]. ^aBlock value
==> 7
| aString anObject aBlock | aString := '[self + 4]'. anObject := 3. aBlock := Kernel.Compiler evaluate: aString for: anObject logged: false. ^aBlock value
==> 7
| aString anObject aContext aNamespace aMethod aBlock |
aString := '[self + 4]'.
anObject := 3.
aContext := thisContext.
aNamespace := Smalltalk.Core.
aMethod := Kernel.Compiler new
compile: aString
in: aContext
allowReceiver: true
class: anObject class
environment: aNamespace
noPattern: true
notifying: nil
ifFail: [^nil].
aBlock := anObject performMethod: aMethod with: aContext.
^aBlock value
==> 7
[:a | 3 + a] value: 4
==> 7
[:x :y | x @ y] value: 3 value: 4
==> 3 @ 4
[:red :green :blue | Graphics.ColorValue red: red green: green blue: blue]
value: 0.5
value: 0.5
value: 1.0
==> ColorValue royalBlue
[:a | 3 + a] valueWithArguments: (Core.Array with: 4)
==> 7
[:x :y | x @ y] valueWithArguments: (Core.Array with: 3 with: 4)
==> 3 @ 4
[:red :green :blue | Graphics.ColorValue red: red green: green blue: blue]
valueWithArguments: (Core.Array with: 0.5 with: 0.5 with: 1.0)
==> ColorValue royalBlue
[Core.Transcript
clear;
flush] cull: Core.Date today cull: Core.Time now
[:date |
Core.Transcript
clear;
nextPutAll: date printString;
flush] cull: Core.Date today cull: Core.Time now
June 29, 2009
[:date :time |
Core.Transcript
clear;
nextPutAll: date printString;
space;
nextPutAll: time printString;
flush] cull: Core.Date today cull: Core.Time now
June 29, 2009 7:19:44 pm
[Core.Transcript
clear;
flush]
cullWithArguments: (Core.Array with: Core.Date today with: Core.Time now)
[:date |
Core.Transcript
clear;
nextPutAll: date printString;
flush]
cullWithArguments: (Core.Array with: Core.Date today with: Core.Time now)
June 29, 2009
[:date :time |
Core.Transcript
clear;
nextPutAll: date printString;
space;
nextPutAll: time printString;
flush]
cullWithArguments: (Core.Array with: Core.Date today with: Core.Time now)
June 29, 2009 7:19:44 pm
(Core.Time dateAndTimeNow detect: [:each | each isKindOf: Core.Time] ifNone: [nil])
ifNotNil:
[:it |
Core.Transcript
clear;
nextPutAll: it printString;
flush]
7:19:44 pm
| redBlock greenBlock blueBlock mainBlock |
redBlock :=
[Core.Transcript
show: 'red';
cr].
greenBlock :=
[Core.Transcript
show: 'green';
cr].
blueBlock :=
[Core.Transcript
show: 'blue';
cr].
mainBlock :=
[Core.Transcript clear.
redBlock value.
greenBlock value.
blueBlock value].
mainBlock value
red green blue
| redBlock greenBlock blueBlock mainBlock |
redBlock :=
[Core.Transcript
show: 'red';
cr.
^nil].
greenBlock :=
[Core.Transcript
show: 'green';
cr].
blueBlock :=
[Core.Transcript
show: 'blue';
cr].
mainBlock :=
[Core.Transcript clear.
redBlock value.
greenBlock value.
blueBlock value].
mainBlock value
red
[[[[[3] value + 4] value + 5] value + 6] value + 7] value
==> 25
[[[[[^3] value + 4] value + 5] value + 6] value + 7] value
==> 3
[[[[^[3] value + 4] value + 5] value + 6] value + 7] value
==> 7
[[[^[[3] value + 4] value + 5] value + 6] value + 7] value
==> 12
[[^[[[3] value + 4] value + 5] value + 6] value + 7] value
==> 18
[^[[[[3] value + 4] value + 5] value + 6] value + 7] value
==> 25
^[[[[[3] value + 4] value + 5] value + 6] value + 7] value
==> 25
| aBlock |
Core.Transcript clear.
aBlock :=
[| endTime |
endTime := Core.Time fromSeconds: Core.Time now asSeconds + 5.
[| currentTime |
currentTime := Core.Time now.
currentTime >= endTime ifTrue: [^nil].
Core.Transcript
show: currentTime printString;
cr.
(Core.Delay forSeconds: 1) wait] repeat].
aBlock value.
Core.Transcript
show: Core.Date today printString;
cr
7:38:59 pm 7:39:00 pm 7:39:01 pm 7:39:02 pm 7:39:03 pm
| aBlock |
Core.Transcript clear.
aBlock :=
[| endTime currentTime |
endTime := Core.Time fromSeconds: Core.Time now asSeconds + 5.
[currentTime := Core.Time now.
currentTime >= endTime] whileFalse:
[Core.Transcript
show: currentTime printString;
cr.
(Core.Delay forSeconds: 1) wait]].
aBlock value.
Core.Transcript
show: Core.Date today printString;
cr
7:39:44 pm 7:39:45 pm 7:39:46 pm 7:39:47 pm 7:39:48 pm June 29, 2009
| aBlock |
Core.Transcript clear.
aBlock :=
[:exit |
| endTime |
endTime := Core.Time fromSeconds: Core.Time now asSeconds + 5.
[| currentTime |
currentTime := Core.Time now.
currentTime >= endTime ifTrue: [exit value].
Core.Transcript
show: currentTime printString;
cr.
(Core.Delay forSeconds: 1) wait] repeat].
aBlock valueWithExit.
Core.Transcript
show: Core.Date today printString;
cr
7:40:13 pm 7:40:14 pm 7:40:15 pm 7:40:16 pm 7:40:17 pm June 29, 2009
| aSignal aBlock |
Core.Transcript clear.
aSignal := Core.Signal new.
aBlock :=
[| endTime |
endTime := Core.Time fromSeconds: Core.Time now asSeconds + 5.
[| currentTime |
currentTime := Core.Time now.
currentTime >= endTime ifTrue: [aSignal raise].
Core.Transcript
show: currentTime printString;
cr.
(Core.Delay forSeconds: 1) wait] repeat].
aBlock on: aSignal do: [:exception | ].
Core.Transcript
show: Core.Date today printString;
cr
7:40:36 pm 7:40:37 pm 7:40:38 pm 7:40:39 pm 7:40:40 pm June 29, 2009
【分岐】
anObject ifNil: ["不定のときの処理"]
| anObject |
Core.Transcript clear.
(anObject := nil)
ifNil: [Core.Transcript nextPutAll: anObject printString].
Core.Transcript flush
anObject ifNotNil: ["不定ではないときの処理"]
| anObject |
Core.Transcript clear.
(anObject := 123)
ifNotNil: [Core.Transcript nextPutAll: anObject printString].
Core.Transcript flush
anObject ifNotNil: [:it | "不定ではないときの処理"]
Core.Transcript clear. 123 ifNotNil: [:it | Core.Transcript nextPutAll: it printString]. Core.Transcript flush
anObject ifNil: ["不定のときの処理"] ifNotNil: ["不定ではないときの処理"]
| anObject |
Core.Transcript clear.
(anObject := 123)
ifNil: [Core.Transcript nextPutAll: anObject printString]
ifNotNil: [Core.Transcript nextPutAll: anObject printString].
Core.Transcript flush
anObject ifNil: ["不定のときの処理"] ifNotNil: [:it | "不定ではないときの処理"]
| anObject |
Core.Transcript clear.
(anObject := 123)
ifNil: [Core.Transcript nextPutAll: anObject printString]
ifNotNil: [:it | Core.Transcript nextPutAll: it printString].
Core.Transcript flush
aBoolean ifTrue: ["真のときの処理"]
Core.Transcript clear.
(Dialog confirm: 'Are you happy?')
ifTrue: [Core.Transcript nextPutAll: 'good'].
Core.Transcript flush
aBoolean ifFalse: ["偽のときの処理"]
Core.Transcript clear.
(Dialog confirm: 'Are you happy?')
ifFalse: [Core.Transcript nextPutAll: 'poor'].
Core.Transcript flush
aBoolean ifTrue: ["真のときの処理"] ifFalse: ["偽のときの処理"]
Core.Transcript clear.
(Dialog confirm: 'Are you happy?')
ifTrue: [Core.Transcript nextPutAll: 'good']
ifFalse: [Core.Transcript nextPutAll: 'poor'].
Core.Transcript flush
aBoolean and: ["真のときの処理"]
Core.Transcript clear.
(Dialog confirm: 'Are you happy?') and:
[Core.Transcript nextPutAll: 'good'.
true yourself].
Core.Transcript flush
aBoolean or: ["偽のときの処理"]
Core.Transcript clear.
(Dialog confirm: 'Are you happy?') or:
[Core.Transcript nextPutAll: 'poor'.
false yourself].
Core.Transcript flush
【繰り返し】
anInteger timesRepeat: ["繰り返し処理"]
Core.Transcript clear.
5 timesRepeat:
[Core.Transcript
nextPutAll: Core.Time now printString;
cr.
(Core.Delay
untilMilliseconds: (Core.Time millisecondClockValue + 1000 truncateTo: 1000))
wait].
Core.Transcript flush
anInterval do: [:each | "繰り返し処理"]
Core.Transcript clear.
(1 to: 10 by: 2) do:
[:each |
Core.Transcript
nextPutAll: each printString;
cr].
Core.Transcript flush
aCollection do: [:each | "繰り返し処理"]
Core.Transcript clear.
#(11 22 33 44 55) do:
[:each |
Core.Transcript
nextPutAll: each printString;
cr].
Core.Transcript flush
aCollection select: [:each | "繰り返し処理(選択条件)"]
Core.Transcript clear.
((1 to: 10 by: 1) select: [:each | each even])
do:
[:each |
Core.Transcript
nextPutAll: each printString;
cr].
Core.Transcript flush
aCollection reject: [:each | "繰り返し処理(排除条件)"]
Core.Transcript clear.
((1 to: 10 by: 1) reject: [:each | each even])
do:
[:each |
Core.Transcript
nextPutAll: each printString;
cr].
Core.Transcript flush
aCollection collect: [:each | "繰り返し処理(収集処理)"]
Core.Transcript clear.
((1 to: 10 by: 2) collect: [:each | each * 100])
do:
[:each |
Core.Transcript
nextPutAll: each printString;
cr].
Core.Transcript flush
aCollection detect: [:each | "繰り返し処理(検出条件)"]
[| aValue |
Core.Transcript clear.
aValue := (1 to: 10) detect: [:each | each factorial = 120].
Core.Transcript
nextPutAll: aValue printString;
cr.
Core.Transcript flush]
value
aCollection detect: [:each | "繰り返し処理(検出条件)"] ifNone: ["検出されなかった時の処理"]
[| aValue |
Core.Transcript clear.
aValue := (1 to: 10) detect: [:each | each factorial = 120] ifNone: [nil].
Core.Transcript
nextPutAll: aValue printString;
cr;
flush]
value
aCollection findFirst: [:each | "繰り返し処理(検出条件)"]
[| anIndex |
Core.Transcript clear.
anIndex := (10 to: 100 by: 10)
findFirst: [:each | 44 <= each and: [each <= 66]].
Core.Transcript
nextPutAll: anIndex printString;
cr;
flush]
value
aCollection findLast: [:each | "繰り返し処理(検出条件)"]
[| anIndex |
Core.Transcript clear.
anIndex := (10 to: 100 by: 10)
findLast: [:each | 44 <= each and: [each <= 66]].
Core.Transcript
nextPutAll: anIndex printString;
cr;
flush]
value
aCollection inject: anObject into: [:object :each | "繰り返し処理(注入処理)"]
[| aValue |
Core.Transcript clear.
aValue := (1 to: 10) inject: 0 into: [:total :each | total + each].
Core.Transcript
nextPutAll: aValue printString;
cr;
flush]
value
firstCollection with: secondCollection do: [:first :second | "繰り返し処理(並び替え条件)"]
[| anArray |
Core.Transcript clear.
anArray := #(111 222 333 444 555).
(1 to: anArray size) with: anArray
do:
[:index :each |
Core.Transcript
nextPutAll: index printString;
nextPutAll: ': ';
nextPutAll: each printString;
cr].
Core.Transcript flush]
value
["繰り返し条件"] whileTrue
[| expiredTime currentTime |
Core.Transcript clear.
expiredTime := Core.Time millisecondClockValue + 5000.
[| aBoolean |
(aBoolean := (currentTime := Core.Time millisecondClockValue) < expiredTime)
ifTrue:
[Core.Transcript
nextPutAll: Core.Time now printString;
cr.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait].
aBoolean yourself]
whileTrue.
Core.Transcript flush]
value
["繰り返し条件"] whileTrue: ["繰り返し処理"]
[| expiredTime currentTime |
Core.Transcript clear.
expiredTime := Core.Time millisecondClockValue + 5000.
[(currentTime := Core.Time millisecondClockValue) < expiredTime] whileTrue:
[Core.Transcript
nextPutAll: Core.Time now printString;
cr.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait].
Core.Transcript flush]
value
["繰り返し条件"] whileFalse
[| expiredTime currentTime |
Core.Transcript clear.
expiredTime := Core.Time millisecondClockValue + 5000.
[| aBoolean |
(aBoolean := (currentTime := Core.Time millisecondClockValue) >= expiredTime)
ifFalse:
[Core.Transcript
nextPutAll: Core.Time now printString;
cr.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait].
aBoolean yourself]
whileFalse.
Core.Transcript flush]
value
["繰り返し条件"] whileFalse: ["繰り返し処理"]
[| expiredTime currentTime |
Core.Transcript clear.
expiredTime := Core.Time millisecondClockValue + 5000.
[(currentTime := Core.Time millisecondClockValue) >= expiredTime] whileFalse:
[Core.Transcript
nextPutAll: Core.Time now printString;
cr.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait].
Core.Transcript flush]
value
aCollection do: [:each | "繰り返し処理"] separatedBy: ["繰り返しの間の処理"]
Core.Transcript
clear;
nextPutAll: '<'.
#(111 222 333 444 555)
do: [:each | Core.Transcript nextPutAll: each printString]
separatedBy: [Core.Transcript space].
Core.Transcript
nextPutAll: '>';
cr;
flush
【再帰】
| aBlock |
aBlock := ["前処理"
aBlock value. "再帰処理"
"後処理"].
aBlock value
| aBlock | aBlock := [:n | n <= 0 ifTrue: [0] ifFalse: [n + (aBlock value: n - 1)]]. aBlock value: 10
【巻き戻し】
["本処理"] ensure: ["後処理"]
| anImage aFilename aStream |
anImage := JunImageUtility fromDisplay: (0 @ 0 extent: 800 @ 600).
aFilename := 'zzz.jpg' asFilename.
aStream := JunJpegImageStream on: aFilename writeStream.
[Cursor write showWhile: [aStream nextPutImage: anImage]]
ensure: [aStream close]
JunControlUtility assert: ["前処理"] do: ["本処理"] ensure: ["後処理"]
| aFilename anImage |
aFilename := 'zzz.jpg' asFilename.
JunControlUtility
assert: [JunJpegImageStream on: aFilename readStream]
do: [:aStream | Cursor write showWhile: [anImage := aStream nextImage]]
ensure: [:aStream | aStream close].
JunImageDisplayModel show: anImage
【例外】
aSignal handle: [:exception | "例外処理"] do: ["本処理"]
Object errorSignal
handle:
[:exception |
Core.Transcript
clear;
nextPutAll: exception messageText asString;
cr;
flush]
do:
[3 seconds wait.
self error: 'Unexpected error']
["本処理"] on: aSignal do: ["例外処理"]
[3 seconds wait.
self error: 'Unexpected error']
on: Object errorSignal
do:
[:exception |
Core.Transcript
clear;
nextPutAll: exception messageText asString;
cr;
flush]
【並行】
"親処理" ["子処理"] fork. "親と子が並行に動作"
| aBlock |
aBlock :=
[:aString |
| expiredTime currentTime |
expiredTime := Core.Time millisecondClockValue + 5000.
[(currentTime := Core.Time millisecondClockValue) < expiredTime] whileTrue:
[Core.Transcript
nextPutAll: aString;
nextPutAll: Core.Time now printString;
cr;
flush.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait]].
Core.Transcript clear.
[aBlock value: 'child: '] fork.
[aBlock value: 'parent: '] value
| aProcess | "親処理" aProcess := ["子処理"] newProcess. aProcess resume. "親と子が並行に動作"
| aBlock aProcess |
aBlock :=
[:aString |
| expiredTime currentTime |
expiredTime := Core.Time millisecondClockValue + 5000.
[(currentTime := Core.Time millisecondClockValue) < expiredTime] whileTrue:
[Core.Transcript
nextPutAll: aString;
nextPutAll: Core.Time now printString;
cr;
flush.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait]].
Core.Transcript clear.
aProcess := [aBlock value: 'child: '] newProcess.
aProcess resume.
[aBlock value: 'parent: '] value
【約束】
"親処理" ["子処理"] promise. "親と子が並行に動作"
| aBlock |
aBlock :=
[:aString |
| expiredTime currentTime |
expiredTime := Core.Time millisecondClockValue + 5000.
[(currentTime := Core.Time millisecondClockValue) < expiredTime] whileTrue:
[Core.Transcript
nextPutAll: aString;
nextPutAll: Core.Time now printString;
cr;
flush.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait]].
Core.Transcript clear.
[aBlock value: 'child: '] promise.
[aBlock value: 'parent: '] value
| aPromise | "親処理" aPromise := ["子処理"] promise. "親と子が並行に動作" aPromise value "親が子を待ち合わせ"
| aPromise aBlock |
aPromise := nil.
aBlock :=
[:aString |
| expiredTime limitTime currentTime |
expiredTime := Core.Time millisecondClockValue + 5000.
limitTime := expiredTime - 3000.
[(currentTime := Core.Time millisecondClockValue) < expiredTime] whileTrue:
[currentTime > limitTime ifTrue: [aPromise ifNotNil: [:it | it value: nil]].
Core.Transcript
nextPutAll: aString;
nextPutAll: Core.Time now printString;
cr;
flush.
(Core.Delay untilMilliseconds: (currentTime + 1000 truncateTo: 1000)) wait]].
Core.Transcript clear.
aPromise := [aBlock value: 'child: '] promise.
aPromise value.
[aBlock value: 'parent: '] value
【継続】
反復:IS (Iteration Style)
| factorial |
factorial :=
[:n |
| a |
(n isInteger not or: [n negative]) ifTrue: [^self error: 'boo!'].
a := 1.
(1 to: n) do: [:i | a := a * i].
a yourself].
factorial value: 10
再帰:RS (Recursion Style)
| factorial |
factorial :=
[:n |
| a |
(n isInteger not or: [n negative]) ifTrue: [^self error: 'boo!'].
a := n = 0 ifTrue: [1] ifFalse: [(factorial value: n - 1) * n].
a yourself].
factorial value: 10
継続:CPS (Continuation Passing Style)
| factorial |
factorial :=
[:n :continuation |
(n isInteger not or: [n negative]) ifTrue: [^self error: 'boo!'].
n = 0
ifTrue: [continuation value: 1]
ifFalse: [factorial value: n - 1 value: [:a | continuation value: a * n]].
n halt].
factorial value: 10 value: [:a | ^a]
継続(コンティニュエーション・パッシング・スタイル)を用いて階乗計算を行うプログラムの実行過程を、 プログラム(ソースコード)として生成し、整形し、実行し、その結果を獲得するプログラム。
| anInteger anInterval aStream aCode aTree aResult |
anInteger := 10.
anInterval := 0 to: anInteger.
aStream := String new writeStream.
aCode :=
[anInterval do:
[:n |
| s |
s := n printString.
aStream nextPutAll: '| con' , s , ' | con' , s , ' := '.
n < anInterval last
ifTrue: [aStream nextPutAll: '[:a' , s , ' | ']
ifFalse: [aStream nextPutAll: '[:a | ^a]. ']].
anInterval reverse do:
[:n |
| s |
s := n printString.
aStream nextPutAll: 'con' , s , ' value: '.
n > anInterval first
ifTrue:
[| r |
r := (n - 1) printString.
aStream nextPutAll: 'a' , r , ' * ' , s , ']. ']
ifFalse: [aStream nextPutAll: '1']].
aStream contents]
ensure: [aStream close].
aTree := Refactory.Browser.RBParser parseExpression: aCode.
aCode := aTree formattedCode.
aResult := Kernel.Compiler evaluate: aCode.
Core.Transcript
clear;
nextPutAll: aCode;
cr;
nextPutAll: '==> ';
nextPutAll: aResult printString.
^aResult
トランスクリプトには次のように出力されます。 conNがfactorialNのコンティニュエーションを意味しています。
| con0 |
con0 :=
[:a0 |
| con1 |
con1 :=
[:a1 |
| con2 |
con2 :=
[:a2 |
| con3 |
con3 :=
[:a3 |
| con4 |
con4 :=
[:a4 |
| con5 |
con5 :=
[:a5 |
| con6 |
con6 :=
[:a6 |
| con7 |
con7 :=
[:a7 |
| con8 |
con8 :=
[:a8 |
| con9 |
con9 :=
[:a9 |
| con10 |
con10 := [:a | ^a].
con10 value: a9 * 10].
con9 value: a8 * 9].
con8 value: a7 * 8].
con7 value: a6 * 7].
con6 value: a5 * 6].
con5 value: a4 * 5].
con4 value: a3 * 4].
con3 value: a2 * 3].
con2 value: a1 * 2].
con1 value: a0 * 1].
con0 value: 1
==> 3628800
for VisualWorks 7.7 with Jun780