diff --git a/Makefile b/Makefile index 7f53907..ff7fba9 100644 --- a/Makefile +++ b/Makefile @@ -47,6 +47,7 @@ UA = \ OSMO = \ osmo/LogAreaOsmo.st \ osmo/OsmoUDPSocket.st osmo/OsmoCtrlLogging.st \ + osmo/OsmoStreamSocketBase.st \ osmo/OsmoCtrlGrammar.st osmo/OsmoAppConnection.st \ osmo/OsmoCtrlConnection.st osmo/OsmoCtrlGrammarTest.st diff --git a/osmo/OsmoAppConnection.st b/osmo/OsmoAppConnection.st index 06b61c7..29d33d2 100644 --- a/osmo/OsmoAppConnection.st +++ b/osmo/OsmoAppConnection.st @@ -16,19 +16,13 @@ along with this program. If not, see . " -Object subclass: OsmoAppConnection [ - | socket writeQueue demuxer muxer dispatcher token hostname port - tx_proc rx_proc started connect_block | +OsmoStreamSocketBase subclass: OsmoAppConnection [ + | writeQueue demuxer muxer dispatcher token connect_block | - OsmoAppConnection class >> connectionException [ - - ^ SystemExceptions.FileError - ] - OsmoAppConnection class >> new [ ^(self basicNew) hostname: '127.0.0.1'; @@ -36,52 +30,6 @@ TODO: re-use the IPADispatcher across connections.'> yourself ] - driveDispatch [ - - - [ - self dispatchOne - ] on: SystemExceptions.EndOfStream do: [:e | - self logError: 'OsmoApplication eof' area: #osmo. - self scheduleReconnect - ] on: SystemExceptions.FileError do: [:e | - self logError: 'OsmoApplication file-error' area: #osmo. - self scheduleReconnect - ] on: Error do: [:e | - e logException: 'OsmoApplication error' area: #osmo. - self scheduleReconnect - ] - ] - - driveSend [ - - [ - self sendOne - ] on: SystemExceptions.EndOfStream do: [:e | - self logError: 'OsmoApplication eof' area: #osmo. - self scheduleReconnect - ] on: Error do: [:e | - e logException: 'OsmoApplication error' area: #osmo. - self scheduleReconnect - ] - ] - - reconnect [ - - self logNotice: 'Going to reconnect socket' area: #osmo. - self terminate. - started ifTrue: [self start] - ] - - scheduleReconnect [ - - socket ifNotNil: [socket close. socket := nil]. - TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect]. - "We are done now" - Processor activeProcess terminate - ] - - initializeDispatcher [ | ipa | "Allow another class to register handlers" @@ -107,16 +55,6 @@ TODO: re-use the IPADispatcher across connections.'> token := aToken. ] - hostname: aHostname [ - - hostname := aHostname - ] - - port: aPort [ - - port := aPort - ] - onConnect: aBlock [ "Call the block when the socket is being connected and the dispatcher @@ -131,47 +69,13 @@ TODO: re-use the IPADispatcher across connections.'> connect [ - socket ifNotNil: [socket close]. - socket := self createConnection: hostname port: port. + super connect. writeQueue := SharedQueue new. demuxer := IPADemuxer initOn: socket. muxer := IPAMuxer initOn: writeQueue. self initializeDispatcher. ] - start [ - - started := true. - - [ - self logNotice: 'Attempting to connect' area: #osmo. - self connect - ] on: self class connectionException do: [ - self logError: 'Failed to connect.' area: #osmo. - ^Osmo.TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect]]. - - rx_proc := - [Processor activeProcess name: 'OsmoAppConnection-RX'. - [self driveDispatch] repeat] fork. - tx_proc := [Processor activeProcess name: 'OsmoAppConnection-TX'. - [self driveSend] repeat] fork - ] - - stop [ - - started := false. - self terminate - "A reconnect timer might be running right now" - ] - - terminate [ - - tx_proc ifNotNil: [tx_proc terminate]. - rx_proc ifNotNil: [rx_proc terminate]. - socket ifNotNil: [socket close. socket := nil] - ] - - sendOne [ | msg | diff --git a/osmo/OsmoStreamSocketBase.st b/osmo/OsmoStreamSocketBase.st new file mode 100644 index 0000000..e2d4e12 --- /dev/null +++ b/osmo/OsmoStreamSocketBase.st @@ -0,0 +1,138 @@ +" + (C) 2011-2013 by Holger Hans Peter Freyther + All Rights Reserved + + This program is free software: you can redistribute it and/or modify + it under the terms of the GNU Affero General Public License as + published by the Free Software Foundation, either version 3 of the + License, or (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU Affero General Public License for more details. + + You should have received a copy of the GNU Affero General Public License + along with this program. If not, see . +" + +Object subclass: OsmoStreamSocketBase [ + | socket hostname port tx_proc rx_proc started | + + + + + OsmoStreamSocketBase class >> connectionException [ + + ^ SystemExceptions.FileError + ] + + hostname: aHostname [ + + hostname := aHostname + ] + + port: aPort [ + + port := aPort + ] + + connect [ + + socket ifNotNil: [socket close]. + socket := self createConnection: hostname port: port + ] + + start [ + + started := true. + + [ + self logNotice: 'Attempting to connect' area: #osmo. + self connect + ] on: self class connectionException do: [ + self logError: 'Failed to connect.' area: #osmo. + ^Osmo.TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect]]. + + rx_proc := + [Processor activeProcess name: 'OsmoAppConnection-RX'. + [self driveDispatch] repeat] fork. + tx_proc := [Processor activeProcess name: 'OsmoAppConnection-TX'. + [self driveSend] repeat] fork + ] + + stop [ + + started := false. + self terminate + "A reconnect timer might be running right now" + ] + + terminate [ + + tx_proc ifNotNil: [tx_proc terminate]. + rx_proc ifNotNil: [rx_proc terminate]. + socket ifNotNil: [socket close. socket := nil] + ] + + driveDispatch [ + + + [ + self dispatchOne + ] on: SystemExceptions.EndOfStream do: [:e | + self logError: 'OsmoApplication eof' area: #osmo. + self scheduleReconnect + ] on: SystemExceptions.FileError do: [:e | + self logError: 'OsmoApplication file-error' area: #osmo. + self scheduleReconnect + ] on: Error do: [:e | + e logException: 'OsmoApplication error' area: #osmo. + self scheduleReconnect + ] + ] + + driveSend [ + + [ + self sendOne + ] on: SystemExceptions.EndOfStream do: [:e | + self logError: 'OsmoApplication eof' area: #osmo. + self scheduleReconnect + ] on: Error do: [:e | + e logException: 'OsmoApplication error' area: #osmo. + self scheduleReconnect + ] + ] + + reconnect [ + + self logNotice: 'Going to reconnect socket' area: #osmo. + self terminate. + started ifTrue: [self start] + ] + + scheduleReconnect [ + + socket ifNotNil: [socket close. socket := nil]. + TimerScheduler instance scheduleInSeconds: 1 block: [self reconnect]. + "We are done now" + Processor activeProcess terminate + ] + + createConnection: aHostname port: aPort [ + + self subclassResponsibility + ] + + dispatchOne [ + + self subclassResponsibility + ] + + sendOne [ + + self subclassResponsibility + ] +] diff --git a/package.xml b/package.xml index 0c4c41d..214c6f9 100644 --- a/package.xml +++ b/package.xml @@ -33,6 +33,7 @@ osmo/OsmoUDPSocket.st osmo/OsmoCtrlLogging.st osmo/OsmoCtrlGrammar.st + osmo/OsmoStreamSocketBase.st osmo/OsmoAppConnection.st osmo/OsmoCtrlConnection.st diff --git a/pharo-porting/changes_for_pharo.st b/pharo-porting/changes_for_pharo.st index 297e0d0..d9678a8 100644 --- a/pharo-porting/changes_for_pharo.st +++ b/pharo-porting/changes_for_pharo.st @@ -25,7 +25,9 @@ OsmoAppConnection extend [ noTimeout; yourself ] +] +OsmoStreamSocketBase extend [ driveDispatch [ [ @@ -49,7 +51,7 @@ OsmoAppConnection extend [ ] ] -OsmoAppConnection class extend [ +OsmoStreamSocketBase class extend [ connectionException [ ^ConnectionTimedOut