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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/user_tests_SUITE_data/src/broken_dialyzer.erl

  • 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
-module(broken_dialyzer).
 
2
 
 
3
-export([do_move_next/1]).
 
4
 
 
5
-define(ap_indices, 512).
 
6
-define(dp_indices, 504).
 
7
 
 
8
 
 
9
-record(apR,{a,c=[],n=[],nc=0,nn=0,nl=[]}).
 
10
-define(apL(L), [#apR{a=A} || A <- L]).
 
11
 
 
12
-define(gr, get(my_return_value)).
 
13
-define(pr(PR), put(my_return_value, PR)).
 
14
-record(bit,{i,c,n,s}).           % index, current, next, state
 
15
 
 
16
 
 
17
do_move_next({BL,AL}) ->
 
18
    Max = max(length(BL), length(AL)),
 
19
    Max2 = max(length(BL)*2, length(AL)),
 
20
    MoveTo = [A || A <- AL, A#apR.nn < Max, A#apR.nn+A#apR.nc < Max2],
 
21
    MoveFrom = [A || A <- AL,
 
22
                     (A#apR.nn > Max) orelse (A#apR.nn+A#apR.nc > Max2)],
 
23
    Unchanged = (AL--MoveTo)--MoveFrom,
 
24
    {BL1,{AL1,{AL2,AL3}}} =
 
25
        lists:mapfoldl(
 
26
          fun(B=#bit{i=I,c=C,s=S,n=Next}, {From,{To,FilledUp}})
 
27
             when S==ok;S==lost_replica;S==moved_replica ->
 
28
                  case lists:keysearch(Next,#apR.a,From) of
 
29
                      {value, F=#apR{n=N1,nn=NN1,nc=NC1}}
 
30
                      when (NN1>Max) or (NN1+NC1>Max2) ->
 
31
                          case C of
 
32
                              [] ->
 
33
                                  {B, {From,{To,FilledUp}}};
 
34
                              ShortList ->
 
35
                                  T=#apR{a=NewNext,n=N2,nn=NN2} =
 
36
                                      find_next(Next,ShortList),
 
37
                                  {value, {C,NL_from}} =
 
38
                                      lists:keysearch(C,1,F#apR.nl),
 
39
                                  {value, {C,NL_to}} =
 
40
                                      lists:keysearch(C,1,T#apR.nl),
 
41
                                  NewNL_from = lists:keyreplace(
 
42
                                                 C,1,F#apR.nl,{C,NL_from--[I]}),
 
43
                                  NewNL_to = lists:keyreplace(
 
44
                                               C,1,T#apR.nl,{C,[I|NL_to]}),
 
45
 
 
46
                                  NewT = T#apR{n=[I|N2],nn=NN2+1,
 
47
                                               nl=NewNL_to},
 
48
 
 
49
                                  {B#bit{n=NewNext,
 
50
                                         s = if
 
51
                                                 S == lost_replica ->
 
52
                                                     lost_replica;
 
53
                                                 true ->
 
54
                                                     moved_replica
 
55
                                             end},
 
56
                                   {lists:keyreplace(
 
57
                                      Next,#apR.a,From,
 
58
                                      F#apR{n=N1--[I],nn=NN1-1,nl=NewNL_from}),
 
59
                                    if
 
60
                                        (NewT#apR.nn+NewT#apR.nc >= Max2)
 
61
                                        or (NewT#apR.nn >= Max) ->
 
62
                                            {lists:keydelete(NewNext,#apR.a,To),
 
63
                                             [NewT|FilledUp]};
 
64
                                        true ->
 
65
                                            {lists:keyreplace(
 
66
                                               NewNext,#apR.a,To,NewT),
 
67
                                             FilledUp}
 
68
                                    end}}
 
69
                          end;
 
70
                      _ ->
 
71
                          {B, {From,{To,FilledUp}}}
 
72
                  end;
 
73
             (B, A) ->
 
74
                  {B, A}
 
75
          end, {MoveFrom,{MoveTo,[]}},BL),
 
76
    {BL1,Unchanged++AL1++AL2++AL3}.
 
77
 
 
78
%%% -----------------------------------------------------------------
 
79
%%% find_next/2
 
80
%%%
 
81
%%% ------------------------------------------------------------------
 
82
 
 
83
find_next(Ap,L) ->
 
84
    hd(catch
 
85
       lists:foreach(
 
86
         fun(SelVal) ->
 
87
                 case [ApR ||
 
88
                          ApR <- L,
 
89
                          begin
 
90
                              {value,{Ap,NL}} =
 
91
                                  lists:keysearch(Ap,1,ApR#apR.nl),
 
92
                              length(NL) =< SelVal
 
93
                          end] of
 
94
                     [] ->
 
95
                         ok;
 
96
                     ShortList ->
 
97
                         throw(ShortList)
 
98
                 end
 
99
         end,
 
100
         lists:seq(0,?ap_indices))).
 
101
 
 
102
%%% -----------------------------------------------------------------
 
103
%%% max/2
 
104
%%%
 
105
%%% Calculates max number of indices per AP, given number of indices
 
106
%%% and number of APs.
 
107
%%% -----------------------------------------------------------------
 
108
max(F,S) ->
 
109
    (F div S) + if
 
110
                    (F rem S) == 0 ->
 
111
                        0;
 
112
                    true ->
 
113
                        1
 
114
                end.
 
115
 
 
116
%%% ==============================================================
 
117
%%%      ADMINISTRATIVE INFORMATION
 
118
%%% ==============================================================
 
119
%%% #Copyright (C) 2005
 
120
%%% by ERICSSON TELECOM AB
 
121
%%% S - 125 26  STOCKHOLM
 
122
%%% SWEDEN, tel int + 46 8 719 0000
 
123
%%% 
 
124
%%% The program may be used and/or copied only with the written 
 
125
%%% permission from ERICSSON TELECOM AB, or in accordance with 
 
126
%%% the terms and conditions stipulated in the agreement/contract 
 
127
%%% under which the program has been supplied.
 
128
%%%   
 
129
%%% All rights reserved
 
130
%%%