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

misc: Add proper categories to the various SIP classes

This commit is contained in:
Holger Hans Peter Freyther 2011-09-27 17:43:43 +02:00
parent e134b1e825
commit 1c58c2fe26
15 changed files with 47 additions and 20 deletions

View File

@ -5,6 +5,8 @@ Eval [
ReadWriteStream subclass: MIMERWStream [
| readLimit |
<category: 'OsmoSIP-Base64'>
nextPut: aInt [
| res |
res := super nextPut: aInt.
@ -25,7 +27,7 @@ ReadWriteStream subclass: MIMERWStream [
Object subclass: MimeConverter [
| dataStream mimeStream |
<category: 'Network-MIME'>
<category: 'OsmoSIP-Base64'>
dataStream [
<category: 'accessing'>
@ -68,7 +70,7 @@ MimeConverter subclass: Base64LikeConverter [
| data |
<comment: 'This class encodes and decodes data in Base64 format. This is MIME encoding. We translate a whole stream at once, taking a Stream as input and giving one as output. Returns a whole stream for the caller to use. 0 A 17 R 34 i 51 z 1 B 18 S 35 j 52 0 2 C 19 T 36 k 53 1 3 D 20 U 37 l 54 2 4 E 21 V 38 m 55 3 5 F 22 W 39 n 56 4 6 G 23 X 40 o 57 5 7 H 24 Y 41 p 58 6 8 I 25 Z 42 q 59 7 9 J 26 a 43 r 60 8 10 K 27 b 44 s 61 9 11 L 28 c 45 t 62 + 12 M 29 d 46 u 63 / 13 N 30 e 47 v 14 O 31 f 48 w (pad) = 15 P 32 g 49 x 16 Q 33 h 50 y Outbound: bytes are broken into 6 bit chunks, and the 0-63 value is converted to a character. 3 data bytes go into 4 characters. Inbound: Characters are translated in to 0-63 values and shifted into 8 bit bytes. (See: N. Borenstein, Bellcore, N. Freed, Innosoft, Network Working Group, Request for Comments: RFC 1521, September 1993, MIME (Multipurpose Internet Mail Extensions) Part One: Mechanisms for Specifying and Describing the Format of Internet Message Bodies. Sec 6.2) By Ted Kaehler, based on Tim Olson''s Base64Filter.'>
<category: 'Network-MIME'>
<category: 'OsmoSIP-Base64'>
FromCharTable := nil.
ToCharTable := nil.

View File

@ -20,7 +20,7 @@ PackageLoader fileInPackage: 'OsmoCore'.
SIPRequest extend [
sipCallDispatch: aCall [
<category: '*sip-call'>
<category: '*-OsmoSIP-call'>
self logError: 'SIPCall(%1) got unhandled request %2.'
% {aCall callId. self class verb} area: #sip.
]
@ -28,7 +28,7 @@ SIPRequest extend [
SIPByeRequest extend [
sipCallDispatch: aCall [
<category: '*sip-call'>
<category: '*-OsmoSIP-call'>
self logDebug: 'SIPCall(%1) got BYE.'
% {aCall callId} area: #sip.
aCall remoteHangup: self.
@ -38,7 +38,7 @@ SIPByeRequest extend [
Object subclass: SIPSessionBase [
| rem ua initial_dialog dialog next_cseq |
<category: 'SIP-Session'>
<category: 'OsmoSIP-Callagent'>
<comment: 'I am the base for sessions. I am a bit backward as the
Dialog will create/hold the session but we start with the session here
as this is what we are really interested in. So this is not really a
@ -146,7 +146,7 @@ a proper session.'>
SIPSessionBase subclass: SIPCall [
| sdp_offer sdp_result invite state |
<category: 'SIP-Session'>
<category: 'OsmoSIP-Callagent'>
<comment: 'I am a high level class to deal with transactions,
sessions and calls. Right now I do not support forking proxies and
will simply ignore everything but the first dialog.'>

View File

@ -20,7 +20,7 @@ PackageLoader fileInPackage: 'Sockets'.
Object subclass: SIPTransport [
| queue handler |
<category: 'SIP-Callagent'>
<category: 'OsmoSIP-Callagent'>
<comment: 'I am the baseclass for a transport'>
SIPTransport class >> type [

View File

@ -20,7 +20,7 @@ Object subclass: SIPDialog [
| from from_tag to to_tag dest_ip dest_port is_client call_id
state contact cseq |
<comment: 'I represent a dialog between two parties'>
<category: 'SIP-Callagent'>
<category: 'OsmoSIP-Callagent'>
SIPDialog class >> stateUnconfirmed [ <category: 'state'> ^ #unconfirmed ]
SIPDialog class >> stateConfirmed [ <category: 'state'> ^ #confirmed ]

View File

@ -19,7 +19,7 @@
PackageLoader fileInPackage: #OsmoLogging.
Osmo.LogArea subclass: SIPLogArea [
<category: 'SIP-logarea'>
<category: 'OsmoSIP-LogArea'>
SIPLogArea class >> areaName [ ^ #sip ]
SIPLogArea class >> areaDescription [

View File

@ -19,6 +19,8 @@
Object subclass: SIPParam [
| data |
<category: 'OsmoSIP-Param'>
asFoldedString [
<category: 'compat'>
^ data
@ -32,6 +34,8 @@ Object subclass: SIPParam [
SIPParam subclass: SIPVia [
| branch |
<category: 'OsmoSIP-Param'>
SIPVia class >> findBranch: aData [
<category: 'creation'>
aData do: [:each |
@ -57,6 +61,8 @@ SIPParam subclass: SIPVia [
SIPParam subclass: SIPCSeq [
| number method |
<category: 'OsmoSIP-Param'>
SIPCSeq class >> parseFrom: aParseDict [
<category: 'creation'>
^ self new
@ -79,14 +85,15 @@ SIPParam subclass: SIPCSeq [
Object extend [
isGenericSIPParam [
<category: '*osmo-sip-extension'>
<category: '*-OsmoSIP-param'>
^ false
]
]
Object subclass: SIPGenericParam [
| key value |
<category: 'SIP-Param'>
<category: 'OsmoSIP-Param'>
<comment: 'I am a simple key value pair with the value being optional'>
SIPGenericParam class >> fromOptional: anArray [
@ -151,7 +158,8 @@ Object subclass: SIPGenericParam [
SIPParam subclass: SIPToFromParam [
| addr params |
<category: 'SIP-Param'>
<category: 'OsmoSIP-Param'>
<comment: 'I represent a To/From parameter'>
SIPToFromParam class >> buildParams: aParam [

View File

@ -18,17 +18,20 @@
Array extend [
asFoldedString [
<category: '*-OsmoSIP-parser'>
^ (Osmo at: #SIPParser) combineUri: self.
]
]
String extend [
asFoldedString [
<category: '*-OsmoSIP-parser'>
^ self
]
]
SIPGrammar subclass: SIPParser [
<category: 'OsmoSIP-Parser'>
<comment: 'I create either a SIPRequest or a SIPResponse'>
SIPParser class >> addArrayRec: anArray on: aStream [

View File

@ -19,6 +19,7 @@
PackageLoader fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: SIPParserTest [
<category: 'OsmoSIP-Parser'>
<comment: 'I excercise the SIPParser a bit'>
parserClass [

View File

@ -19,12 +19,15 @@
PackageLoader fileInPackage: 'Sockets'.
Object subclass: SIPBase64 [
<category: 'OsmoSIP-Misc'>
SIPBase64 class >> encode: aString [
^ (Base64LikeConverter mimeEncode: aString readStream) contents
]
]
Object subclass: SIPSecureRandom [
<category: 'OsmoSIP-Misc'>
<comment: 'I try to give some cryptographically secure random numbers'>
SIPSecureRandom class >> nextByte [
@ -57,6 +60,7 @@ Object subclass: SIPSecureRandom [
]
Object subclass: SIPRandomHelper [
<category: 'OsmoSIP-Misc'>
<comment: 'I help with generating numbers'>
SIPRandomHelper class >> generateTag [

View File

@ -20,8 +20,9 @@
Object subclass: SIPRequest [
| dest parameters sdp dialog |
<category: 'OsmoSIP-Callagent'>
<comment: 'I should share a parent with MGCPCommand'>
<category: 'SIP-Callagent'>
SIPRequest class >> requestForVerb: aVerb [
"Find a class that handles this verb"
@ -130,7 +131,7 @@ Object subclass: SIPRequest [
]
SIPRequest subclass: SIPInviteRequest [
<category: 'SIP-Callagent'>
<category: 'OsmoSIP-Callagent'>
SIPInviteRequest class >> verb [
<category: 'verb'>
@ -148,7 +149,7 @@ SIPRequest subclass: SIPInviteRequest [
]
SIPRequest subclass: SIPACKRequest [
<category: 'SIP-Callagent'>
<category: 'OsmoSIP-Callagent'>
SIPACKRequest class >> verb [
<category: 'verb'>
@ -157,7 +158,7 @@ SIPRequest subclass: SIPACKRequest [
]
SIPRequest subclass: SIPCancelRequest [
<category: 'SIP-Callagent'>
<category: 'OsmoSIP-Callagent'>
SIPCancelRequest class >> verb [
<category: 'verb'>

View File

@ -19,6 +19,8 @@
Object subclass: SIPResponse [
| code phrase params sdp |
<category: 'OsmoSIP-Callagent'>
SIPResponse class >> parseFrom: aParseDict [
| res |
res := (self

View File

@ -23,6 +23,8 @@ Object subclass: SIPTransaction [
| sem useragent initial_dialog state timeout success failure notification
cseq branch retransmit_time fail_time removal |
<category: 'OsmoSIP-Callagent'>
SIPTransaction class >> stateInitial [ <category: 'states'> ^ #initial ]
SIPTransaction class >> stateTrying [ <category: 'states'> ^ #trying ]
SIPTransaction class >> stateProceeding [ <category: 'states'> ^ #proceeding ]
@ -310,7 +312,9 @@ Object subclass: SIPTransaction [
SIPTransaction subclass: SIPInviteTransaction [
| sdp ack_branch canceled |
<category: 'RFC3161 17.2.1'>
<category: 'OsmoSIP-Callagent'>
<comment: 'RFC3161 17.2.1'>
"200ms to get TRYING or OK"
@ -441,7 +445,7 @@ SIPTransaction subclass: SIPInviteTransaction [
]
SIPTransaction subclass: SIPByeTransaction [
<category: 'a bye...'>
<category: 'OsmoSIP-Callagent'>
transmit [
| bye |

View File

@ -17,6 +17,8 @@
"
TestCase subclass: SIPRequestTest [
<category: 'OsmoSIP-Callagent'>
testINVITE [
| dialog req out |

View File

@ -28,7 +28,7 @@ PP.PPCompositeParser subclass: SIPGrammar [
RequestURI
|
"http://sofia-sip.org/repos/sofia-sip/libsofia-sip-ua/sip/GRAMMAR"
<category: 'SIP-Core'>
<category: 'OsmoSIP-Grammar'>
<comment: 'I try to parse RFC3261'>
start [

View File

@ -19,8 +19,8 @@
PackageLoader fileInPackage: 'PetitParserTests'.
PP.PPCompositeParserTest subclass: SIPGrammarTest [
<category: 'OsmoSIP-Grammar'>
<comment: 'I try to parse some SIP messages.'>
<category: 'SIP-Core'>
SIPGrammarTest class >> packageNamesUnderTest [
<category: 'accessing'>