~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/erl_docgen/priv/xsl/db_man.xsl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
3
3
     #
4
4
     # %CopyrightBegin%
5
5
     #
6
 
     # Copyright Ericsson AB 2009-2010. All Rights Reserved.
 
6
     # Copyright Ericsson AB 2009-2011. All Rights Reserved.
7
7
     #
8
8
     # The contents of this file are subject to the Erlang Public License,
9
9
     # Version 1.1, (the "License"); you may not use this file except in
21
21
     -->
22
22
 
23
23
<xsl:stylesheet version="1.0"
24
 
  xmlns:xsl="http://www.w3.org/1999/XSL/Transform">
 
24
  xmlns:xsl="http://www.w3.org/1999/XSL/Transform"
 
25
  xmlns:exsl="http://exslt.org/common"
 
26
  extension-element-prefixes="exsl">
25
27
 
26
 
  <xsl:preserve-space elements="code pre"/>
 
28
  <xsl:preserve-space elements="code pre p"/>
27
29
  <xsl:strip-space elements="*"/>
28
30
  <xsl:output method="text" encoding="UTF-8" indent="no"/>
29
31
 
30
 
  <!-- Start of Dialyzer type/spec tags. See also the template matching "name"
 
32
  <!-- Start of Dialyzer type/spec tags. See also the templates
 
33
        matching "name", "seealso" and "br"
31
34
  -->
32
35
 
33
36
  <!-- Note: specs data for *one* module (as opposed to html and pdf) -->
35
38
  <xsl:variable name="i" select="document($specs_file)"></xsl:variable>
36
39
 
37
40
  <xsl:template name="err">
 
41
    <xsl:param name="f"/>
38
42
    <xsl:param name="m"/>
39
43
    <xsl:param name="n"/>
40
44
    <xsl:param name="a"/>
41
45
    <xsl:param name="s"/>
42
46
    <xsl:message terminate="yes">
43
 
  Error <xsl:if test="$m != ''"><xsl:value-of select ="$m"/>:</xsl:if>
44
 
         <xsl:value-of
45
 
                   select="$n"/>/<xsl:value-of
46
 
                   select="$a"/>: <xsl:value-of select="$s"/>
 
47
  Error <xsl:if test="$f != ''">in <xsl:value-of select ="$f"/>:</xsl:if>
 
48
        <xsl:if test="$m != ''"><xsl:value-of select ="$m"/>:</xsl:if>
 
49
        <xsl:value-of select="$n"/>
 
50
        <xsl:if test="$a != ''">/<xsl:value-of
 
51
             select ="$a"/></xsl:if>: <xsl:value-of select="$s"/>
47
52
    </xsl:message>
48
53
  </xsl:template>
49
54
 
 
55
  <xsl:template name="find_spec">
 
56
    <xsl:variable name="curModule" select="ancestor::erlref/module"/>
 
57
    <xsl:variable name="mod" select="@mod"/>
 
58
    <xsl:variable name="name" select="@name"/>
 
59
    <xsl:variable name="arity" select="@arity"/>
 
60
    <xsl:variable name="clause_i" select="@clause_i"/>
 
61
    <xsl:variable name="spec0" select=
 
62
        "$i/module[@name=$curModule]/spec
 
63
             [name=$name and arity=$arity
 
64
              and (string-length($mod) = 0 or module = $mod)]"/>
 
65
    <xsl:variable name="spec" select="$spec0[string-length($clause_i) = 0
 
66
                                             or position() = $clause_i]"/>
 
67
 
 
68
    <xsl:if test="count($spec) != 1">
 
69
      <xsl:variable name="why">
 
70
        <xsl:choose>
 
71
          <xsl:when test="count($spec) > 1">ambiguous spec</xsl:when>
 
72
          <xsl:when test="count($spec) = 0">unknown spec</xsl:when>
 
73
        </xsl:choose>
 
74
      </xsl:variable>
 
75
      <xsl:call-template name="err">
 
76
        <xsl:with-param name="f" select="$curModule"/>
 
77
        <xsl:with-param name="m" select="$mod"/>
 
78
        <xsl:with-param name="n" select="$name"/>
 
79
        <xsl:with-param name="a" select="$arity"/>
 
80
        <xsl:with-param name="s" select="$why"/>
 
81
      </xsl:call-template>
 
82
    </xsl:if>
 
83
    <xsl:copy-of select="$spec"/>
 
84
  </xsl:template>
 
85
 
50
86
  <xsl:template name="spec_name">
51
 
    <xsl:variable name="curModule" select="ancestor::erlref/module"/>
52
 
    <xsl:variable name="mod" select="@mod"/>
53
87
    <xsl:variable name="name" select="@name"/>
54
88
    <xsl:variable name="arity" select="@arity"/>
55
 
    <xsl:variable name="clause" select="@clause"/>
56
 
    <xsl:variable name="spec0" select=
57
 
        "$i/module[@name=$curModule]/spec
58
 
             [name=$name and arity=$arity
59
 
              and (string-length($mod) = 0 or module = $mod)]"/>
60
 
    <xsl:variable name="spec" select="$spec0[string-length($clause) = 0
61
 
                                             or position() = $clause]"/>
62
 
    <xsl:if test="count($spec) = 0">
63
 
      <xsl:call-template name="err">
64
 
        <xsl:with-param name="m" select="$mod"/>
65
 
        <xsl:with-param name="n" select="$name"/>
66
 
        <xsl:with-param name="a" select="$arity"/>
67
 
        <xsl:with-param name="s">unknown spec</xsl:with-param>
68
 
      </xsl:call-template>
69
 
    </xsl:if>
 
89
    <xsl:variable name="spec0">
 
90
      <xsl:call-template name="find_spec"/>
 
91
    </xsl:variable>
 
92
    <xsl:variable name="spec" select="exsl:node-set($spec0)/spec"/>
70
93
 
71
94
    <xsl:choose>
72
95
      <xsl:when test="ancestor::cref">
75
98
        </xsl:message>
76
99
      </xsl:when>
77
100
      <xsl:when test="ancestor::erlref">
 
101
        <xsl:apply-templates select="$spec/contract/clause/head"/>
 
102
        <xsl:text>&#10;.br</xsl:text>
 
103
      </xsl:when>
 
104
    </xsl:choose>
 
105
  </xsl:template>
 
106
 
 
107
  <xsl:template match="head">
 
108
    <xsl:text>&#10;.nf&#10;</xsl:text>
 
109
    <xsl:text>&#10;.B&#10;</xsl:text>
 
110
    <xsl:apply-templates/>
 
111
    <xsl:text>&#10;.br</xsl:text>
 
112
    <xsl:text>&#10;.fi</xsl:text>
 
113
  </xsl:template>
 
114
 
 
115
  <!-- The *last* <name name="..." arity=".."/> -->
 
116
  <xsl:template match="name" mode="types">
 
117
    <xsl:variable name="name" select="@name"/>
 
118
    <xsl:variable name="arity" select="@arity"/>
 
119
    <xsl:variable name="spec0">
 
120
      <xsl:call-template name="find_spec"/>
 
121
    </xsl:variable>
 
122
    <xsl:variable name="spec" select="exsl:node-set($spec0)/spec"/>
 
123
    <xsl:variable name="clause" select="$spec/contract/clause"/>
 
124
 
 
125
    <xsl:variable name="type_desc" select="../type_desc"/>
 
126
    <!-- $type is data types to be presented as guards ("local types") -->
 
127
    <xsl:variable name="type"
 
128
                  select="../type[string-length(@name) > 0
 
129
                                  or string-length(@variable) > 0]"/>
 
130
    <xsl:variable name="type_variables"
 
131
                  select ="$type[string-length(@variable) > 0]"/>
 
132
    <xsl:variable name="local_types"
 
133
                  select ="$type[string-length(@name) > 0]"/>
 
134
    <xsl:variable name="output_subtypes" select="count($type_variables) = 0"/>
 
135
 
 
136
    <!-- It is assumed there is no support for overloaded specs
 
137
         (there is no spec with more than one clause) -->
 
138
    <xsl:if test="count($clause/guard) > 0 or count($type) > 0">
 
139
      <xsl:text>&#10;.RS</xsl:text>
 
140
      <xsl:text>&#10;.LP</xsl:text>
 
141
      <xsl:text>&#10;Types:&#10;</xsl:text>
 
142
      <xsl:text>&#10;.RS 3</xsl:text>
 
143
 
 
144
        <xsl:choose>
 
145
          <xsl:when test="$output_subtypes">
 
146
            <xsl:call-template name="subtype">
 
147
              <xsl:with-param name="subtype" select="$clause/guard/subtype"/>
 
148
              <xsl:with-param name="type_desc" select="$type_desc"/>
 
149
              <xsl:with-param name="local_types" select="$local_types"/>
 
150
            </xsl:call-template>
 
151
          </xsl:when>
 
152
          <xsl:otherwise>
 
153
            <xsl:call-template name="type_variables">
 
154
              <xsl:with-param name="type_variables" select="$type_variables"/>
 
155
              <xsl:with-param name="type_desc" select="$type_desc"/>
 
156
              <xsl:with-param name="local_types" select="$local_types"/>
 
157
              <xsl:with-param name="fname" select="$name"/>
 
158
              <xsl:with-param name="arity" select="$arity"/>
 
159
            </xsl:call-template>
 
160
 
 
161
          </xsl:otherwise>
 
162
        </xsl:choose>
 
163
 
 
164
        <xsl:call-template name="local_type">
 
165
          <xsl:with-param name="type_desc" select="$type_desc"/>
 
166
          <xsl:with-param name="local_types" select="$local_types"/>
 
167
        </xsl:call-template>
 
168
        <xsl:text>&#10;.RE</xsl:text>
 
169
 
 
170
      <xsl:text>&#10;.RE</xsl:text>
 
171
 
 
172
    </xsl:if>
 
173
  </xsl:template>
 
174
 
 
175
  <!-- Handle <type variable="..." name_i="..."/> -->
 
176
  <xsl:template name="type_variables">
 
177
    <xsl:param name="type_variables"/>
 
178
    <xsl:param name="type_desc"/>
 
179
    <xsl:param name="local_types"/>
 
180
    <xsl:param name="fname"/>
 
181
    <xsl:param name="arity"/>
 
182
 
 
183
    <xsl:variable name="names" select="../name[string-length(@arity) > 0]"/>
 
184
    <xsl:for-each select="$type_variables">
 
185
      <xsl:variable name="name_i">
78
186
        <xsl:choose>
79
 
          <xsl:when test="string(@with_guards) = 'no'">
80
 
             <xsl:apply-templates select="$spec/contract/clause/head"/>
 
187
          <xsl:when test="string-length(@name_i) > 0">
 
188
            <xsl:value-of select="@name_i"/>
81
189
          </xsl:when>
82
190
          <xsl:otherwise>
83
 
            <xsl:call-template name="contract">
84
 
              <xsl:with-param name="contract" select="$spec/contract"/>
85
 
            </xsl:call-template>
 
191
            <xsl:value-of select="count($names)"/>
86
192
          </xsl:otherwise>
87
193
        </xsl:choose>
88
 
        <xsl:text>&#10;.br</xsl:text>
89
 
      </xsl:when>
90
 
    </xsl:choose>
91
 
  </xsl:template>
92
 
 
93
 
  <xsl:template name="contract">
94
 
    <xsl:param name="contract"/>
95
 
    <xsl:call-template name="clause">
96
 
      <xsl:with-param name="clause" select="$contract/clause"/>
97
 
    </xsl:call-template>
98
 
  </xsl:template>
99
 
 
100
 
  <xsl:template name="clause">
101
 
    <xsl:param name="clause"/>
102
 
    <xsl:variable name="type_desc" select="../type_desc"/>
103
 
    <xsl:for-each select="$clause">
104
 
      <xsl:apply-templates select="head"/>
105
 
      <xsl:if test="count(guard) > 0">
106
 
        <xsl:call-template name="guard">
107
 
          <xsl:with-param name="guard" select="guard"/>
108
 
          <xsl:with-param name="type_desc" select="$type_desc"/>
 
194
      </xsl:variable>
 
195
      <xsl:variable name="spec0">
 
196
        <xsl:for-each select="$names[position() = $name_i]">
 
197
          <xsl:call-template name="find_spec"/>
 
198
        </xsl:for-each>
 
199
      </xsl:variable>
 
200
      <xsl:variable name="spec" select="exsl:node-set($spec0)/spec"/>
 
201
      <xsl:variable name="clause" select="$spec/contract/clause"/>
 
202
      <xsl:variable name="variable" select="@variable"/>
 
203
      <xsl:variable name="subtype"
 
204
                    select="$clause/guard/subtype[typename = $variable]"/>
 
205
 
 
206
      <xsl:if test="count($subtype) = 0">
 
207
        <xsl:call-template name="err">
 
208
          <xsl:with-param name="f" select="ancestor::erlref/module"/>
 
209
          <xsl:with-param name="n" select="$fname"/>
 
210
          <xsl:with-param name="a" select="$arity"/>
 
211
          <xsl:with-param name="s">unknown type variable <xsl:value-of select="$variable"/>
 
212
          </xsl:with-param>
109
213
        </xsl:call-template>
110
214
      </xsl:if>
 
215
 
 
216
      <xsl:call-template name="subtype">
 
217
        <xsl:with-param name="subtype" select="$subtype"/>
 
218
        <xsl:with-param name="type_desc" select="$type_desc"/>
 
219
      </xsl:call-template>
111
220
    </xsl:for-each>
112
221
  </xsl:template>
113
222
 
114
 
  <xsl:template match="head">
115
 
    <xsl:text>&#10;.nf&#10;</xsl:text>
116
 
    <xsl:text>&#10;.B&#10;</xsl:text>
117
 
    <xsl:apply-templates/>
118
 
    <xsl:text>&#10;.br</xsl:text>
119
 
    <xsl:text>&#10;.fi</xsl:text>
120
 
  </xsl:template>
121
 
 
122
 
  <xsl:template name="guard">
123
 
    <xsl:param name="guard"/>
124
 
    <xsl:param name="type_desc"/>
125
 
    <xsl:text>&#10;.RS</xsl:text>
126
 
    <xsl:text>&#10;.TP</xsl:text>
127
 
    <xsl:text>&#10;Types</xsl:text>
128
 
    <xsl:call-template name="subtype">
129
 
      <xsl:with-param name="subtype" select="$guard/subtype"/>
130
 
      <xsl:with-param name="type_desc" select="$type_desc"/>
131
 
    </xsl:call-template>
132
 
    <xsl:text>&#10;.RE</xsl:text>
133
 
  </xsl:template>
134
 
 
135
223
  <xsl:template name="subtype">
136
224
    <xsl:param name="subtype"/>
137
225
    <xsl:param name="type_desc"/>
 
226
 
138
227
    <xsl:for-each select="$subtype">
139
228
      <xsl:variable name="tname" select="typename"/>
140
 
      <xsl:variable name="tdesc" select="$type_desc[@name = $tname]"/>
141
 
        <xsl:text>&#10;</xsl:text>
142
 
        <xsl:apply-templates select="string"/>
143
 
        <xsl:text>&#10;.br</xsl:text>
144
 
      <xsl:apply-templates select="$type_desc[@name = $tname]"/>
 
229
      <xsl:variable name="string" select="string"/>
 
230
      <xsl:if test="string-length($string) > 0">
 
231
        <xsl:text>&#10;</xsl:text>
 
232
        <xsl:apply-templates select="$string"/>
 
233
        <xsl:text>&#10;.br</xsl:text>
 
234
        <xsl:apply-templates select="$type_desc[@variable = $tname]"/>
 
235
      </xsl:if>
 
236
    </xsl:for-each>
 
237
  </xsl:template>
 
238
 
 
239
  <xsl:template name="local_type">
 
240
    <xsl:param name="type_desc"/>
 
241
    <xsl:param name="local_types"/>
 
242
 
 
243
    <xsl:for-each select ="$local_types">
 
244
      <xsl:text>&#10;</xsl:text>
 
245
      <xsl:call-template name="type_name">
 
246
        <xsl:with-param name="mode" select="'local_type'"/>
 
247
      </xsl:call-template>
 
248
      <xsl:text>&#10;.br</xsl:text>
 
249
      <xsl:variable name="tname" select="@name"/>
 
250
      <xsl:variable name="tnvars" select="@n_vars"/>
 
251
      <xsl:apply-templates select=
 
252
         "$type_desc[@name = $tname
 
253
                     and (@n_vars = $tnvars
 
254
                          or string-length(@n_vars) = 0 and
 
255
                             string-length($tnvars) = 0)]"/>
145
256
    </xsl:for-each>
146
257
  </xsl:template>
147
258
 
149
260
 
150
261
  <!-- Similar to <d> -->
151
262
  <xsl:template match="type_desc">
152
 
    <xsl:text>&#10;</xsl:text><xsl:apply-templates/>
153
 
    <xsl:text>&#10;.br</xsl:text>
 
263
    <xsl:text>&#10;.RS 2&#10;</xsl:text><xsl:apply-templates/>
 
264
    <xsl:text>&#10;.RE</xsl:text>
154
265
  </xsl:template>
155
266
 
156
267
  <!-- Datatypes -->
164
275
    <xsl:apply-templates/>
165
276
  </xsl:template>
166
277
 
167
 
  <xsl:template match="typehead">
168
 
    <xsl:text>&#10;.nf&#10;</xsl:text>
169
 
    <xsl:text>&#10;.B&#10;</xsl:text>
170
 
    <xsl:apply-templates/>
171
 
    <xsl:text>&#10;.br</xsl:text>
172
 
    <xsl:text>&#10;.fi</xsl:text>
173
 
  </xsl:template>
174
 
 
175
 
  <xsl:template match="local_defs">
176
 
    <xsl:text>&#10;.RS</xsl:text>
177
 
    <xsl:apply-templates/>
178
 
    <xsl:text>&#10;.RE</xsl:text>
179
 
  </xsl:template>
180
 
 
181
 
  <xsl:template match="local_def">
182
 
    <xsl:text>&#10;</xsl:text>
183
 
    <xsl:apply-templates/>
184
 
    <xsl:text>&#10;.br</xsl:text>
185
 
  </xsl:template>
186
 
 
187
278
  <xsl:template name="type_name">
 
279
    <xsl:param name="mode"/> <!-- '' if <datatype> -->
188
280
    <xsl:variable name="curModule" select="ancestor::erlref/module"/>
189
281
    <xsl:variable name="mod" select="@mod"/>
190
282
    <xsl:variable name="name" select="@name"/>
191
 
    <xsl:variable name="n_vars">
192
 
      <xsl:choose>
193
 
        <xsl:when test="string-length(@n_vars) > 0">
194
 
          <xsl:value-of select="@n_vars"/>
195
 
        </xsl:when>
196
 
        <xsl:otherwise>
197
 
          <xsl:value-of select="0"/>
198
 
        </xsl:otherwise>
199
 
      </xsl:choose>
200
 
    </xsl:variable>
 
283
    <xsl:variable name="n_vars" select="@n_vars"/>
201
284
 
202
285
    <xsl:choose>
203
286
      <xsl:when test="string-length($name) > 0">
204
287
        <xsl:variable name="type" select=
205
288
            "$i/module[@name=$curModule]/type
206
 
                 [name=$name and n_vars=$n_vars
 
289
                 [name=$name
 
290
                  and (string-length($n_vars) = 0 or n_vars = $n_vars)
207
291
                  and (string-length($mod) = 0 or module = $mod)]"/>
208
292
 
209
293
        <xsl:if test="count($type) != 1">
 
294
          <xsl:variable name="why">
 
295
            <xsl:choose>
 
296
              <xsl:when test="count($type) > 1">ambiguous type</xsl:when>
 
297
              <xsl:when test="count($type) = 0">unknown type</xsl:when>
 
298
            </xsl:choose>
 
299
          </xsl:variable>
210
300
          <xsl:call-template name="err">
 
301
            <xsl:with-param name="f" select="$curModule"/>
211
302
            <xsl:with-param name="m" select="$mod"/>
212
303
            <xsl:with-param name="n" select="$name"/>
213
304
            <xsl:with-param name="a" select="$n_vars"/>
214
 
            <xsl:with-param name="s">unknown type</xsl:with-param>
 
305
            <xsl:with-param name="s" select="$why"/>
215
306
          </xsl:call-template>
216
307
        </xsl:if>
217
 
        <xsl:apply-templates select="$type/typedecl"/>
 
308
        <xsl:choose>
 
309
          <xsl:when test="$mode = ''">
 
310
            <xsl:apply-templates select="$type/typedecl"/>
 
311
          </xsl:when>
 
312
          <xsl:when test="$mode = 'local_type'">
 
313
            <xsl:apply-templates select="$type/typedecl" mode="local_type"/>
 
314
          </xsl:when>
 
315
        </xsl:choose>
218
316
      </xsl:when>
219
 
      <xsl:otherwise>
 
317
      <xsl:otherwise> <!-- <datatype> with <name> -->
220
318
        <xsl:text>&#10;.nf&#10;</xsl:text>
221
319
        <xsl:text>&#10;.B&#10;</xsl:text>
222
320
        <xsl:apply-templates/>
226
324
    </xsl:choose>
227
325
  </xsl:template>
228
326
 
 
327
  <xsl:template match="typehead">
 
328
    <xsl:text>&#10;.nf&#10;&#10;</xsl:text>
 
329
    <xsl:apply-templates/>
 
330
    <xsl:text>&#10;.br</xsl:text>
 
331
    <xsl:text>&#10;.fi</xsl:text>
 
332
  </xsl:template>
 
333
 
 
334
  <xsl:template match="typehead" mode="local_type">
 
335
    <xsl:text>.nf&#10;</xsl:text>
 
336
    <xsl:apply-templates/>
 
337
    <xsl:text>&#10;.fi</xsl:text>
 
338
  </xsl:template>
 
339
 
 
340
  <!-- Not used right now -->
 
341
  <xsl:template match="local_defs">
 
342
    <xsl:text>&#10;.RS</xsl:text>
 
343
    <xsl:apply-templates/>
 
344
    <xsl:text>&#10;.RE</xsl:text>
 
345
  </xsl:template>
 
346
 
 
347
  <xsl:template match="local_def">
 
348
    <xsl:text>&#10;</xsl:text>
 
349
    <xsl:apply-templates/>
 
350
    <xsl:text>&#10;.br</xsl:text>
 
351
  </xsl:template>
 
352
 
 
353
  <!-- The name of data types -->
 
354
  <xsl:template match="marker">
 
355
    <xsl:if test="string-length(.) != 0">
 
356
      <xsl:text>\fB</xsl:text><xsl:apply-templates/><xsl:text>\fR\&amp;</xsl:text>
 
357
    </xsl:if>
 
358
  </xsl:template>
 
359
 
229
360
  <!-- Used both in <datatype> and in <func>! -->
230
361
  <xsl:template match="anno">
231
362
    <xsl:variable name="curModule" select="ancestor::erlref/module"/>
232
363
    <xsl:variable name="anno" select="normalize-space(text())"/>
233
364
    <xsl:variable name="namespec"
234
 
                  select="ancestor::desc/preceding-sibling::name"/>
 
365
                  select="ancestor::type_desc/preceding-sibling::name
 
366
                          | ancestor::desc/preceding-sibling::name"/>
235
367
    <xsl:if test="count($namespec) = 0 and string-length($specs_file) > 0">
236
368
      <xsl:call-template name="err">
237
 
        <xsl:with-param name="s">cannot find 'name' (<xsl:value-of select="$anno"/>)
238
 
        </xsl:with-param>
239
 
      </xsl:call-template>
240
 
    </xsl:if>
241
 
 
242
 
    <xsl:variable name="mod" select="$namespec/@mod"/>
243
 
    <xsl:variable name="name" select="$namespec/@name"/>
244
 
    <xsl:variable name="arity" select="$namespec/@arity"/>
245
 
    <xsl:variable name="clause" select="$namespec/@clause"/>
246
 
    <xsl:variable name="tmp_n_vars" select="$namespec/@n_vars"/>
247
 
    <xsl:variable name="n_vars">
248
 
      <xsl:choose>
249
 
        <xsl:when test="string-length($tmp_n_vars) > 0">
250
 
          <xsl:value-of select="$tmp_n_vars"/>
251
 
        </xsl:when>
252
 
        <xsl:otherwise>
253
 
          <xsl:value-of select="0"/>
254
 
        </xsl:otherwise>
255
 
      </xsl:choose>
256
 
    </xsl:variable>
 
369
        <xsl:with-param name="f" select="$curModule"/>
 
370
        <xsl:with-param name="s">cannot find tag 'name' (anno <xsl:value-of select="$anno"/>)
 
371
        </xsl:with-param>
 
372
      </xsl:call-template>
 
373
    </xsl:if>
 
374
 
 
375
    <!-- Search "local types" as well -->
 
376
    <xsl:variable name="local_types"
 
377
                select="ancestor::desc/preceding-sibling::type
 
378
                               [string-length(@name) > 0]
 
379
                      | ancestor::type_desc/preceding-sibling::type
 
380
                               [string-length(@name) > 0]"/>
 
381
    <xsl:variable name="has_anno_in_local_type">
 
382
      <xsl:for-each select="$local_types">
 
383
        <xsl:call-template name="anno_name">
 
384
          <xsl:with-param name="curModule" select="$curModule"/>
 
385
          <xsl:with-param name="anno" select="$anno"/>
 
386
        </xsl:call-template>
 
387
      </xsl:for-each>
 
388
    </xsl:variable>
 
389
 
 
390
    <xsl:variable name="has_anno">
 
391
      <xsl:for-each select="$namespec">
 
392
        <xsl:call-template name="anno_name">
 
393
          <xsl:with-param name="curModule" select="$curModule"/>
 
394
          <xsl:with-param name="anno" select="$anno"/>
 
395
        </xsl:call-template>
 
396
      </xsl:for-each>
 
397
    </xsl:variable>
 
398
 
 
399
    <xsl:if test="$has_anno = '' and $has_anno_in_local_type = ''">
 
400
      <xsl:call-template name="err">
 
401
        <xsl:with-param name="f" select="$curModule"/>
 
402
        <xsl:with-param name="m" select="$namespec/@mod"/>
 
403
        <xsl:with-param name="n" select="$namespec/@name"/>
 
404
        <xsl:with-param name="a" select="'-'"/>
 
405
        <xsl:with-param name="s">unknown annotation <xsl:value-of select="$anno"/>
 
406
        </xsl:with-param>
 
407
      </xsl:call-template>
 
408
    </xsl:if>
 
409
    <xsl:value-of select="$anno"/>
 
410
  </xsl:template>
 
411
 
 
412
  <xsl:template name="anno_name">
 
413
    <xsl:param name="curModule"/>
 
414
    <xsl:param name="anno"/>
 
415
    <xsl:variable name="mod" select="@mod"/>
 
416
    <xsl:variable name="name" select="@name"/>
 
417
    <xsl:variable name="arity" select="@arity"/>
 
418
    <xsl:variable name="n_vars" select="@n_vars"/>
 
419
    <xsl:variable name="clause_i" select="@clause_i"/>
 
420
 
257
421
    <xsl:variable name="spec0" select=
258
422
        "$i/module[@name=$curModule]/spec
259
423
             [name=$name and arity=$arity
260
424
              and (string-length($mod) = 0 or module = $mod)]"/>
261
425
    <xsl:variable name="spec_annos" select=
262
 
         "$spec0[string-length($clause) = 0
263
 
                 or position() = $clause]/anno[.=$anno]"/>
 
426
         "$spec0[string-length($clause_i) = 0
 
427
                 or position() = $clause_i]/anno[.=$anno]"/>
264
428
    <xsl:variable name="type_annos" select=
265
429
        "$i/module[@name=$curModule]/type
266
 
             [name=$name and n_vars=$n_vars
 
430
             [name=$name
 
431
              and (string-length($n_vars) = 0 or n_vars=$n_vars)
267
432
              and (string-length($mod) = 0 or module = $mod)]/anno[.=$anno]"/>
268
 
 
269
 
    <xsl:if test="count($spec_annos) = 0
270
 
                  and count($type_annos) = 0
271
 
                  and string-length($specs_file) > 0">
272
 
      <xsl:variable name="n">
273
 
        <xsl:choose>
274
 
          <xsl:when test="string-length($arity) = 0">
275
 
            <xsl:value-of select="$n_vars"/>
276
 
          </xsl:when>
277
 
          <xsl:otherwise>
278
 
            <xsl:value-of select="$arity"/>
279
 
          </xsl:otherwise>
280
 
        </xsl:choose>
281
 
      </xsl:variable>
282
 
      <xsl:call-template name="err">
283
 
        <xsl:with-param name="m" select="$mod"/>
284
 
        <xsl:with-param name="n" select="$name"/>
285
 
        <xsl:with-param name="a" select="$n"/>
286
 
        <xsl:with-param name="s">unknown annotation <xsl:value-of select="$anno"/>
287
 
        </xsl:with-param>
288
 
      </xsl:call-template>
 
433
    <xsl:if test="count($spec_annos) != 0
 
434
                  or count($type_annos) != 0
 
435
                  or string-length($specs_file) = 0">
 
436
      <xsl:value-of select="true()"/>
289
437
    </xsl:if>
290
 
    <xsl:value-of select="$anno"/>
291
438
  </xsl:template>
292
439
 
293
440
  <!-- Used for indentation of formatted types and specs -->
330
477
    <xsl:text>&#10;.TP 2&#10;</xsl:text>
331
478
    <xsl:text>*&#10;</xsl:text>
332
479
    <xsl:apply-templates/>
333
 
    <xsl:text>&#10;.LP&#10;</xsl:text>
 
480
    <xsl:text>&#10;.LP</xsl:text>
334
481
  </xsl:template>
335
482
 
336
483
  <xsl:template match="taglist">
337
484
    <xsl:text>&#10;.RS 2</xsl:text>
338
485
    <xsl:apply-templates select="tag|item"/>
339
 
    <xsl:text>&#10;.RE&#10;</xsl:text>
 
486
    <xsl:text>&#10;.RE</xsl:text>
340
487
  </xsl:template>
341
488
 
342
489
  <xsl:template match="taglist/tag">
359
506
      </xsl:when>
360
507
      <xsl:otherwise>
361
508
        <xsl:text>&#10;.RS 2</xsl:text>
362
 
        <xsl:text>&#10;.LP&#10;&#10;.LP&#10;</xsl:text>
 
509
        <xsl:text>&#10;.LP&#10;</xsl:text>
363
510
        <xsl:value-of select="$content"/>
364
511
        <xsl:text>&#10;.RE</xsl:text>
365
512
      </xsl:otherwise>
368
515
 
369
516
  <!-- Note -->
370
517
  <xsl:template match="note">
371
 
    <xsl:text>&#10;.SS Note:</xsl:text>
 
518
    <xsl:text>&#10;.LP&#10;</xsl:text>
 
519
    <xsl:text>&#10;.RS -4</xsl:text>
 
520
    <xsl:text>&#10;.B&#10;</xsl:text>
 
521
    <xsl:text>Note:</xsl:text>
 
522
    <xsl:text>&#10;.RE</xsl:text>
372
523
    <xsl:apply-templates/>
373
524
    <xsl:text>&#10;</xsl:text>
374
525
  </xsl:template>
375
526
 
376
527
  <!-- Warning -->
377
528
  <xsl:template match="warning">
378
 
    <xsl:text>&#10;.SS Warning:</xsl:text>
 
529
    <xsl:text>&#10;.LP&#10;</xsl:text>
 
530
    <xsl:text>&#10;.RS -4</xsl:text>
 
531
    <xsl:text>&#10;.B&#10;</xsl:text>
 
532
    <xsl:text>Warning:</xsl:text>
 
533
    <xsl:text>&#10;.RE</xsl:text>
379
534
    <xsl:apply-templates/>
380
535
    <xsl:text>&#10;</xsl:text>
381
536
  </xsl:template>
382
537
 
 
538
  <xsl:template match="warning/p | note/p">
 
539
    <xsl:variable name="content">
 
540
      <xsl:text>&#10;</xsl:text>
 
541
      <xsl:apply-templates/>
 
542
    </xsl:variable>
 
543
    <xsl:choose>
 
544
      <xsl:when test="position() = 1">
 
545
        <xsl:value-of select="$content"/>
 
546
      </xsl:when>
 
547
      <xsl:otherwise>
 
548
        <xsl:text>&#10;.LP</xsl:text>
 
549
        <xsl:value-of select="$content"/>
 
550
      </xsl:otherwise>
 
551
    </xsl:choose>
 
552
  </xsl:template>
 
553
 
383
554
 <!-- Paragraph -->
384
555
  <xsl:template match="p">
385
556
    <xsl:text>&#10;.LP&#10;</xsl:text>
394
565
  </xsl:template>
395
566
 
396
567
  <xsl:template match="br">
397
 
    <xsl:text>&#10;.br&#10;</xsl:text>
 
568
    <xsl:choose>
 
569
      <xsl:when test="ancestor::head">
 
570
        <!-- The header of Dialyzer specs.
 
571
             .B makes next line appear in bold face -->
 
572
        <xsl:text>&#10;.B&#10;</xsl:text>
 
573
      </xsl:when>
 
574
      <xsl:otherwise>
 
575
        <xsl:text>&#10;.br&#10;</xsl:text>
 
576
      </xsl:otherwise>
 
577
    </xsl:choose>
398
578
  </xsl:template>
399
579
 
400
580
  <xsl:template match="c">
406
586
  </xsl:template>
407
587
 
408
588
  <xsl:template match="seealso">
409
 
    <xsl:text>\fB</xsl:text><xsl:apply-templates/><xsl:text>\fR\&amp;</xsl:text>
 
589
    <xsl:choose>
 
590
      <xsl:when test="ancestor::head">
 
591
        <!-- The header of Dialyzer specs -->
 
592
        <xsl:apply-templates/>
 
593
      </xsl:when>
 
594
      <xsl:otherwise>
 
595
        <xsl:text>\fB</xsl:text><xsl:apply-templates/><xsl:text>\fR\&amp;</xsl:text>
 
596
      </xsl:otherwise>
 
597
    </xsl:choose>
410
598
  </xsl:template>
411
599
 
412
600
  <!-- Code -->
413
601
  <xsl:template match="code">
414
602
    <xsl:text>&#10;.LP&#10;</xsl:text>
415
 
    <xsl:text>&#10;.nf&#10;</xsl:text>
 
603
    <xsl:text>.nf&#10;</xsl:text>
416
604
    <xsl:apply-templates/>
417
 
    <xsl:text>&#10;.fi&#10;</xsl:text>
 
605
    <xsl:text>&#10;.fi</xsl:text>
418
606
  </xsl:template>
419
607
 
420
608
  <!-- Pre -->
421
609
  <xsl:template match="pre">
422
610
    <xsl:text>&#10;.LP&#10;</xsl:text>
423
 
    <xsl:text>&#10;.nf&#10;</xsl:text>
 
611
    <xsl:text>.nf&#10;</xsl:text>
424
612
    <xsl:apply-templates/>
425
 
    <xsl:text>&#10;.fi&#10;</xsl:text>
 
613
    <xsl:text>&#10;.fi</xsl:text>
426
614
  </xsl:template>
427
615
 
428
616
 
542
730
  <xsl:template match="func">
543
731
    <xsl:text>&#10;.LP</xsl:text>
544
732
    <xsl:apply-templates select="name"/>
 
733
    <xsl:apply-templates
 
734
        select="name[string-length(@arity) > 0 and position()=last()]"
 
735
        mode="types"/>
545
736
    <xsl:apply-templates select="fsummary|type|desc"/>
546
737
  </xsl:template>
547
738
 
554
745
      <xsl:when test="ancestor::datatype">
555
746
        <xsl:call-template name="type_name"/>
556
747
      </xsl:when>
 
748
      <xsl:when test="string-length(text()) = 0 and ancestor::erlref">
 
749
        <xsl:message terminate="yes">
 
750
          Error <xsl:value-of select="@name"/>: arity is mandatory when referring to specifications!
 
751
        </xsl:message>
 
752
      </xsl:when>
557
753
      <xsl:otherwise>
558
754
        <xsl:call-template name="name"/>
559
755
      </xsl:otherwise>
569
765
 
570
766
  <!-- Type -->
571
767
  <xsl:template match="type">
572
 
    <xsl:text>&#10;.RS</xsl:text>
573
 
    <xsl:text>&#10;.TP</xsl:text>
574
 
    <xsl:text>&#10;Types</xsl:text>
575
 
    <xsl:apply-templates/>
576
 
    <xsl:text>&#10;.RE</xsl:text>
 
768
    <!-- The case where @name != 0 is taken care of in "type_name" -->
 
769
    <xsl:if test="string-length(@name) = 0 and string-length(@variable) = 0">
 
770
      <xsl:text>&#10;.RS</xsl:text>
 
771
      <xsl:text>&#10;.LP</xsl:text>
 
772
      <xsl:text>&#10;Types:&#10;</xsl:text>
 
773
      <xsl:text>&#10;.RS 3</xsl:text>
 
774
      <xsl:apply-templates/>
 
775
      <xsl:text>&#10;.RE</xsl:text>
 
776
      <xsl:text>&#10;.RE</xsl:text>
 
777
    </xsl:if>
577
778
  </xsl:template>
578
779
 
579
780
 
580
781
  <!-- V -->
581
782
  <xsl:template match="v">
582
 
    <xsl:text>&#10;</xsl:text><xsl:value-of select="normalize-space(text())"/>
 
783
    <xsl:text>&#10;</xsl:text><xsl:apply-templates/>
583
784
    <xsl:text>&#10;.br</xsl:text>
584
785
  </xsl:template>
585
786
 
586
787
  <!-- D -->
587
788
  <xsl:template match="d">
588
 
    <xsl:text>&#10;</xsl:text><xsl:apply-templates/>
589
 
    <xsl:text>&#10;.br</xsl:text>
 
789
    <xsl:text>&#10;.RS 2&#10;</xsl:text><xsl:apply-templates/>
 
790
    <xsl:text>&#10;.RE</xsl:text>
590
791
  </xsl:template>
591
792
 
592
793
  <!-- Desc -->
622
823
    <xsl:text>&gt;</xsl:text>
623
824
  </xsl:template>
624
825
 
625
 
  <!-- Do not noramlize any text within pre and code tags. -->
 
826
  <!-- Do not normalize any text within pre and code tags. -->
626
827
  <xsl:template match="pre/text()">
627
828
      <xsl:call-template name="replace-string">
628
829
        <xsl:with-param name="text" select="." />
642
843
  <!-- Replace ' by \&' ans . by \&. -->
643
844
  <xsl:template match="text()">
644
845
    <xsl:variable name="startstring">
645
 
      <xsl:value-of select="normalize-space()"/><xsl:text> </xsl:text>
 
846
      <xsl:value-of select="normalize-space()"/>
 
847
    </xsl:variable>
 
848
    <!-- 'C' is just any character but whitespace -->
 
849
    <xsl:variable name="tmp" select="normalize-space(concat('C',.,'C'))"/>
 
850
    <xsl:variable name="space_before">
 
851
      <xsl:choose>
 
852
         <!-- '<p>A<marker id="swamp"/> swamp</p>' does not work; instead:
 
853
              '<p>A <marker id="swamp"/>swamp</p>' -->
 
854
         <xsl:when test="starts-with($tmp, 'C ')
 
855
                and not (string(preceding-sibling::*[position()=1]) = ''
 
856
                         and parent::p)">
 
857
           <!-- and not (position() = 1 and parent::p)"> -->
 
858
           <xsl:text> </xsl:text>
 
859
         </xsl:when>
 
860
         <xsl:otherwise>
 
861
           <xsl:text/>
 
862
         </xsl:otherwise>
 
863
      </xsl:choose>
 
864
    </xsl:variable>
 
865
    <xsl:variable name="space_after">
 
866
      <xsl:choose>
 
867
         <xsl:when test="substring($tmp, string-length($tmp)-1,1) = ' '
 
868
                         and $startstring != ''
 
869
                         and not (position() = last() and parent::p)">
 
870
           <xsl:text> </xsl:text>
 
871
         </xsl:when>
 
872
         <xsl:otherwise>
 
873
           <xsl:text/>
 
874
         </xsl:otherwise>
 
875
      </xsl:choose>
646
876
    </xsl:variable>
647
877
    <xsl:variable name="rep1">
648
878
      <xsl:call-template name="replace-string">
658
888
        <xsl:with-param name="with" select="&quot;\&amp;&apos;&quot;" />
659
889
      </xsl:call-template>
660
890
    </xsl:variable>
661
 
    <xsl:call-template name="replace-string">
662
 
      <xsl:with-param name="text" select="$rep2" />
663
 
      <xsl:with-param name="replace" select="&quot;.&quot;" />
664
 
      <xsl:with-param name="with" select="&quot;\&amp;.&quot;" />
665
 
    </xsl:call-template>
 
891
    <xsl:variable name="reply">
 
892
      <xsl:call-template name="replace-string">
 
893
        <xsl:with-param name="text" select="$rep2" />
 
894
        <xsl:with-param name="replace" select="&quot;.&quot;" />
 
895
        <xsl:with-param name="with" select="&quot;\&amp;.&quot;" />
 
896
      </xsl:call-template>
 
897
    </xsl:variable>
 
898
    <xsl:value-of select="$space_before"/>
 
899
    <xsl:value-of select="$reply"/>
 
900
    <xsl:value-of select="$space_after"/>
666
901
  </xsl:template>
667
902
 
668
903
  <!-- Template replace-string is borrowed at http://www.dpawson.co.uk/xsl/sect2/replace.html -->