~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/tools/emacs/test.erl.indented

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang -*-
2
2
%%
3
3
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 2009. All Rights Reserved.
6
 
%% 
 
4
%%
 
5
%% Copyright Ericsson AB 2009-2010. All Rights Reserved.
 
6
%%
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
9
9
%% compliance with the License. You should have received a copy of the
10
10
%% Erlang Public License along with this software. If not, it can be
11
11
%% retrieved online at http://www.erlang.org/.
12
 
%% 
 
12
%%
13
13
%% Software distributed under the License is distributed on an "AS IS"
14
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
15
%% the License for the specific language governing rights and limitations
16
16
%% under the License.
17
 
%% 
 
17
%%
18
18
%% %CopyrightEnd%
19
19
 
20
20
%%%-------------------------------------------------------------------
44
44
          b
45
45
         }).
46
46
 
 
47
-record(record3, {a = 8#42423 bor
 
48
                      8#4234,
 
49
                  b = 8#5432 
 
50
                      bor 2#1010101
 
51
                  c = 123 +
 
52
                      234,
 
53
                  d}).
 
54
 
 
55
-record(record4, {
 
56
          a = 8#42423 bor
 
57
              8#4234,
 
58
          b = 8#5432 
 
59
              bor 2#1010101
 
60
          c = 123 +
 
61
              234,
 
62
          d}).
 
63
 
 
64
 
47
65
-define(MACRO_1, macro).
48
66
-define(MACRO_2(_), macro).
49
67
 
51
69
 
52
70
-type ann() :: Var :: integer(). 
53
71
-type ann2() :: Var :: 
54
 
            'return' | 'return_white_spaces' | 'return_comments'
55
 
            | 'text' | ann(). 
 
72
            'return' 
 
73
          | 'return_white_spaces' 
 
74
          | 'return_comments'
 
75
          | 'text' | ann(). 
56
76
-type paren() :: 
57
77
        (ann2()). 
58
78
-type t1() :: atom(). 
73
93
-type t13() :: maybe_improper_list(integer(), t11()). 
74
94
-type t14() :: [erl_scan:foo() | 
75
95
                %% Should be highlighted
76
 
                non_neg_integer() | nonempty_list() | 
 
96
                term() |
 
97
                bool() |
 
98
                byte() |
 
99
                char() |
 
100
                non_neg_integer() | nonempty_list() |
 
101
                pos_integer() |
 
102
                neg_integer() |
 
103
                number() |
 
104
                list() |
77
105
                nonempty_improper_list() | nonempty_maybe_improper_list() |
 
106
                maybe_improper_list() | string() | iolist() | byte() |
 
107
                module() |
 
108
                mfa()   |
 
109
                node()  |
 
110
                timeout() |
 
111
                no_return() |
78
112
                %% Should not be highlighted
79
113
                nonempty_() | nonlist() | 
80
 
                erl_scan:bar(34, 92) | t13() | m:f(integer() | <<_:_*16>>)]. 
 
114
                erl_scan:bar(34, 92) | t13() | m:f(integer() | <<_:_*16>>)].
 
115
 
 
116
 
81
117
-type t15() :: {binary(),<<>>,<<_:34>>,<<_:_*42>>,
82
118
                <<_:3,_:_*14>>,<<>>} | [<<>>|<<_:34>>|<<_:16>>|
83
119
                                        <<_:3,_:_*1472>>|<<_:19,_:_*14>>| <<_:34>>|
89
125
               fun((nonempty_maybe_improper_list('integer', any())|
90
126
                    1|2|3|a|b|<<_:3,_:_*14>>|integer()) ->
91
127
                          nonempty_maybe_improper_list('integer', any())|
92
 
                              1|2|3|a|b|<<_:3,_:_*14>>|integer()). 
 
128
                          1|2|3|a|b|<<_:3,_:_*14>>|integer()). 
93
129
-type t20() :: [t19(), ...]. 
94
130
-type t21() :: tuple(). 
95
131
-type t21(A) :: A. 
110
146
        (t24()) -> t24() when is_subtype(t24(), atom()),
111
147
                              is_subtype(t24(), t14()),
112
148
                              is_subtype(t24(), t4()).
 
149
 
 
150
-spec over(I :: integer()) -> R1 :: foo:typen();
 
151
          (A :: atom()) -> R2 :: foo:atomen();
 
152
          (T :: tuple()) -> R3 :: bar:typen().
 
153
 
113
154
-spec mod:t2() -> any(). 
 
155
 
 
156
-spec handle_cast(Cast :: {'exchange', node(), [[name(),...]]} 
 
157
                        | {'del_member', name(), pid()},
 
158
                  #state{}) -> {'noreply', #state{}}.
 
159
 
 
160
-spec handle_cast(Cast :: 
 
161
                    {'exchange', node(), [[name(),...]]} 
 
162
                  | {'del_member', name(), pid()},
 
163
                  #state{}) -> {'noreply', #state{}}.
 
164
 
 
165
-spec all(fun((T) -> boolean()), List :: [T]) ->
 
166
                 boolean() when is_subtype(T, term()). % (*)
 
167
 
 
168
-spec get_closest_pid(term()) -> 
 
169
                             Return :: pid()
 
170
                                     | {'error', {'no_process', term()}
 
171
                                        | {'no_such_group', term()}}.
 
172
 
114
173
-opaque attributes_data() :: 
115
174
          [{'column', column()} | {'line', info_line()} |
116
175
           {'text', string()}] |  {line(),column()}.   
129
188
          f19 = 3 :: integer()|undefined,
130
189
          f5 = 3 :: undefined|integer()}). 
131
190
 
 
191
-record(state, {
 
192
          sequence_number = 1          :: integer()
 
193
         }).
132
194
 
133
195
 
134
196
highlighting(X)                   % Function definitions should be highlighted
277
339
      c
278
340
    ),
279
341
 
280
 
 
 
342
    call(2#42423 bor 
 
343
             #4234,
 
344
         2#5432,
 
345
         other_arg),
281
346
    ok;
282
347
indent_basics(Xlongname, 
283
348
              #struct{a=Foo,
305
370
    foo.
306
371
 
307
372
 
 
373
 
 
374
indent_nested() ->
 
375
    [
 
376
     {foo, 2, "string"},
 
377
     {bar, 3, "another string"}
 
378
    ].
 
379
 
 
380
 
308
381
indent_icr(Z) ->                                % icr = if case receive
309
382
    %% If
310
383
    if Z >= 0 ->
359
432
            X = 43 div 4,
360
433
            foo(X) 
361
434
    end,
362
 
    receive 
 
435
    receive
363
436
        {Z,_,_} ->
364
437
            X = 43 div 4,
365
438
            foo(X);
439
512
        file:close(Xfile)
440
513
    end;
441
514
indent_try_catch() ->
442
 
    try foo(bar) of
 
515
    try
 
516
        foo(bar)
 
517
    of
443
518
        X when true andalso
444
519
               kalle ->
445
520
            io:format(stdout, "Parsing file ~s, ",
491
566
    B = catch oskar(X),
492
567
 
493
568
    A = catch (baz + 
494
 
               bax),
 
569
                   bax),
495
570
    catch foo(),
496
571
 
497
572
    C = catch B + 
498
573
        float(43.1),
499
574
 
500
 
    case catch (X) of 
501
 
        A ->
502
 
            B
503
 
    end,
 
575
    case catch foo(X) of
 
576
        A ->
 
577
            B
 
578
    end,
 
579
 
 
580
    case
 
581
        catch foo(X)
 
582
    of
 
583
        A ->
 
584
            B
 
585
    end,
 
586
 
 
587
    case
 
588
        foo(X)
 
589
    of
 
590
        A ->
 
591
            catch B,
 
592
            X
 
593
    end,
 
594
 
504
595
    try sune of
505
596
        _ -> foo
506
597
    catch _:_ -> baf
507
 
    end.
 
598
    end,
 
599
 
 
600
    try
 
601
        sune
 
602
    of
 
603
        _ ->
 
604
            X = 5,
 
605
            (catch foo(X)),
 
606
            X + 10
 
607
    catch _:_ -> baf
 
608
    end,
 
609
 
 
610
    try
 
611
        (catch sune)
 
612
    of
 
613
        _ ->
 
614
            catch foo()  %% BUGBUG can't handle catch inside try without parentheses
 
615
    catch _:_ ->
 
616
            baf
 
617
    end,
 
618
 
 
619
    try
 
620
        (catch exit())
 
621
    catch
 
622
        _ ->
 
623
            catch baf()
 
624
    end,
 
625
    ok.
508
626
 
509
627
indent_binary() ->
510
628
    X = lists:foldr(fun(M) ->
534
652
                            true = (X rem 2)
535
653
              >>,
536
654
    ok.
 
655
 
 
656
%% This causes an error in earlier erlang-mode versions.
 
657
foo() ->
 
658
    [#foo{
 
659
        foo = foo}].