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-network/mtp3/MTP3Messages.st

1436 lines
26 KiB
Smalltalk
Raw Permalink Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

"
(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 <http://www.gnu.org/licenses/>.
"
Object subclass: MTP3Address [
| dpc opc |
<category: 'MTP3-Codec'>
<comment: 'A representation of a MTP3 Address. It includes the Destination Point Code (DPC) and the Originating Point Code (OPC).'>
]
Object subclass: MTP3Service [
| on_transfer on_pause on_resume on_status |
<category: 'MTP3-LinkHandling'>
<comment: 'I represent the primitives of Q.701 for MTP3.
This service is not implemented yet!'>
transfer: aByteArray to: anAddr [
<category: 'request'>
^self notYetImplemented
]
onPause: aBlock [
"Called with DPC"
<category: 'indication'>
on_pause := aBlock
]
onResume: aBlock [
"Called with affected DPC"
<category: 'indication'>
on_resume := aBlock
]
onStatus: aBlock [
"Called with the Affected DPC"
<category: 'indication'>
on_status := aBlock
]
onTransfer: aBlock [
"Called with MTP3Address and UserData"
<category: 'indication'>
on_transfer := aBlock
]
]
Object subclass: MTP3NetworkManagementTimer [
<category: 'MTP3-Codec'>
<comment: 'I represent the legal ranges from Q.704'>
MTP3NetworkManagementTimer class >> T1 [
"Delay to avoid message mis-sequencing on changeover."
<category: 'timer-ranges'>
^500 to: 1200
]
MTP3NetworkManagementTimer class >> T10 [
"Waiting to repeat signalling route set test message.
The maximum value may be extended at the discretion of the management function in
certain situations, e.g. many signalling points being unavailable or signalling point of
known long term unavailability."
<category: 'timer-ranges'>
^30000 to: 60000
]
MTP3NetworkManagementTimer class >> T11 [
"Transfer restricted timer. (This is one way of implementing the function described in
13.4 and mainly intended to simplify STPs.)"
<category: 'timer-ranges'>
^30000 to: 90000
]
MTP3NetworkManagementTimer class >> T12 [
"Waiting for uninhibit acknowledgement."
<category: 'timer-ranges'>
^800 to: 1500
]
MTP3NetworkManagementTimer class >> T13 [
"Waiting for force uninhibit."
<category: 'timer-ranges'>
^800 to: 1500
]
MTP3NetworkManagementTimer class >> T14 [
"Waiting for inhibition acknowledgement."
<category: 'timer-ranges'>
^2000 to: 3000
]
MTP3NetworkManagementTimer class >> T15 [
"Waiting to start signalling route set congestion test."
<category: 'timer-ranges'>
^2000 to: 3000
]
MTP3NetworkManagementTimer class >> T16 [
"Waiting for route set congestion status update."
<category: 'timer-ranges'>
^1400 to: 2000
]
MTP3NetworkManagementTimer class >> T17 [
"Delay to avoid oscillation of initial alignment failure and link restart."
<category: 'timer-ranges'>
^800 to: 1500
]
MTP3NetworkManagementTimer class >> T18 [
"Timer8 within a signalling point whose MTP restarts for supervising link and link set
activation as well as the receipt of routing information.
The value is implementation and network dependent.
Criteria to choose T18 are given in 9.2."
<category: 'timer-ranges'>
^self notYetImplemented
]
MTP3NetworkManagementTimer class >> T19 [
"Supervision timer during MTP restart to avoid possible ping-pong of TFP, TFR1 and
TRA messages."
<category: 'timer-ranges'>
^67000 to: 69000
]
MTP3NetworkManagementTimer class >> T2 [
"Waiting for changeover acknowledgement."
<category: 'timer-ranges'>
^700 to: 2000
]
MTP3NetworkManagementTimer class >> T20 [
"Overall MTP restart timer at the signalling point whose MTP restarts."
<category: 'timer-ranges'>
^59000 to: 61000
]
MTP3NetworkManagementTimer class >> T21 [
"Overall MTP restart timer at a signalling point adjacent to one whose MTP restarts."
<category: 'timer-ranges'>
^63000 to: 65000
]
MTP3NetworkManagementTimer class >> T22 [
"Local inhibit test timer."
<category: 'timer-ranges'>
^3 * 60 * 1000 to: 6 * 60 * 1000
]
MTP3NetworkManagementTimer class >> T23 [
"Remote inhibit test timer."
<category: 'timer-ranges'>
^3 * 60 * 1000 to: 6 * 60 * 1000
]
MTP3NetworkManagementTimer class >> T24 [
"Stabilising timer after removal of local processor outage, used in LPO latching to RPO
(national option)."
<category: 'timer-ranges'>
^500 to: 500
]
MTP3NetworkManagementTimer class >> T3 [
"Time controlled diversion-delay to avoid mis-sequencing on changeback."
<category: 'timer-ranges'>
^500 to: 1200
]
MTP3NetworkManagementTimer class >> T4 [
"Waiting for changeback acknowledgement (first attempt)."
<category: 'timer-ranges'>
^500 to: 1200
]
MTP3NetworkManagementTimer class >> T5 [
"Waiting for changeback acknowledgement (second attempt)."
<category: 'timer-ranges'>
^500 to: 1200
]
MTP3NetworkManagementTimer class >> T6 [
"Delay to avoid message mis-sequencing on controlled rerouting."
<category: 'timer-ranges'>
^500 to: 1200
]
MTP3NetworkManagementTimer class >> T7 [
"Waiting for signalling data link connection acknowledgement."
<category: 'timer-ranges'>
^1000 to: 2000
]
MTP3NetworkManagementTimer class >> T8 [
"Transfer prohibited inhibition timer (transient solution)."
<category: 'timer-ranges'>
^800 to: 1200
]
MTP3NetworkManagementTimer class >> T9 [
<category: 'timer-ranges'>
^self shouldNotImplement
]
]
Object subclass: MTP3Field [
<category: 'MTP3-Codec'>
<comment: 'I am a baseclass for MTP3 Fields. I provide no functionality myself.'>
]
MTP3Field subclass: MTP3Heading [
| h0 h1 |
<category: 'MTP3-Codec'>
<comment: 'Encoding/Decoding of the Heading code H0 and Heading code H1. Please refer to MTP3MSG for the possible h0 and h1 values.'>
MTP3Heading class >> parseFrom: aStream [
| byte |
byte := aStream next.
^(self new)
h0: (byte bitAnd: 2r1111);
h1: (byte bitShift: -4);
yourself
]
h0: aHeading [
<category: 'creation'>
h0 := aHeading
]
h1: aHeading [
<category: 'creation'>
h1 := aHeading
]
h0 [
<category: 'accessing'>
^h0
]
h1 [
<category: 'accessing'>
^h1
]
writeOn: aBuffer [
<category: 'encoding'>
| byte |
byte := h0 bitOr: (h1 bitShift: 4).
aBuffer putByte: byte
]
]
Object subclass: MTP3LinkTestTimer [
<category: 'MTP3-Codec'>
<comment: nil>
T1 [
"Supervision timer for signalling link test
acknowledgement message. Equal or greater than T6 of Q.703"
^4 * 1000 to: 12 * 1000
]
T2 [
"Interval timer for sending signalling link
test messages"
^30 * 1000 to: 90 * 1000
]
]
Object subclass: MTP3MSG [
| service label heading |
<category: 'MTP3-Codec'>
<comment: nil>
MTP3MSG class >> findMessageClassFor: aServiceIndicator heading: aHeading [
<category: 'parsing'>
self subclassesDo:
[:each |
(each isServiceCompatible: aServiceIndicator)
ifTrue: [^each findClassForHeading: aHeading]].
^nil
]
MTP3MSG class >> parseFrom: aStream [
<category: 'parsing'>
| service label heading msg |
service := MTP3ServiceIndicators parseFrom: aStream.
label := MTP3Label parseFrom: aStream.
heading := MTP3Heading parseFrom: aStream.
msg := ((self findMessageClassFor: service heading: heading) new)
service: service;
label: label;
heading: heading;
parseFrom: aStream;
yourself.
^msg
]
heading: aHeading [
<category: 'creation'>
heading := aHeading
]
label: aLabel [
<category: 'creation'>
label := aLabel
]
service: aService [
<category: 'creation'>
service := aService
]
writeOn: aBuffer [
<category: 'encoding'>
service writeOn: aBuffer.
label writeOn: aBuffer.
heading writeOn: aBuffer
]
]
MTP3MSG subclass: MTP3LinkTestMSG [
| pattern |
<category: 'MTP3-Codec'>
<comment: 'I represent messages specified in Q.707'>
MTP3LinkTestMSG class >> h0 [
^2r0001
]
MTP3LinkTestMSG class >> h1SLTA [
^2r0010
]
MTP3LinkTestMSG class >> h1SLTM [
^2r0001
]
MTP3LinkTestMSG class >> findClassForHeading: aHeading [
<category: 'parsing'>
aHeading h0 = self h0 ifFalse: [^self error: 'Wrong heading'].
self subclassesDo: [:each | each h1 = aHeading h1 ifTrue: [^each]]
]
MTP3LinkTestMSG class >> isServiceCompatible: aServiceIndicator [
<category: 'parsing'>
^aServiceIndicator serviceIndicator
= MTP3ServiceIndicators signallingNetworkTestingAndMaintenance
]
writeOn: aBuffer [
<category: 'encoding'>
| len |
super writeOn: aBuffer.
len := (pattern size bitShift: 4) bitAnd: 2r11110000.
aBuffer putByte: len.
aBuffer putByteArray: pattern
]
parseFrom: aStream [
<category: 'parsing'>
| length |
length := aStream next bitShift: -4.
self testPattern: (aStream next: length)
]
testPattern [
<category: 'parsing'>
^pattern
]
testPattern: aPattern [
<category: 'creation'>
pattern := aPattern
]
]
MTP3MSG subclass: MTP3NetworkManagementMSG [
<category: 'MTP3-Codec'>
<comment: 'MTP3Message is a codec class for the MessageTransferPart as of Q.701-Q.704, Q.706 and Q.707. Currently only the ITU version will be supported.
The spec is really difficult to read a MTP3 Message will have:
DCBA (MTPSubservice 4bit)
DCBA (MTPServiceIndicator 4bit)
Label (MTP3Label 32bit)
H0 (4bit)
H1 (4bit)
DATA'>
MTP3NetworkManagementMSG class >> h0Chm [
<category: 'h0'>
^2r0001
]
MTP3NetworkManagementMSG class >> h0Dlm [
<category: 'h0'>
^2r1000
]
MTP3NetworkManagementMSG class >> h0Ecm [
<category: 'h0'>
^2r0010
]
MTP3NetworkManagementMSG class >> h0Fcm [
<category: 'h0'>
^2r0011
]
MTP3NetworkManagementMSG class >> h0Mim [
<category: 'h0'>
^2r0110
]
MTP3NetworkManagementMSG class >> h0Rsm [
<category: 'h0'>
^2r0101
]
MTP3NetworkManagementMSG class >> h0Tfm [
<category: 'h0'>
^2r0100
]
MTP3NetworkManagementMSG class >> h0Trm [
<category: 'h0'>
^2r0111
]
MTP3NetworkManagementMSG class >> h0Ufc [
<category: 'h0'>
^2r1010
]
MTP3NetworkManagementMSG class >> h1CBA [
<category: 'h1CHM'>
^2r0110
]
MTP3NetworkManagementMSG class >> h1CBD [
<category: 'h1CHM'>
^2r0101
]
MTP3NetworkManagementMSG class >> h1COA [
<category: 'h1CHM'>
^2r0010
]
MTP3NetworkManagementMSG class >> h1COO [
<category: 'h1CHM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1CNP [
<category: 'h1DLM'>
^2r0100
]
MTP3NetworkManagementMSG class >> h1CNS [
<category: 'h1DLM'>
^2r0011
]
MTP3NetworkManagementMSG class >> h1CSS [
<category: 'h1DLM'>
^2r0010
]
MTP3NetworkManagementMSG class >> h1DLC [
<category: 'h1DLM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1ECA [
<category: 'h1ECM'>
^2r0010
]
MTP3NetworkManagementMSG class >> h1ECO [
<category: 'h1ECM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1RCT [
<category: 'h1FCM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1TFC [
<category: 'h1FCM'>
^2r0010
]
MTP3NetworkManagementMSG class >> h1LFU [
<category: 'h1MIM'>
^2r0110
]
MTP3NetworkManagementMSG class >> h1LIA [
<category: 'h1MIM'>
^2r0011
]
MTP3NetworkManagementMSG class >> h1LID [
<category: 'h1MIM'>
^2r0101
]
MTP3NetworkManagementMSG class >> h1LIN [
<category: 'h1MIM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1LLT [
<category: 'h1MIM'>
^2r0111
]
MTP3NetworkManagementMSG class >> h1LRT [
<category: 'h1MIM'>
^2r1000
]
MTP3NetworkManagementMSG class >> h1LUA [
<category: 'h1MIM'>
^2r0100
]
MTP3NetworkManagementMSG class >> h1LUN [
<category: 'h1MIM'>
^2r0010
]
MTP3NetworkManagementMSG class >> h1RSR [
<category: 'h1RSM'>
^2r0010
]
MTP3NetworkManagementMSG class >> h1RST [
<category: 'h1RSM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1TFA [
<category: 'h1TFM'>
^2r0101
]
MTP3NetworkManagementMSG class >> h1TFP [
<category: 'h1TFM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1TFR [
<category: 'h1TFM'>
^2r0011
]
MTP3NetworkManagementMSG class >> h1TRA [
<category: 'h1TRM'>
^2r0001
]
MTP3NetworkManagementMSG class >> h1UPU [
<category: 'h1UFC'>
^2r0001
]
MTP3NetworkManagementMSG class >> isServiceCompatible: aServiceIndicator [
<category: 'parsing'>
^aServiceIndicator serviceIndicator
= MTP3ServiceIndicators signallingNetworkManagement
]
]
MTP3NetworkManagementMSG subclass: MTP3TRMMSG [
<category: 'MTP3-Codec'>
<comment: 'TRM message base class'>
MTP3TRMMSG class >> h0 [
^self h0Trm
]
MTP3TRMMSG class >> humanName [
^'Traffic-restart-allowed message'
]
]
MTP3NetworkManagementMSG subclass: MTP3CHMMSG [
<category: 'MTP3-Codec'>
<comment: 'CHM message base class'>
MTP3CHMMSG class >> h0 [
^self h0Chm
]
MTP3CHMMSG class >> humanName [
^'Changeover and changeback messages'
]
]
MTP3NetworkManagementMSG subclass: MTP3ECMMSG [
<category: 'MTP3-Codec'>
<comment: 'ECM message base class'>
MTP3ECMMSG class >> h0 [
^self h0Ecm
]
MTP3ECMMSG class >> humanName [
^'Emergency-changeover message'
]
]
MTP3LinkTestMSG subclass: MTP3SLTMMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3SLTMMSG class >> h1 [
^self h1SLTM
]
MTP3SLTMMSG class >> humanName [
^'signalling link test acknowledgement message'
]
]
MTP3CHMMSG subclass: MTP3CBAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3CBAMSG class >> h1 [
^self h1CBA
]
MTP3CBAMSG class >> humanName [
^'Changeback-acknowledgement signal'
]
]
MTP3CHMMSG subclass: MTP3COOMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3COOMSG class >> h1 [
^self h1COO
]
MTP3COOMSG class >> humanName [
^'Changeover-order signal'
]
]
MTP3Field subclass: MTP3Label [
| dpc opc slc |
<category: 'MTP3-Codec'>
<comment: 'I represent a Q.704 15.2 Label. Maybe I should use GSMBitField or such in the future.'>
MTP3Label class >> parseFrom: aStream [
| slc opc dpc tmp |
tmp := aStream next: 4.
"TODO: Use the GSMBitfield or a bitreader"
slc := (tmp at: 4) bitAnd: 16r0F.
dpc := tmp first.
dpc := dpc bitOr: ((tmp second bitAnd: 2r00111111) bitShift: 8).
opc := tmp second bitShift: -6.
opc := opc bitOr: (tmp third bitShift: 2).
opc := opc bitOr: ((tmp fourth bitAnd: 2r00001111) bitShift: 10).
^(MTP3Label new)
dpc: dpc;
opc: opc;
slc: slc;
yourself
]
dpc [
<category: 'accessing'>
^dpc
]
opc [
<category: 'accessing'>
^opc
]
slc [
<category: 'accessing'>
^slc
]
dpc: aDpc [
<category: 'creation'>
dpc := aDpc
]
opc: anOpc [
<category: 'creation'>
opc := anOpc
]
slc: aSlc [
<category: 'creation'>
slc := aSlc
]
writeOn: aBuffer [
<category: 'encode'>
| data w_slc w_dpc w_opc |
w_slc := slc bitAnd: 2r111.
w_dpc := dpc bitAnd: 2r11111111111111.
w_opc := opc bitAnd: 2r11111111111111.
data := (w_dpc bitOr: (w_opc bitShift: 14))
bitOr: (w_slc bitShift: 14 + 14).
aBuffer
putByte: ((data bitShift: 0) bitAnd: 16rFF);
putByte: ((data bitShift: -8) bitAnd: 16rFF);
putByte: ((data bitShift: -16) bitAnd: 16rFF);
putByte: ((data bitShift: -24) bitAnd: 16rFF)
]
]
MTP3NetworkManagementMSG subclass: MTP3RSMMSG [
<category: 'MTP3-Codec'>
<comment: 'RSM message base class'>
MTP3RSMMSG class >> h0 [
^self h0Rsm
]
MTP3RSMMSG class >> humanName [
^'Signalling-route-set-test message'
]
]
MTP3RSMMSG subclass: MTP3RSTMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3RSTMSG class >> h1 [
^self h1RST
]
MTP3RSTMSG class >> humanName [
^'Signalling-route-set-test signal for prohibited destination'
]
]
MTP3CHMMSG subclass: MTP3CBDMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3CBDMSG class >> h1 [
^self h1CBD
]
MTP3CBDMSG class >> humanName [
^'Changeback-declaration signal'
]
]
MTP3LinkTestMSG subclass: MTP3SLTAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3SLTAMSG class >> h1 [
^self h1SLTA
]
MTP3SLTAMSG class >> humanName [
^'Signalling link test message'
]
]
MTP3ECMMSG subclass: MTP3ECOMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3ECOMSG class >> h1 [
^self h1ECO
]
MTP3ECOMSG class >> humanName [
^'Emergency-changeover-order signal'
]
]
MTP3NetworkManagementMSG subclass: MTP3DLMMSG [
<category: 'MTP3-Codec'>
<comment: 'DLM message base class'>
MTP3DLMMSG class >> h0 [
^self h0Dlm
]
MTP3DLMMSG class >> humanName [
^'Signalling-data-link-connection-order message'
]
]
MTP3DLMMSG subclass: MTP3CNPMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3CNPMSG class >> h1 [
^self h1CNP
]
MTP3CNPMSG class >> humanName [
^'Connection-not-possible signal'
]
]
MTP3DLMMSG subclass: MTP3DLCMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3DLCMSG class >> h1 [
^self h1DLC
]
MTP3DLCMSG class >> humanName [
^'Signalling-data-link-connection-order signal'
]
]
MTP3DLMMSG subclass: MTP3CNSMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3CNSMSG class >> h1 [
^self h1CNS
]
MTP3CNSMSG class >> humanName [
^'Connection-not-successful signal'
]
]
MTP3DLMMSG subclass: MTP3CSSMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3CSSMSG class >> h1 [
^self h1CSS
]
MTP3CSSMSG class >> humanName [
^'Connection-successful signal'
]
]
MTP3RSMMSG subclass: MTP3RSRMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3RSRMSG class >> h1 [
^self h1RSR
]
MTP3RSRMSG class >> humanName [
^'Signalling-route-set-test signal for restricted destination (national option)'
]
]
MTP3CHMMSG subclass: MTP3COAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3COAMSG class >> h1 [
^self h1COA
]
MTP3COAMSG class >> humanName [
^'Changeover-acknowledgement signal'
]
]
MTP3NetworkManagementMSG subclass: MTP3MIMMSG [
<category: 'MTP3-Codec'>
<comment: 'MIM message base class'>
MTP3MIMMSG class >> h0 [
^self h0Mim
]
MTP3MIMMSG class >> humanName [
^'Management inhibit messages'
]
]
MTP3MIMMSG subclass: MTP3LIAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LIAMSG class >> h1 [
^self h1LIA
]
MTP3LIAMSG class >> humanName [
^'Link inhibit acknowledgement signal'
]
]
MTP3MIMMSG subclass: MTP3LINMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LINMSG class >> h1 [
^self h1LIN
]
MTP3LINMSG class >> humanName [
^'Link inhibit signal'
]
]
MTP3MIMMSG subclass: MTP3LFUMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LFUMSG class >> h1 [
^self h1LFU
]
MTP3LFUMSG class >> humanName [
^'Link forced uninhibit signal'
]
]
MTP3MIMMSG subclass: MTP3LIDMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LIDMSG class >> h1 [
^self h1LID
]
MTP3LIDMSG class >> humanName [
^'Link inhibit denied signal'
]
]
MTP3MIMMSG subclass: MTP3LUAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LUAMSG class >> h1 [
^self h1LUA
]
MTP3LUAMSG class >> humanName [
^'Link uninhibit acknowledgement signal'
]
]
MTP3MIMMSG subclass: MTP3LUNMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LUNMSG class >> h1 [
^self h1LUN
]
MTP3LUNMSG class >> humanName [
^'Link uninhibit signal'
]
]
MTP3MIMMSG subclass: MTP3LLTMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LLTMSG class >> h1 [
^self h1LLT
]
MTP3LLTMSG class >> humanName [
^'Link local inhibit test signal'
]
]
MTP3NetworkManagementMSG subclass: MTP3FCMMSG [
<category: 'MTP3-Codec'>
<comment: 'FCM message base class'>
MTP3FCMMSG class >> h0 [
^self h0Fcm
]
MTP3FCMMSG class >> humanName [
^'Signalling-traffic-flow-control messages'
]
]
MTP3FCMMSG subclass: MTP3TFCMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3TFCMSG class >> humanName [
^'Transfer-controlled signal'
]
]
MTP3FCMMSG subclass: MTP3RCTMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3RCTMSG class >> humanName [
^'Signalling-route-set-congestion-test signal'
]
]
MTP3TRMMSG subclass: MTP3TRAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3TRAMSG class >> h1 [
^self h1TRA
]
MTP3TRAMSG class >> humanName [
^'Traffic-restart-allowed signal'
]
]
MTP3Field subclass: MTP3ServiceIndicators [
| serviceIndicator subServiceField |
<category: 'MTP3-Codec'>
<comment: 'I represent a Q.704 14.2.1 service Indicator and 14.2.2 sub-service field'>
MTP3ServiceIndicators class >> broadbandIsdnUserPart [
<category: 'service-indicators'>
^2r1001
]
MTP3ServiceIndicators class >> dataUserPartCallAndCircuit [
<category: 'service-indicators'>
^2r0110
]
MTP3ServiceIndicators class >> dataUserPartFacilityAndCancellation [
<category: 'service-indicators'>
^2r0111
]
MTP3ServiceIndicators class >> isdnUserPart [
<category: 'service-indicators'>
^2r0101
]
MTP3ServiceIndicators class >> reservedMtpTestingUserPart [
<category: 'service-indicators'>
^2r1000
]
MTP3ServiceIndicators class >> satelliteIsdnUserPart [
<category: 'service-indicators'>
^2r1010
]
MTP3ServiceIndicators class >> sccp [
<category: 'service-indicators'>
^2r0011
]
MTP3ServiceIndicators class >> serviceSpare [
<category: 'service-indicators'>
^2r0010
]
MTP3ServiceIndicators class >> signallingNetworkManagement [
<category: 'service-indicators'>
^2r0000
]
MTP3ServiceIndicators class >> signallingNetworkTestingAndMaintenance [
<category: 'service-indicators'>
^2r0001
]
MTP3ServiceIndicators class >> telephoneUserPart [
<category: 'service-indicators'>
^2r0100
]
MTP3ServiceIndicators class >> internationalNetwork [
<category: 'subservice-indicators'>
^2r0000
]
MTP3ServiceIndicators class >> nationalNetwork [
<category: 'subservice-indicators'>
^2r1000
]
MTP3ServiceIndicators class >> reservedNationalUse [
<category: 'subservice-indicators'>
^2r1100
]
MTP3ServiceIndicators class >> subServiceSpare [
<category: 'subservice-indicators'>
^2r0100
]
MTP3ServiceIndicators class >> parseFrom: aStream [
<category: 'parsing'>
| byte |
byte := aStream next.
^(self new)
serviceIndicator: (byte bitAnd: 2r1111);
subServiceField: (byte bitShift: -4);
yourself
]
serviceIndicator: anIndicator [
<category: 'creation'>
serviceIndicator := anIndicator
]
subServiceField: aSubServiceField [
<category: 'creation'>
subServiceField := aSubServiceField
]
serviceIndicator [
<category: 'accessing'>
^serviceIndicator
]
subServiceField [
<category: 'accessing'>
^subServiceField
]
writeOn: aMsg [
<category: 'encoding'>
| data |
data := (subServiceField bitShift: 4) bitAnd: 2r11110000.
data := (serviceIndicator bitAnd: 2r1111) bitOr: data.
aMsg putByte: data
]
]
MTP3NetworkManagementMSG subclass: MTP3TFMMSG [
<category: 'MTP3-Codec'>
<comment: 'TFM message base class'>
MTP3TFMMSG class >> h0 [
^self h0Tfm
]
MTP3TFMMSG class >> humanName [
^'Transfer-prohibited-transfer-allowed-transfer-restricted messages'
]
]
MTP3TFMMSG subclass: MTP3TFAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3TFAMSG class >> h1 [
^self h1TFA
]
MTP3TFAMSG class >> humanName [
^'Transfer-allowed signal'
]
]
MTP3TFMMSG subclass: MTP3TFRMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3TFRMSG class >> h1 [
^self h1TFR
]
MTP3TFRMSG class >> humanName [
^'Transfer-restricted signal (national option)'
]
]
MTP3TFMMSG subclass: MTP3TFPMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3TFPMSG class >> h1 [
^self h1TFP
]
MTP3TFPMSG class >> humanName [
^'Transfer-prohibited signal'
]
]
MTP3NetworkManagementMSG subclass: MTP3UFCMSG [
<category: 'MTP3-Codec'>
<comment: 'UFC message base class'>
MTP3UFCMSG class >> h0 [
^self h0Ufc
]
MTP3UFCMSG class >> humanName [
^'User part flow control messages'
]
]
MTP3UFCMSG subclass: MTP3UPUMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3UPUMSG class >> h1 [
^self h1UPU
]
MTP3UPUMSG class >> humanName [
^'User part unavailable signal'
]
]
MTP3ECMMSG subclass: MTP3ECAMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3ECAMSG class >> h1 [
^self h1ECA
]
MTP3ECAMSG class >> humanName [
^'Emergency-changeover-acknowledgement signal'
]
]
MTP3MIMMSG subclass: MTP3LRTMSG [
<category: 'MTP3-Codec'>
<comment: nil>
MTP3LRTMSG class >> h1 [
^self h1LRT
]
MTP3LRTMSG class >> humanName [
^'Link remote inhibit test signal'
]
]