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/isup/ISUP.st

473 lines
18 KiB
Smalltalk
Raw Normal View History

"
(C) 2011-2012 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: ISUPConstants [
<comment: 'Constants for the ISDN User Part (ISUP) protocol'>
<category: 'OsmoNetwork-ISUP'>
ISUPConstants class [
msgAPT [
"Application transport"
<category: 'constants'>
^ 2r01000001
]
msgACM [
"Address complete"
<category: 'constants'> ^ 2r00000110
]
msgAMN [
"Answer"
<category: 'constants'> ^ 2r00001001
]
msgBLA [
"Blocking acknowledgement"
<category: 'constants'> ^ 2r00010101
]
msgBLO [
"Blocking"
<category: 'constants'> ^ 2r00010011
]
msgCCR [
"Continuity check request"
<category: 'constants'> ^ 2r00010001
]
msgCFN [
"Confusion"
<category: 'constants'> ^ 2r00101111
]
msgCGB [
"Circuit group blocking"
<category: 'constants'> ^ 2r00011000
]
msgCGBA [
"Circuit group blocking acknowledgement"
<category: 'constants'> ^ 2r00011010
]
msgCGU [
"Circuit group unblocking"
<category: 'constants'> ^ 2r00011001
]
msgCGUA [
"Circuit group unblocking acknowledgement"
<category: 'constants'> ^ 2r00011011
]
msgCON [
"Connect"
<category: 'constants'> ^ 2r00000111
]
msgCOT [
"Continuity"
<category: 'constants'> ^ 2r00000101
]
msgCPG [
"Call progress"
<category: 'constants'> ^ 2r00101100
]
msgCRG [
"Charge information"
<category: 'constants'> ^ 2r00110001
]
msgCQM [
"Circuit group query"
<category: 'constants'> ^ 2r00101010
]
msgCQR [
"Circuit group query response"
<category: 'constants'> ^ 2r00101011
]
msgDRS [
"Delayed release (reserved used in 1988 version)"
<category: 'constants'> ^ 2r00100111
]
msgFAC [
"Facility"
<category: 'constants'> ^ 2r00110011
]
msgFAA [
"Facility accepted"
<category: 'constants'> ^ 2r00100000
]
msgFAR [
"Facility request"
<category: 'constants'> ^ 2r00011111
]
msgFOT [
"Forward transfer"
<category: 'constants'> ^ 2r00001000
]
msgFRJ [
"Facility reject"
<category: 'constants'> ^ 2r00100001
]
msgGRA [
"Circuit group reset acknowledgement"
<category: 'constants'> ^ 2r00101001
]
msgGRS [
"Circuit group reset"
<category: 'constants'> ^ 2r00010111
]
msgIDR [
"Identification request"
<category: 'constants'> ^ 2r00110110
]
msgIDS [
"Identification response"
<category: 'constants'> ^ 2r00110111
]
msgIAM [
"Initial address"
<category: 'constants'> ^ 2r00000001
]
msgINF [
"Information"
<category: 'constants'> ^ 2r00000100
]
msgINR [
"Information request"
<category: 'constants'> ^ 2r00000011
]
msgLPA [
"Loop back acknowledgement"
<category: 'constants'> ^ 2r00100100
]
msgLPR [
"Loop prevention"
<category: 'constants'> ^ 2r01000000
]
msgOLM [
"Overload"
<category: 'constants'> ^ 2r00110000
]
msgPAM [
"Pass-along"
<category: 'constants'> ^ 2r00101000
]
msgREL [
"Release"
<category: 'constants'> ^ 2r00001100
]
msgRES [
"Resume"
<category: 'constants'> ^ 2r00001110
]
msgRLC [
"Release complete"
<category: 'constants'> ^ 2r00010000
]
msgRSC [
"Reset circuit"
<category: 'constants'> ^ 2r00010010
]
msgSAM [
"Subsequent address"
<category: 'constants'> ^ 2r00000010
]
msgSUS [
"Suspend"
<category: 'constants'> ^ 2r00001101
]
msgUBL [
"Unblocking"
<category: 'constants'> ^ 2r00010100
]
msgUBA [
"Unblocking acknowledgement"
<category: 'constants'> ^ 2r00010110
]
msgUCIC [
"Unequipped circuit identification code"
<category: 'constants'> ^ 2r00101110
]
msgUSR [
"User-to-user information"
<category: 'constants'> ^ 2r00101101
]
msgNRM [
"Network resource management"
<category: 'constants'> ^ 2r00110010
]
msgPRI [
"Pre-release information"
<category: 'constants'> ^ 2r01000010
]
msgSAN [
"Subsequent Directory Number"
<category: 'constants'> ^ 2r01000011
]
msgSEG [
"Segmentation"
<category: 'constants'> ^ 2r00111000
]
msgUPA [
"User Part available"
<category: 'constants'> ^ 2r00110100
]
msgUPT [
"User Part test"
<category: 'constants'> ^ 2r00110100
]
parAccessDeliveryInformation [ <category: 'constants-Q767'> ^ 2r00101110 ]
parAccessTransport [ <category: 'constants-Q767'> ^ 2r00000011 ]
parApplicationTransportParameter [ <category: 'constants-Q767'> ^ 2r01111000 ]
parAutomaticCongestionLevel [ <category: 'constants-Q767'> ^ 2r00100111 ]
parBackwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00010001 ]
parBackwardGVNS [ <category: 'constants-Q767'> ^ 2r01001101 ]
parCallDiversionInformation [ <category: 'constants-Q767'> ^ 2r00110110 ]
parCallDiversionTreatmentIndicators [ <category: 'constants-Q767'> ^ 2r01101110 ]
parCallHistoryInformation [ <category: 'constants-Q767'> ^ 2r00101101 ]
parCallOfferingTreatmentIndicators [ <category: 'constants-Q767'> ^ 2r01110000 ]
parCallReference [ <category: 'constants-Q767'> ^ 2r00000001 ]
parCallTransferNumber [ <category: 'constants-Q767'> ^ 2r01000101 ]
parCallTransferReference [ <category: 'constants-Q767'> ^ 2r01000011 ]
parCalledINNumber [ <category: 'constants-Q767'> ^ 2r01101111 ]
parCalledDirectoryNumber [ <category: 'constants-Q767'> ^ 2r01111101 ]
parCalledPartyNumber [ <category: 'constants-Q767'> ^ 2r00000100 ]
parCallingGeodeticLocation [ <category: 'constants-Q767'> ^ 2r10000001 ]
parCallingPartyNumber [ <category: 'constants-Q767'> ^ 2r00001010 ]
parCallingPartysCategory [ <category: 'constants-Q767'> ^ 2r00001001 ]
parCauseIndicators [ <category: 'constants-Q767'> ^ 2r00010010 ]
parCCNRPossibleIndicator [ <category: 'constants-Q767'> ^ 2r01111010 ]
parCCSS [ <category: 'constants-Q767'> ^ 2r01001011 ]
parChargedPartyIdentification [ <category: 'constants-Q767'> ^ 2r01110001 ]
parCircuitAssignmentMap [ <category: 'constants-Q767'> ^ 2r00100101 ]
parCircuitGroupSupervisionMessageType [ <category: 'constants-Q767'> ^ 2r00010101 ]
parCircuitStateIndicator [ <category: 'constants-Q767'> ^ 2r00100110 ]
parClosedUserGroupInterlockCode [ <category: 'constants-Q767'> ^ 2r00011010 ]
parCollectCallRequest [ <category: 'constants-Q767'> ^ 2r01111001 ]
parConferenceTreatmentIndicators [ <category: 'constants-Q767'> ^ 2r01110010 ]
parConnectedNumber [ <category: 'constants-Q767'> ^ 2r00100001 ]
parConnectionRequest [ <category: 'constants-Q767'> ^ 2r00001101 ]
parContinuityIndicators [ <category: 'constants-Q767'> ^ 2r00010000 ]
parCorrelationId [ <category: 'constants-Q767'> ^ 2r01100101 ]
parDisplayInformation [ <category: 'constants-Q767'> ^ 2r01110011 ]
parEchoControlInformation [ <category: 'constants-Q767'> ^ 2r00110111 ]
parEndOfOptionalParameters [ <category: 'constants-Q767'> ^ 2r00000000 ]
parEventInformation [ <category: 'constants-Q767'> ^ 2r00100100 ]
parFacilityIndicator [ <category: 'constants-Q767'> ^ 2r00011000 ]
parForwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00000111 ]
parForwardGVNS [ <category: 'constants-Q767'> ^ 2r01001100 ]
parGenericDigits [ <category: 'constants-Q767'> ^ 2r11000001 ]
parGenericNotificationIndicator [ <category: 'constants-Q767'> ^ 2r00101100 ]
parGenericNumber [ <category: 'constants-Q767'> ^ 2r11000000 ]
parGenericReference [ <category: 'constants-Q767'> ^ 2r10000010 ]
parHTRInformation [ <category: 'constants-Q767'> ^ 2r10000010 ]
parHopCounter [ <category: 'constants-Q767'> ^ 2r00111101 ]
parInformationIndicators [ <category: 'constants-Q767'> ^ 2r00001111 ]
parInformationRequestIndicators [ <category: 'constants-Q767'> ^ 2r00001110 ]
parLocationNumber [ <category: 'constants-Q767'> ^ 2r00111111 ]
parLoopPreventionIndicators [ <category: 'constants-Q767'> ^ 2r01000100 ]
parMCIDRequestIndicators [ <category: 'constants-Q767'> ^ 2r00111011 ]
parMCIDResponseIndicators [ <category: 'constants-Q767'> ^ 2r00111100 ]
parMessageCompatibilityInformation [ <category: 'constants-Q767'> ^ 2r00111000 ]
parMLPPPrecedence [ <category: 'constants-Q767'> ^ 2r00111010 ]
parNatureOfConnectionIndicators [ <category: 'constants-Q767'> ^ 2r00000110 ]
parNetworkManagementControls [ <category: 'constants-Q767'> ^ 2r01011011 ]
parNetworkRoutingNumber [ <category: 'constants-Q767'> ^ 2r10000100 ]
parNetworkSpecificFacility [ <category: 'constants-Q767'> ^ 2r00101111 ]
parNumberPortabilityForwardInformation [ <category: 'constants-Q767'> ^ 2r10001101 ]
parOptionalBackwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00101001 ]
parOptionalForwardCallIndicators [ <category: 'constants-Q767'> ^ 2r00001000 ]
parOriginalCalledNumber [ <category: 'constants-Q767'> ^ 2r00101000 ]
parOriginalCalledINNumber [ <category: 'constants-Q767'> ^ 2r01111111 ]
parOriginationISCPointCode [ <category: 'constants-Q767'> ^ 2r00101011 ]
parParameterCompatibilityInformation [ <category: 'constants-Q767'> ^ 2r00111001 ]
parPivotCapability [ <category: 'constants-Q767'> ^ 2r01111011 ]
parPivotCounter [ <category: 'constants-Q767'> ^ 2r10000111 ]
parPivotRoutingBackwardInformation [ <category: 'constants-Q767'> ^ 2r10001001 ]
parPivotRoutingForwardInformation [ <category: 'constants-Q767'> ^ 2r10001000 ]
parPivotRoutingIndicators [ <category: 'constants-Q767'> ^ 2r01111100 ]
parPivotStatus [ <category: 'constants-Q767'> ^ 2r10000110 ]
parPropagationDelayCounter [ <category: 'constants-Q767'> ^ 2r00110001 ]
parQoRCapability [ <category: 'constants-Q767'> ^ 2r10000101 ]
parRange [ <category: 'constants-Q767'> ^ 2r00010110 ]
parRangeAndStatus [ <category: 'constants-Q767'> ^ 2r00010110 ]
parRedirectBackwardInformation [ <category: 'constants-Q767'> ^ 2r10001100 ]
parRedirectCapability [ <category: 'constants-Q767'> ^ 2r01001110 ]
parRedirectCounter [ <category: 'constants-Q767'> ^ 2r01110111 ]
parRedirectForwardInformation [ <category: 'constants-Q767'> ^ 2r10001011 ]
parRedirectStatus [ <category: 'constants-Q767'> ^ 2r10001010 ]
parRedirectingNumber [ <category: 'constants-Q767'> ^ 2r00001011 ]
parRedirectionInformation [ <category: 'constants-Q767'> ^ 2r00010011 ]
parRedirectionNumber [ <category: 'constants-Q767'> ^ 2r00001100 ]
parRedirectionNumberRestriction [ <category: 'constants-Q767'> ^ 2r01000000 ]
parRemoteOperations [ <category: 'constants-Q767'> ^ 2r00110010 ]
parSCFId [ <category: 'constants-Q767'> ^ 2r01100110 ]
parServiceActivation [ <category: 'constants-Q767'> ^ 2r00110011 ]
parSignallingPointCode [ <category: 'constants-Q767'> ^ 2r00011110 ]
parSubsequentNumber [ <category: 'constants-Q767'> ^ 2r00000101 ]
parSuspendResumeIndicators [ <category: 'constants-Q767'> ^ 2r00100010 ]
parTransitNetworkSelection [ <category: 'constants-Q767'> ^ 2r00100011 ]
parTransmissionMediumRequirement [ <category: 'constants-Q767'> ^ 2r00000010 ]
parTransmissionMediumRequirementPrime [ <category: 'constants-Q767'> ^ 2r00111110 ]
parTransmissionMediumUsed [ <category: 'constants-Q767'> ^ 2r00110101 ]
parUIDActionIndicators [ <category: 'constants-Q767'> ^ 2r01110100 ]
parUIDCapabilityIndicators [ <category: 'constants-Q767'> ^ 2r01110101 ]
parUserServiceInformation [ <category: 'constants-Q767'> ^ 2r00011101 ]
parUserServiceInformationPrime [ <category: 'constants-Q767'> ^ 2r00110000 ]
parUserTeleserviceInformation [ <category: 'constants-Q767'> ^ 2r00110100 ]
parUserToUserIndicators [ <category: 'constants-Q767'> ^ 2r00101010 ]
parUserToUserInformation [ <category: 'constants-Q767'> ^ 2r00100000 ]
addrNAT_NATIONAL [
"National (significant) number"
<category: 'constants-address'>
^ 2r0000011
]
addrNAT_INTERNATIONAL [
"International number"
<category: 'constants-address'>
^ 2r0000100
]
]
]
TLVDescriptionContainer subclass: ISUPMessage [
<comment: 'I am the base class for the ISUP messages'>
<category: 'OsmoNetwork-ISUP'>
ISUPMessage class >> decodeByteStream: aStream [
<category: 'parsing'>
| col cic type |
cic := (aStream next: 2) shortAt: 1.
type := (aStream next: 1) at: 1.
col := self decodeByteStream: aStream type: type.
^ OrderedCollection with: cic with: type with: col.
]
ISUPMessage class >> encodeCollection: aCollection [
<category: 'encoding'>
| msg type |
msg := Osmo.MessageBuffer new.
type := aCollection at: 2.
msg put16: (aCollection at: 1).
msg putByte: type.
msg putByteArray: (self encodeCollection: (aCollection at: 3) type: type).
^ msg
]
parseVariable: aStream with: aClass into: decoded [
<category: 'parsing'>
| pos ptr res |
pos := aStream position.
ptr := aStream next.
aStream skip: ptr - 1.
res := super parseVariable: aStream with: aClass into: decoded.
aStream position: pos + 1.
^ res
]
prepareOptional: aStream [
"We are done with the variable section and now get the pointer
to the optional part and will move the stream there."
<category: 'parsing'>
| pos ptr |
pos := aStream position.
ptr := aStream next.
aStream skip: ptr - 1.
]
writeVariableEnd: aStream state: aState [
<category: 'encoding'>
"Write the optional pointer. TODO: In case of no optional this
should be 0"
aStream nextPut: (aState at: 'data') size + 1.
aStream nextPutAll: (aState at: 'data') contents.
]
writeVariable: msg with: clazz from: field state: aState [
| var_len |
"We will write a pointer and then store the data in the state"
<category: 'encoding'>
"Write the pointer of where the data will be"
var_len := self variable size.
msg nextPut: (aState at: 'data') size + var_len + 1.
"Store the data for later"
super writeVariable: (aState at: 'data') with: clazz from: field state: nil.
]
createState [
"Our parsing state. We need to queue the variable fields until all
of them have been written."
<category: 'encoding'>
^ Dictionary from: {'data' -> (WriteStream on: (ByteArray new: 3))}.
]
]