viewedit (locked)attachhistoryswikistopchangessearchhelp

アラビア数字から漢数字への変換

SHIMADA さんのところで出された“お題その3”を Squeak で書いてみました。--sumim

壱弐参拾などのときは省略しないのですね。修正の要ありです。--sumim

▼桁が知っている版(KansuujiArray.cs)

'From Squeak 3.2 of 11 July 2002 [latest update: #4917] on 7 September 2002 at 11:38:03 pm'!
Object subclass: #'漢数字桁'
  instanceVariableNames: '数字 配列 桁 '
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Goodies-漢数字'!
Array variableSubclass: #'漢数字配列'
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Goodies-漢数字'!
漢数字配列 class
  instanceVariableNames: ''!

!Object methodsFor: 'converting' stamp: 'sumim 9/7/2002 23:03'!
as漢数字配列
  ^ self printString asInteger asString as漢数字配列! !


!漢数字桁 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! !


!SequenceableCollection methodsFor: 'converting' stamp: 'sumim 9/7/2002 23:08'!
as漢数字配列
  "Answer an 漢数字配列 whose elements are the elements of the receiver."

  ^ 漢数字配列 withAll: self asInteger asString! !


!漢数字配列 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/7/2002 21:56'!
asString
  | stream |
  stream _ WriteStream on: (String new: 200).
  self do: [:each | stream nextPutAll: each asString ].
  ^ stream contents! !


!漢数字配列 class methodsFor: 'examples' stamp: 'sumim 9/7/2002 23:33'!

  ^ 100000000000000000000000000000000000000000000000000000000000000000000000000000001 as漢数字配列 asString "'壱不可思議壱'"! !



Uploaded Image: kansuujiarray1.gif

Uploaded Image: kansuujiarray2.gif


▼再帰版

as漢数字文字列
"Integer のインスタンスメソッドとして定義します"

  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漢数字文字列"



▼一行野郎版

(((((100000000000000000000000000000000000000000000000000000000000000000000001
  asString asArray collectWithIndex: [ :itm :idx |
    (#(#'' 壱 弐 参 四 五 六 七 八 九) at: itm asString asInteger + 1) asString])
  reverse collectWithIndex: [ :itm :idx |
    ((itm = '壱' and: [idx \\ 4 ~~ 1]) ifTrue: [''] ifFalse: [itm]),
    (itm = '' ifFalse: [(#(#'' 拾 百 千) at: idx - 1 \\ 4 + 1) asString] ifTrue: ['']),
    (idx \\ 4 == 1 ifTrue: [
      '*', ((#(#'' 萬 億 兆 京 垓 杼 "...(禾予)の代替"
      穣 溝 澗 正 戴 極 萬+ 恒河砂 萬+ 阿僧祇 "...(禾氏)の代替"
      萬+ 那由他 萬+ 不可思議 萬+ 無量 萬+ 大数 萬+)
        " 無量と大数を区別しないときは、'無量 萬+ 大数' 部分を '無量大数' に "
        " copyWithout: #萬+ " "...萬萬進法でないときコメントアウトを復活"
          ) at: idx // 4 + 1) asString, ' '] ifFalse: [''])])
  reverse asStringWithCr copyWithout: Character cr)
  copyReplaceAll: '+ *' with: '')
  substrings select: [ :itm | itm first ~= $* ] thenCollect: [ :itm | (itm copyWithout: $*) copyWithout: $+])
      asStringWithCr copyWithout: Character cr



▼計算も出来ちゃう版
意味があるかどうかは別にして…。

100 as漢数字 "--> ('百' as漢数字)"
'一京壱百参' as漢数字 asInteger "--> 10000000000000103"
'一萬無量参拾四' as漢数字 + '三十萬四千七百参拾弐' as漢数字 "--> ('壱萬無量参拾萬四千七百六拾六' as漢数字)"
'四拾七万三千四大数弐拾四極三十二万四千三百弐拾壱' as漢数字 / 3 "--> ('拾五萬七千六百六拾八大数八極拾萬八千百七' as漢数字)"
1234 / '六百壱拾七' as漢数字 "--> 2"


KansuujiKeisan.cs.gz

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


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

This page has been visited 29373 times.