smalltalk
/
osmo-st-all
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-all/soapopera/Extensions.st

121 lines
2.9 KiB
Smalltalk

Collection extend [
beginsWith: aString [
<category: '*soapopera-core'>
"This comes from Pharo 1.1 and is on SequencableCollection"
"Answer true if the receiver starts with the argument collection"
(aString isEmpty or: [self size < aString size]) ifTrue: [^false].
aString withIndexDo: [:each :index | (self at: index) ~= each ifTrue: [^false]].
^true
]
withIndexDo: elementAndIndexBlock [
<category: '*soapopera-core'>
"This comes from Pharo 1.1 and is on SequencableCollection"
"Just like with:do: except that the iteration index supplies the second argument to the block."
1 to: self size do:
[:index |
elementAndIndexBlock
value: (self at: index)
value: index]
]
ifEmpty: aBlock [
<category: '*soapopera-core'>
self isEmpty ifTrue: [^ aBlock value]
]
isEmptyOrNil [
<category: '*soapopera-core'>
^ self isEmpty
]
ifNotEmptyDo: aBlock [
<category: '*soapopera-core'>
"Evaluate the given block with the receiver as its argument."
self isEmpty ifFalse: [^ aBlock value: self].
]
copyWithoutAll: aCollection [
"Answer a copy of the receiver that does not contain any elements
equal to those in aCollection."
^ self reject: [:each | aCollection includes: each]
]
]
String extend [
findString: subString startingAt: aStart [
| res start |
<category: '*soapopera-core'>
"This comes from Pharo 1.1 and is on String"
"Answer the index of subString within the receiver, starting at start. If
the receiver does not contain subString, answer 0."
start := aStart = 0 ifTrue: [1] ifFalse: [aStart].
res := self indexOf: subString matchCase: true startingAt: start.
res ifNil: [^ 0]
ifNotNil: [^ res first]
]
base64Encoded [
<category: '*network-mime'>
"Encode the receiver as base64"
"'Hello World' base64Encoded"
^(Base64MimeConverter mimeEncode: self readStream) contents
]
base64Decoded [
<category: '*network-mime'>
"Decode the receiver from base 64"
"'SGVsbG8gV29ybGQ=' base64Decoded"
^(Base64MimeConverter mimeDecode: self as: self class)
]
withFirstCharacterDownshifted [
"Return a copy with the first letter downShifted"
| answer |
self ifEmpty: [^ self copy].
answer := self copy.
answer at: 1 put: (answer at: 1) asLowercase.
^ answer.
]
]
ByteArray extend [
base64Encoded [
<category: '*network-mime'>
"Encode the receiver as base64"
"'Hello World' base64Encoded"
^(Base64MimeConverter mimeEncode: self readStream) contents
]
]
UndefinedObject extend [
isEmptyOrNil [
<category: '*soapopera-core'>
^ true
]
]
Character extend [
charCode [
<category: '*soapopera-core'>
^ codePoint
]
]
DateTime extend [
DateTime class >> fromString: aString [
^ self readFrom: aString readStream.
]
asString [
^ String streamContents: [:stream | self printOn: stream]
]
]