-
Notifications
You must be signed in to change notification settings - Fork 71
/
PrintfNumberFormatDescriptor.class.st
127 lines (110 loc) · 2.76 KB
/
PrintfNumberFormatDescriptor.class.st
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
Class {
#name : #PrintfNumberFormatDescriptor,
#superclass : #PrintfFormatDescriptor,
#instVars : [
'operator',
'padding',
'radix',
'space'
],
#classVars : [
'Base',
'Cased',
'Radix'
],
#category : #Printf
}
{ #category : #'class initialization' }
PrintfNumberFormatDescriptor class >> initialize [
"PrintfNumberFormatDescriptor initialize"
Base := Dictionary newFromPairs: #( $d 10
$o 8
$p 16
$u 10
$x 16
$X 16).
Radix := Dictionary newFromPairs: #( $d ''
$o '0'
$p '0x'
$u ''
$x '0x'
$X '0X').
Cased := 'AaEeFfGgXx'
]
{ #category : #'instance creation' }
PrintfNumberFormatDescriptor class >> newFrom: desc [
desc class == self ifTrue: [^ desc].
^ (super newFrom: desc) setPadding: desc padding
]
{ #category : #rendering }
PrintfNumberFormatDescriptor >> applyOperator: object [
"Character and Number are the only valid classes"
| number string |
object ifNil: [^'-'].
number := object asInteger.
string := number printStringBase: self base.
(radix or: [operator == $p]) ifTrue: [string := self radixString , string].
(Cased includes: operator) ifTrue:
[string := operator isLowercase
ifTrue: [string asLowercase]
ifFalse: [string asUppercase]].
(space and: [operator == $d and: [number < 0]]) ifTrue:
[string := ' ' , string].
^ (width ~= 0 and: [string size > self stringLength])
ifTrue: [String new: width withAll: $*]
ifFalse: [string]
]
{ #category : #private }
PrintfNumberFormatDescriptor >> base [
^ Base at: operator
]
{ #category : #'initialize-release' }
PrintfNumberFormatDescriptor >> initialize [
super initialize.
padding := $ .
radix := false.
space := false
]
{ #category : #private }
PrintfNumberFormatDescriptor >> padding [
^ padding
]
{ #category : #printing }
PrintfNumberFormatDescriptor >> printOn: aStream [
super printOn: aStream.
padding == $0 ifTrue: [aStream nextPut: $0].
radix ifTrue: [aStream nextPut: $#].
space ifTrue: [aStream nextPut: $ ].
self printWidthOn: aStream.
aStream nextPut: operator
]
{ #category : #scanning }
PrintfNumberFormatDescriptor >> radix [
radix := true
]
{ #category : #private }
PrintfNumberFormatDescriptor >> radixString [
^ Radix at: operator
]
{ #category : #private }
PrintfNumberFormatDescriptor >> setOperator: char [
operator := char
]
{ #category : #private }
PrintfNumberFormatDescriptor >> setPadding: paddingChar [
padding := paddingChar
]
{ #category : #scanning }
PrintfNumberFormatDescriptor >> space [
space := true
]
{ #category : #private }
PrintfNumberFormatDescriptor >> stringLength [
^precision isNil
ifTrue: [SmallInteger maxVal]
ifFalse: [precision]
]
{ #category : #scanning }
PrintfNumberFormatDescriptor >> zero [
padding := $0
]