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

« back to all changes in this revision

Viewing changes to lib/erl_docgen/priv/xsl/db_pdf.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
<xsl:stylesheet version="1.0"
23
23
  xmlns:xsl="http://www.w3.org/1999/XSL/Transform"
 
24
  xmlns:exsl="http://exslt.org/common"
 
25
  extension-element-prefixes="exsl"
24
26
  xmlns:fo="http://www.w3.org/1999/XSL/Format">
25
27
 
26
28
  <xsl:output method="xml" indent="yes"/>
28
30
  <xsl:include href="db_pdf_params.xsl"/>
29
31
 
30
32
  <!-- Start of Dialyzer type/spec tags.
31
 
       See also the template matching "name" and the template "bookmarks6"
 
33
       See also the templates matching "name" and "seealso" as well as
 
34
       the template "bookmarks6"
32
35
  -->
33
36
 
34
37
  <xsl:param name="specs_file" select="''"/>
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/specs/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/specs/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">
76
99
      </xsl:when>
77
100
      <xsl:when test="ancestor::erlref">
78
101
        <fo:block id="{generate-id()}">
79
 
          <xsl:choose>
80
 
            <xsl:when test="string(@with_guards) = 'no'">
81
 
               <xsl:apply-templates select="$spec/contract/clause/head"/>
82
 
            </xsl:when>
83
 
            <xsl:otherwise>
84
 
              <xsl:call-template name="contract">
85
 
                <xsl:with-param name="contract" select="$spec/contract"/>
86
 
              </xsl:call-template>
87
 
            </xsl:otherwise>
88
 
          </xsl:choose>
 
102
          <xsl:apply-templates select="$spec/contract/clause/head"/>
89
103
        </fo:block>
90
104
      </xsl:when>
91
105
    </xsl:choose>
92
106
  </xsl:template>
93
107
 
94
 
  <xsl:template name="contract">
95
 
    <xsl:param name="contract"/>
96
 
    <xsl:call-template name="clause">
97
 
      <xsl:with-param name="clause" select="$contract/clause"/>
98
 
    </xsl:call-template>
 
108
  <xsl:template match="head">
 
109
    <fo:block xsl:use-attribute-sets="function-name">
 
110
      <xsl:apply-templates/>
 
111
    </fo:block>
99
112
  </xsl:template>
100
113
 
101
 
  <xsl:template name="clause">
102
 
    <xsl:param name="clause"/>
 
114
  <!-- The *last* <name name="..." arity=".."/> -->
 
115
  <xsl:template match="name" mode="types">
 
116
    <xsl:variable name="name" select="@name"/>
 
117
    <xsl:variable name="arity" select="@arity"/>
 
118
    <xsl:variable name="spec0">
 
119
      <xsl:call-template name="find_spec"/>
 
120
    </xsl:variable>
 
121
    <xsl:variable name="spec" select="exsl:node-set($spec0)/spec"/>
 
122
    <xsl:variable name="clause" select="$spec/contract/clause"/>
 
123
 
103
124
    <xsl:variable name="type_desc" select="../type_desc"/>
104
 
    <xsl:for-each select="$clause">
105
 
      <xsl:apply-templates select="head"/>
106
 
      <xsl:if test="count(guard) > 0">
107
 
        <xsl:call-template name="guard">
108
 
          <xsl:with-param name="guard" select="guard"/>
 
125
    <!-- $type is data types to be presented as guards ("local types") -->
 
126
    <xsl:variable name="type"
 
127
                  select="../type[string-length(@name) > 0
 
128
                                  or string-length(@variable) > 0]"/>
 
129
    <xsl:variable name="type_variables"
 
130
                  select ="$type[string-length(@variable) > 0]"/>
 
131
    <xsl:variable name="local_types"
 
132
                  select ="$type[string-length(@name) > 0]"/>
 
133
    <xsl:variable name="output_subtypes" select="count($type_variables) = 0"/>
 
134
 
 
135
    <!-- It is assumed there is no support for overloaded specs
 
136
         (there is no spec with more than one clause) -->
 
137
    <xsl:if test="count($clause/guard) > 0 or count($type) > 0">
 
138
      <fo:block>
 
139
        <xsl:text>Types:</xsl:text>
 
140
      </fo:block>
 
141
      <fo:list-block xsl:use-attribute-sets="type-listblock">
 
142
        <xsl:choose>
 
143
          <xsl:when test="$output_subtypes">
 
144
            <xsl:call-template name="subtype">
 
145
              <xsl:with-param name="subtype" select="$clause/guard/subtype"/>
 
146
              <xsl:with-param name="type_desc" select="$type_desc"/>
 
147
              <xsl:with-param name="local_types" select="$local_types"/>
 
148
            </xsl:call-template>
 
149
          </xsl:when>
 
150
          <xsl:otherwise>
 
151
            <xsl:call-template name="type_variables">
 
152
              <xsl:with-param name="type_variables" select="$type_variables"/>
 
153
              <xsl:with-param name="type_desc" select="$type_desc"/>
 
154
              <xsl:with-param name="local_types" select="$local_types"/>
 
155
              <xsl:with-param name="fname" select="$name"/>
 
156
              <xsl:with-param name="arity" select="$arity"/>
 
157
            </xsl:call-template>
 
158
 
 
159
          </xsl:otherwise>
 
160
        </xsl:choose>
 
161
 
 
162
        <xsl:call-template name="local_type">
109
163
          <xsl:with-param name="type_desc" select="$type_desc"/>
 
164
          <xsl:with-param name="local_types" select="$local_types"/>
 
165
        </xsl:call-template>
 
166
      </fo:list-block>
 
167
    </xsl:if>
 
168
  </xsl:template>
 
169
 
 
170
  <!-- Handle <type variable="..." name_i="..."/> -->
 
171
  <xsl:template name="type_variables">
 
172
    <xsl:param name="type_variables"/>
 
173
    <xsl:param name="type_desc"/>
 
174
    <xsl:param name="local_types"/>
 
175
    <xsl:param name="fname"/>
 
176
    <xsl:param name="arity"/>
 
177
 
 
178
    <xsl:variable name="names" select="../name[string-length(@arity) > 0]"/>
 
179
    <xsl:for-each select="$type_variables">
 
180
      <xsl:variable name="name_i">
 
181
        <xsl:choose>
 
182
          <xsl:when test="string-length(@name_i) > 0">
 
183
            <xsl:value-of select="@name_i"/>
 
184
          </xsl:when>
 
185
          <xsl:otherwise>
 
186
            <xsl:value-of select="count($names)"/>
 
187
          </xsl:otherwise>
 
188
        </xsl:choose>
 
189
      </xsl:variable>
 
190
      <xsl:variable name="spec0">
 
191
        <xsl:for-each select="$names[position() = $name_i]">
 
192
          <xsl:call-template name="find_spec"/>
 
193
        </xsl:for-each>
 
194
      </xsl:variable>
 
195
      <xsl:variable name="spec" select="exsl:node-set($spec0)/spec"/>
 
196
      <xsl:variable name="clause" select="$spec/contract/clause"/>
 
197
      <xsl:variable name="variable" select="@variable"/>
 
198
      <xsl:variable name="subtype"
 
199
                    select="$clause/guard/subtype[typename = $variable]"/>
 
200
 
 
201
      <xsl:if test="count($subtype) = 0">
 
202
        <xsl:call-template name="err">
 
203
          <xsl:with-param name="f" select="ancestor::erlref/module"/>
 
204
          <xsl:with-param name="n" select="$fname"/>
 
205
          <xsl:with-param name="a" select="$arity"/>
 
206
          <xsl:with-param name="s">unknown type variable <xsl:value-of select="$variable"/>
 
207
          </xsl:with-param>
110
208
        </xsl:call-template>
111
209
      </xsl:if>
112
 
    </xsl:for-each>
113
 
  </xsl:template>
114
 
 
115
 
  <xsl:template match="head">
116
 
    <fo:block xsl:use-attribute-sets="function-name">
117
 
      <xsl:apply-templates/>
118
 
    </fo:block>
119
 
  </xsl:template>
120
 
 
121
 
  <xsl:template name="guard">
122
 
    <fo:block>
123
 
      <xsl:text>Types:</xsl:text>
124
 
    </fo:block>
125
 
    <fo:list-block xsl:use-attribute-sets="type-listblock">
 
210
 
126
211
      <xsl:call-template name="subtype">
127
 
        <xsl:with-param name="subtype" select="$guard/subtype"/>
128
 
        <xsl:with-param name="type_desc" select="$type_desc"/>
 
212
        <xsl:with-param name="subtype" select="$subtype"/>
 
213
        <xsl:with-param name="type_desc" select="$type_desc"/>
129
214
      </xsl:call-template>
130
 
    </fo:list-block>
 
215
    </xsl:for-each>
131
216
  </xsl:template>
132
217
 
 
218
  <!-- Substituted
 
219
       <fo:block xsl:use-attribute-sets="function-name">
 
220
       for
 
221
       <fo:block font-weight="bold">
 
222
       to get proper indentation (a monospace font)
 
223
  -->
133
224
  <xsl:template name="subtype">
134
225
    <xsl:param name="subtype"/>
135
226
    <xsl:param name="type_desc"/>
 
227
 
136
228
    <xsl:for-each select="$subtype">
137
229
      <xsl:variable name="tname" select="typename"/>
138
 
      <xsl:variable name="tdesc" select="$type_desc[@name = $tname]"/>
139
 
      <fo:list-item xsl:use-attribute-sets="type-listitem">
140
 
        <fo:list-item-label end-indent="label-end()">
141
 
          <fo:block>
142
 
          </fo:block>
143
 
        </fo:list-item-label>
144
 
        <fo:list-item-body start-indent="body-start()" format="justify">
145
 
          <fo:block font-weight="bold">
146
 
            <xsl:apply-templates select="string"/>
147
 
          </fo:block>
148
 
        </fo:list-item-body>
149
 
      </fo:list-item>
150
 
      <xsl:apply-templates select="$type_desc[@name = $tname]"/>
 
230
      <fo:list-item xsl:use-attribute-sets="type-listitem">
 
231
        <fo:list-item-label end-indent="label-end()">
 
232
          <fo:block>
 
233
          </fo:block>
 
234
        </fo:list-item-label>
 
235
        <fo:list-item-body start-indent="body-start()" format="justify">
 
236
          <fo:block xsl:use-attribute-sets="function-name">
 
237
            <xsl:apply-templates select="string"/>
 
238
          </fo:block>
 
239
        </fo:list-item-body>
 
240
      </fo:list-item>
 
241
      <xsl:apply-templates select="$type_desc[@variable = $tname]"/>
 
242
    </xsl:for-each>
 
243
  </xsl:template>
 
244
 
 
245
  <xsl:template name="local_type">
 
246
    <xsl:param name="type_desc"/>
 
247
    <xsl:param name="local_types"/>
 
248
 
 
249
    <xsl:for-each select="$local_types">
 
250
      <fo:list-item xsl:use-attribute-sets="type-listitem">
 
251
        <fo:list-item-label end-indent="label-end()">
 
252
          <fo:block>
 
253
          </fo:block>
 
254
        </fo:list-item-label>
 
255
        <fo:list-item-body start-indent="body-start()" format="justify">
 
256
          <!-- <fo:block font-weight="bold">
 
257
               (use function-name in "typehead" instead) -->
 
258
            <xsl:call-template name="type_name">
 
259
              <xsl:with-param name="mode" select="'local_type'"/>
 
260
            </xsl:call-template>
 
261
          <!-- </fo:block> -->
 
262
        </fo:list-item-body>
 
263
      </fo:list-item>
 
264
      <xsl:variable name="tname" select="@name"/>
 
265
      <xsl:variable name="tnvars" select="@n_vars"/>
 
266
      <xsl:apply-templates select=
 
267
         "$type_desc[@name = $tname
 
268
                     and (@n_vars = $tnvars
 
269
                          or string-length(@n_vars) = 0 and
 
270
                             string-length($tnvars) = 0)]"/>
151
271
    </xsl:for-each>
152
272
  </xsl:template>
153
273
 
182
302
    <xsl:apply-templates select="desc"/>
183
303
  </xsl:template>
184
304
 
185
 
  <!-- Like <head>... -->
186
 
  <xsl:template match="typehead">
187
 
    <fo:block xsl:use-attribute-sets="function-name">
188
 
      <xsl:apply-templates/>
189
 
    </fo:block>
190
 
  </xsl:template>
191
 
 
192
 
  <!-- Like <guard>, except "Types:"... -->
193
 
  <xsl:template match="local_defs">
194
 
    <fo:list-block xsl:use-attribute-sets="type-listblock">
195
 
      <xsl:apply-templates/>
196
 
    </fo:list-block>
197
 
  </xsl:template>
198
 
 
199
 
  <!-- Like <subtype>... -->
200
 
  <xsl:template match="local_def">
201
 
    <fo:list-item xsl:use-attribute-sets="type-listitem">
202
 
      <fo:list-item-label end-indent="label-end()">
203
 
        <fo:block>
204
 
        </fo:block>
205
 
      </fo:list-item-label>
206
 
      <fo:list-item-body start-indent="body-start()" format="justify">
207
 
        <fo:block font-weight="bold">
208
 
          <xsl:apply-templates/>
209
 
        </fo:block>
210
 
      </fo:list-item-body>
211
 
    </fo:list-item>
212
 
  </xsl:template>
213
 
 
214
305
  <xsl:template name="type_name">
 
306
    <xsl:param name="mode"/> <!-- '' if <datatype> -->
215
307
    <xsl:variable name="curModule" select="ancestor::erlref/module"/>
216
308
    <xsl:variable name="mod" select="@mod"/>
217
309
    <xsl:variable name="name" select="@name"/>
218
 
    <xsl:variable name="n_vars">
219
 
      <xsl:choose>
220
 
        <xsl:when test="string-length(@n_vars) > 0">
221
 
          <xsl:value-of select="@n_vars"/>
222
 
        </xsl:when>
223
 
        <xsl:otherwise>
224
 
          <xsl:value-of select="0"/>
225
 
        </xsl:otherwise>
226
 
      </xsl:choose>
227
 
    </xsl:variable>
 
310
    <xsl:variable name="n_vars" select="@n_vars"/>
228
311
 
229
312
    <xsl:choose>
230
313
      <xsl:when test="string-length($name) > 0">
231
314
        <xsl:variable name="type" select=
232
315
            "$i/specs/module[@name=$curModule]/type
233
 
                 [name=$name and n_vars=$n_vars
 
316
                 [name=$name
 
317
                  and (string-length($n_vars) = 0 or n_vars = $n_vars)
234
318
                  and (string-length($mod) = 0 or module = $mod)]"/>
235
319
 
236
320
        <xsl:if test="count($type) != 1">
 
321
          <xsl:variable name="why">
 
322
            <xsl:choose>
 
323
              <xsl:when test="count($type) > 1">ambiguous type</xsl:when>
 
324
              <xsl:when test="count($type) = 0">unknown type</xsl:when>
 
325
            </xsl:choose>
 
326
          </xsl:variable>
237
327
          <xsl:call-template name="err">
 
328
            <xsl:with-param name="f" select="$curModule"/>
238
329
            <xsl:with-param name="m" select="$mod"/>
239
330
            <xsl:with-param name="n" select="$name"/>
240
331
            <xsl:with-param name="a" select="$n_vars"/>
241
 
            <xsl:with-param name="s">unknown type</xsl:with-param>
 
332
            <xsl:with-param name="s" select="$why"/>
242
333
          </xsl:call-template>
243
334
        </xsl:if>
244
 
        <xsl:apply-templates select="$type/typedecl"/>
 
335
        <xsl:choose>
 
336
          <xsl:when test="$mode = ''">
 
337
            <xsl:apply-templates select="$type/typedecl"/>
 
338
          </xsl:when>
 
339
          <xsl:when test="$mode = 'local_type'">
 
340
            <xsl:apply-templates select="$type/typedecl" mode="local_type"/>
 
341
          </xsl:when>
 
342
        </xsl:choose>
245
343
      </xsl:when>
246
344
      <xsl:otherwise>
247
345
        <fo:inline font-weight="bold" xsl:use-attribute-sets="type-listitem">
251
349
    </xsl:choose>
252
350
  </xsl:template>
253
351
 
 
352
  <!-- Like <head>... -->
 
353
  <xsl:template match="typehead">
 
354
    <fo:block xsl:use-attribute-sets="function-name">
 
355
      <xsl:apply-templates/>
 
356
    </fo:block>
 
357
  </xsl:template>
 
358
 
 
359
  <!-- Substituted
 
360
       <fo:block xsl:use-attribute-sets="function-name">
 
361
       for
 
362
       <fo:block font-weight="bold">
 
363
       to get proper indentation (a monospace font)
 
364
  -->
 
365
 
 
366
  <xsl:template match="typehead" mode="local_type">
 
367
    <fo:block xsl:use-attribute-sets="function-name">
 
368
      <xsl:apply-templates/>
 
369
    </fo:block>
 
370
  </xsl:template>
 
371
 
 
372
  <!-- Not used right now -->
 
373
  <!-- Like <guard>, except "Types:"... -->
 
374
  <xsl:template match="local_defs">
 
375
    <fo:list-block xsl:use-attribute-sets="type-listblock">
 
376
      <xsl:apply-templates/>
 
377
    </fo:list-block>
 
378
  </xsl:template>
 
379
 
 
380
  <!-- Like <subtype>... -->
 
381
  <xsl:template match="local_def">
 
382
    <fo:list-item xsl:use-attribute-sets="type-listitem">
 
383
      <fo:list-item-label end-indent="label-end()">
 
384
        <fo:block>
 
385
        </fo:block>
 
386
      </fo:list-item-label>
 
387
      <fo:list-item-body start-indent="body-start()" format="justify">
 
388
        <fo:block font-weight="bold">
 
389
          <xsl:apply-templates/>
 
390
        </fo:block>
 
391
      </fo:list-item-body>
 
392
    </fo:list-item>
 
393
  </xsl:template>
 
394
 
254
395
  <!-- Used both in <datatype> and in <func>! -->
255
396
  <xsl:template match="anno">
256
397
    <xsl:variable name="curModule" select="ancestor::erlref/module"/>
257
398
    <xsl:variable name="anno" select="normalize-space(text())"/>
258
399
    <xsl:variable name="namespec"
259
 
                  select="ancestor::desc/preceding-sibling::name"/>
 
400
                  select="ancestor::type_desc/preceding-sibling::name
 
401
                          | ancestor::desc/preceding-sibling::name"/>
260
402
    <xsl:if test="count($namespec) = 0 and string-length($specs_file) > 0">
261
403
      <xsl:call-template name="err">
262
 
        <xsl:with-param name="s">cannot find 'name' (<xsl:value-of select="$anno"/>)
263
 
        </xsl:with-param>
264
 
      </xsl:call-template>
265
 
    </xsl:if>
266
 
 
267
 
    <xsl:variable name="mod" select="$namespec/@mod"/>
268
 
    <xsl:variable name="name" select="$namespec/@name"/>
269
 
    <xsl:variable name="arity" select="$namespec/@arity"/>
270
 
    <xsl:variable name="clause" select="$namespec/@clause"/>
271
 
    <xsl:variable name="tmp_n_vars" select="$namespec/@n_vars"/>
272
 
    <xsl:variable name="n_vars">
273
 
      <xsl:choose>
274
 
        <xsl:when test="string-length($tmp_n_vars) > 0">
275
 
          <xsl:value-of select="$tmp_n_vars"/>
276
 
        </xsl:when>
277
 
        <xsl:otherwise>
278
 
          <xsl:value-of select="0"/>
279
 
        </xsl:otherwise>
280
 
      </xsl:choose>
281
 
    </xsl:variable>
 
404
        <xsl:with-param name="f" select="$curModule"/>
 
405
        <xsl:with-param name="s">cannot find tag 'name' (anno <xsl:value-of select="$anno"/>)
 
406
        </xsl:with-param>
 
407
      </xsl:call-template>
 
408
    </xsl:if>
 
409
 
 
410
    <!-- Search "local types" as well -->
 
411
    <xsl:variable name="local_types"
 
412
                select="ancestor::desc/preceding-sibling::type
 
413
                               [string-length(@name) > 0]
 
414
                      | ancestor::type_desc/preceding-sibling::type
 
415
                               [string-length(@name) > 0]"/>
 
416
    <xsl:variable name="has_anno_in_local_type">
 
417
      <xsl:for-each select="$local_types">
 
418
        <xsl:call-template name="anno_name">
 
419
          <xsl:with-param name="curModule" select="$curModule"/>
 
420
          <xsl:with-param name="anno" select="$anno"/>
 
421
        </xsl:call-template>
 
422
      </xsl:for-each>
 
423
    </xsl:variable>
 
424
 
 
425
    <xsl:variable name="has_anno">
 
426
      <xsl:for-each select="$namespec">
 
427
        <xsl:call-template name="anno_name">
 
428
          <xsl:with-param name="curModule" select="$curModule"/>
 
429
          <xsl:with-param name="anno" select="$anno"/>
 
430
        </xsl:call-template>
 
431
      </xsl:for-each>
 
432
    </xsl:variable>
 
433
 
 
434
    <xsl:if test="$has_anno = '' and $has_anno_in_local_type = ''">
 
435
      <xsl:call-template name="err">
 
436
        <xsl:with-param name="f" select="$curModule"/>
 
437
        <xsl:with-param name="m" select="$namespec/@mod"/>
 
438
        <xsl:with-param name="n" select="$namespec/@name"/>
 
439
        <xsl:with-param name="a" select="'-'"/>
 
440
        <xsl:with-param name="s">unknown annotation <xsl:value-of select="$anno"/>
 
441
        </xsl:with-param>
 
442
      </xsl:call-template>
 
443
    </xsl:if>
 
444
    <xsl:value-of select="$anno"/>
 
445
  </xsl:template>
 
446
 
 
447
  <xsl:template name="anno_name">
 
448
    <xsl:param name="curModule"/>
 
449
    <xsl:param name="anno"/>
 
450
    <xsl:variable name="mod" select="@mod"/>
 
451
    <xsl:variable name="name" select="@name"/>
 
452
    <xsl:variable name="arity" select="@arity"/>
 
453
    <xsl:variable name="n_vars" select="@n_vars"/>
 
454
    <xsl:variable name="clause_i" select="@clause_i"/>
 
455
 
282
456
    <xsl:variable name="spec0" select=
283
457
        "$i/specs/module[@name=$curModule]/spec
284
458
             [name=$name and arity=$arity
285
459
              and (string-length($mod) = 0 or module = $mod)]"/>
286
460
    <xsl:variable name="spec_annos" select=
287
 
         "$spec0[string-length($clause) = 0
288
 
                 or position() = $clause]/anno[.=$anno]"/>
 
461
         "$spec0[string-length($clause_i) = 0
 
462
                 or position() = $clause_i]/anno[.=$anno]"/>
289
463
    <xsl:variable name="type_annos" select=
290
464
        "$i/specs/module[@name=$curModule]/type
291
 
             [name=$name and n_vars=$n_vars
 
465
             [name=$name
 
466
              and (string-length($n_vars) = 0 or n_vars=$n_vars)
292
467
              and (string-length($mod) = 0 or module = $mod)]/anno[.=$anno]"/>
293
 
 
294
 
    <xsl:if test="count($spec_annos) = 0
295
 
                  and count($type_annos) = 0
296
 
                  and string-length($specs_file) > 0">
297
 
      <xsl:variable name="n">
298
 
        <xsl:choose>
299
 
          <xsl:when test="string-length($arity) = 0">
300
 
            <xsl:value-of select="$n_vars"/>
301
 
          </xsl:when>
302
 
          <xsl:otherwise>
303
 
            <xsl:value-of select="$arity"/>
304
 
          </xsl:otherwise>
305
 
        </xsl:choose>
306
 
      </xsl:variable>
307
 
      <xsl:call-template name="err">
308
 
        <xsl:with-param name="m" select="$mod"/>
309
 
        <xsl:with-param name="n" select="$name"/>
310
 
        <xsl:with-param name="a" select="$n"/>
311
 
        <xsl:with-param name="s">unknown annotation <xsl:value-of select="$anno"/>
312
 
        </xsl:with-param>
313
 
      </xsl:call-template>
 
468
    <xsl:if test="count($spec_annos) != 0
 
469
                  or count($type_annos) != 0
 
470
                  or string-length($specs_file) = 0">
 
471
      <xsl:value-of select="true()"/>
314
472
    </xsl:if>
315
 
    <xsl:value-of select="$anno"/>
316
473
  </xsl:template>
317
474
 
318
475
  <!-- Used for indentation of formatted types and specs -->
575
732
  <xsl:template name="bookmarks1">
576
733
    <xsl:param name="entries"/>
577
734
    <xsl:if test="$entries != ''">
578
 
 
579
 
      <fo:bookmark internal-destination="{generate-id(/book/parts/part)}"
580
 
        starting-state="hide">
581
 
        <fo:bookmark-title>User's Guide</fo:bookmark-title>
582
 
 
583
 
        <xsl:for-each select="$entries">
 
735
      <xsl:for-each select="$entries">
 
736
 
 
737
        <fo:bookmark internal-destination="{generate-id(header/title)}"
 
738
          starting-state="hide">
 
739
          <fo:bookmark-title><xsl:value-of select="header/title"/></fo:bookmark-title>
 
740
          
584
741
          <xsl:call-template name="bookmarks2">
585
742
            <xsl:with-param name="entries"
586
743
              select="chapter[header/title]"/>
587
744
          </xsl:call-template>
588
 
        </xsl:for-each>
589
 
 
590
 
      </fo:bookmark>
 
745
          
 
746
        </fo:bookmark>
 
747
      </xsl:for-each>
591
748
    </xsl:if>
592
749
  </xsl:template>
593
750
 
 
751
 
594
752
  <xsl:template name="bookmarks2">
595
753
    <xsl:param name="entries"/>
596
754
    <xsl:for-each select="$entries">
777
935
  <xsl:template match="part">
778
936
    <xsl:variable name="partnum"><xsl:number level="any" from="book" count="part|application"/></xsl:variable>
779
937
 
780
 
    <fo:block xsl:use-attribute-sets="h1" id="{generate-id()}">
 
938
    <fo:block xsl:use-attribute-sets="h1" id="{generate-id(header/title)}">
781
939
      <xsl:value-of select="$partnum"/>&#160;&#160;&#160;
782
 
      <xsl:text>User's Guide</xsl:text>
 
940
      <xsl:value-of select="header/title"/>
783
941
    </fo:block>
784
942
 
785
943
    <xsl:apply-templates select="description">
827
985
 
828
986
  </xsl:template>
829
987
 
830
 
  <!--  Chapter/Subsection -->
 
988
  <!--  Chapter/Subsection  -->
831
989
  <xsl:template match="chapter/section/section">
832
990
    <xsl:param name="partnum"/>
833
991
    <xsl:param name="chapnum"/>
844
1002
  </xsl:template>
845
1003
 
846
1004
 
 
1005
  <!--  Subsection below level 2 -->
 
1006
  <xsl:template match="section/section/section">
 
1007
    <xsl:param name="partnum"/>
 
1008
    <xsl:param name="chapnum"/>
 
1009
    <xsl:param name="sectnum"/>
 
1010
    <fo:block xsl:use-attribute-sets="h5" id="{generate-id(title)}">
 
1011
      <!-- xsl:value-of select="$partnum"/>.<xsl:value-of select="$chapnum"/>.<xsl:value-of select="$sectnum"/>.<xsl:number/ -->
 
1012
      <xsl:value-of select="title"/>
 
1013
    </fo:block>
 
1014
    <xsl:apply-templates>
 
1015
      <xsl:with-param name="partnum" select="$partnum"/>
 
1016
      <xsl:with-param name="chapnum" select="$chapnum"/>
 
1017
      <xsl:with-param name="sectnum" select="$sectnum"/>
 
1018
    </xsl:apply-templates>
 
1019
  </xsl:template>
 
1020
 
847
1021
 
848
1022
  <!-- *ref/Section -->
849
1023
  <xsl:template match="erlref/section|comref/section|cref/section|fileref/section|appref/section">
1209
1383
  <!-- Func -->
1210
1384
  <xsl:template match="func">
1211
1385
    <xsl:param name="partnum"/>
1212
 
 
1213
 
    <xsl:apply-templates select="name"/>
1214
 
 
1215
 
    <xsl:apply-templates select="fsummary|type|desc">
1216
 
      <xsl:with-param name="partnum" select="$partnum"/>
1217
 
    </xsl:apply-templates>
1218
 
 
 
1386
    <fo:block space-before="1.5em">
 
1387
      <xsl:apply-templates select="name"/>
 
1388
      <xsl:apply-templates
 
1389
          select="name[string-length(@arity) > 0 and position()=last()]"
 
1390
          mode="types"/>
 
1391
      <xsl:apply-templates select="fsummary|type|desc">
 
1392
        <xsl:with-param name="partnum" select="$partnum"/>
 
1393
      </xsl:apply-templates>
 
1394
    </fo:block>
1219
1395
  </xsl:template>
1220
1396
 
1221
1397
 
1229
1405
      <xsl:when test="ancestor::datatype">
1230
1406
        <xsl:call-template name="type_name"/>
1231
1407
      </xsl:when>
 
1408
      <xsl:when test="string-length(text()) = 0 and ancestor::erlref">
 
1409
        <xsl:message terminate="yes">
 
1410
          Error <xsl:value-of select="@name"/>: arity is mandatory when referring to specifications!
 
1411
        </xsl:message>
 
1412
      </xsl:when>
1232
1413
      <xsl:otherwise>
1233
1414
        <fo:block xsl:use-attribute-sets="function-name">
1234
1415
          <xsl:call-template name="name">
1243
1424
    <xsl:param name="partnum"/>
1244
1425
    <xsl:choose>
1245
1426
      <xsl:when test="ancestor::cref">
1246
 
        <fo:block id="{generate-id(nametext)}">
1247
 
          <xsl:value-of select="ret"/><xsl:text> </xsl:text><xsl:value-of select="nametext"/>
1248
 
        </fo:block>
 
1427
        <fo:block id="{generate-id(nametext)}"><xsl:value-of select="ret"/><xsl:text></xsl:text><xsl:value-of select="nametext"/></fo:block>
1249
1428
      </xsl:when>
1250
1429
      <xsl:otherwise>
1251
 
        <fo:block id="{generate-id(.)}">
1252
 
          <xsl:value-of select="."/>
1253
 
        </fo:block>
 
1430
        <fo:block id="{generate-id(.)}"><xsl:value-of select="."/></fo:block>
1254
1431
      </xsl:otherwise>
1255
1432
    </xsl:choose>
1256
1433
  </xsl:template>
1260
1437
  <xsl:template match="type">
1261
1438
    <xsl:param name="partnum"/>
1262
1439
 
1263
 
    <fo:block>
1264
 
      <xsl:text>Types:</xsl:text>
1265
 
    </fo:block>
1266
 
 
1267
 
    <fo:list-block xsl:use-attribute-sets="type-listblock">
1268
 
      <xsl:apply-templates>
1269
 
        <xsl:with-param name="partnum" select="$partnum"/>
1270
 
      </xsl:apply-templates>
1271
 
    </fo:list-block>
 
1440
    <!-- The case where @name != 0 is taken care of in "type_name" -->
 
1441
    <xsl:if test="string-length(@name) = 0 and string-length(@variable) = 0">
 
1442
 
 
1443
      <fo:block>
 
1444
        <xsl:text>Types:</xsl:text>
 
1445
      </fo:block>
 
1446
 
 
1447
      <fo:list-block xsl:use-attribute-sets="type-listblock">
 
1448
        <xsl:apply-templates>
 
1449
          <xsl:with-param name="partnum" select="$partnum"/>
 
1450
        </xsl:apply-templates>
 
1451
      </fo:list-block>
 
1452
 
 
1453
    </xsl:if>
1272
1454
 
1273
1455
  </xsl:template>
1274
1456
 
1282
1464
        </fo:block>
1283
1465
      </fo:list-item-label>
1284
1466
      <fo:list-item-body start-indent="body-start()" format="justify">
1285
 
        <fo:block font-weight="bold">
 
1467
        <fo:block font-weight="bold" font-family="monospace" >
1286
1468
          <xsl:apply-templates>
1287
1469
            <xsl:with-param name="partnum" select="$partnum"/>
1288
1470
          </xsl:apply-templates>
1415
1597
  </xsl:template>
1416
1598
 
1417
1599
 
 
1600
  <!-- Does not look at @n_vars -->
1418
1601
  <xsl:template match="seealso">
1419
1602
    <fo:inline font-style="italic">
1420
1603
     <xsl:apply-templates/>
1497
1680
    <xsl:choose>
1498
1681
      <xsl:when test="string-length($tmp1) > 0 or starts-with($string, $start)">
1499
1682
        <xsl:variable name="tmp2">
1500
 
          <xsl:value-of select="substring-after($string, $end)"/>
 
1683
          <xsl:value-of select="substring-after(substring-after($string, $start), $end)"/>
1501
1684
        </xsl:variable>
1502
1685
        <xsl:variable name="retstring">
1503
1686
          <xsl:call-template name="remove-paren">