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

« back to all changes in this revision

Viewing changes to lib/dialyzer/test/opaque_SUITE_data/src/wings/wings_edge_cmd.erl

  • 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:
 
1
%%
 
2
%%  wings_edge.erl --
 
3
%%
 
4
%%     This module contains most edge command and edge utility functions.
 
5
%%
 
6
 
 
7
-module(wings_edge_cmd).
 
8
 
 
9
-export([loop_cut/1]).
 
10
 
 
11
-include("wings.hrl").
 
12
 
 
13
%%%
 
14
%%% The Loop Cut command.
 
15
%%%
 
16
 
 
17
loop_cut(St0) ->
 
18
    {Sel,St} = wings_sel:fold(fun loop_cut/3, {[],St0}, St0),
 
19
    wings_sel:set(body, Sel, St).
 
20
 
 
21
loop_cut(Edges, #we{name=Name,id=Id,fs=Ftab}=We0, {Sel,St0}) ->
 
22
    AdjFaces = wings_face:from_edges(Edges, We0),
 
23
    case loop_cut_partition(AdjFaces, Edges, We0, []) of
 
24
        [_] ->
 
25
            io:format("Edge loop doesn't divide ~p into two parts.", [Name]);
 
26
        Parts0 ->
 
27
            %% We arbitrarily decide that the largest part of the object
 
28
            %% will be left unselected and will keep the name of the object.
 
29
 
 
30
            Parts1 = [{gb_trees:size(P),P} || P <- Parts0],
 
31
            Parts2 = lists:reverse(lists:sort(Parts1)),
 
32
            [_|Parts] = [gb_sets:to_list(P) || {_,P} <- Parts2],
 
33
 
 
34
            %% Also, this first part will also contain any sub-object
 
35
            %% that was not reachable from any of the edges. Therefore,
 
36
            %% we calculate the first part as the complement of the union
 
37
            %% of all other parts.
 
38
 
 
39
            FirstComplement = ordsets:union(Parts),
 
40
            First = ordsets:subtract(gb_trees:keys(Ftab), FirstComplement),
 
41
 
 
42
            We = wings_dissolve:complement(First, We0),
 
43
            Shs = St0#st.shapes,
 
44
            St = St0#st{shapes=gb_trees:update(Id, We, Shs)},
 
45
            loop_cut_make_copies(Parts, We0, Sel, St)
 
46
    end.
 
47
 
 
48
loop_cut_make_copies([P|Parts], We0, Sel0, #st{onext=Id}=St0) ->
 
49
    Sel = [{Id,gb_sets:singleton(0)}|Sel0],
 
50
    We = wings_dissolve:complement(P, We0),
 
51
    St = wings_shape:insert(We, cut, St0),
 
52
    loop_cut_make_copies(Parts, We0, Sel, St);
 
53
loop_cut_make_copies([], _, Sel, St) -> {Sel,St}.
 
54
 
 
55
loop_cut_partition(Faces0, Edges, We, Acc) ->
 
56
    case gb_sets:is_empty(Faces0) of
 
57
        true -> Acc;
 
58
        false ->
 
59
            {AFace,Faces1} = gb_sets:take_smallest(Faces0),
 
60
            Reachable = collect_faces(AFace, Edges, We),
 
61
            Faces = gb_sets:difference(Faces1, Reachable),
 
62
            loop_cut_partition(Faces, Edges, We, [Reachable|Acc])
 
63
    end.
 
64
 
 
65
collect_faces(Face, Edges, We) ->
 
66
    collect_faces(gb_sets:singleton(Face), We, Edges, gb_sets:empty()).
 
67
 
 
68
collect_faces(Work0, We, Edges, Acc0) ->
 
69
    case gb_sets:is_empty(Work0) of
 
70
        true -> Acc0;
 
71
        false ->
 
72
            {Face,Work1} = gb_sets:take_smallest(Work0),
 
73
            Acc = gb_sets:insert(Face, Acc0),
 
74
            Work = collect_maybe_add(Work1, Face, Edges, We, Acc),
 
75
            collect_faces(Work, We, Edges, Acc)
 
76
    end.
 
77
 
 
78
collect_maybe_add(Work, Face, Edges, We, Res) ->
 
79
    wings_face:fold(
 
80
      fun(_, Edge, Rec, A) ->
 
81
              case gb_sets:is_member(Edge, Edges) of
 
82
                  true -> A;
 
83
                  false ->
 
84
                      Of = wings_face:other(Face, Rec),
 
85
                      case gb_sets:is_member(Of, Res) of
 
86
                          true -> A;
 
87
                          false -> gb_sets:add(Of, A)
 
88
                      end
 
89
              end
 
90
      end, Work, Face, We).