smalltalk
/
osmo-st-core
Archived
1
0
Fork 0

pharo: Introduce the expandMacros related String classes from Pharo

The >>bindWith: or >>% is not available in Pharo and other dialects.
From a licensing point of view it is easier to introduce the Pharo
equivalent to GST than to use the GST code in Pharo. Add a simple testcase
for some parts of the API. Pharo doesn't appear to use the % and ?
syntax at all.
This commit is contained in:
Holger Hans Peter Freyther 2013-02-23 11:10:15 +01:00
parent 5e571e0e69
commit 147307900d
3 changed files with 106 additions and 0 deletions

31
ExtensionTest.st Normal file
View File

@ -0,0 +1,31 @@
"
Test the Pharo extensions.
"
TestCase subclass: StringFormatTest [
<category: 'OsmoCore-Pharo-Tests'>
testExpandMacros [
| str |
str := 'Bla<n>' expandMacros.
self assert: str = ('Bla', Character nl asString).
str := 'Bla<t>' expandMacros.
self assert: str = ('Bla', Character tab asString).
]
testExpandWithMacro [
| str |
str := 'Bla Bla <1p>' expandMacrosWith: 10.
self assert: str = 'Bla Bla 10'.
str := 'Bla Bla <1s>' expandMacrosWith: 10 asString.
self assert: str = 'Bla Bla 10'.
]
testExpandMacros2 [
| str |
str := 'Bla Bla <1p> <2s>' expandMacrosWith: 10 with: '20'.
self assert: str = 'Bla Bla 10 20'.
]
]

72
GSTExtensions.st Normal file
View File

@ -0,0 +1,72 @@
"This is from Pharo 1.4. It is MIT licensed"
String extend [
expandMacros [
<category: '*OsmoCore-FromPharo'>
^self expandMacrosWithArguments: #()
]
expandMacrosWith: anObject [
<category: '*OsmoCore-FromPharo'>
^self expandMacrosWithArguments: (Array with: anObject)
]
expandMacrosWith: anObject with: anotherObject [
<category: '*OsmoCore-FromPharo'>
^self
expandMacrosWithArguments: (Array with: anObject with: anotherObject)
]
expandMacrosWith: anObject with: anotherObject with: thirdObject [
<category: '*OsmoCore-FromPharo'>
^self expandMacrosWithArguments: (Array
with: anObject
with: anotherObject
with: thirdObject)
]
expandMacrosWith: anObject with: anotherObject with: thirdObject with: fourthObject [
<category: '*OsmoCore-FromPharo'>
^self expandMacrosWithArguments: (Array
with: anObject
with: anotherObject
with: thirdObject
with: fourthObject)
]
expandMacrosWithArguments: anArray [
<category: '*OsmoCore-FromPharo'>
| newStream readStream char index |
newStream := (String new: self size) writeStream.
readStream := self readStream.
[ readStream atEnd ] whileFalse:
[ char := readStream next.
char == $<
ifTrue:
[ | nextChar |
nextChar := readStream next asUppercase.
nextChar == $N ifTrue: [ newStream nl ].
nextChar == $T ifTrue: [ newStream tab ].
nextChar isDigit ifTrue:
[ index := nextChar digitValue.
[ readStream atEnd or: [ (nextChar := readStream next asUppercase) isDigit not ] ] whileFalse: [ index := index * 10 + nextChar digitValue ] ].
nextChar == $? ifTrue:
[ | trueString falseString |
trueString := readStream upTo: $:.
falseString := readStream upTo: $>.
readStream position: readStream position - 1.
newStream nextPutAll: ((anArray at: index)
ifTrue: [ trueString ]
ifFalse: [ falseString ]) ].
nextChar == $P ifTrue: [ newStream nextPutAll: (anArray at: index) printString ].
nextChar == $S ifTrue: [ newStream nextPutAll: (anArray at: index) ].
readStream skipTo: $> ]
ifFalse:
[ newStream nextPut: (char == $%
ifTrue: [ readStream next ]
ifFalse: [ char ]) ] ].
^ newStream contents
]
]

View File

@ -3,6 +3,7 @@
<namespace>Osmo</namespace>
<prereq>OsmoLogging</prereq>
<filein>GSTExtensions.st</filein>
<filein>LogArea.st</filein>
<filein>Dispatcher.st</filein>
<filein>Timer.st</filein>
@ -11,5 +12,7 @@
<sunit>Osmo.DispatcherTest</sunit>
<sunit>Osmo.TimerTest</sunit>
<filein>Tests.st</filein>
<sunit>Osmo.StringFormatTest</sunit>
<filein>ExtensionTest.st</filein>
</test>
</package>