" (C) 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: M2UAApplicationServerProcess [ | socket asp_active_block asp_down_block asp_inactive_block asp_up_block error_block notify_block sctp_confirm_block sctp_released_block sctp_restarted_block sctp_status_block established state t_ack lastMsg on_state_change as_state | M2UAApplicationServerProcess class >> initWith: aService [ ^self new socketService: aService; yourself ] M2UAApplicationServerProcess class >> new [ ^super new initialize; yourself ] onError: aBlock [ "M-ERROR indication Direction: M2UA -> LM Purpose: ASP or SGP reports that it has received an ERROR message from its peer." error_block := aBlock ] onNotify: aBlock [ "M-NOTIFY indication Direction: M2UA -> LM Purpose: ASP reports that it has received a NOTIFY message from its peer." notify_block := aBlock ] onSctpEstablished: aBlock [ "M-SCTP_ESTABLISH confirm Direction: M2UA -> LM Purpose: ASP confirms to LM that it has established an SCTP association with an SGP." sctp_confirm_block := aBlock ] onSctpReleased: aBlock [ "M-SCTP_RELEASE confirm Direction: M2UA -> LM Purpose: ASP confirms to LM that it has released SCTP association with SGP." sctp_released_block := aBlock ] onSctpRestarted: aBlock [ "M-SCTP_RELEASE indication Direction: M2UA -> LM Purpose: SGP informs LM that ASP has released an SCTP association." sctp_restarted_block := aBlock ] onSctpStatus: aBlock [ "M-SCTP_STATUS indication Direction: M2UA -> LM Purpose: M2UA reports status of SCTP association." sctp_status_block := aBlock ] sctpEstablish [ "M-SCTP_ESTABLISH request Direction: LM -> M2UA Purpose: LM requests ASP to establish an SCTP association with an SGP." established := false. socket stop. socket start ] sctpRelease [ "M-SCTP_RELEASE request Direction: LM -> M2UA Purpose: LM requests ASP to release an SCTP association with SGP." established := false. socket stop. t_ack ifNotNil: [t_ack cancel] ] sctpStatusRequest [ "M-SCTP_STATUS request Direction: LM -> M2UA Purpose: LM requests M2UA to report status of SCTP association." self notYetImplemented ] aspActive [ "M-ASP_ACTIVE request Direction: LM -> M2UA Purpose: LM requests ASP to send an ASP ACTIVE message to the SGP." | msg | self checkNextState: M2UAAspStateActive. msg := M2UAMSG new class: M2UAConstants clsASPTM; msgType: M2UAConstants asptmActiv; addTag: self createIdentIntTag; addTag: self createInfoTag; yourself. self send: msg ] aspDown [ "M-ASP_DOWN request Direction: LM -> M2UA Purpose: LM requests ASP to stop its operation and send an ASP DOWN message to the SGP." | msg | self checkNextState: M2UAAspStateDown. msg := M2UAMSG new class: M2UAConstants clsASPSM; msgType: M2UAConstants aspsmDown; addTag: self createAspIdentTag; addTag: self createInfoTag; yourself. self send: msg ] aspInactive [ "M-ASP_INACTIVE request Direction: LM -> M2UA Purpose: LM requests ASP to send an ASP INACTIVE message to the SGP." | msg | self checkNextState: M2UAAspStateInactive. msg := M2UAMSG new class: M2UAConstants clsASPTM; msgType: M2UAConstants asptmInactiv; addTag: self createIdentIntTag; addTag: self createInfoTag; yourself. self send: msg ] aspUp [ "M-ASP_UP request Direction: LM -> M2UA Purpose: LM requests ASP to start its operation and send an ASP UP message to the SGP." | msg | self checkNextState: M2UAAspStateInactive. msg := M2UAMSG new class: M2UAConstants clsASPSM; msgType: M2UAConstants aspsmUp; addTag: self createAspIdentTag; addTag: self createInfoTag; yourself. self send: msg ] onAspActive: aBlock [ "M-ASP_ACTIVE confirm Direction: M2UA -> LM Purpose: ASP reports that is has received an ASP ACTIVE Acknowledgment message from the SGP." asp_active_block := aBlock ] onAspDown: aBlock [ "M-ASP_DOWN confirm Direction: M2UA -> LM Purpose: ASP reports that is has received an ASP DOWN Acknowledgment message from the SGP." asp_down_block := aBlock ] onAspInactive: aBlock [ "M-ASP_INACTIVE confirm Direction: M2UA -> LM Purpose: ASP reports that is has received an ASP INACTIVE Acknowledgment message from the SGP." asp_inactive_block := aBlock ] onAspUp: aBlock [ "M-ASP_UP confirm Direction: M2UA -> LM Purpose: ASP reports that it has received an ASP UP Acknowledgment message from the SGP." asp_up_block := aBlock ] onStateChange: aBlock [ "A generic callback for all state changes" on_state_change := aBlock ] deregisterLinkKey [ "M-LINK_KEY_DEREG Request Direction: LM -> M2UA Purpose: LM requests ASP to de-register Link Key with SG by sending DEREG REQ message." self notYetImplemented ] onLinkKeyDeregistered: aBlock [ "M-LINK_KEY_DEREG Confirm Direction: M2UA -> LM Purpose: ASP reports to LM that it has successfully received a DEREG RSP message from SG." self notYetImplemented ] onLinkKeyRegistered: aBlock [ "M-LINK_KEY_REG Confirm Direction: M2UA -> LM Purpose: ASP reports to LM that it has successfully received a REG RSP message from SG." self notYetImplemented ] registerLinkKey [ "M-LINK_KEY_REG Request Direction: LM -> M2UA Purpose: LM requests ASP to register Link Key with SG by sending REG REQ message." self notYetImplemented ] hostname: aHostname port: aPort [ "Select the SCTP hostname/port for the SG to connect to" socket hostname: aHostname; port: aPort ] createAspIdentTag [ ^M2UATag initWith: M2UAConstants tagAspIdent data: #(1 2 3 4) ] createIdentIntTag [ ^M2UATag initWith: M2UAConstants tagIdentInt data: #(0 0 0 0) ] createInfoTag [ ^M2UATag initWith: M2UAConstants tagInfo data: 'Hello from Smalltalk' asByteArray ] callNotification: aBlock [ "Inform the generic method first, then all the others" on_state_change ifNotNil: [on_state_change value]. aBlock ifNotNil: [aBlock value] ] checkNextState: nextState [ "Check if nextState and state are compatible and if not throw an exception. TODO:" self state = nextState ifTrue: [^self error: ('M2UA ASP already in state <1p>' expandMacrosWith: state)]. (self state nextPossibleStates includes: nextState) ifFalse: [^self error: ('M2UA ASP illegal state transition from <1p> to <2p>.' expandMacrosWith: state with: nextState)] ] dispatchData: aByteArray [ | msg | msg := M2UAMSG parseToClass: aByteArray. msg dispatchOnAsp: self ] dispatchNotification: aBlock [ aBlock value ] internalReset [ self socketService: socket ] moveToState: newState [ ((state nextPossibleStates includes: newState) or: [state = newState]) ifFalse: [^self error: ('M2UA ASP Illegal state transition from <1p> to <2p>' expandMacrosWith: state with: newState)]. "TODO: general on entry, on exit" state := newState ] sctpConnected [ "The connect was issued." | wasEstablished | wasEstablished := established. established := true. state := M2UAAspStateDown. t_ack ifNotNil: [t_ack cancel]. wasEstablished = true ifTrue: [sctp_confirm_block ifNotNil: [sctp_confirm_block value]] ifFalse: [sctp_restarted_block ifNotNil: [sctp_restarted_block value]] ] sctpReleased [ "The SCTP connection has been released." self moveToState: M2UAAspStateDown. established = true ifFalse: [^self]. sctp_released_block ifNotNil: [sctp_released_block value] ] send: aMsg [ "Forget about what we did before" t_ack ifNotNil: [t_ack cancel]. t_ack := TimerScheduler instance scheduleInSeconds: 2 block: ["Re-send the message" self logNotice: ('<1p>:<2p> Sending message has timed out' expandMacrosWith: socket hostname with: socket port) area: #m2ua. self send: aMsg]. socket nextPut: aMsg toMessage asByteArray ] initialize [ state := M2UAAspStateDown ] socketService: aService [ socket := aService. socket onSctpConnect: [self sctpConnected]; onSctpReleased: [self sctpReleased]; onSctpData: [:stream :assoc :ppid :data | ppid = 2 ifFalse: [^self logNotice: 'M2UAApplicationServerProcess expecting PPID 2.' area: #m2ua]. self dispatchData: data] ] handleAspActiveAck: aMsg [ t_ack cancel. self moveToState: M2UAAspStateActive. self callNotification: asp_active_block ] handleAspDownAck: aMsg [ t_ack cancel. as_state := nil. self moveToState: M2UAAspStateDown. self callNotification: asp_down_block ] handleAspInactiveAck: aMsg [ t_ack cancel. as_state := nil. self moveToState: M2UAAspStateInactive. self callNotification: asp_inactive_block ] handleAspUpAck: aMsg [ t_ack cancel. self moveToState: M2UAAspStateInactive. self callNotification: asp_inactive_block ] handleError: aMsg [ "Cancel pending operations.. because something went wrong" t_ack cancel. error_block ifNotNil: [error_block value: aMsg] ] handleNotify: aMsg [ "Extract the status" | tag type ident | tag := aMsg findTag: M2UAConstants tagStatus. tag ifNil: [^self]. type := (tag data ushortAt: 1) swap16. ident := (tag data ushortAt: 3) swap16. type = M2UAConstants ntfyKindStateChange ifTrue: [as_state := ident]. "Inform our user about it" notify_block ifNotNil: [notify_block value: type value: ident] ] handleUnknownMessage: aMsg [ "We got something we don't know. ignore it for now." ] isASActive [ ^as_state = M2UAConstants ntfyStateASActive ] isASInactive [ ^as_state = M2UAConstants ntfyStateASInactive ] isASPending [ ^as_state = M2UAConstants ntfyStateASPending ] state [ ^state ] ]