smalltalk
/
osmo-st-core
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-core/GSTExtensions.st

95 lines
3.4 KiB
Smalltalk

"This is from Pharo 1.4. It is MIT licensed"
String extend [
expandMacros [
<category: '*PharoCompat'>
"From Pharo, for Phexample/OsmoCore, MIT license"
^self expandMacrosWithArguments: #()
]
expandMacrosWith: anObject [
<category: '*PharoCompat'>
"From Pharo, for Phexample/OsmoCore, MIT license"
^self expandMacrosWithArguments: (Array with: anObject)
]
expandMacrosWith: anObject with: anotherObject [
<category: '*PharoCompat'>
"From Pharo, for Phexample/OsmoCore, MIT license"
^self
expandMacrosWithArguments: (Array with: anObject with: anotherObject)
]
expandMacrosWith: anObject with: anotherObject with: thirdObject [
<category: '*PharoCompat'>
"From Pharo, for Phexample/OsmoCore, MIT license"
^self expandMacrosWithArguments: (Array
with: anObject
with: anotherObject
with: thirdObject)
]
expandMacrosWith: anObject with: anotherObject with: thirdObject with: fourthObject [
<category: '*PharoCompat'>
"From Pharo, for Phexample/OsmoCore, MIT license"
^self expandMacrosWithArguments: (Array
with: anObject
with: anotherObject
with: thirdObject
with: fourthObject)
]
expandMacrosWithArguments: anArray [
<category: '*PharoCompat'>
"From Pharo, for Phexample/OsmoCore, MIT license"
| 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
]
]
Object extend [
deprecated: aString [
"Compat for pharo. Use it to indicate deprecated functions"
]
]
Duration extend [
asMilliSeconds [
^self asMilliseconds
]
asDelay [
^Delay forMilliseconds: self asMilliseconds
]
]