サンタクロース問題を Squeak Smalltalk で 4


id:sumim:20070612:p1 の続きで、こんどは結城さんの 結城浩のはてな日記 - サンタクロース問題を解く(Java) における Java 版を Squeak Smalltalk に。


Ruby と違って Java だと Smalltalk へ直訳っぽく…というのは無理みたいで、書いていていろいろと発見があって面白かったです。

Object subclass: #CyclicBarrier
    instanceVariableNames: 'waitingParties awaitingProcess numOfParties barrierAction'

CyclicBarrier>>initialize
    waitingParties := SharedQueue new

CyclicBarrier>>await
    | process |
        waitingParties size < (numOfParties - 1)
            ifTrue: [
                process := Processor activeProcess.
                waitingParties nextPut: process.
                process wait]
            ifFalse: [
                barrierAction value.
                numOfParties - 1 timesRepeat: [waitingParties next notify]]

CyclicBarrier>>setParties: anInteger action: aBlock
    numOfParties := anInteger.
    barrierAction := aBlock


CyclicBarrier class>>parties: numOfParties
    ^self parties: numOfParties action: []

CyclicBarrier class>>parties: numOfParties action: actionBlock
    ^self new setParties: numOfParties action: actionBlock; yourself
Process subclass: #Santa
    instanceVariableNames: 'readyAllElvesToWork readyAllReindeersToWork reindeerPlayBarrier elfPlayBarrier reindeerWorkBarrier elfWorkBarrier sema workers'
    classVariableNames: 'ElfNum ReindeerNum'

Santa>>initialize
    readyAllElvesToWork := false.
    readyAllReindeersToWork := false.

    reindeerWorkBarrier := CyclicBarrier
        parties: ReindeerNum
        action: [self notifyAllReindeersAreReadyToWork].
    elfWorkBarrier := CyclicBarrier
        parties: ElfNum
        action: [self notifyAllElvesAreReadyToWork].

    reindeerPlayBarrier := CyclicBarrier parties: ReindeerNum + 1.
    elfPlayBarrier := CyclicBarrier parties: ElfNum + 1.

    sema := Semaphore new.
    Santa out flush

Santa>>notifyAllElvesAreReadyToWork
    Santa out nextPut: 'All elves are ready to work!!'.
    readyAllElvesToWork := true.
    self notify

Santa>>notifyAllReindeersAreReadyToWork
    Santa out nextPut: 'All reindeers are ready to work!!'.
    readyAllReindeersToWork := true.
    self notify

Santa>>startAllWorkers
    | worker |
    workers := OrderedCollection new.
    (1 to: ReindeerNum) do: [:i |
        worker := Worker
            named: 'Reindeer No.', i printString
            workBarrier: reindeerWorkBarrier
            playBarrier: reindeerPlayBarrier.
        workers add: worker.
        worker resume
    ].

    (1 to: ElfNum) do: [:i |
        worker := Worker
            named: 'Elf No.', i printString
            workBarrier: elfWorkBarrier
            playBarrier: elfPlayBarrier.
        workers add: worker.
        worker resume
    ]

Santa>>run
    self startAllWorkers.
    [    [readyAllElvesToWork not and: [readyAllReindeersToWork not]] whileTrue: [
            self wait
        ].

        readyAllReindeersToWork ifTrue: [
            readyAllReindeersToWork := false.
            reindeerPlayBarrier await
        ].

        readyAllElvesToWork ifTrue: [
            readyAllElvesToWork := false.
            elfPlayBarrier await
        ]
    ] repeat

Santa>>workers
    ^workers

Santa>>notify
    sema signal

Santa>>wait
    sema wait


Santa class
    instanceVariableNames: 'out'

Santa class>>initialize
    ReindeerNum := 9.
    ElfNum := 3.
    out := SharedQueue new
"Santa initialize"

Santa class>>new
    | newProcess |
    newProcess _ super new.
    newProcess suspendedContext: [newProcess run. Processor terminateActive] asContext.
    newProcess priority: Processor activePriority.
    ^newProcess

Santa class>>example
    | santa |

    World findATranscript: nil.
    Transcript clear.

    santa := Santa new.
    santa resume.
    (Delay forSeconds: 8) wait.
    santa workers do: [:wk | wk terminate].
    santa terminate.
    Santa out size timesRepeat: [Transcript cr; show: Santa out next]
"self example"

Santa class>>out
    ^out
Process subclass: #Worker
    instanceVariableNames: 'workBarrier playBarrier sema'

Worker>>setName: nameString workBarrier: wBarrier playBarrier: pBarrier
    self name: nameString.
    workBarrier := wBarrier.
    playBarrier := pBarrier.
    Santa out nextPut: self name, ' is born.'

Worker>>play
    Santa out nextPut: self name, ' is waiting to play.'.
    playBarrier await.
    self randomSleep

Worker>>work
    Santa out nextPut: self name, ' is waiting to work.'.
    workBarrier await.
    self randomSleep

Worker>>randomSleep
    (Delay forMilliseconds: 1000 atRandom) wait

Worker>>run
    [self work; play] repeat

Worker>>notify
    sema signal

Worker>>wait
    sema wait

Worker>>initialize
    sema := Semaphore new

Worker class>>named: nameString workBarrier: wBarrier playBarrier: pBarrier
    | newProcess |
    newProcess := self new.
    newProcess setName: nameString workBarrier: wBarrier playBarrier: pBarrier.
    newProcess suspendedContext: [newProcess run. Processor terminateActive] asContext.
    newProcess priority: Processor activePriority.
    ^newProcess


Squeak Smalltlak には CyclicBarrier のようなクラスを見つけられなかったので、自前でなんちゃって版を用意しました。あと、Java の Object#wait()、#notify() っぽいものも、Santa と Worker にはセマフォへの委譲でしつらえてあります(くだんの CyclicBarrier でもそれらを使っています)。加えて、Squeak のトランスクリプト(環境内の標準出力っぽい機構)は、排他的処理がちょっとおかしいみたいなので、Santa のクラスインスタンス変数 out に関連づけた a SharedQueue で代用しました。一定時間実行後、out の内容をトランスクリプトにはき出しています。


Santa example の出力例はこんな感じ。

Reindeer No.1 is born.
Reindeer No.2 is born.
Reindeer No.3 is born.
Reindeer No.4 is born.
Reindeer No.5 is born.
Reindeer No.6 is born.
Reindeer No.7 is born.
Reindeer No.8 is born.
Reindeer No.9 is born.
Elf No.1 is born.
Elf No.2 is born.
Elf No.3 is born.
Reindeer No.1 is waiting to work.
Reindeer No.2 is waiting to work.
Reindeer No.3 is waiting to work.
Reindeer No.4 is waiting to work.
Reindeer No.5 is waiting to work.
Reindeer No.6 is waiting to work.
Reindeer No.7 is waiting to work.
Reindeer No.8 is waiting to work.
Reindeer No.9 is waiting to work.
All reindeers are ready to work!!
Elf No.1 is waiting to work.
Elf No.2 is waiting to work.
Elf No.3 is waiting to work.
All elves are ready to work!!
Reindeer No.1 is waiting to play.
Reindeer No.4 is waiting to play.
Reindeer No.9 is waiting to play.
Reindeer No.7 is waiting to play.
Reindeer No.3 is waiting to play.
Elf No.3 is waiting to play.
Reindeer No.8 is waiting to play.
Reindeer No.5 is waiting to play.
Reindeer No.2 is waiting to play.
Elf No.1 is waiting to play.
Elf No.2 is waiting to play.
Reindeer No.6 is waiting to play.
Reindeer No.8 is waiting to work.
Elf No.3 is waiting to work.
Reindeer No.4 is waiting to work.
Elf No.1 is waiting to work.
Elf No.2 is waiting to work.
All elves are ready to work!!
Reindeer No.3 is waiting to work.
Reindeer No.5 is waiting to work.
Elf No.2 is waiting to play.
Elf No.3 is waiting to play.
Reindeer No.9 is waiting to work.
Reindeer No.6 is waiting to work.
Elf No.1 is waiting to play.
Elf No.1 is waiting to work.
Reindeer No.1 is waiting to work.
Elf No.2 is waiting to work.
Reindeer No.7 is waiting to work.
Reindeer No.2 is waiting to work.
All reindeers are ready to work!! ...


id:sumim:20070613:p2 に続く。