vieweditattachhistoryswikistopchangessearchhelp

Haskell vs Smalltalk(あるいは、抽象データ型 vs オブジェクト指向)

クックの "Object-Oriented Programming Versus Abstract Data Types"(PDF) の例を
で書いてみる。--sumim



Figure 5: Implementation of an ADT for lists by Haskell (Hugs 98)

-- adt IntList
module IntList (List, nil, adjoin, isNull, ilHead, ilTail, equal) where

-- representation
data List = Nil | Cell Integer List
  deriving Show

-- operations
nil = Nil

adjoin x l = Cell x l

isNull Nil = True
isNull (Cell _ _) = False

ilHead Nil = error "no head"
ilHead (Cell x _) = x

ilTail Nil = error "no tail"
ilTail (Cell _ l) = l

equal Nil m = isNull m
equal (Cell x l') m = not (isNull m)
                         && x == ilHead m
                            && equal l' (ilTail m)

Figure 7: Implementation of lists as PDAs (i.e. OO) by Smalltalk (Squeak)

'From Squeak3.6'!
Object subclass: #Cell
	instanceVariableNames: 'head tail '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Category-ProceduralDataAbstraction'!

!Cell methodsFor: 'testing'!
isNull
	^ false! !

!Cell methodsFor: 'accessing'!
head
	^ head! !

!Cell methodsFor: 'accessing'!
tail
	^ tail! !

!Cell methodsFor: 'testing'!
equal: m
	^ m isNull not
		and: [self head = m head
			and: [self tail equal: m tail]]! !


!Cell methodsFor: 'private'!
head: anInteger tail: tree
	head := anInteger.
	tail := tree! !

!Cell methodsFor: 'printing'!
printOn: aStream
	aStream nextPutAll: self class printString, ' adjoin: ', head printString, ' with: '.
	tail isNull ifFalse: [aStream nextPut: $(].
	aStream print: tail.
	tail isNull ifFalse: [aStream nextPut: $)]! !


!Cell class methodsFor: 'instance creation'!
adjoin: anInteger with: tree
	^ super new head: anInteger tail: tree; yourself! !


Object subclass: #Nil
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Category-ProceduralDataAbstraction'!

!Nil methodsFor: 'testing'!
isNull
	^ true! !

!Nil methodsFor: 'accessing'!
head
	^ self error: 'no head'! !

!Nil methodsFor: 'accessing'!
tail
	^ self error: 'no tail'! !

!Nil methodsFor: 'testing'!
equal: m
	^ m isNull! !


!Nil methodsFor: 'printing'!
printOn: aStream
	aStream nextPutAll: self class name, ' new'! !


Object subclass: #IntList
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Category-ProceduralDataAbstraction'!

!IntList class methodsFor: 'example'!
example
	"IntList example"
	| list list2 getBlockSource samples |

	getBlockSource := [ :block | 
		| node method map startpc endpc start stop code index |
		node := block methodNode.
		method := block method.
		map := node sourceMap.
		startpc := block startpc.
		endpc := (method at: startpc-2)\\16-4*256 + (method at: startpc-1) + startpc - 1.
		stop := ((Dictionary newFrom: map) at: endpc) value last.
		index := map findLast: [ :each | each key < startpc].
		index < 2 ifTrue: [start := 1] ifFalse: [
			start := (map at: index) value last + 1.
			start > stop ifTrue: [start := 1]].
		code := node sourceText copyFrom: start to: stop - 1.
		code allButFirst: (code indexOf: $[)].

	samples := {
		[list := Cell adjoin: 1 with: (Cell adjoin: 2 with: Nil new).]. 
		[list isNull.]. 
		[list head.]. 
		[list tail.]. 
		[list tail head.]. 
		[list2 := Nil new.]. 
		[list2 isNull.]. 
		[list equal: list2.].
		[list equal: list copy.]}.

	World findATranscript: nil.
	samples do: [ :block |
		Transcript cr.
		Transcript show: (getBlockSource value: block).
		Transcript show: '  " ==> ', block value printString, ' "']

.[ "an output: "
list := Cell adjoin: 1 with: (Cell adjoin: 2 with: Nil new).
list isNull.  " ==> false "
list head.  " ==> 1 "
list tail.  " ==> Cell adjoin: 2 with: Nil new "
list tail head.  " ==> 2 "
list2 := Nil new.  " ==> Nil new "
list2 isNull.  " ==> true "
list equal: list2.  " ==> false "
list equal: list copy.  " ==> true " ].! !



Haskell のコードは抽象データ型の特徴を際立たせるためにわざと冗長にしてあります。
Haskell の head と tail は Prelude で定義済みのものとぶつかるので ilHead、ilTail に変えました。
Smalltalk の example は遊びです。--sumim



このページを編集 (4331 bytes)


Congratulations! 以下の 2 ページから参照されています。

This page has been visited 4401 times.