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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/digraph.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
43
43
 
44
44
%%
45
45
%% Type is a list of
46
 
%%  protected | private | public
 
46
%%  protected | private
47
47
%%  acyclic | cyclic
48
48
%%
49
49
%%  default is [cyclic,protected]
74
74
    check_type(Ts, protected, L);
75
75
check_type([private | Ts], _, L) ->
76
76
    check_type(Ts, private, L);
77
 
check_type([public | Ts], _, L) ->
78
 
    check_type(Ts, public, L);
79
77
check_type([T | _], _, _) -> 
80
78
    {error, {unknown_type, T}};
81
79
check_type([], A, L) -> {A,L}.
117
115
add_vertex(G, V) -> 
118
116
    do_add_vertex({V,[]}, G).
119
117
 
120
 
add_vertex(G, V, D) -> 
 
118
add_vertex(G, V, D) ->
121
119
    do_add_vertex({V,D}, G).
122
120
 
123
121
del_vertex(G, V) ->
150
148
in_neighbours(G,V) ->
151
149
    ET = G#graph.etab,
152
150
    NT = G#graph.ntab,
153
 
    collect_elems(ets:lookup(NT,{in,V}),ET,2).
 
151
    collect_elems(ets:lookup(NT,{in,V}), ET, 2).
154
152
 
155
153
in_edges(G, V) ->
156
154
    ets:select(G#graph.ntab, [{{{in,V},'$1'},[],['$1']}]).
161
159
out_neighbours(G, V) -> 
162
160
    ET = G#graph.etab,
163
161
    NT = G#graph.ntab,
164
 
    collect_elems(ets:lookup(NT,{out,V}),ET,3).
 
162
    collect_elems(ets:lookup(NT,{out,V}), ET, 3).
165
163
 
166
164
out_edges(G, V) -> 
167
165
    ets:select(G#graph.ntab, [{{{out,V},'$1'},[],['$1']}]).
223
221
%% Collect elements for a index in a tuple
224
222
%%
225
223
collect_elems(Keys, Table, Index) ->
226
 
    collect_elems(Keys, Table, Index,[]).
 
224
    collect_elems(Keys, Table, Index, []).
227
225
 
228
226
collect_elems([{_,Key}|Keys], Table, Index, Acc) ->
229
227
    collect_elems(Keys, Table, Index,
252
250
do_del_vertices([V | Vs], G) ->
253
251
    do_del_vertex(V, G),
254
252
    do_del_vertices(Vs, G);
255
 
do_del_vertices([], _) -> true.
256
 
 
 
253
do_del_vertices([], #graph{}) -> true.
257
254
 
258
255
do_del_vertex(V, G) ->
259
256
    do_del_nedges(ets:lookup(G#graph.ntab, {in,V}), G),
260
257
    do_del_nedges(ets:lookup(G#graph.ntab, {out,V}), G),
261
258
    ets:delete(G#graph.vtab, V).
262
 
 
263
259
 
264
260
do_del_nedges([{_,E} | Ns], G) ->
265
261
    case ets:lookup(G#graph.etab, E) of
269
265
        [] ->
270
266
            do_del_nedges(Ns, G)
271
267
    end;
272
 
do_del_nedges([], _) -> true.
 
268
do_del_nedges([], #graph{}) -> true.
273
269
 
274
270
%%
275
271
%% Delete edges
282
278
        [] ->
283
279
            do_del_edges(Es, G)
284
280
    end;
285
 
do_del_edges([], _) -> true.
 
281
do_del_edges([], #graph{}) -> true.
286
282
 
287
283
do_del_edge(E,V1,V2,G) ->
288
284
    ets:select_delete(G#graph.ntab, [{{{in,V2},E},[],[true]},
292
288
rm_edges([V1,V2|Vs], G) ->
293
289
    rm_edge(V1,V2,G),
294
290
    rm_edges([V2|Vs],G);
295
 
rm_edges(_,_) -> true.
 
291
rm_edges(_, _) -> true.
296
292
 
297
293
rm_edge(V1,V2,G) ->
298
294
    Ns = ets:lookup(G#graph.ntab,{out,V1}),
306
302
        _ ->
307
303
            rm_edge_0(Es,V1,V2,G)
308
304
    end;
309
 
rm_edge_0([],_,_,_) -> ok.
 
305
rm_edge_0([],_,_,#graph{}) -> ok.
310
306
    
311
307
%%
312
308
%% Check that endpoints exists
360
356
%%
361
357
 
362
358
get_cycle(G, V) ->
363
 
    case one_path(out_neighbours(G,V), V, [], [V], [V], {2,infinity}, G, 1) of
 
359
    case one_path(out_neighbours(G,V), V, [], [V], [V], 2, G, 1) of
364
360
        false ->
365
361
            case lists:member(V, out_neighbours(G, V)) of
366
362
                true -> [V];
376
372
%%
377
373
 
378
374
get_path(G, V1, V2) ->
379
 
    one_path(out_neighbours(G, V1), V2, [], [V1], [V1], {1,infinity}, G, 1).
 
375
    one_path(out_neighbours(G, V1), V2, [], [V1], [V1], 1, G, 1).
380
376
 
381
377
%%
382
 
%% prune_path (evaluate conditions on path)
383
 
%% long  : if path is too long
384
 
%% short : if path is to short
 
378
%% prune_short_path (evaluate conditions on path)
 
379
%% short : if path is too short
385
380
%% ok    : if path is ok
386
381
%%
387
 
prune_path(Counter, {Min,_Max}) when Counter < Min ->
 
382
prune_short_path(Counter, Min) when Counter < Min ->
388
383
    short;
389
 
prune_path(_Counter, {_Min,Max}) when Max =:= infinity ->
390
 
    ok;
391
 
prune_path(Counter, {_Min,Max}) when Counter > Max ->
392
 
    long;
393
 
prune_path(_Counter, {_Min, _Max}) ->
 
384
prune_short_path(_Counter, _Min) ->
394
385
    ok.
395
386
 
396
387
one_path([W|Ws], W, Cont, Xs, Ps, Prune, G, Counter) ->
397
 
    case prune_path(Counter, Prune) of
398
 
        long  -> one_path([], W, Cont, Xs, Ps, Prune, G, Counter);
 
388
    case prune_short_path(Counter, Prune) of
399
389
        short -> one_path(Ws, W, Cont, Xs, Ps, Prune, G, Counter);
400
390
        ok -> lists:reverse([W|Ps])
401
391
    end;
402
392
one_path([V|Vs], W, Cont, Xs, Ps, Prune, G, Counter) ->
403
 
    case prune_path(Counter, Prune) of
404
 
        long -> one_path([], W, Cont, Xs, Ps, Prune, G, Counter);
405
 
        _ ->
406
 
            case lists:member(V, Xs) of
407
 
                true ->  one_path(Vs, W, Cont, Xs, Ps, Prune, G, Counter);
408
 
                false -> one_path(out_neighbours(G, V), W, 
409
 
                                  [{Vs,Ps} | Cont], [V|Xs], [V|Ps], 
410
 
                                  Prune, G, Counter+1)
411
 
            end
 
393
    case lists:member(V, Xs) of
 
394
        true ->  one_path(Vs, W, Cont, Xs, Ps, Prune, G, Counter);
 
395
        false -> one_path(out_neighbours(G, V), W, 
 
396
                          [{Vs,Ps} | Cont], [V|Xs], [V|Ps], 
 
397
                          Prune, G, Counter+1)
412
398
    end;
413
399
one_path([], W, [{Vs,Ps}|Cont], Xs, _, Prune, G, Counter) ->
414
400
    one_path(Vs, W, Cont, Xs, Ps, Prune, G, Counter-1);