summaryrefslogtreecommitdiffstats
path: root/pharo-porting/changes_for_pharo.st
blob: 9de32d1825361e733fdb991866fa8e843aabf96a (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
SIPURandom class extend [
    nextByte [
        <category: 'random'>
        ^(RAND rand: 1) first.
    ]

    nextInt [
        <category: 'random'>
        ^(RAND rand: 4) asInteger
    ]

    nextFourBytes [
        <category: 'random'>
        ^RAND rand: 4
    ]
]

SIPUserAgentBase class extend [
    generateCSeq [
        <category: 'helper'>
        "For pharo just use the random we have"
        ^(RAND rand: 4) asInteger abs
    ]

    generateBranch [
        | data |
        data := '<1p>,<2p>' expandMacrosWithArguments:
                    {DateTime now asUTC asSeconds.
                     (RAND rand: 2) asInteger}.
        ^ self branchStart, (SIPBase64 encode: data).
    ]
]

SIPUserAgentBase extend [
    generateVia: aBranch [
        <category: 'ids'>
        "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
    ]
]