'From Squeak 3.2 of 11 July 2002 [latest update: #4917] on 12 September 2002 at 12:45:12 am'! Object subclass: #'漢数字桁' instanceVariableNames: '数字 配列 桁 ' classVariableNames: '' poolDictionaries: '' category: 'Goodies-漢数字'! Array variableSubclass: #'漢数字配列' instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Goodies-漢数字'! 漢数字配列 class instanceVariableNames: ''! Number subclass: #'漢数字' instanceVariableNames: '私的漢数字配列 符号 ' classVariableNames: '' poolDictionaries: '' category: 'Goodies-漢数字'! !Object methodsFor: 'testing' stamp: 'sumim 9/11/2002 22:18'! is漢数字 ^ false! ! !漢数字桁 methodsFor: 'accessing' stamp: 'sumim 9/7/2002 21:21'! 桁 ^ 桁! ! !漢数字桁 methodsFor: 'accessing' stamp: 'sumim 9/7/2002 20:03'! 桁: 数値 桁 _ 数値! ! !漢数字桁 methodsFor: 'accessing' stamp: 'sumim 9/7/2002 21:21'! 数字 ^ 数字! ! !漢数字桁 methodsFor: 'accessing' stamp: 'sumim 9/7/2002 20:03'! 数字: 文字 数字 _ 文字! ! !漢数字桁 methodsFor: 'accessing' stamp: 'sumim 9/7/2002 21:21'! 配列 ^ 配列! ! !漢数字桁 methodsFor: 'accessing' stamp: 'sumim 9/7/2002 20:01'! 配列: ある配列 配列 _ ある配列! ! !漢数字桁 methodsFor: 'printing' stamp: 'sumim 9/7/2002 23:31'! asString | 文字列 十進単位 万進単位 | 文字列 _ (#(零 壱 弐 参 四 五 六 七 八 九) at: 数字 asString asInteger + 1) asString. 十進単位 _ (#(#'' 拾 百 千) at: 桁 - 1 \\ 4 + 1) asString. 万進単位 _ (#(#'' 萬 億 兆 京 垓 禾予 穣 溝 澗 正 戴 極 萬 恒河砂 萬 阿僧祇 萬 那由他 萬 不可思議 萬 無量 萬 大数 萬) at: 桁 // 4 + 1 ifAbsent: [#〓]) asString. (数字 == $0 and: [配列 size > 1]) ifTrue: [文字列 _ ''. 十進単位 _ '']. (数字 == $1 and: [桁 \\ 4 ~~ 1]) ifTrue: [文字列 _ '']. (桁 \\ 8 == 1 and: [桁 // 4 > 11]) ifTrue: [(self 単位無用: 8) ifTrue: [万進単位 _ '']] ifFalse: [(桁 \\ 4 ~~ 1 or: [(self 単位無用: 4 )]) ifTrue: [万進単位 _ '']]. ^ 文字列, 十進単位, 万進単位! ! !漢数字桁 methodsFor: 'printing' stamp: 'sumim 9/7/2002 20:55'! printOn: aStream aStream nextPut: $'. aStream nextPutAll: self asString. aStream nextPut: $'! ! !漢数字桁 methodsFor: 'printing' stamp: 'sumim 9/7/2002 23:30'! 単位無用: 4か8 ^ ((桁 to: (桁 + 4か8 - 1 min: 配列 size)) select: [ :idx | (配列 at: 配列 size - idx + 1) 数字 ~~ $0 ]) size = 0! ! !漢数字桁 methodsFor: 'initialize-release' stamp: 'sumim 9/11/2002 13:38'! release 配列 _ 数字 _ 桁 _ nil. super release! ! !漢数字配列 methodsFor: 'private' stamp: 'sumim 9/7/2002 20:06'! replaceFrom: start to: stop with: replacement startingAt: repStart | index repOff | repOff _ repStart - start. index _ start - 1. [(index _ index + 1) <= stop] whileTrue: [self at: index put: (漢数字桁 new 配列: self; 数字: (replacement at: repOff + index); 桁: self size - index + 1)]! ! !漢数字配列 methodsFor: 'converting' stamp: 'sumim 9/11/2002 13:04'! asInteger ^ (String withAll: (self collect: [ :桁 | 桁 数字 ])) asInteger! ! !漢数字配列 methodsFor: 'converting' stamp: 'sumim 9/7/2002 21:56'! asString | strem | strem _ WriteStream on: (String new: 200). self do: [:each | strem nextPutAll: each asString ]. ^ strem contents! ! !漢数字配列 methodsFor: 'initialize-release' stamp: 'sumim 9/11/2002 13:37'! release self do: [ :each | each release ]. super release! ! !漢数字配列 class methodsFor: 'examples' stamp: 'sumim 9/7/2002 23:33'! 例 ^ 100000000000000000000000000000000000000000000000000000000000000000000000000000001 as漢数字配列 asString "'壱不可思議壱'"! ! !MultiString methodsFor: 'converting' stamp: 'sumim 9/11/2002 22:58'! as漢数字 ^ 漢数字 文字列: self! ! !MultiSymbol methodsFor: 'converting' stamp: 'sumim 9/11/2002 12:48'! as漢数字 ^ self asString as漢数字! ! !Number methodsFor: 'converting' stamp: 'sumim 9/11/2002 13:43'! as漢数字 ^ 漢数字 数値: self asInteger! ! !Number methodsFor: 'converting' stamp: 'sumim 9/12/2002 00:30'! as漢数字配列 ^ 漢数字配列 withAll: self asInteger asString! ! !漢数字 methodsFor: 'initialize-release' stamp: 'sumim 9/11/2002 22:41'! release 私的漢数字配列 release. 私的漢数字配列 _ 符号 _ nil. super release! ! !漢数字 methodsFor: 'accessing' stamp: 'sumim 9/11/2002 22:43'! 数値 ^ 私的漢数字配列 asInteger * 符号! ! !漢数字 methodsFor: 'accessing' stamp: 'sumim 9/11/2002 22:44'! 数値: ある数値 私的漢数字配列 _ ある数値 as漢数字配列. ある数値 negative ifTrue: [符号 _ (-1)] ifFalse: [符号 _ 1]! ! !漢数字 methodsFor: 'accessing' stamp: 'sumim 9/11/2002 22:41'! 符号 ^ 符号! ! !漢数字 methodsFor: 'accessing' stamp: 'sumim 9/11/2002 22:37'! 符号: プラマイ1 符号 _ プラマイ1! ! !漢数字 methodsFor: 'printing' stamp: 'sumim 9/11/2002 22:59'! printOn: aStream aStream nextPutAll: '('''. aStream nextPutAll: (self 符号 negative ifTrue: ['負の'] ifFalse: ['']). aStream nextPutAll: 私的漢数字配列 asString. aStream nextPutAll: ''' as漢数字)' ! ! !漢数字 methodsFor: 'converting' stamp: 'sumim 9/11/2002 22:17'! is漢数字 ^ true! ! !漢数字 methodsFor: 'converting' stamp: 'sumim 9/12/2002 00:08'! adaptToFraction: rcvr andSend: selector "If I am involved in arithmetic with a Fraction, convert me to a Fraction." ^ rcvr perform: selector with: self asFraction! ! !漢数字 methodsFor: 'converting' stamp: 'sumim 9/12/2002 00:44'! adaptToInteger: rcvr andSend: selector "If I am involved in arithmetic with an Integer, convert me to a Integer." ^ rcvr perform: selector with: self asInteger! ! !漢数字 methodsFor: 'converting' stamp: 'sumim 9/12/2002 00:09'! asFloat ^ self asInteger asFloat! ! !漢数字 methodsFor: 'converting' stamp: 'sumim 9/12/2002 00:09'! asFraction ^ self asInteger asFraction! ! !漢数字 methodsFor: 'converting' stamp: 'sumim 9/11/2002 22:44'! asInteger ^ self 数値! ! !漢数字 methodsFor: 'comparing' stamp: 'sumim 9/11/2002 23:29'! < aNumber (aNumber is漢数字 or: [aNumber isInteger]) ifTrue: [^ self asInteger < (aNumber asInteger)]. ^ aNumber adaptToFraction: self andSend: # 1 ifTrue: [その配列 do: [ :その項目 | 処理済文字列 _ 処理済文字列 copyReplaceAll: その項目 asString with: (String withAll: (Array new: その番号 - 1 withAll: $0)), ' +']]]. self 大漢数詞群 doWithIndex: [ :その配列 :その番号 | その番号 > 1 ifTrue: [その配列 do: [ :その項目 | 処理済文字列 _ 処理済文字列 copyReplaceAll: その項目 asString with: '\', (その番号 - 1 * 4) asString, '\']]]. 仮数部配列 _ ((1 to: 処理済文字列 withCRs lineCount) collect: [ :その番号 | 処理済文字列 withCRs lineNumber: その番号]), #('0'). (1 to: 仮数部配列 size - 2 by: 2) do: [ :その番号 | ((仮数部配列 at: その番号 + 1) = '4' and: [(仮数部配列 at: その番号 + 3) // 4 >= 12]) ifTrue: [ 仮数部配列 at: その番号 + 1 put: ((仮数部配列 at: その番号 + 3) initialInteger + 4) asString]]. 評価用文字列 _ ''. 仮数部配列 pairsDo: [ :その仮数部 :その指数部 | その仮数部 = '' ifFalse: [ その仮数部 last == $+ ifTrue: [その仮数部 _ その仮数部 allButLast]. その仮数部 first == $0 ifTrue: [その仮数部 _ '1', その仮数部]. その仮数部 _ その仮数部 copyReplaceAll: '+0' with: '+10'. 評価用文字列 _ 評価用文字列, '+((', その仮数部, ') * (10 raisedTo: ',その指数部, '))']]. 評価用文字列 first == $+ ifTrue: [評価用文字列 _ 評価用文字列 allButFirst]] ifTrue: [評価用文字列 _ '0'. 符号 _ 1]. ^ super new 数値: (Compiler evaluate: 評価用文字列); 符号: 符号; yourself! ! !Fraction methodsFor: 'converting' stamp: 'sumim 9/11/2002 23:05'! as漢数字 ^ self! ! !Integer methodsFor: 'kansuuji' stamp: 'sumim 9/11/2002 18:38'! as漢数字文字列 self < 0 ifTrue: [^ '負の', self abs as漢数字文字列 ]. self < 10 ifTrue: [ ^ (#(零 壱 弐 参 四 五 六 七 八 九) at: self abs + 1) asString]. self < 10000 ifTrue: [ ^ (self asString asArray collectWithIndex: [ :itm :idx | (itm asString asInteger as漢数字文字列 = '零' ifTrue: [''] ifFalse: [ ((idx < self asString size and: [itm asString asInteger as漢数字文字列 = '壱']) ifTrue: [''] ifFalse: [itm asString asInteger as漢数字文字列]), (#(#'' 拾 百 千) at: (self asString size - idx + 1)) asString])]) asStringWithCr copyReplaceAll: String cr with: '']. self < (10 raisedTo: 4 * 12) ifTrue: [ ^ (((self asString size to: 1 by: -4) collect: [ :idx | self asString copyFrom: (idx - 3 max: 1) to: idx ]) collectWithIndex: [ :itm :idx | (itm asInteger > 0 ifTrue: [itm asInteger as漢数字文字列] ifFalse: ['']), ((#(#'' 萬 億 兆 京 垓 禾予 穣 溝 澗 正 戴)) at: idx) asString]) reverse asStringWithCr copyReplaceAll: String cr with: '']. self < (10 raisedTo: 4 * 26) ifTrue: [ ^ ((((self asString size to: 1 by: -8) collect: [ :idx | self asString copyFrom: (idx - 7 max: 1) to: idx ]) collectWithIndex: [ :itm :idx | idx > 6 ifFalse: [''] ifTrue: [ (itm asInteger > 0 ifTrue: [itm asInteger as漢数字文字列] ifFalse: ['']), ((#(極 恒河砂 阿僧祇 那由他 不可思議 無量 大数) at: idx - 6) asString)]]) reverse asStringWithCr copyReplaceAll: String cr with: ''), ((self \\ 10e47) as漢数字文字列)]. self error: ['変換できません'] "12345678123456781234567812345678123456781234567812345678123456781234567812345678123456781234567812345678 as漢数字文字列"! !