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

Merge branch 'master' of git://git.osmocom.org/smalltalk/osmo-st-core

This commit is contained in:
Holger Hans Peter Freyther 2013-05-23 17:36:25 +02:00
commit e60384432e
11 changed files with 230 additions and 8 deletions

View File

@ -1 +1,2 @@
*.sw?
fileout.st

View File

@ -18,7 +18,7 @@
Object subclass: Dispatcher [
| queue dispatch quit |
<category: 'OsmoCore'>
<category: 'OsmoCore-Core'>
<comment: 'I run tasks from the same context.'>
Dispatcher class >> instance [
@ -52,12 +52,19 @@ Object subclass: Dispatcher [
]
dispatch [
| block |
| block sem |
block := queue next.
sem := Semaphore new.
"Run the code in a new process as the debugger might terminate this
and then the dispatcher would not dispatch anymore. Use a Semaphore
to make sure we keep on processing items in order."
[[
block on: Error do: [:error |
error logException: 'dispatch failed on "%1".' % {block} area: #core.
]
error logException: ('dispatch failed on "', block printString, '".') area: #core.
]] ensure: [sem signal]] fork.
sem wait.
]
]

View File

@ -0,0 +1,40 @@
"
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'.
]
testExpandMacrosTrue [
| str |
str := 'Should be true=<1?true:false>' expandMacrosWith: true.
self assert: str = 'Should be true=true'.
str := 'Should be false=<1?tue:false>' expandMacrosWith: false.
self assert: str = 'Should be false=false'.
]
testExpandMacros2 [
| str |
str := 'Bla Bla <1p> <2s>' expandMacrosWith: 10 with: '20'.
self assert: str = 'Bla Bla 10 20'.
]
]

View File

@ -0,0 +1,78 @@
"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
]
]
Object extend [
deprecated: aString [
"Compat for pharo. Use it to indicate deprecated functions"
]
]

View File

@ -16,8 +16,6 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
PackageLoader fileInPackage: #OsmoLogging.
Osmo.LogArea subclass: LogAreaTimer [
<category: 'OsmoCore-Logging'>

18
osmo-st-core/Makefile Normal file
View File

@ -0,0 +1,18 @@
GST_PACKAGE = gst-package
GST_CONVERT = gst-convert
CONVERT_RULES = -r'Osmo.LogManager->LogManager' \
-r'Osmo.LogArea->LogArea' \
-r'Osmo.LogLevel->LogLevel' \
-r'DateTime->DateAndTime' \
-r'(Duration milliseconds: ``@args1) -> (Duration milliSeconds: ``@args1)'
all:
$(GST_PACKAGE) --test package.xml
convert:
$(GST_CONVERT) $(CONVERT_RULES) -F squeak -f gst \
-o fileout.st compat_for_pharo.st LogArea.st Dispatcher.st Timer.st Tests.st \
changes_for_pharo.st

View File

@ -16,8 +16,24 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
"
TestCase subclass: DispatcherTest [
<category: 'OsmoCore-Tests'>
testDispatcher [
| sem |
sem := Semaphore new.
self assert: sem signals = 0.
"Force a debugger or some abortion? And a log message"
OsmoDispatcher dispatchBlock: [123 unknownMessageForSmallInteger].
OsmoDispatcher dispatchBlock: [Processor activeProcess terminate].
OsmoDispatcher dispatchBlock: [sem signal].
self assert: sem signals = 1.
]
]
TestCase subclass: TimerTest [
<category: 'Very simple timer tests'>
<category: 'OsmoCore-Tests'>
testTimer [
| sem now |

View File

@ -94,11 +94,24 @@ bit difficult to do this race free.'>
quit := true.
]
platformInit [
<category: 'creation'>
"Nothing for GST..."
]
initialize [
<category: 'private'>
queue := SortedCollection sortBlock: [:a :b | a timeout < b timeout].
sem := Semaphore forMutualExclusion.
quit := false.
self
startLoop;
platformInit.
]
startLoop [
<category: 'creation'>
loop := [Processor activeProcess name: 'Osmo Timers'.
self runTimers] fork.
]
@ -142,7 +155,8 @@ bit difficult to do this race free.'>
each := sem critical: [queue removeFirst].
each isCanceled ifFalse: [
[each fire] on: Error do: [:e |
e logException: 'Execution of timer failed: %1' % {e tag} area: #timer.
e logException:
('Execution of timer failed: ', e messageText) area: #timer.
]].
]
]

View File

@ -0,0 +1,30 @@
TimerScheduler extend [
TimerScheduler class >> initialize [
<category: 'loading'>
^ self instance
]
TimerScheduler class >> startUp [
Smalltalk at: #OsmoTimeScheduler ifPresent: [
OsmoTimeScheduler reinitialize.
].
]
platformInit [
<category: 'creation'>
"Pharo requires us to do some post-processing"
Smalltalk addToStartUpList: self class.
]
reinitialize [
<category: 'creation'>
loop terminate.
self startLoop.
]
]
Dispatcher class extend [
initialize [
^ self instance
]
]

View File

@ -0,0 +1,16 @@
"This is to be easily loadable on Pharo 1.4 and up"
Object extend [
addToBeFinalized [
<category: '*OsmoCore'>
"No idea how to implement it"
]
]
Semaphore extend [
signals [
<category: '*OsmoCore'>
"Used in our testcase"
^ excessSignals
]
]

View File

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