SIPURandom class extend [ nextByte [ ^(OsmoSecureRandom rand: 1) first. ] nextInt [ ^(OsmoSecureRandom rand: 4) asInteger ] nextFourBytes [ ^OsmoSecureRandom rand: 4 ] ] SIPUserAgentBase class extend [ generateCSeq [ "For pharo just use the random we have" ^(OsmoSecureRandom rand: 4) asInteger abs ] generateBranch [ | data | data := '<1p>,<2p>' expandMacrosWithArguments: {DateTime now asUTC asSeconds. (OsmoSecureRandom rand: 2) asInteger}. ^ self branchStart, (SIPBase64 encode: data). ] ] SIPUserAgentBase extend [ generateVia: aBranch [ "For Pharo assume that transport address is a string" ^ (WriteStream on: String new) nextPutAll: 'SIP/2.0/'; nextPutAll: transport type; nextPutAll: ' '; nextPutAll: transport address; nextPutAll: ':'; nextPutAll: transport port asString; nextPutAll: ';branch='; nextPutAll: aBranch; nextPutAll: ';rport'; contents. ] ] SIPQuotedStringParser extend [ skipWhitespace: aStream [ [aStream atEnd] whileFalse: [ | c | c := aStream uncheckedPeek. c = Character tab ifTrue: [aStream next]. c = Character space ifTrue: [aStream next]. ^self ] ] parseOn: aContext [ | memento startPosition result | startPosition := aContext position. memento := aContext remember. "Skip whitespace" self skipWhitespace: aContext. "Check for the opening space" aContext atEnd ifTrue: [ result := PPFailure message: 'No space for opening quote' context: aContext. aContext restore: memento. ^result]. aContext uncheckedPeek = $" ifFalse: [ result := PPFailure message: 'No opening quote' context: aContext. aContext restore: memento. ^result]. aContext skip: 1. result := self parseToClosingQuote: aContext. result isPetitFailure ifTrue: [ aContext restore: memento]. ^result ] parseToClosingQuote: aStream [ | text inQuote finish parsed | text := WriteStream on: String new. inQuote := false. parsed := false. finish := aStream atEnd. [finish] whileFalse: ["Did we have an escape?" inQuote ifTrue: [ "TODO: Check if that is a valid sequence" text nextPut: aStream next. inQuote := false. finish := aStream atEnd] ifFalse: [ | c | c := aStream uncheckedPeek. c = $" ifTrue: [ aStream skip: 1. parsed := true. ^text contents] ifFalse: [ c = $\ ifTrue: [inQuote := true]. text nextPut: c. aStream skip: 1. finish := aStream atEnd]]]. ^PPFailure message: 'Expected closing quote' context: aStream ] ] Base64LikeConverter class extend [ mimeEncode: aStream [ "Return a ReadWriteStream of characters. The data of aStream is encoded as 65 innocuous characters. (See class comment). 3 bytes in aStream goes to 4 bytes in output." | me | me := self new dataStream: aStream. me mimeStream: (ReadWriteStream on: (String new: (aStream size + 20) * 4 // 3)). me mimeEncode. me mimeStream position: 0. ^me mimeStream ] ] SIPDigest class extend [ ha1: aName realm: aRealm password: aPassword [ ^(MD5 hashMessage: (String streamContents: [:str | str nextPutAll: aName; nextPutAll: ':'; nextPutAll: aRealm; nextPutAll: ':'; nextPutAll: aPassword])) hex. ] ha2: anOperation uri: aSipUrlString [ ^(MD5 hashMessage: (String streamContents: [:str | str nextPutAll: anOperation; nextPutAll: ':'; nextPutAll: aSipUrlString])) hex. ] authUser: aName password: aPassword realm: aRealm nonce: aNonce operation: anOperation url: aSipUrlString [ | ha1 ha2 resp md5 | ha1 := self ha1: aName realm: aRealm password: aPassword. ha2 := self ha2: anOperation uri: aSipUrlString. ^(MD5 hashMessage: (String streamContents: [:str | str nextPutAll: ha1; nextPutAll: ':'; nextPutAll: aNonce; nextPutAll: ':'; nextPutAll: ha2])) hex ] authUser: aName password: aPassword realm: aRealm nonce: aNonce operation: anOperation url: aSipUrlString qop: aQop clientNonce: aCnonce nonceCount: aNc [ | ha1 ha2 resp md5 | ha1 := self ha1: aName realm: aRealm password: aPassword. ha2 := self ha2: anOperation uri: aSipUrlString. ^(MD5 hashMessage: (String streamContents: [:str | str nextPutAll: ha1; nextPutAll: ':'; nextPutAll: aNonce; nextPutAll: ':'; nextPutAll: aNc; nextPutAll: ':'; nextPutAll: aCnonce; nextPutAll: ':'; nextPutAll: aQop; nextPutAll: ':'; nextPutAll: ha2])) hex ] ] SIPUdpTransport extend [ initialize: anAddress port: aPort [ self flag: #todo. "Cant select which interface to bind to..." socket := Socket newUDP setPort: aPort; yourself. net := OsmoUDPSocket new name: 'SIPTransport'; onData: [ :data | self handleData: data ]; yourself ] ] SIPUdpTransportTest extend [ testSending [ | target transp datagram read | [ target := Socket newUDP. target setPort: 0. datagram := OsmoUDPDatagram new. datagram port: target localPort. datagram address: (NetNameResolver localHostAddress). datagram data: 'foooo'. transp := SIPUdpTransport startOn: '127.0.0.1'. transp start. transp queueDatagram: datagram. read := target next. self deny: read data isNil. self assert: read size equals: 5. self assert: (read data copyFrom: 1 to: 5) equals: 'foooo' asByteArray ] ensure: [ target closeAndDestroy. transp stop. ] ] ]