~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/tools/emacs/erlang-skels.el

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
;;
 
2
;; %CopyrightBegin%
 
3
;;
 
4
;; Copyright Ericsson AB 2010. All Rights Reserved.
 
5
;;
 
6
;; The contents of this file are subject to the Erlang Public License,
 
7
;; Version 1.1, (the "License"); you may not use this file except in
 
8
;; compliance with the License. You should have received a copy of the
 
9
;; Erlang Public License along with this software. If not, it can be
 
10
;; retrieved online at http://www.erlang.org/.
 
11
;;
 
12
;; Software distributed under the License is distributed on an "AS IS"
 
13
;; basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
;; the License for the specific language governing rights and limitations
 
15
;; under the License.
 
16
;;
 
17
;; %CopyrightEnd%
 
18
;;;
 
19
;;; Purpose: Provide Erlang code skeletons.
 
20
;;; See 'erlang-skel-file' variable.
 
21
 
 
22
(defvar erlang-tempo-tags nil
 
23
  "Tempo tags for erlang mode")
 
24
 
 
25
(defvar erlang-skel
 
26
  '(("If"            "if"            erlang-skel-if)
 
27
    ("Case"          "case"          erlang-skel-case)
 
28
    ("Receive"       "receive"       erlang-skel-receive)
 
29
    ("Receive After" "after"         erlang-skel-receive-after)
 
30
    ("Receive Loop"  "loop"          erlang-skel-receive-loop)
 
31
    ("Module"        "module"        erlang-skel-module)
 
32
    ("Author"        "author"        erlang-skel-author)
 
33
    ("Function"      "function"      erlang-skel-function)
 
34
    ()
 
35
    ("Small Header"  "small-header"
 
36
     erlang-skel-small-header erlang-skel-header)
 
37
    ("Normal Header" "normal-header"
 
38
     erlang-skel-normal-header erlang-skel-header)
 
39
    ("Large Header"  "large-header"
 
40
     erlang-skel-large-header erlang-skel-header)
 
41
    ()
 
42
    ("Small Server"   "small-server"
 
43
     erlang-skel-small-server erlang-skel-header)
 
44
    ()
 
45
    ("Application" "application"
 
46
     erlang-skel-application erlang-skel-header)
 
47
    ("Supervisor" "supervisor"
 
48
     erlang-skel-supervisor erlang-skel-header)
 
49
    ("supervisor_bridge" "supervisor-bridge"
 
50
     erlang-skel-supervisor-bridge erlang-skel-header)
 
51
    ("gen_server" "generic-server"
 
52
     erlang-skel-generic-server erlang-skel-header)
 
53
    ("gen_event" "gen-event"
 
54
     erlang-skel-gen-event erlang-skel-header)
 
55
    ("gen_fsm" "gen-fsm"
 
56
     erlang-skel-gen-fsm erlang-skel-header)
 
57
    ("Library module" "gen-lib"
 
58
     erlang-skel-lib erlang-skel-header)
 
59
    ("Corba callback" "gen-corba-cb"
 
60
     erlang-skel-corba-callback erlang-skel-header)
 
61
    ("Small Common Test suite" "ct-test-suite-s"
 
62
     erlang-skel-ct-test-suite-s erlang-skel-header)
 
63
    ("Large Common Test suite" "ct-test-suite-l"
 
64
     erlang-skel-ct-test-suite-l erlang-skel-header)
 
65
    ("Erlang TS test suite" "ts-test-suite"
 
66
     erlang-skel-ts-test-suite erlang-skel-header)
 
67
  )
 
68
  "*Description of all skeleton templates.
 
69
Both functions and menu entries will be created.
 
70
 
 
71
Each entry in `erlang-skel' should be a list with three or four
 
72
elements, or the empty list.
 
73
 
 
74
The first element is the name which shows up in the menu.  The second
 
75
is the `tempo' identifier (The string \"erlang-\" will be added in
 
76
front of it).  The third is the skeleton descriptor, a variable
 
77
containing `tempo' attributes as described in the function
 
78
`tempo-define-template'.  The optional fourth elements denotes a
 
79
function which should be called when the menu is selected.
 
80
 
 
81
Functions corresponding to every template will be created.  The name
 
82
of the function will be `tempo-template-erlang-X' where `X' is the
 
83
tempo identifier as specified in the second argument of the elements
 
84
in this list.
 
85
 
 
86
A list with zero elements means that the a horizontal line should
 
87
be placed in the menu.")
 
88
 
 
89
(defvar erlang-skel-use-separators t
 
90
  "A boolean than determines whether the skeletons include horizontal
 
91
separators.
 
92
 
 
93
Should this variable be nil, the documentation for functions will not
 
94
include separators of the form %%--...")
 
95
 
 
96
;; In XEmacs `user-mail-address' returns "x@y.z (Foo Bar)" ARGH!
 
97
;; What's wrong with that? RFC 822 says it's legal.   [sverkerw]
 
98
;; This needs to use the customized value.  If that's not sane, things like
 
99
;; add-log will lose anyhow.  Avoid it if there _is_ a paren.
 
100
(defvar erlang-skel-mail-address
 
101
  (if (or (not user-mail-address) (string-match "(" user-mail-address))
 
102
      (concat (user-login-name) "@"
 
103
              (or (and (boundp 'mail-host-address)
 
104
                       mail-host-address)
 
105
                  (system-name)))
 
106
    user-mail-address)
 
107
  "Mail address of the user.")
 
108
 
 
109
;; Expression templates:
 
110
(defvar erlang-skel-case
 
111
  '((erlang-skel-skip-blank) o >
 
112
    "case " p " of" n> p "_ ->" n> p "ok" n> "end" p)
 
113
  "*The skeleton of a `case' expression.
 
114
Please see the function `tempo-define-template'.")
 
115
 
 
116
(defvar erlang-skel-if
 
117
  '((erlang-skel-skip-blank) o >
 
118
    "if"  n> p " ->" n> p "ok" n> "end" p)
 
119
  "The skeleton of an `if' expression.
 
120
Please see the function `tempo-define-template'.")
 
121
 
 
122
(defvar erlang-skel-receive
 
123
  '((erlang-skel-skip-blank) o >
 
124
    "receive" n> p "_ ->" n> p "ok" n> "end" p)
 
125
  "*The skeleton of a `receive' expression.
 
126
Please see the function `tempo-define-template'.")
 
127
 
 
128
(defvar erlang-skel-receive-after
 
129
  '((erlang-skel-skip-blank) o >
 
130
    "receive" n> p "_ ->" n> p "ok" n> "after " p "T ->" n>
 
131
    p "ok" n> "end" p)
 
132
  "*The skeleton of a `receive' expression with an `after' clause.
 
133
Please see the function `tempo-define-template'.")
 
134
 
 
135
(defvar erlang-skel-receive-loop
 
136
  '(& o "loop(" p ") ->" n> "receive" n> p "_ ->" n>
 
137
      "loop(" p ")" n> "end.")
 
138
  "*The skeleton of a simple `receive' loop.
 
139
Please see the function `tempo-define-template'.")
 
140
 
 
141
 
 
142
(defvar erlang-skel-function
 
143
  '((erlang-skel-separator-start 2)
 
144
    "%% @doc" n
 
145
    "%% @spec" n
 
146
    (erlang-skel-separator-end 2))
 
147
    "*The template of a function skeleton.
 
148
Please see the function `tempo-define-template'.")
 
149
 
 
150
 
 
151
;; Attribute templates
 
152
 
 
153
(defvar erlang-skel-module
 
154
  '(& "-module("
 
155
      (erlang-add-quotes-if-needed (erlang-get-module-from-file-name))
 
156
      ")." n)
 
157
  "*The skeleton of a `module' attribute.
 
158
Please see the function `tempo-define-template'.")
 
159
 
 
160
(defvar erlang-skel-author
 
161
  '(& "-author('" erlang-skel-mail-address "')." n)
 
162
  "*The skeleton of a `author' attribute.
 
163
Please see the function `tempo-define-template'.")
 
164
 
 
165
(defvar erlang-skel-vc nil
 
166
  "*The skeleton template to generate a version control attribute.
 
167
The default is to insert nothing.  Example of usage:
 
168
 
 
169
    (setq erlang-skel-vc '(& \"-rcs(\\\"$\Id: $ \\\").\") n)
 
170
 
 
171
Please see the function `tempo-define-template'.")
 
172
 
 
173
(defvar erlang-skel-export
 
174
  '(& "-export([" n> "])." n)
 
175
  "*The skeleton of an `export' attribute.
 
176
Please see the function `tempo-define-template'.")
 
177
 
 
178
(defvar erlang-skel-import
 
179
  '(& "%%-import(Module, [Function/Arity, ...])." n)
 
180
  "*The skeleton of an `import' attribute.
 
181
Please see the function `tempo-define-template'.")
 
182
 
 
183
(defvar erlang-skel-compile nil
 
184
  ;;  '(& "%%-compile(export_all)." n)
 
185
  "*The skeleton of a `compile' attribute.
 
186
Please see the function `tempo-define-template'.")
 
187
 
 
188
 
 
189
;; Comment templates.
 
190
 
 
191
(defvar erlang-skel-date-function 'erlang-skel-dd-mmm-yyyy
 
192
  "*Function which returns date string.
 
193
Look in the module `time-stamp' for a battery of functions.")
 
194
 
 
195
(defvar erlang-skel-copyright-comment
 
196
  (if (boundp '*copyright-organization*)
 
197
      '(& "%%% @copyright (C) " (format-time-string "%Y") ", "
 
198
          *copyright-organization*  n)
 
199
      '(& "%%% @copyright (C) " (format-time-string "%Y") ", "
 
200
          (user-full-name)  n))
 
201
  "*The template for a copyright line in the header, normally empty.
 
202
This variable should be bound to a `tempo' template, for example:
 
203
  '(& \"%%% Copyright (C) 2000, Yoyodyne, Inc.\" n)
 
204
Please see the function `tempo-define-template'.")
 
205
 
 
206
(defvar erlang-skel-created-comment
 
207
  '(& "%%% Created : " (funcall erlang-skel-date-function) " by "
 
208
      (user-full-name) " <" erlang-skel-mail-address ">" n)
 
209
  "*The template for the \"Created:\" comment line.")
 
210
 
 
211
(defvar erlang-skel-author-comment
 
212
  '(& "%%% @author " (user-full-name) " <" erlang-skel-mail-address ">" n)
 
213
  "*The template for creating the \"Author:\" line in the header.
 
214
Please see the function `tempo-define-template'.")
 
215
 
 
216
(defvar erlang-skel-small-header
 
217
  '(o (erlang-skel-include erlang-skel-module)
 
218
      n
 
219
      (erlang-skel-include erlang-skel-compile erlang-skel-vc))
 
220
  "*The template of a small header without any comments.
 
221
Please see the function `tempo-define-template'.")
 
222
 
 
223
(defvar erlang-skel-normal-header
 
224
  '(o (erlang-skel-include  erlang-skel-author-comment)
 
225
      (erlang-skel-include erlang-skel-copyright-comment)
 
226
      "%%% @doc"  n
 
227
      "%%%" p n
 
228
      "%%% @end" n
 
229
      (erlang-skel-include erlang-skel-created-comment) n
 
230
      (erlang-skel-include erlang-skel-small-header) n)
 
231
  "*The template of a normal header.
 
232
Please see the function `tempo-define-template'.")
 
233
 
 
234
(defvar erlang-skel-large-header
 
235
  '(o (erlang-skel-separator)
 
236
      (erlang-skel-include erlang-skel-author-comment)
 
237
      (erlang-skel-include erlang-skel-copyright-comment)
 
238
      "%%% @doc" n
 
239
      "%%%" p n
 
240
      "%%% @end" n
 
241
      (erlang-skel-include erlang-skel-created-comment)
 
242
      (erlang-skel-separator)
 
243
      (erlang-skel-include erlang-skel-small-header) )
 
244
  "*The template of a large header.
 
245
Please see the function `tempo-define-template'.")
 
246
 
 
247
 
 
248
 ;; Server templates.
 
249
(defvar erlang-skel-small-server
 
250
  '((erlang-skel-include erlang-skel-large-header)
 
251
    "-export([start/0, init/1])." n n n
 
252
    "start() ->" n> "spawn(" (erlang-get-module-from-file-name)
 
253
    ", init, [self()])." n n
 
254
    "init(From) ->" n>
 
255
    "loop(From)." n n
 
256
    "loop(From) ->" n>
 
257
    "receive" n>
 
258
    p "_ ->" n>
 
259
    "loop(From)" n>
 
260
    "end." n
 
261
    )
 
262
  "*Template of a small server.
 
263
Please see the function `tempo-define-template'.")
 
264
 
 
265
;; Behaviour templates.
 
266
(defvar erlang-skel-application
 
267
  '((erlang-skel-include erlang-skel-large-header)
 
268
    "-behaviour(application)." n n
 
269
    "%% Application callbacks" n
 
270
    "-export([start/2, stop/1])." n n
 
271
    (erlang-skel-double-separator-start 3)
 
272
    "%%% Application callbacks" n
 
273
    (erlang-skel-double-separator-end 3) n
 
274
    (erlang-skel-separator-start 2)
 
275
    "%% @private" n
 
276
    "%% @doc" n
 
277
    "%% This function is called whenever an application is started using" n
 
278
    "%% application:start/[1,2], and should start the processes of the" n
 
279
    "%% application. If the application is structured according to the OTP" n
 
280
    "%% design principles as a supervision tree, this means starting the" n
 
281
    "%% top supervisor of the tree." n
 
282
    "%%" n
 
283
    "%% @spec start(StartType, StartArgs) -> {ok, Pid} |" n
 
284
    "%%                                      {ok, Pid, State} |" n
 
285
    "%%                                      {error, Reason}" n
 
286
    "%%      StartType = normal | {takeover, Node} | {failover, Node}" n
 
287
    "%%      StartArgs = term()" n
 
288
    (erlang-skel-separator-end 2)
 
289
    "start(_StartType, _StartArgs) ->" n>
 
290
    "case 'TopSupervisor':start_link() of" n>
 
291
    "{ok, Pid} ->" n>
 
292
    "{ok, Pid};" n>
 
293
    "Error ->" n>
 
294
    "Error" n>
 
295
    "end." n
 
296
    n
 
297
    (erlang-skel-separator-start 2)
 
298
    "%% @private" n
 
299
    "%% @doc" n
 
300
    "%% This function is called whenever an application has stopped. It" n
 
301
    "%% is intended to be the opposite of Module:start/2 and should do" n
 
302
    "%% any necessary cleaning up. The return value is ignored." n
 
303
    "%%" n
 
304
    "%% @spec stop(State) -> void()" n
 
305
    (erlang-skel-separator-end 2)
 
306
    "stop(_State) ->" n>
 
307
    "ok." n
 
308
    n
 
309
    (erlang-skel-double-separator-start 3)
 
310
    "%%% Internal functions" n
 
311
    (erlang-skel-double-separator-end 3)
 
312
    )
 
313
  "*The template of an application behaviour.
 
314
Please see the function `tempo-define-template'.")
 
315
 
 
316
(defvar erlang-skel-supervisor
 
317
  '((erlang-skel-include erlang-skel-large-header)
 
318
    "-behaviour(supervisor)." n n
 
319
 
 
320
    "%% API" n
 
321
    "-export([start_link/0])." n n
 
322
 
 
323
    "%% Supervisor callbacks" n
 
324
    "-export([init/1])." n n
 
325
 
 
326
    "-define(SERVER, ?MODULE)." n n
 
327
 
 
328
    (erlang-skel-double-separator-start 3)
 
329
    "%%% API functions" n
 
330
    (erlang-skel-double-separator-end 3) n
 
331
    (erlang-skel-separator-start 2)
 
332
    "%% @doc" n
 
333
    "%% Starts the supervisor" n
 
334
    "%%" n
 
335
    "%% @spec start_link() -> {ok, Pid} | ignore | {error, Error}" n
 
336
    (erlang-skel-separator-end 2)
 
337
    "start_link() ->" n>
 
338
    "supervisor:start_link({local, ?SERVER}, ?MODULE, [])." n
 
339
    n
 
340
    (erlang-skel-double-separator-start 3)
 
341
    "%%% Supervisor callbacks" n
 
342
    (erlang-skel-double-separator-end 3) n
 
343
    (erlang-skel-separator-start 2)
 
344
    "%% @private" n
 
345
    "%% @doc" n
 
346
    "%% Whenever a supervisor is started using supervisor:start_link/[2,3]," n
 
347
    "%% this function is called by the new process to find out about" n
 
348
    "%% restart strategy, maximum restart frequency and child" n
 
349
    "%% specifications." n
 
350
    "%%" n
 
351
    "%% @spec init(Args) -> {ok, {SupFlags, [ChildSpec]}} |" n
 
352
    "%%                     ignore |" n
 
353
    "%%                     {error, Reason}" n
 
354
    (erlang-skel-separator-end 2)
 
355
    "init([]) ->" n>
 
356
    "RestartStrategy = one_for_one," n>
 
357
    "MaxRestarts = 1000," n>
 
358
    "MaxSecondsBetweenRestarts = 3600," n
 
359
    "" n>
 
360
    "SupFlags = {RestartStrategy, MaxRestarts, MaxSecondsBetweenRestarts}," n
 
361
    "" n>
 
362
    "Restart = permanent," n>
 
363
    "Shutdown = 2000," n>
 
364
    "Type = worker," n
 
365
    "" n>
 
366
    "AChild = {'AName', {'AModule', start_link, []}," n>
 
367
    "Restart, Shutdown, Type, ['AModule']}," n
 
368
    "" n>
 
369
    "{ok, {SupFlags, [AChild]}}." n
 
370
    n
 
371
    (erlang-skel-double-separator-start 3)
 
372
    "%%% Internal functions" n
 
373
    (erlang-skel-double-separator-end 3)
 
374
    )
 
375
  "*The template of an supervisor behaviour.
 
376
Please see the function `tempo-define-template'.")
 
377
 
 
378
(defvar erlang-skel-supervisor-bridge
 
379
  '((erlang-skel-include erlang-skel-large-header)
 
380
    "-behaviour(supervisor_bridge)." n n
 
381
 
 
382
    "%% API" n
 
383
    "-export([start_link/0])." n n
 
384
 
 
385
    "%% supervisor_bridge callbacks" n
 
386
    "-export([init/1, terminate/2])." n n
 
387
 
 
388
    "-define(SERVER, ?MODULE)." n n
 
389
 
 
390
    "-record(state, {})." n n
 
391
 
 
392
    (erlang-skel-double-separator-start 3)
 
393
    "%%% API" n
 
394
    (erlang-skel-double-separator-end 3) n
 
395
    (erlang-skel-separator-start 2)
 
396
    "%% @doc" n
 
397
    "%% Starts the supervisor bridge" n
 
398
    "%%" n
 
399
    "%% @spec start_link() -> {ok, Pid} | ignore | {error, Error}" n
 
400
    (erlang-skel-separator-end 2)
 
401
    "start_link() ->" n>
 
402
    "supervisor_bridge:start_link({local, ?SERVER}, ?MODULE, [])." n
 
403
    n
 
404
    (erlang-skel-double-separator-start 3)
 
405
    "%%% supervisor_bridge callbacks" n
 
406
    (erlang-skel-double-separator-end 3) n
 
407
    (erlang-skel-separator-start 2)
 
408
    "%% @private" n
 
409
    "%% @doc" n
 
410
    "%% Creates a supervisor_bridge process, linked to the calling process," n
 
411
    "%% which calls Module:init/1 to start the subsystem. To ensure a" n
 
412
    "%% synchronized start-up procedure, this function does not return" n
 
413
    "%% until Module:init/1 has returned." n
 
414
    "%%" n
 
415
    "%% @spec init(Args) -> {ok, Pid, State} |" n
 
416
    "%%                     ignore |" n
 
417
    "%%                     {error, Reason}" n
 
418
    (erlang-skel-separator-end 2)
 
419
    "init([]) ->" n>
 
420
    "case 'AModule':start_link() of" n>
 
421
    "{ok, Pid} ->" n>
 
422
    "{ok, Pid, #state{}};" n>
 
423
    "Error ->" n>
 
424
    "Error" n>
 
425
    "end." n
 
426
    n
 
427
    (erlang-skel-separator-start 2)
 
428
    "%% @private" n
 
429
    "%% @doc" n
 
430
    "%% This function is called by the supervisor_bridge when it is about" n
 
431
    "%% to terminate. It should be the opposite of Module:init/1 and stop" n
 
432
    "%% the subsystem and do any necessary cleaning up.The return value is" n
 
433
    "%% ignored." n
 
434
    "%%" n
 
435
    "%% @spec terminate(Reason, State) -> void()" n
 
436
    (erlang-skel-separator-end 2)
 
437
    "terminate(Reason, State) ->" n>
 
438
    "'AModule':stop()," n>
 
439
    "ok." n
 
440
    n
 
441
    (erlang-skel-double-separator-start 3)
 
442
    "%%% Internal functions" n
 
443
    (erlang-skel-double-separator-end 3)
 
444
    )
 
445
  "*The template of an supervisor_bridge behaviour.
 
446
Please see the function `tempo-define-template'.")
 
447
 
 
448
(defvar erlang-skel-generic-server
 
449
  '((erlang-skel-include erlang-skel-large-header)
 
450
    "-behaviour(gen_server)." n n
 
451
 
 
452
    "%% API" n
 
453
    "-export([start_link/0])." n n
 
454
 
 
455
    "%% gen_server callbacks" n
 
456
    "-export([init/1, handle_call/3, handle_cast/2, "
 
457
    "handle_info/2," n>
 
458
    "terminate/2, code_change/3])." n n
 
459
 
 
460
    "-define(SERVER, ?MODULE). " n n
 
461
 
 
462
    "-record(state, {})." n n
 
463
 
 
464
    (erlang-skel-double-separator-start 3)
 
465
    "%%% API" n
 
466
    (erlang-skel-double-separator-end 3) n
 
467
    (erlang-skel-separator-start 2)
 
468
    "%% @doc" n
 
469
    "%% Starts the server" n
 
470
    "%%" n
 
471
    "%% @spec start_link() -> {ok, Pid} | ignore | {error, Error}" n
 
472
    (erlang-skel-separator-end 2)
 
473
    "start_link() ->" n>
 
474
    "gen_server:start_link({local, ?SERVER}, ?MODULE, [], [])." n
 
475
    n
 
476
    (erlang-skel-double-separator-start 3)
 
477
    "%%% gen_server callbacks" n
 
478
    (erlang-skel-double-separator-end 3)
 
479
    n
 
480
    (erlang-skel-separator-start 2)
 
481
    "%% @private" n
 
482
    "%% @doc" n
 
483
    "%% Initializes the server" n
 
484
    "%%" n
 
485
    "%% @spec init(Args) -> {ok, State} |" n
 
486
    "%%                     {ok, State, Timeout} |" n
 
487
    "%%                     ignore |" n
 
488
    "%%                     {stop, Reason}" n
 
489
    (erlang-skel-separator-end 2)
 
490
    "init([]) ->" n>
 
491
    "{ok, #state{}}." n
 
492
    n
 
493
    (erlang-skel-separator-start 2)
 
494
    "%% @private" n
 
495
    "%% @doc" n
 
496
    "%% Handling call messages" n
 
497
    "%%" n
 
498
    "%% @spec handle_call(Request, From, State) ->" n
 
499
    "%%                                   {reply, Reply, State} |" n
 
500
    "%%                                   {reply, Reply, State, Timeout} |" n
 
501
    "%%                                   {noreply, State} |" n
 
502
    "%%                                   {noreply, State, Timeout} |" n
 
503
    "%%                                   {stop, Reason, Reply, State} |" n
 
504
    "%%                                   {stop, Reason, State}" n
 
505
    (erlang-skel-separator-end 2)
 
506
    "handle_call(_Request, _From, State) ->" n>
 
507
    "Reply = ok," n>
 
508
    "{reply, Reply, State}." n
 
509
    n
 
510
    (erlang-skel-separator-start 2)
 
511
    "%% @private" n
 
512
    "%% @doc" n
 
513
    "%% Handling cast messages" n
 
514
    "%%" n
 
515
    "%% @spec handle_cast(Msg, State) -> {noreply, State} |" n
 
516
    "%%                                  {noreply, State, Timeout} |" n
 
517
    "%%                                  {stop, Reason, State}" n
 
518
    (erlang-skel-separator-end 2)
 
519
    "handle_cast(_Msg, State) ->" n>
 
520
    "{noreply, State}." n
 
521
    n
 
522
    (erlang-skel-separator-start 2)
 
523
    "%% @private" n
 
524
    "%% @doc" n
 
525
    "%% Handling all non call/cast messages" n
 
526
    "%%" n
 
527
    "%% @spec handle_info(Info, State) -> {noreply, State} |" n
 
528
    "%%                                   {noreply, State, Timeout} |" n
 
529
    "%%                                   {stop, Reason, State}" n
 
530
    (erlang-skel-separator-end 2)
 
531
    "handle_info(_Info, State) ->" n>
 
532
    "{noreply, State}." n
 
533
    n
 
534
    (erlang-skel-separator-start 2)
 
535
    "%% @private" n
 
536
    "%% @doc" n
 
537
    "%% This function is called by a gen_server when it is about to" n
 
538
    "%% terminate. It should be the opposite of Module:init/1 and do any" n
 
539
    "%% necessary cleaning up. When it returns, the gen_server terminates" n
 
540
    "%% with Reason. The return value is ignored." n
 
541
    "%%" n
 
542
    "%% @spec terminate(Reason, State) -> void()" n
 
543
    (erlang-skel-separator-end 2)
 
544
    "terminate(_Reason, _State) ->" n>
 
545
    "ok." n
 
546
    n
 
547
    (erlang-skel-separator-start 2)
 
548
    "%% @private" n
 
549
    "%% @doc" n
 
550
    "%% Convert process state when code is changed" n
 
551
    "%%" n
 
552
    "%% @spec code_change(OldVsn, State, Extra) -> {ok, NewState}" n
 
553
    (erlang-skel-separator-end 2)
 
554
    "code_change(_OldVsn, State, _Extra) ->" n>
 
555
    "{ok, State}." n
 
556
    n
 
557
    (erlang-skel-double-separator-start 3)
 
558
    "%%% Internal functions" n
 
559
    (erlang-skel-double-separator-end 3)
 
560
    )
 
561
  "*The template of a generic server.
 
562
Please see the function `tempo-define-template'.")
 
563
 
 
564
(defvar erlang-skel-gen-event
 
565
  '((erlang-skel-include erlang-skel-large-header)
 
566
    "-behaviour(gen_event)." n n
 
567
 
 
568
    "%% API" n
 
569
    "-export([start_link/0, add_handler/0])." n n
 
570
 
 
571
    "%% gen_event callbacks" n
 
572
    "-export([init/1, handle_event/2, handle_call/2, " n>
 
573
    "handle_info/2, terminate/2, code_change/3])." n n
 
574
 
 
575
    "-define(SERVER, ?MODULE). " n n
 
576
 
 
577
    "-record(state, {})." n n
 
578
 
 
579
    (erlang-skel-double-separator-start 3)
 
580
    "%%% gen_event callbacks" n
 
581
    (erlang-skel-double-separator-end 3) n
 
582
    (erlang-skel-separator-start 2)
 
583
    "%% @doc" n
 
584
    "%% Creates an event manager" n
 
585
    "%%" n
 
586
    "%% @spec start_link() -> {ok, Pid} | {error, Error}" n
 
587
    (erlang-skel-separator-end 2)
 
588
    "start_link() ->" n>
 
589
    "gen_event:start_link({local, ?SERVER})." n
 
590
    n
 
591
    (erlang-skel-separator-start 2)
 
592
    "%% @doc" n
 
593
    "%% Adds an event handler" n
 
594
    "%%" n
 
595
    "%% @spec add_handler() -> ok | {'EXIT', Reason} | term()" n
 
596
    (erlang-skel-separator-end 2)
 
597
    "add_handler() ->" n>
 
598
    "gen_event:add_handler(?SERVER, ?MODULE, [])." n
 
599
    n
 
600
    (erlang-skel-double-separator-start 3)
 
601
    "%%% gen_event callbacks" n
 
602
    (erlang-skel-double-separator-end 3) n
 
603
    (erlang-skel-separator-start 2)
 
604
    "%% @private" n
 
605
    "%% @doc" n
 
606
    "%% Whenever a new event handler is added to an event manager," n
 
607
    "%% this function is called to initialize the event handler." n
 
608
    "%%" n
 
609
    "%% @spec init(Args) -> {ok, State}" n
 
610
    (erlang-skel-separator-end 2)
 
611
    "init([]) ->" n>
 
612
    "{ok, #state{}}." n
 
613
    n
 
614
    (erlang-skel-separator-start 2)
 
615
    "%% @private" n
 
616
    "%% @doc" n
 
617
    "%% Whenever an event manager receives an event sent using" n
 
618
    "%% gen_event:notify/2 or gen_event:sync_notify/2, this function is" n
 
619
    "%% called for each installed event handler to handle the event." n
 
620
    "%%" n
 
621
    "%% @spec handle_event(Event, State) ->" n
 
622
    "%%                          {ok, State} |" n
 
623
    "%%                          {swap_handler, Args1, State1, Mod2, Args2} |"n
 
624
    "%%                          remove_handler" n
 
625
    (erlang-skel-separator-end 2)
 
626
    "handle_event(_Event, State) ->" n>
 
627
    "{ok, State}." n
 
628
    n
 
629
    (erlang-skel-separator-start 2)
 
630
    "%% @private" n
 
631
    "%% @doc" n
 
632
    "%% Whenever an event manager receives a request sent using" n
 
633
    "%% gen_event:call/3,4, this function is called for the specified" n
 
634
    "%% event handler to handle the request." n
 
635
    "%%" n
 
636
    "%% @spec handle_call(Request, State) ->" n
 
637
    "%%                   {ok, Reply, State} |" n
 
638
    "%%                   {swap_handler, Reply, Args1, State1, Mod2, Args2} |" n
 
639
    "%%                   {remove_handler, Reply}" n
 
640
    (erlang-skel-separator-end 2)
 
641
    "handle_call(_Request, State) ->" n>
 
642
    "Reply = ok," n>
 
643
    "{ok, Reply, State}." n
 
644
    n
 
645
    (erlang-skel-separator-start 2)
 
646
    "%% @private" n
 
647
    "%% @doc" n
 
648
    "%% This function is called for each installed event handler when" n
 
649
    "%% an event manager receives any other message than an event or a" n
 
650
    "%% synchronous request (or a system message)." n
 
651
    "%%" n
 
652
    "%% @spec handle_info(Info, State) ->" n
 
653
    "%%                         {ok, State} |" n
 
654
    "%%                         {swap_handler, Args1, State1, Mod2, Args2} |" n
 
655
    "%%                         remove_handler" n
 
656
    (erlang-skel-separator-end 2)
 
657
    "handle_info(_Info, State) ->" n>
 
658
    "{ok, State}." n
 
659
    n
 
660
    (erlang-skel-separator-start 2)
 
661
    "%% @private" n
 
662
    "%% @doc" n
 
663
    "%% Whenever an event handler is deleted from an event manager, this" n
 
664
    "%% function is called. It should be the opposite of Module:init/1 and" n
 
665
    "%% do any necessary cleaning up." n
 
666
    "%%" n
 
667
    "%% @spec terminate(Reason, State) -> void()" n
 
668
    (erlang-skel-separator-end 2)
 
669
    "terminate(_Reason, _State) ->" n>
 
670
    "ok." n
 
671
    n
 
672
    (erlang-skel-separator-start 2)
 
673
    "%% @private" n
 
674
    "%% @doc" n
 
675
    "%% Convert process state when code is changed" n
 
676
    "%%" n
 
677
    "%% @spec code_change(OldVsn, State, Extra) -> {ok, NewState}" n
 
678
    (erlang-skel-separator-end 2)
 
679
    "code_change(_OldVsn, State, _Extra) ->" n>
 
680
    "{ok, State}." n
 
681
    n
 
682
    (erlang-skel-double-separator-start 3)
 
683
    "%%% Internal functions" n
 
684
    (erlang-skel-double-separator-end 3)
 
685
    )
 
686
  "*The template of a gen_event.
 
687
Please see the function `tempo-define-template'.")
 
688
 
 
689
(defvar erlang-skel-gen-fsm
 
690
  '((erlang-skel-include erlang-skel-large-header)
 
691
    "-behaviour(gen_fsm)." n n
 
692
 
 
693
    "%% API" n
 
694
    "-export([start_link/0])." n n
 
695
 
 
696
    "%% gen_fsm callbacks" n
 
697
    "-export([init/1, state_name/2, state_name/3, handle_event/3," n>
 
698
    "handle_sync_event/4, handle_info/3, terminate/3, code_change/4])." n n
 
699
 
 
700
    "-define(SERVER, ?MODULE)." n n
 
701
 
 
702
    "-record(state, {})." n n
 
703
 
 
704
    (erlang-skel-double-separator-start 3)
 
705
    "%%% API" n
 
706
    (erlang-skel-double-separator-end 3) n
 
707
    (erlang-skel-separator-start 2)
 
708
    "%% @doc" n
 
709
    "%% Creates a gen_fsm process which calls Module:init/1 to" n
 
710
    "%% initialize. To ensure a synchronized start-up procedure, this" n
 
711
    "%% function does not return until Module:init/1 has returned." n
 
712
    "%%" n
 
713
    "%% @spec start_link() -> {ok, Pid} | ignore | {error, Error}" n
 
714
    (erlang-skel-separator-end 2)
 
715
    "start_link() ->" n>
 
716
    "gen_fsm:start_link({local, ?SERVER}, ?MODULE, [], [])." n
 
717
    n
 
718
    (erlang-skel-double-separator-start 3)
 
719
    "%%% gen_fsm callbacks" n
 
720
    (erlang-skel-double-separator-end 3) n
 
721
    (erlang-skel-separator-start 2)
 
722
    "%% @private" n
 
723
    "%% @doc" n
 
724
    "%% Whenever a gen_fsm is started using gen_fsm:start/[3,4] or" n
 
725
    "%% gen_fsm:start_link/[3,4], this function is called by the new" n
 
726
    "%% process to initialize." n
 
727
    "%%" n
 
728
    "%% @spec init(Args) -> {ok, StateName, State} |" n
 
729
    "%%                     {ok, StateName, State, Timeout} |" n
 
730
    "%%                     ignore |" n
 
731
    "%%                     {stop, StopReason}" n
 
732
    (erlang-skel-separator-end 2)
 
733
    "init([]) ->" n>
 
734
    "{ok, state_name, #state{}}." n
 
735
    n
 
736
    (erlang-skel-separator-start 2)
 
737
    "%% @private" n
 
738
    "%% @doc" n
 
739
    "%% There should be one instance of this function for each possible" n
 
740
    "%% state name. Whenever a gen_fsm receives an event sent using" n
 
741
    "%% gen_fsm:send_event/2, the instance of this function with the same" n
 
742
    "%% name as the current state name StateName is called to handle" n
 
743
    "%% the event. It is also called if a timeout occurs." n
 
744
    "%%" n
 
745
    "%% @spec state_name(Event, State) ->" n
 
746
    "%%                   {next_state, NextStateName, NextState} |" n
 
747
    "%%                   {next_state, NextStateName, NextState, Timeout} |" n
 
748
    "%%                   {stop, Reason, NewState}" n
 
749
    (erlang-skel-separator-end 2)
 
750
    "state_name(_Event, State) ->" n>
 
751
    "{next_state, state_name, State}." n
 
752
    n
 
753
    (erlang-skel-separator-start 2)
 
754
    "%% @private" n
 
755
    "%% @doc" n
 
756
    "%% There should be one instance of this function for each possible" n
 
757
    "%% state name. Whenever a gen_fsm receives an event sent using" n
 
758
    "%% gen_fsm:sync_send_event/[2,3], the instance of this function with" n
 
759
    "%% the same name as the current state name StateName is called to" n
 
760
    "%% handle the event." n
 
761
    "%%" n
 
762
    "%% @spec state_name(Event, From, State) ->" n
 
763
    "%%                   {next_state, NextStateName, NextState} |"n
 
764
    "%%                   {next_state, NextStateName, NextState, Timeout} |" n
 
765
    "%%                   {reply, Reply, NextStateName, NextState} |" n
 
766
    "%%                   {reply, Reply, NextStateName, NextState, Timeout} |" n
 
767
    "%%                   {stop, Reason, NewState} |" n
 
768
    "%%                   {stop, Reason, Reply, NewState}" n
 
769
    (erlang-skel-separator-end 2)
 
770
    "state_name(_Event, _From, State) ->" n>
 
771
    "Reply = ok," n>
 
772
    "{reply, Reply, state_name, State}." n
 
773
    n
 
774
    (erlang-skel-separator-start 2)
 
775
    "%% @private" n
 
776
    "%% @doc" n
 
777
    "%% Whenever a gen_fsm receives an event sent using" n
 
778
    "%% gen_fsm:send_all_state_event/2, this function is called to handle" n
 
779
    "%% the event." n
 
780
    "%%" n
 
781
    "%% @spec handle_event(Event, StateName, State) ->" n
 
782
    "%%                   {next_state, NextStateName, NextState} |" n
 
783
    "%%                   {next_state, NextStateName, NextState, Timeout} |" n
 
784
    "%%                   {stop, Reason, NewState}" n
 
785
    (erlang-skel-separator-end 2)
 
786
    "handle_event(_Event, StateName, State) ->" n>
 
787
    "{next_state, StateName, State}." n
 
788
    n
 
789
    (erlang-skel-separator-start 2)
 
790
    "%% @private" n
 
791
    "%% @doc" n
 
792
    "%% Whenever a gen_fsm receives an event sent using" n
 
793
    "%% gen_fsm:sync_send_all_state_event/[2,3], this function is called" n
 
794
    "%% to handle the event." n
 
795
    "%%" n
 
796
    "%% @spec handle_sync_event(Event, From, StateName, State) ->" n
 
797
    "%%                   {next_state, NextStateName, NextState} |" n
 
798
    "%%                   {next_state, NextStateName, NextState, Timeout} |" n
 
799
    "%%                   {reply, Reply, NextStateName, NextState} |" n
 
800
    "%%                   {reply, Reply, NextStateName, NextState, Timeout} |" n
 
801
    "%%                   {stop, Reason, NewState} |" n
 
802
    "%%                   {stop, Reason, Reply, NewState}" n
 
803
    (erlang-skel-separator-end 2)
 
804
    "handle_sync_event(_Event, _From, StateName, State) ->" n>
 
805
    "Reply = ok," n>
 
806
    "{reply, Reply, StateName, State}." n
 
807
    n
 
808
    (erlang-skel-separator-start 2)
 
809
    "%% @private" n
 
810
    "%% @doc" n
 
811
    "%% This function is called by a gen_fsm when it receives any" n
 
812
    "%% message other than a synchronous or asynchronous event" n
 
813
    "%% (or a system message)." n
 
814
    "%%" n
 
815
    "%% @spec handle_info(Info,StateName,State)->" n
 
816
    "%%                   {next_state, NextStateName, NextState} |" n
 
817
    "%%                   {next_state, NextStateName, NextState, Timeout} |" n
 
818
    "%%                   {stop, Reason, NewState}" n
 
819
    (erlang-skel-separator-end 2)
 
820
    "handle_info(_Info, StateName, State) ->" n>
 
821
    "{next_state, StateName, State}." n
 
822
    n
 
823
    (erlang-skel-separator-start 2)
 
824
    "%% @private" n
 
825
    "%% @doc" n
 
826
    "%% This function is called by a gen_fsm when it is about to" n
 
827
    "%% terminate. It should be the opposite of Module:init/1 and do any" n
 
828
    "%% necessary cleaning up. When it returns, the gen_fsm terminates with" n
 
829
    "%% Reason. The return value is ignored." n
 
830
    "%%" n
 
831
    "%% @spec terminate(Reason, StateName, State) -> void()" n
 
832
    (erlang-skel-separator-end 2)
 
833
    "terminate(_Reason, _StateName, _State) ->" n>
 
834
    "ok." n
 
835
    n
 
836
    (erlang-skel-separator-start 2)
 
837
    "%% @private" n
 
838
    "%% @doc" n
 
839
    "%% Convert process state when code is changed" n
 
840
    "%%" n
 
841
    "%% @spec code_change(OldVsn, StateName, State, Extra) ->" n
 
842
    "%%                   {ok, StateName, NewState}" n
 
843
    (erlang-skel-separator-end 2)
 
844
    "code_change(_OldVsn, StateName, State, _Extra) ->" n>
 
845
    "{ok, StateName, State}." n
 
846
    n
 
847
    (erlang-skel-double-separator-start 3)
 
848
    "%%% Internal functions" n
 
849
    (erlang-skel-double-separator-end 3)
 
850
    )
 
851
  "*The template of a gen_fsm.
 
852
Please see the function `tempo-define-template'.")
 
853
 
 
854
(defvar erlang-skel-lib
 
855
  '((erlang-skel-include erlang-skel-large-header)
 
856
 
 
857
    "%% API" n
 
858
    "-export([])." n n
 
859
 
 
860
    (erlang-skel-double-separator-start 3)
 
861
    "%%% API" n
 
862
    (erlang-skel-double-separator-end 3) n
 
863
    (erlang-skel-separator-start 2)
 
864
    "%% @doc" n
 
865
    "%% @spec" n
 
866
    (erlang-skel-separator-end 2)
 
867
    n
 
868
    (erlang-skel-double-separator-start 3)
 
869
    "%%% Internal functions" n
 
870
    (erlang-skel-double-separator-end 3)
 
871
    )
 
872
  "*The template of a library module.
 
873
Please see the function `tempo-define-template'.")
 
874
 
 
875
(defvar erlang-skel-corba-callback
 
876
  '((erlang-skel-include erlang-skel-large-header)
 
877
    "%% Include files" n n
 
878
 
 
879
    "%% API" n
 
880
    "-export([])." n n
 
881
 
 
882
    "%% Corba callbacks" n
 
883
    "-export([init/1, terminate/2, code_change/3])." n n
 
884
 
 
885
    "-record(state, {})." n n
 
886
 
 
887
    (erlang-skel-double-separator-start 3)
 
888
    "%%% Corba callbacks" n
 
889
    (erlang-skel-double-separator-end 3) n
 
890
    (erlang-skel-separator-start 2)
 
891
    "%% @private" n
 
892
    "%% @doc" n
 
893
    "%% Initializes the server" n
 
894
    "%%" n
 
895
    "%% @spec init(Args) -> {ok, State} |" n
 
896
    "%%                     {ok, State, Timeout} |" n
 
897
    "%%                     ignore |" n
 
898
    "%%                     {stop, Reason}" n
 
899
    (erlang-skel-separator-end 2)
 
900
    "init([]) ->" n>
 
901
    "{ok, #state{}}." n
 
902
    n
 
903
    (erlang-skel-separator-start 2)
 
904
    "%% @private" n
 
905
    "%% @doc" n
 
906
    "%% Shutdown the server" n
 
907
    "%%" n
 
908
    "%% @spec terminate(Reason, State) -> void()" n
 
909
    (erlang-skel-separator-end 2)
 
910
    "terminate(_Reason, _State) ->" n>
 
911
    "ok." n
 
912
    n
 
913
    (erlang-skel-separator-start 2)
 
914
    "%% @private" n
 
915
    "%% @doc" n
 
916
    "%% Convert process state when code is changed" n
 
917
    "%%" n
 
918
    "%% @spec code_change(OldVsn, State, Extra) -> {ok, NewState}" n
 
919
    (erlang-skel-separator-end 2)
 
920
    "code_change(_OldVsn, State, _Extra) ->" n>
 
921
    "{ok, State}." n
 
922
    n
 
923
    (erlang-skel-double-separator-start 3)
 
924
    "%%% Internal functions" n
 
925
    (erlang-skel-double-separator-end 3)
 
926
    )
 
927
  "*The template of a library module.
 
928
Please see the function `tempo-define-template'.")
 
929
 
 
930
(defvar erlang-skel-ts-test-suite
 
931
 '((erlang-skel-include erlang-skel-large-header)
 
932
   "%% Note: This directive should only be used in test suites." n
 
933
    "-compile(export_all)." n n
 
934
 
 
935
    "-include_lib(\"test_server/include/test_server.hrl\")." n n
 
936
 
 
937
    (erlang-skel-separator-start 2)
 
938
    "%% TEST SERVER CALLBACK FUNCTIONS" n
 
939
    (erlang-skel-separator 2)
 
940
    n
 
941
    (erlang-skel-separator-start 2)
 
942
    "%%" n
 
943
    "%% @doc" n
 
944
    "%% Initialization before the suite." n
 
945
    "%%" n
 
946
    "%% Config0 = Config1 = [tuple()]" n
 
947
    "%%   A list of key/value pairs, holding the test case configuration." n
 
948
    "%% Reason = term()" n
 
949
    "%%   The reason for skipping the suite." n
 
950
    "%%" n
 
951
    "%% Note: This function is free to add any key/value pairs to the Config" n
 
952
    "%% variable, but should NOT alter/remove any existing entries." n
 
953
    "%%" n
 
954
    "%% @spec init_per_suite(Config) -> Config" n
 
955
    (erlang-skel-separator-end 2)
 
956
    "init_per_suite(Config) ->" n >
 
957
    "Config." n n
 
958
 
 
959
    (erlang-skel-separator-start 2)
 
960
    "%% @doc" n
 
961
    "%% Cleanup after the suite." n
 
962
    "%% Config - [tuple()]" n
 
963
    "%%   A list of key/value pairs, holding the test case configuration." n
 
964
    "%%" n
 
965
    "%% @spec end_per_suite(Config) -> _" n
 
966
    (erlang-skel-separator-end 2)
 
967
    "end_per_suite(_Config) ->" n >
 
968
    "ok." n n
 
969
 
 
970
    (erlang-skel-separator-start 2)
 
971
    "%% @doc" n
 
972
    "%% Initialization before each test case" n
 
973
    "%%" n
 
974
    "%% TestCase - atom()" n
 
975
    "%%   Name of the test case that is about to be run." n
 
976
    "%% Config - [tuple()]" n
 
977
    "%%   A list of key/value pairs, holding the test case configuration." n
 
978
    "%% Reason = term()" n
 
979
    "%%   The reason for skipping the test case." n
 
980
    "%%" n
 
981
    "%% Note: This function is free to add any key/value pairs to the Config" n
 
982
    "%% variable, but should NOT alter/remove any existing entries." n
 
983
    "%%" n
 
984
    "%% @spec init_per_testcase(TestCase, Config) -> Config" n
 
985
    (erlang-skel-separator-end 2)
 
986
    "init_per_testcase(_TestCase, Config) ->" n >
 
987
    "Config." n n
 
988
 
 
989
    (erlang-skel-separator-start 2)
 
990
    "%% @doc" n
 
991
    "%% Cleanup after each test case" n
 
992
    "%%" n
 
993
    "%% TestCase = atom()" n
 
994
    "%%   Name of the test case that is finished." n
 
995
    "%% Config = [tuple()]" n
 
996
    "%%   A list of key/value pairs, holding the test case configuration." n
 
997
    "%%" n
 
998
    "%% @spec end_per_testcase(TestCase, Config) -> _" n
 
999
    (erlang-skel-separator-end 2)
 
1000
    "end_per_testcase(_TestCase, _Config) ->" n >
 
1001
    "ok."n n
 
1002
 
 
1003
    (erlang-skel-separator-start 2)
 
1004
    "%% @doc" n
 
1005
    "%% Returns a description of the test suite when" n
 
1006
    "%% Clause == doc, and a test specification (list" n
 
1007
    "%% of the conf and test cases in the suite) when" n
 
1008
    "%% Clause == suite." n   
 
1009
    "%% Returns a list of all test cases in this test suite" n
 
1010
    "%%" n
 
1011
    "%% Clause = doc | suite" n
 
1012
    "%%   Indicates expected return value." n
 
1013
    "%% Descr = [string()] | []" n
 
1014
    "%%   String that describes the test suite." n
 
1015
    "%% Spec = [TestCase]" n
 
1016
    "%%   A test specification." n
 
1017
    "%% TestCase = ConfCase | atom()" n
 
1018
    "%%   Configuration case, or the name of a test case function." n
 
1019
    "%% ConfCase = {conf,Init,Spec,End} |" n
 
1020
    "%%            {conf,Properties,Init,Spec,End}" n
 
1021
    "%% Init = End = {Mod,Func} | Func" n
 
1022
    "%%   Initialization and cleanup function." n
 
1023
    "%% Mod = Func = atom()" n
 
1024
    "%% Properties = [parallel | sequence | Shuffle | {RepeatType,N}]" n
 
1025
    "%%   Execution properties of the test cases (may be combined)." n
 
1026
    "%% Shuffle = shuffle | {shuffle,Seed}" n
 
1027
    "%%   To get cases executed in random order." n
 
1028
    "%% Seed = {integer(),integer(),integer()}" n
 
1029
    "%% RepeatType = repeat | repeat_until_all_ok | repeat_until_all_fail |" n
 
1030
    "%%              repeat_until_any_ok | repeat_until_any_fail" n
 
1031
    "%%   To get execution of cases repeated." n
 
1032
    "%% N = integer() | forever" n
 
1033
    "%% Reason = term()" n
 
1034
    "%%   The reason for skipping the test suite." n
 
1035
    "%%" n
 
1036
    "%% @spec all(Clause) -> TestCases" n
 
1037
    (erlang-skel-separator-end 2)
 
1038
    "all(doc) ->" n >
 
1039
    "[\"Describe the main purpose of this suite\"];" n n
 
1040
    "all(suite) -> " n >
 
1041
    "[a_test_case]." n n
 
1042
    n
 
1043
    (erlang-skel-separator-start 2)
 
1044
    "%% TEST CASES" n
 
1045
    (erlang-skel-separator 2)
 
1046
    n
 
1047
    (erlang-skel-separator-start 2)
 
1048
    "%% @doc" n
 
1049
    "%%  Test case function. Returns a description of the test" n
 
1050
    "%%  case (doc), then returns a test specification (suite)," n
 
1051
    "%%  or performs the actual test (Config)." n
 
1052
    "%%" n
 
1053
    "%% Arg = doc | suite | Config" n
 
1054
    "%%   Indicates expected behaviour and return value." n
 
1055
    "%% Config = [tuple()]" n
 
1056
    "%%   A list of key/value pairs, holding the test case configuration." n
 
1057
    "%% Descr = [string()] | []" n
 
1058
    "%%   String that describes the test case." n
 
1059
    "%% Spec = [tuple()] | []" n
 
1060
    "%%   A test specification, see all/1." n
 
1061
    "%% Reason = term()" n
 
1062
    "%%   The reason for skipping the test case." n
 
1063
    "%%" n
 
1064
    "%% @spec TestCase(Arg) -> Descr | Spec | ok | exit() | {skip,Reason}" n
 
1065
 
 
1066
    (erlang-skel-separator-end 2)
 
1067
    "a_test_case(doc) -> " n >
 
1068
    "[\"Describe the main purpose of this test case\"];" n n
 
1069
    "a_test_case(suite) -> " n >
 
1070
    "[];" n n
 
1071
    "a_test_case(Config) when is_list(Config) -> " n >
 
1072
    "ok." n
 
1073
   )
 
1074
 "*The template of a library module.
 
1075
Please see the function `tempo-define-template'.")
 
1076
 
 
1077
(defvar erlang-skel-ct-test-suite-s
 
1078
  '((erlang-skel-include erlang-skel-large-header)
 
1079
    "-compile(export_all)." n n
 
1080
 
 
1081
    "-include_lib(\"common_test/include/ct.hrl\")." n n
 
1082
 
 
1083
    (erlang-skel-separator-start 2)
 
1084
    "%% @spec suite() -> Info" n
 
1085
    "%% Info = [tuple()]" n
 
1086
    (erlang-skel-separator-end 2)
 
1087
    "suite() ->" n >
 
1088
    "[{timetrap,{seconds,30}}]." n n
 
1089
 
 
1090
    (erlang-skel-separator-start 2)
 
1091
    "%% @spec init_per_suite(Config0) ->" n
 
1092
    "%%     Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}" n
 
1093
    "%% Config0 = Config1 = [tuple()]" n
 
1094
    "%% Reason = term()" n
 
1095
    (erlang-skel-separator-end 2)
 
1096
    "init_per_suite(Config) ->" n >
 
1097
    "Config." n n
 
1098
 
 
1099
    (erlang-skel-separator-start 2)
 
1100
    "%% @spec end_per_suite(Config0) -> void() | {save_config,Config1}" n
 
1101
    "%% Config0 = Config1 = [tuple()]" n
 
1102
    (erlang-skel-separator-end 2)
 
1103
    "end_per_suite(_Config) ->" n >
 
1104
    "ok." n n
 
1105
 
 
1106
    (erlang-skel-separator-start 2)
 
1107
    "%% @spec init_per_group(GroupName, Config0) ->" n
 
1108
    "%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}" n
 
1109
    "%% GroupName = atom()" n
 
1110
    "%% Config0 = Config1 = [tuple()]" n
 
1111
    "%% Reason = term()" n
 
1112
    (erlang-skel-separator-end 2)
 
1113
    "init_per_group(_GroupName, Config) ->" n >
 
1114
    "Config." n n
 
1115
 
 
1116
    (erlang-skel-separator-start 2)
 
1117
    "%% @spec end_per_group(GroupName, Config0) ->" n
 
1118
    "%%               void() | {save_config,Config1}" n
 
1119
    "%% GroupName = atom()" n
 
1120
    "%% Config0 = Config1 = [tuple()]" n
 
1121
    (erlang-skel-separator-end 2)
 
1122
    "end_per_group(_GroupName, _Config) ->" n >
 
1123
    "ok." n n
 
1124
 
 
1125
    (erlang-skel-separator-start 2)
 
1126
    "%% @spec init_per_testcase(TestCase, Config0) ->" n
 
1127
    "%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}" n
 
1128
    "%% TestCase = atom()" n
 
1129
    "%% Config0 = Config1 = [tuple()]" n
 
1130
    "%% Reason = term()" n
 
1131
    (erlang-skel-separator-end 2)
 
1132
    "init_per_testcase(_TestCase, Config) ->" n >
 
1133
    "Config." n n
 
1134
 
 
1135
    (erlang-skel-separator-start 2)
 
1136
    "%% @spec end_per_testcase(TestCase, Config0) ->" n
 
1137
    "%%               void() | {save_config,Config1} | {fail,Reason}" n
 
1138
    "%% TestCase = atom()" n
 
1139
    "%% Config0 = Config1 = [tuple()]" n
 
1140
    "%% Reason = term()" n
 
1141
    (erlang-skel-separator-end 2)
 
1142
    "end_per_testcase(_TestCase, _Config) ->" n >
 
1143
    "ok." n n
 
1144
 
 
1145
    (erlang-skel-separator-start 2)
 
1146
    "%% @spec groups() -> [Group]" n
 
1147
    "%% Group = {GroupName,Properties,GroupsAndTestCases}" n
 
1148
    "%% GroupName = atom()" n
 
1149
    "%% Properties = [parallel | sequence | Shuffle | {RepeatType,N}]" n
 
1150
    "%% GroupsAndTestCases = [Group | {group,GroupName} | TestCase]" n
 
1151
    "%% TestCase = atom()" n
 
1152
    "%% Shuffle = shuffle | {shuffle,{integer(),integer(),integer()}}" n
 
1153
    "%% RepeatType = repeat | repeat_until_all_ok | repeat_until_all_fail |" n
 
1154
    "%%              repeat_until_any_ok | repeat_until_any_fail" n
 
1155
    "%% N = integer() | forever" n
 
1156
    (erlang-skel-separator-end 2)
 
1157
    "groups() ->" n >
 
1158
    "[]." n n
 
1159
 
 
1160
    (erlang-skel-separator-start 2)
 
1161
    "%% @spec all() -> GroupsAndTestCases | {skip,Reason}" n
 
1162
    "%% GroupsAndTestCases = [{group,GroupName} | TestCase]" n
 
1163
    "%% GroupName = atom()" n
 
1164
    "%% TestCase = atom()" n
 
1165
    "%% Reason = term()" n
 
1166
    (erlang-skel-separator-end 2)
 
1167
    "all() -> " n >
 
1168
    "[my_test_case]." n n
 
1169
 
 
1170
    (erlang-skel-separator-start 2)
 
1171
    "%% @spec TestCase() -> Info" n
 
1172
    "%% Info = [tuple()]" n
 
1173
    (erlang-skel-separator-end 2)
 
1174
    "my_test_case() -> " n >
 
1175
    "[]." n n
 
1176
 
 
1177
    (erlang-skel-separator-start 2)
 
1178
    "%% @spec TestCase(Config0) ->" n
 
1179
    "%%               ok | exit() | {skip,Reason} | {comment,Comment} |" n
 
1180
    "%%               {save_config,Config1} | {skip_and_save,Reason,Config1}" n
 
1181
    "%% Config0 = Config1 = [tuple()]" n
 
1182
    "%% Reason = term()" n
 
1183
    "%% Comment = term()" n
 
1184
    (erlang-skel-separator-end 2)
 
1185
    "my_test_case(_Config) -> " n >
 
1186
    "ok." n
 
1187
    )
 
1188
  "*The template of a library module.
 
1189
Please see the function `tempo-define-template'.")
 
1190
 
 
1191
 
 
1192
(defvar erlang-skel-ct-test-suite-l
 
1193
  '((erlang-skel-include erlang-skel-large-header)
 
1194
    "%% Note: This directive should only be used in test suites." n
 
1195
    "-compile(export_all)." n n
 
1196
 
 
1197
    "-include_lib(\"common_test/include/ct.hrl\")." n n
 
1198
 
 
1199
    (erlang-skel-separator-start 2)
 
1200
    "%% COMMON TEST CALLBACK FUNCTIONS" n
 
1201
    (erlang-skel-separator 2)
 
1202
    n
 
1203
    (erlang-skel-separator-start 2)
 
1204
    "%% @doc" n
 
1205
    "%%  Returns list of tuples to set default properties" n
 
1206
    "%%  for the suite." n
 
1207
    "%%" n
 
1208
    "%% Function: suite() -> Info" n
 
1209
    "%%" n
 
1210
    "%% Info = [tuple()]" n
 
1211
    "%%   List of key/value pairs." n
 
1212
    "%%" n
 
1213
    "%% Note: The suite/0 function is only meant to be used to return" n
 
1214
    "%% default data values, not perform any other operations." n
 
1215
    "%%" n
 
1216
    "%% @spec suite() -> Info" n
 
1217
    (erlang-skel-separator-end 2)
 
1218
    "suite() ->" n >
 
1219
    "[{timetrap,{minutes,10}}]." n n
 
1220
 
 
1221
    (erlang-skel-separator-start 2)
 
1222
    "%% @doc" n    
 
1223
    "%% Initialization before the whole suite" n
 
1224
    "%%" n
 
1225
    "%% Config0 = Config1 = [tuple()]" n
 
1226
    "%%   A list of key/value pairs, holding the test case configuration." n
 
1227
    "%% Reason = term()" n
 
1228
    "%%   The reason for skipping the suite." n
 
1229
    "%%" n
 
1230
    "%% Note: This function is free to add any key/value pairs to the Config" n
 
1231
    "%% variable, but should NOT alter/remove any existing entries." n
 
1232
    "%%" n
 
1233
    "%% @spec init_per_suite(Config0) ->" n
 
1234
    "%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}" n
 
1235
    (erlang-skel-separator-end 2)
 
1236
    "init_per_suite(Config) ->" n >
 
1237
    "Config." n n
 
1238
 
 
1239
    (erlang-skel-separator-start 2)
 
1240
    "%% @doc" n
 
1241
    "%% Cleanup after the whole suite" n
 
1242
    "%%" n
 
1243
    "%% Config - [tuple()]" n
 
1244
    "%%   A list of key/value pairs, holding the test case configuration." n
 
1245
    "%%" n
 
1246
    "%% @spec end_per_suite(Config) -> _" n
 
1247
    (erlang-skel-separator-end 2)
 
1248
    "end_per_suite(_Config) ->" n >
 
1249
    "ok." n n
 
1250
 
 
1251
    (erlang-skel-separator-start 2)
 
1252
    "%% @doc" n
 
1253
    "%% Initialization before each test case group." n
 
1254
    "%%" n
 
1255
    "%% GroupName = atom()" n
 
1256
    "%%   Name of the test case group that is about to run." n
 
1257
    "%% Config0 = Config1 = [tuple()]" n
 
1258
    "%%   A list of key/value pairs, holding configuration data for the group." n
 
1259
    "%% Reason = term()" n
 
1260
    "%%   The reason for skipping all test cases and subgroups in the group." n
 
1261
    "%%" n
 
1262
    "%% @spec init_per_group(GroupName, Config0) ->" n
 
1263
    "%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}" n
 
1264
    (erlang-skel-separator-end 2)
 
1265
    "init_per_group(_GroupName, Config) ->" n >
 
1266
    "Config." n n
 
1267
 
 
1268
    (erlang-skel-separator-start 2)
 
1269
    "%% @doc" n
 
1270
    "%% Cleanup after each test case group." n
 
1271
    "%%" n
 
1272
    "%% GroupName = atom()" n
 
1273
    "%%   Name of the test case group that is finished." n
 
1274
    "%% Config0 = Config1 = [tuple()]" n
 
1275
    "%%   A list of key/value pairs, holding configuration data for the group." n
 
1276
    "%%" n
 
1277
    "%% @spec end_per_group(GroupName, Config0) ->" n
 
1278
    "%%               void() | {save_config,Config1}" n
 
1279
    (erlang-skel-separator-end 2)
 
1280
    "end_per_group(_GroupName, _Config) ->" n >
 
1281
    "ok." n n
 
1282
    (erlang-skel-separator-start 2)
 
1283
    "%% @doc" n
 
1284
    "%% Initialization before each test case" n
 
1285
    "%%" n
 
1286
    "%% TestCase - atom()" n
 
1287
    "%%   Name of the test case that is about to be run." n
 
1288
    "%% Config0 = Config1 = [tuple()]" n
 
1289
    "%%   A list of key/value pairs, holding the test case configuration." n
 
1290
    "%% Reason = term()" n
 
1291
    "%%   The reason for skipping the test case." n
 
1292
    "%%" n
 
1293
    "%% Note: This function is free to add any key/value pairs to the Config" n
 
1294
    "%% variable, but should NOT alter/remove any existing entries." n
 
1295
    "%%" n
 
1296
    "%% @spec init_per_testcase(TestCase, Config0) ->" n
 
1297
    "%%               Config1 | {skip,Reason} | {skip_and_save,Reason,Config1}" n
 
1298
    (erlang-skel-separator-end 2)
 
1299
    "init_per_testcase(_TestCase, Config) ->" n >
 
1300
    "Config." n n
 
1301
 
 
1302
    (erlang-skel-separator-start 2)
 
1303
    "%% @doc" n
 
1304
    "%% Cleanup after each test case" n
 
1305
    "%%" n
 
1306
    "%% TestCase - atom()" n
 
1307
    "%%   Name of the test case that is finished." n
 
1308
    "%% Config0 = Config1 = [tuple()]" n
 
1309
    "%%   A list of key/value pairs, holding the test case configuration." n
 
1310
    "%%" n
 
1311
    "%% @spec end_per_testcase(TestCase, Config0) ->" n
 
1312
    "%%               void() | {save_config,Config1} | {fail,Reason}" n
 
1313
    (erlang-skel-separator-end 2)
 
1314
    "end_per_testcase(_TestCase, _Config) ->" n >
 
1315
    "ok." n n
 
1316
 
 
1317
    (erlang-skel-separator-start 2)
 
1318
    "%% @doc" n
 
1319
    "%% Returns a list of test case group definitions." n
 
1320
    "%%" n
 
1321
    "%% Group = {GroupName,Properties,GroupsAndTestCases}" n
 
1322
    "%% GroupName = atom()" n
 
1323
    "%%   The name of the group." n
 
1324
    "%% Properties = [parallel | sequence | Shuffle | {RepeatType,N}]" n
 
1325
    "%%   Group properties that may be combined." n
 
1326
    "%% GroupsAndTestCases = [Group | {group,GroupName} | TestCase]" n
 
1327
    "%% TestCase = atom()" n
 
1328
    "%%   The name of a test case." n
 
1329
    "%% Shuffle = shuffle | {shuffle,Seed}" n
 
1330
    "%%   To get cases executed in random order." n
 
1331
    "%% Seed = {integer(),integer(),integer()}" n
 
1332
    "%% RepeatType = repeat | repeat_until_all_ok | repeat_until_all_fail |" n
 
1333
    "%%              repeat_until_any_ok | repeat_until_any_fail" n
 
1334
    "%%   To get execution of cases repeated." n
 
1335
    "%% N = integer() | forever" n
 
1336
    "%%" n
 
1337
    "%% @spec: groups() -> [Group]" n
 
1338
    (erlang-skel-separator-end 2)
 
1339
    "groups() ->" n >
 
1340
    "[]." n n
 
1341
 
 
1342
    (erlang-skel-separator-start 2)
 
1343
    "%% @doc" n 
 
1344
    "%%  Returns the list of groups and test cases that" n
 
1345
    "%%  are to be executed." n
 
1346
    "%%" n
 
1347
    "%% GroupsAndTestCases = [{group,GroupName} | TestCase]" n
 
1348
    "%% GroupName = atom()" n
 
1349
    "%%   Name of a test case group." n
 
1350
    "%% TestCase = atom()" n
 
1351
    "%%   Name of a test case." n
 
1352
    "%% Reason = term()" n
 
1353
    "%%   The reason for skipping all groups and test cases." n
 
1354
    "%%" n
 
1355
    "%% @spec all() -> GroupsAndTestCases | {skip,Reason}" n
 
1356
    (erlang-skel-separator-end 2)
 
1357
    "all() -> " n >
 
1358
    "[my_test_case]." n n
 
1359
 
 
1360
    n
 
1361
    (erlang-skel-separator-start 2)
 
1362
    "%% TEST CASES" n
 
1363
    (erlang-skel-separator 2)
 
1364
    n
 
1365
 
 
1366
    (erlang-skel-separator-start 2)
 
1367
    "%% @doc " n
 
1368
    "%%  Test case info function - returns list of tuples to set" n
 
1369
    "%%  properties for the test case." n
 
1370
    "%%" n
 
1371
    "%% Info = [tuple()]" n
 
1372
    "%%   List of key/value pairs." n
 
1373
    "%%" n
 
1374
    "%% Note: This function is only meant to be used to return a list of" n
 
1375
    "%% values, not perform any other operations." n
 
1376
    "%%" n
 
1377
    "%% @spec TestCase() -> Info " n
 
1378
    (erlang-skel-separator-end 2)
 
1379
    "my_test_case() -> " n >
 
1380
    "[]." n n
 
1381
 
 
1382
    (erlang-skel-separator 2)
 
1383
    "%% @doc Test case function. (The name of it must be specified in" n
 
1384
    "%%              the all/0 list or in a test case group for the test case" n
 
1385
    "%%              to be executed)." n
 
1386
    "%%" n
 
1387
    "%% Config0 = Config1 = [tuple()]" n
 
1388
    "%%   A list of key/value pairs, holding the test case configuration." n
 
1389
    "%% Reason = term()" n
 
1390
    "%%   The reason for skipping the test case." n
 
1391
    "%% Comment = term()" n
 
1392
    "%%   A comment about the test case that will be printed in the html log." n
 
1393
    "%%" n
 
1394
    "%% @spec TestCase(Config0) ->" n
 
1395
    "%%           ok | exit() | {skip,Reason} | {comment,Comment} |" n
 
1396
    "%%           {save_config,Config1} | {skip_and_save,Reason,Config1}" n
 
1397
    (erlang-skel-separator-end 2)
 
1398
    "my_test_case(_Config) -> " n >
 
1399
    "ok." n
 
1400
 
 
1401
    )
 
1402
 "*The template of a library module.
 
1403
 Please see the function `tempo-define-template'.")
 
1404
 
 
1405
;; Skeleton code:
 
1406
 
 
1407
;; This code is based on the package `tempo' which is part of modern
 
1408
;; Emacsen.  (GNU Emacs 19.25 (?) and XEmacs 19.14.)
 
1409
 
 
1410
(defun erlang-skel-init ()
 
1411
  "Generate the skeleton functions and menu items.
 
1412
The variable `erlang-skel' contains the name and descriptions of
 
1413
all skeletons.
 
1414
 
 
1415
The skeleton routines are based on the `tempo' package.  Should this
 
1416
package not be present, this function does nothing."
 
1417
  (interactive)
 
1418
  (condition-case nil
 
1419
      (require 'tempo)
 
1420
    (error t))
 
1421
  (if (featurep 'tempo)
 
1422
      (let ((skel erlang-skel)
 
1423
            (menu '()))
 
1424
        (while skel
 
1425
          (cond ((null (car skel))
 
1426
                 (setq menu (cons nil menu)))
 
1427
                (t
 
1428
                 (funcall (symbol-function 'tempo-define-template)
 
1429
                          (concat "erlang-" (nth 1 (car skel)))
 
1430
                          ;; The tempo template used contains an `include'
 
1431
                          ;; function call only, hence changes to the
 
1432
                          ;; variables describing the templates take effect
 
1433
                          ;; immdiately.
 
1434
                          (list (list 'erlang-skel-include (nth 2 (car skel))))
 
1435
                          (nth 1 (car skel)))
 
1436
                 (setq menu (cons (erlang-skel-make-menu-item
 
1437
                                   (car skel)) menu))))
 
1438
          (setq skel (cdr skel)))
 
1439
        (setq erlang-menu-skel-items
 
1440
              (list nil (list "Skeletons" (nreverse menu))))
 
1441
        (setq erlang-menu-items
 
1442
              (erlang-menu-add-above 'erlang-menu-skel-items
 
1443
                                     'erlang-menu-version-items
 
1444
                                     erlang-menu-items))
 
1445
        (erlang-menu-init))))
 
1446
 
 
1447
(defun erlang-skel-make-menu-item (skel)
 
1448
  (let ((func (intern (concat "tempo-template-erlang-" (nth 1 skel)))))
 
1449
    (cond ((null (nth 3 skel))
 
1450
           (list (car skel) func))
 
1451
          (t
 
1452
           (list (car skel)
 
1453
                 (list 'lambda '()
 
1454
                       '(interactive)
 
1455
                       (list 'funcall
 
1456
                             (list 'quote (nth 3 skel))
 
1457
                             (list 'quote func))))))))
 
1458
 
 
1459
;; Functions designed to be added to the skeleton menu.
 
1460
;; (Not normally used)
 
1461
(defun erlang-skel-insert (func)
 
1462
  "Insert skeleton generated by FUNC and goto first tempo mark."
 
1463
  (save-excursion (funcall func))
 
1464
  (funcall (symbol-function 'tempo-forward-mark)))
 
1465
 
 
1466
(defun erlang-skel-header (func)
 
1467
  "Insert the header generated by FUNC at the beginning of the buffer."
 
1468
  (goto-char (point-min))
 
1469
  (save-excursion (funcall func))
 
1470
  (funcall (symbol-function 'tempo-forward-mark)))
 
1471
 
 
1472
 
 
1473
;; Functions used inside the skeleton descriptions.
 
1474
(defun erlang-skel-skip-blank ()
 
1475
  (skip-chars-backward " \t")
 
1476
  nil)
 
1477
 
 
1478
(defun erlang-skel-include (&rest args)
 
1479
  "Include a template inside another template.
 
1480
 
 
1481
Example of use, assuming that `erlang-skel-func' is defined:
 
1482
 
 
1483
 (defvar foo-skeleton '(\"%%% New function:\"
 
1484
                        (erlang-skel-include erlang-skel-func)))
 
1485
 
 
1486
Technically, this function returns the `tempo' attribute`(l ...)' which
 
1487
can contain other `tempo' attributes.  Please see the function
 
1488
`tempo-define-template' for a description of the `(l ...)' attribute."
 
1489
  (let ((res '())
 
1490
        entry)
 
1491
    (while args
 
1492
      (setq entry (car args))
 
1493
      (while entry
 
1494
        (setq res (cons (car entry) res))
 
1495
        (setq entry (cdr entry)))
 
1496
      (setq args (cdr args)))
 
1497
    (cons 'l (nreverse res))))
 
1498
 
 
1499
(defun erlang-skel-separator (&optional percent)
 
1500
  "Return a comment separator."
 
1501
  (let ((percent (or percent 3)))
 
1502
    (concat (make-string percent ?%)
 
1503
            (make-string (- 70 percent) ?-)
 
1504
            "\n")))
 
1505
 
 
1506
(defun erlang-skel-separator-start (&optional percent)
 
1507
  "Return a comment separator or an empty string if separators
 
1508
are configured off."
 
1509
  (if erlang-skel-use-separators
 
1510
      (erlang-skel-separator percent)
 
1511
    ""))
 
1512
 
 
1513
(defun erlang-skel-separator-end (&optional percent)
 
1514
  "Return a comment separator to end a function comment block or an
 
1515
empty string if separators are configured off."
 
1516
  (if erlang-skel-use-separators
 
1517
      (concat "%% @end\n" (erlang-skel-separator percent))
 
1518
    ""))
 
1519
 
 
1520
(defun erlang-skel-double-separator (&optional percent)
 
1521
  "Return a double line (equals sign) comment separator."
 
1522
  (let ((percent (or percent 3)))
 
1523
    (concat (make-string percent ?%)
 
1524
            (make-string (- 70 percent) ?=)
 
1525
            "\n")))
 
1526
 
 
1527
(defun erlang-skel-double-separator-start (&optional percent)
 
1528
  "Return a double separator or a newline if separators are configured off."
 
1529
  (if erlang-skel-use-separators
 
1530
      (erlang-skel-double-separator percent)
 
1531
    "\n"))
 
1532
 
 
1533
(defun erlang-skel-double-separator-end (&optional percent)
 
1534
  "Return a double separator or an empty string if separators are
 
1535
configured off."
 
1536
  (if erlang-skel-use-separators
 
1537
      (erlang-skel-double-separator percent)
 
1538
    ""))
 
1539
 
 
1540
(defun erlang-skel-dd-mmm-yyyy ()
 
1541
  "Return the current date as a string in \"DD Mon YYYY\" form.
 
1542
The first character of DD is space if the value is less than 10."
 
1543
  (let ((date (current-time-string)))
 
1544
    (format "%2d %s %s"
 
1545
            (string-to-int (substring date 8 10))
 
1546
            (substring date 4 7)
 
1547
            (substring date -4))))
 
1548
 
 
1549
;; Local variables:
 
1550
;; coding: iso-8859-1
 
1551
;; End:
 
1552
 
 
1553
;;; erlang-skels.el ends here