summaryrefslogtreecommitdiffstats
path: root/callagent/session/SIPSessionBase.st
blob: 2cadbadd2b16b43b706ac35c1e855d4815e901f9 (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
"
 (C) 2011 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: SIPSessionBase [
    | rem ua identity initial_dialog dialog next_cseq |
    <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
session as of the RFC... but at some stage in the exchange we will be
a proper session.'>

    SIPSessionBase class >> on: aDialog useragent: aUseragent [
        <category: 'creation'>
        ^ self new
            useragent: aUseragent;
            identity: aUseragent mainIdentity;
            initialDialog: aDialog;
            yourself
    ]

    initialDialog: aDialog [
        <category: 'creation'>
        initial_dialog := aDialog.
        initial_dialog contact: ('sip:<1s>@<2p>:<3p>'
                expandMacrosWith: identity username with: ua transport address with: ua transport port).
    ]

    useragent: aUseragent [
        <category: 'creation'>
        ua := aUseragent
    ]

    identity: anIdentity [
        <category: 'creation'>
        identity := anIdentity
    ]

    callId [
        <category: 'info'>
        ^ initial_dialog callId
    ]

    check: aDialog [
        <category: 'private'>
        "I check if this enters a new confirmed dialog or if this is the
        confirmed dialog."

        "We have no confirmed dialog, accept it"
        ^ dialog isNil
            ifTrue: [
                aDialog isConfirmed ifTrue: [
                    dialog := aDialog.
                    self registerDialog.
                    self logNotice: ('SIPCall(<1s>) dialog is confirmed now.'
                            expandMacrosWith: self callId) area: #sip.
                ].
                true]
            ifFalse: [
                "We could fork things here. For multi party call"
                dialog to_tag = aDialog to_tag].
    ]

    registerDialog [
        <category: 'session'>
        ua registerDialog: self.
    ]

    unregisterDialog [
        <category: 'session'>
        rem isNil ifTrue: [
            rem := Osmo.TimerScheduler instance
                    scheduleInSeconds: 60 block: [
                        ua unregisterDialog: self.
                    ]]
    ]

    nextCSeq [
        | res |
        <category: 'accessing'>
        res := next_cseq.
        next_cseq := next_cseq + 1.
        ^ res
    ]

    isCompatible: aDialog [
        <category: 'dialog'>
        ^ dialog isNil
                    ifTrue:  [initial_dialog isCompatible: aDialog]
                    ifFalse: [dialog isCompatible: aDialog].
    ]

    newRequest: aRequest dialog: aDialog [
        <category: 'dialog'>
        self logError: ('<1p>(<2s>) unhandled request <3p>.'
                expandMacrosWithArguments: {self class. self callId. aRequest class verb})
                     area: #sip.
    ]
]