0024428: Implementation of LGPL license
[occt.git] / src / BRepFill / BRepFill_CompatibleWires.cxx
1 // Created on: 1998-07-02
2 // Created by: Joelle CHAUVET
3 // Copyright (c) 1998-1999 Matra Datavision
4 // Copyright (c) 1999-2014 OPEN CASCADE SAS
5 //
6 // This file is part of Open CASCADE Technology software library.
7 //
8 // This library is free software; you can redistribute it and / or modify it
9 // under the terms of the GNU Lesser General Public version 2.1 as published
10 // by the Free Software Foundation, with special exception defined in the file
11 // OCCT_LGPL_EXCEPTION.txt. Consult the file LICENSE_LGPL_21.txt included in OCCT
12 // distribution for complete text of the license and disclaimer of any warranty.
13 //
14 // Alternatively, this file may be used under the terms of Open CASCADE
15 // commercial license or contractual agreement.
16
17 #include <BRepFill_CompatibleWires.ixx>
18
19 #include <BRepAdaptor_Curve.hxx>
20
21 #include <BRepFill.hxx>
22 #include <BRepLib.hxx>
23 #include <BRepLib_FindSurface.hxx>
24 #include <BRepLib_MakeWire.hxx>
25 #include <BRepLib_MakeEdge.hxx>
26 #include <BRepCheck_Wire.hxx>
27 #include <BRepExtrema_DistShapeShape.hxx>
28 #include <Bnd_Box.hxx>
29 #include <BRepBndLib.hxx>
30 #include <BRep_Builder.hxx>
31 #include <BRep_Tool.hxx>
32 #include <BRepTools_WireExplorer.hxx>
33 #include <BRepLProp.hxx>
34 #include <BRepGProp.hxx>
35 #include <GProp_GProps.hxx>
36 #include <GProp_PrincipalProps.hxx>
37 #include <Geom_Surface.hxx>
38 #include <Geom_Plane.hxx>
39 #include <Precision.hxx>
40 #include <TopAbs.hxx> 
41 #include <TopExp.hxx>
42 #include <TopExp_Explorer.hxx>
43 #include <TopoDS.hxx>
44 #include <TopoDS_Wire.hxx>
45 #include <TopTools_ListIteratorOfListOfShape.hxx>
46 #include <TopTools_DataMapOfShapeListOfShape.hxx>
47 #include <TopTools_IndexedDataMapOfShapeListOfShape.hxx>
48 #include <TopTools_DataMapIteratorOfDataMapOfShapeListOfShape.hxx>
49 #include <TopTools_HSequenceOfShape.hxx>
50 #include <TopTools_SequenceOfShape.hxx>
51 #include <TopTools_ListOfShape.hxx>    
52
53 #include <gp.hxx>
54 #include <gp_Vec.hxx>
55 #include <gp_Ax2.hxx>
56 #include <gp_Pln.hxx>
57 #include <gp_Circ.hxx>
58 #include <gp_Elips.hxx>
59 #include <TColgp_HArray1OfVec.hxx>
60 #include <TColgp_HArray1OfPnt.hxx>
61
62 #include <TColStd_Array1OfInteger.hxx>
63 #include <TColStd_Array1OfReal.hxx>
64 #include <TColStd_SequenceOfReal.hxx>
65
66 #ifdef DEB_EFV
67 static void EdgesFromVertex (const TopoDS_Wire&   W,
68                              const TopoDS_Vertex& V, 
69                              TopoDS_Edge& E1, 
70                              TopoDS_Edge& E2)
71 {
72   TopTools_IndexedDataMapOfShapeListOfShape Map;
73   TopExp::MapShapesAndAncestors(W,TopAbs_VERTEX,TopAbs_EDGE,Map);
74
75   const TopTools_ListOfShape& List = Map.FindFromKey(V);
76   TopoDS_Edge          e1   = TopoDS::Edge(List.First());
77   TopoDS_Edge          e2   = TopoDS::Edge(List. Last());
78
79   BRepTools_WireExplorer anExp;
80   Standard_Integer I1=0, I2=0, NE=0;
81
82   for(anExp.Init(W); anExp.More(); anExp.Next()) {
83     NE++;
84     const TopoDS_Edge& ECur = anExp.Current();
85     if (e1.IsSame(ECur)) {
86       I1 = NE;
87     }
88     if (e2.IsSame(ECur)) {
89       I2 = NE;
90     }
91   }
92
93   if (Abs(I2-I1)==1) {
94     // consecutive numbers
95     if (I2==I1+1) {
96       E1 = e1;
97       E2 = e2;
98     }
99     else {
100       E1 = e2;
101       E2 = e1;
102     }
103   }
104   else {
105     // non consecutive numbers on a closed wire
106     if (I1==1&&I2==NE) {
107       E1 = e2;
108       E2 = e1;
109     }
110     else {
111       E1 = e1;
112       E2 = e2;
113     }
114   }
115 }
116                                       
117 #endif
118 static void SeqOfVertices (const TopoDS_Wire&   W,
119                            TopTools_SequenceOfShape& S)
120 {
121   S.Clear();
122   Standard_Integer jj, cpt = 0;
123   TopExp_Explorer PE;
124   for (PE.Init(W,TopAbs_VERTEX); PE.More(); PE.Next()) {
125     cpt++;
126     Standard_Boolean trouve=Standard_False;
127     for (jj=1;jj<=S.Length() && (!trouve);jj++) {
128       if (S.Value(jj).IsSame(PE.Current())) trouve = Standard_True; 
129       }
130       if (!trouve) S.Append(PE.Current());
131     }
132 }
133                                       
134
135 static Standard_Boolean PlaneOfWire (const TopoDS_Wire& W, gp_Pln& P)
136 {
137   Standard_Boolean isplane = Standard_True;
138   BRepLib_FindSurface findPlanarSurf;
139   Handle(Geom_Surface) S;
140   TopLoc_Location      L;
141   
142   GProp_GProps GP;
143   BRepGProp::LinearProperties(W,GP);
144   gp_Pnt Bary = GP.CentreOfMass();
145
146 // shielding for particular cases : only one edge circle or ellipse
147 // on a closed wire !
148   Standard_Integer nbEdges = 0;
149   BRepTools_WireExplorer anExp;
150   anExp.Init(W);
151   Standard_Boolean wClosed = W.Closed();
152   if (!wClosed) {
153     // it is checked if the vertices are the same.
154     TopoDS_Vertex V1, V2;
155     TopExp::Vertices(W,V1,V2);
156     if ( V1.IsSame(V2)) wClosed = Standard_True;
157   }
158   TopoDS_Edge Edge = TopoDS::Edge(anExp.Current());
159   Standard_Real first, last;
160   TopLoc_Location loc;
161   Handle(Geom_Curve) curv;
162   curv = BRep_Tool::Curve(Edge, loc, first, last);
163   curv = 
164       Handle(Geom_Curve)::DownCast(curv->Transformed(loc.Transformation()));
165   if (wClosed) {
166     GeomAdaptor_Curve AdC;
167     AdC.Load(curv);
168     for(; anExp.More(); anExp.Next()) {
169       nbEdges ++;
170     }
171     if ( nbEdges==1 && AdC.GetType() == GeomAbs_Circle ) {
172       Bary = AdC.Circle().Location();
173     }
174     if ( nbEdges==1 && AdC.GetType() == GeomAbs_Ellipse ) {
175       Bary = AdC.Ellipse().Location();
176     }
177   }
178
179   findPlanarSurf.Init(W, -1, Standard_True);
180   if ( findPlanarSurf.Found()) {
181     S = findPlanarSurf.Surface();
182     L = findPlanarSurf.Location();
183     if (!L.IsIdentity()) S = Handle(Geom_Surface)::
184       DownCast(S->Transformed(L.Transformation()));
185     P = (Handle(Geom_Plane)::DownCast(S))->Pln();
186     P.SetLocation(Bary);
187   }
188   else {
189     // wire not plane !
190     GProp_PrincipalProps Pp  = GP.PrincipalProperties();
191     gp_Vec Vec;
192     Standard_Real R1, R2, R3,Tol = Precision::Confusion();
193     Pp.RadiusOfGyration(R1,R2,R3);
194     Standard_Real RMax = Max(Max(R1,R2),R3);
195     if ( ( Abs(RMax-R1)<Tol && Abs(RMax-R2)<Tol )
196         || ( Abs(RMax-R1)<Tol && Abs(RMax-R3)<Tol ) 
197         || ( Abs(RMax-R2)<Tol && Abs(RMax-R3)<Tol ) )
198       isplane = Standard_False;
199     else {
200       if (R1>=R2 && R1>=R3) {
201         Vec = Pp.FirstAxisOfInertia();
202       }
203       else if (R2>=R1 && R2>=R3) {
204         Vec = Pp.SecondAxisOfInertia();
205       }
206       else if (R3>=R1 && R3>=R2) {
207         Vec = Pp.ThirdAxisOfInertia();
208       }
209       gp_Dir NDir(Vec);
210       if (R3<=R2 && R3<=R1) {
211         Vec = Pp.ThirdAxisOfInertia();
212       }
213       else if (R2<=R1 && R2<=R3) {
214         Vec = Pp.SecondAxisOfInertia();
215       }
216       else if (R1<=R2 && R1<=R3) {
217         Vec = Pp.FirstAxisOfInertia();
218       }
219       gp_Dir XDir(Vec);
220       gp_Ax3 repere(Bary,NDir,XDir);
221       Geom_Plane GPlan(repere);
222       P = GPlan.Pln();
223     }
224   }
225
226   return isplane;
227
228 }
229                                       
230
231 static void WireContinuity (const TopoDS_Wire& W,
232                             GeomAbs_Shape& contW)
233 {
234   contW = GeomAbs_CN;
235   GeomAbs_Shape cont;
236   Standard_Boolean IsDegenerated = Standard_False;
237
238   BRepTools_WireExplorer anExp;
239   Standard_Integer nbEdges=0;
240   Handle(TopTools_HSequenceOfShape) Edges = new TopTools_HSequenceOfShape();
241   for(anExp.Init(W); anExp.More(); anExp.Next()) {
242     nbEdges++;
243     Edges->Append(anExp.Current());
244     if (BRep_Tool::Degenerated(anExp.Current())) IsDegenerated = Standard_True;
245   }
246   
247   if (!IsDegenerated) {
248
249     Standard_Boolean testconti = Standard_True;
250
251     for (Standard_Integer j=1;j<=nbEdges;j++) {
252       
253       TopoDS_Edge Edge1, Edge2;
254       
255       if (j == nbEdges) {
256         Edge1 = TopoDS::Edge (Edges->Value(nbEdges));
257         Edge2 = TopoDS::Edge (Edges->Value(1));
258       }
259       else {
260         Edge1 = TopoDS::Edge (Edges->Value(j));
261         Edge2 = TopoDS::Edge (Edges->Value(j+1));
262       } 
263       
264       TopoDS_Vertex V1,V2,Vbid;
265       TopExp::Vertices(Edge1,Vbid,V1,Standard_True);
266       TopExp::Vertices(Edge2,V2,Vbid,Standard_True);
267       Standard_Real U1 = BRep_Tool::Parameter(V1,Edge1);
268       Standard_Real U2 = BRep_Tool::Parameter(V2,Edge2);
269       BRepAdaptor_Curve Curve1(Edge1);
270       BRepAdaptor_Curve Curve2(Edge2);
271       Standard_Real Eps = BRep_Tool::Tolerance(V2) + BRep_Tool::Tolerance(V1);
272       
273       if(j == nbEdges) 
274         testconti = Curve1.Value(U1).IsEqual(Curve2.Value(U2), Eps);
275       
276       if(testconti) {
277         cont = BRepLProp::Continuity(Curve1,Curve2,U1,U2,
278                                      Eps, Precision::Angular()); 
279         if (cont <= contW) contW = cont;
280       }
281     }
282   }
283   
284 }
285
286 static void TrimEdge (const TopoDS_Edge&              CurrentEdge,
287                       const TColStd_SequenceOfReal&   CutValues,
288                       const Standard_Real   t0, const Standard_Real   t1,
289                       const Standard_Boolean          SeqOrder,
290                       TopTools_SequenceOfShape& S)
291
292 {
293   S.Clear();
294   Standard_Integer j, ndec=CutValues.Length();
295   Standard_Real first,last,m0,m1;
296   Handle(Geom_Curve) C = BRep_Tool::Curve(CurrentEdge,first,last);
297
298   TopoDS_Vertex Vf,Vl,Vbid,V0,V1;
299   TopAbs_Orientation CurrentOrient = CurrentEdge.Orientation();
300   TopExp::Vertices(CurrentEdge,Vf,Vl);
301   Vbid.Nullify();
302
303   if (SeqOrder) {
304     // from first to last
305     m0 = first;
306     V0 = Vf;
307     for (j=1; j<=ndec; j++) {
308       // piece of edge  
309       m1 = (CutValues.Value(j)-t0)*(last-first)/(t1-t0)+first;
310       TopoDS_Edge CutE = BRepLib_MakeEdge(C,V0,Vbid,m0,m1);
311       CutE.Orientation(CurrentOrient);
312       S.Append(CutE);
313       m0 = m1;
314       V0 = TopExp::LastVertex(CutE);
315       if (j==ndec) {
316         // last piece
317         TopoDS_Edge LastE = BRepLib_MakeEdge(C,V0,Vl,m0,last);
318         LastE.Orientation(CurrentOrient);
319         S.Append(LastE);
320       }
321     }
322   }
323   else {
324     // from last to first
325     m1 = last;
326     V1 = Vl;
327     for (j=ndec; j>=1; j--) {
328       // piece of edge  
329       m0 = (CutValues.Value(j)-t0)*(last-first)/(t1-t0)+first;
330       TopoDS_Edge CutE = BRepLib_MakeEdge(C,Vbid,V1,m0,m1);
331       CutE.Orientation(CurrentOrient);
332       S.Append(CutE);
333       m1 = m0;
334       V1 = TopExp::FirstVertex(CutE);
335       if (j==1) {
336         // last piece
337         TopoDS_Edge LastE = BRepLib_MakeEdge(C,Vf,V1,first,m1);
338         LastE.Orientation(CurrentOrient);
339         S.Append(LastE);
340       }
341     }
342   }
343 }
344
345
346
347 static Standard_Boolean SearchRoot (const TopoDS_Vertex& V,
348                                     const TopTools_DataMapOfShapeListOfShape& Map,
349                                     TopoDS_Vertex& VRoot)
350 {
351   Standard_Boolean trouve = Standard_False;
352   VRoot.Nullify();
353   TopTools_DataMapIteratorOfDataMapOfShapeListOfShape it;
354   for (it.Initialize(Map); it.More(); it.Next()) {
355     const TopTools_ListOfShape & List = it.Value();
356     TopTools_ListIteratorOfListOfShape itL;
357     Standard_Boolean ilyest = Standard_False;
358     for (itL.Initialize(List); itL.More(); itL.Next()) {
359       TopoDS_Vertex Vcur = TopoDS::Vertex(itL.Value());
360       if (Vcur.IsSame(V)) {
361         ilyest = Standard_True;
362       }
363       if (ilyest) break;
364     }
365     if (ilyest) {
366       trouve = Standard_True;
367       VRoot = TopoDS::Vertex(it.Key());
368     }
369     if (trouve) break;
370   }
371   return trouve;
372 }
373
374 static Standard_Boolean SearchVertex (const TopTools_ListOfShape& List,
375                                       const TopoDS_Wire&   W,
376                                       TopoDS_Vertex& VonW)
377 {
378   Standard_Boolean trouve = Standard_False;
379   VonW.Nullify();
380   TopTools_SequenceOfShape SeqV;
381   SeqOfVertices(W,SeqV);
382   for (Standard_Integer ii=1;ii<=SeqV.Length();ii++) {
383     TopoDS_Vertex Vi = TopoDS::Vertex(SeqV.Value(ii));
384     TopTools_ListIteratorOfListOfShape itL;
385     Standard_Boolean ilyest = Standard_False;
386     for (itL.Initialize(List); itL.More(); itL.Next()) {
387       TopoDS_Vertex Vcur = TopoDS::Vertex(itL.Value());
388       if (Vcur.IsSame(Vi)) {
389         ilyest = Standard_True;
390       }
391       if (ilyest) break;
392     }
393     if (ilyest) {
394       trouve = Standard_True;
395       VonW = Vi;
396     }
397     if (trouve) break;
398   }
399   return trouve;
400 }
401
402
403 static Standard_Boolean EdgeIntersectOnWire (const gp_Pnt& P1,
404                                              const gp_Pnt& P2,
405                                              Standard_Real percent,
406                                              const TopTools_DataMapOfShapeListOfShape& Map,
407                                              const TopoDS_Wire&   W,
408                                              TopoDS_Vertex& Vsol,
409                                              TopoDS_Wire&   newW)
410 {
411
412   BRepTools_WireExplorer anExp;
413
414   // construction of the edge of intersection
415   Standard_Boolean NewVertex = Standard_False;
416   gp_Lin droite(P1,gp_Dir(gp_Vec(P1,P2)));
417   // ATTENTION : it is required to construct a half-straight
418   //             but there is a bug in BRepExtrema_DistShapeShape
419   //             it is enough to take 100 * distance between P1 and P2
420   //             hoping that it is enough until the bug is corrected
421   //  Standard_Real dernierparam = Precision::Infinite();
422   // ATTENTION : return !!
423   //             100 is better than 10 but it is too much !
424   //             finally, nothing is better than a blocking box
425   //  Standard_Real dernierparam = 100 * P1.Distance(P2);
426   Bnd_Box B;
427   BRepBndLib::Add(W,B);
428   Standard_Real x1,x2,y1,y2,z1,z2;
429   B.Get(x1,y1,z1,x2,y2,z2);
430   gp_Pnt BP1(x1,y1,z1), BP2(x2,y2,z2);
431   Standard_Real diag = BP1.Distance(BP2);
432   Standard_Real dernierparam = diag;
433   BRepLib_MakeEdge ME(droite,0.,dernierparam);
434   TopoDS_Edge ECur = BRepLib_MakeEdge(droite,0.,P1.Distance(P2));
435
436   // calculate the intersection by BRepExtrema (point of min distance)
437   BRepExtrema_DistShapeShape DSS(ME.Edge(),W);
438   if (DSS.IsDone()) {
439     // choose the solution closest to P2
440     Standard_Integer isol = 1;
441     Standard_Real dss = P2.Distance(DSS.PointOnShape2(isol));
442     for (Standard_Integer iss=2; iss<=DSS.NbSolution(); iss++) {
443       if (dss>P2.Distance(DSS.PointOnShape2(iss))) {
444         dss = P2.Distance(DSS.PointOnShape2(iss));
445         isol = iss;
446       }
447     }
448 #ifdef DEB
449     gp_Pnt Psol = 
450 #endif
451       DSS.PointOnShape2(isol);
452     // is the solution a new vertex ?
453     NewVertex = (DSS.SupportTypeShape2(isol) != BRepExtrema_IsVertex);
454     if (NewVertex) {
455       TopoDS_Shape aLocalShape = DSS.SupportOnShape2(isol);
456       TopoDS_Edge E = TopoDS::Edge(aLocalShape);
457 //      TopoDS_Edge E = TopoDS::Edge(DSS.SupportOnShape2(isol));
458       Standard_Real tol = Precision::PConfusion();
459       Standard_Real first,last,param;
460       BRep_Tool::Range(E,first,last);
461       tol = Max(tol,percent*Abs(last-first));
462       DSS.ParOnEdgeS2(isol,param);
463       if (Abs(first-param)<tol) {
464         NewVertex = Standard_False;
465         Vsol = TopExp::FirstVertex(E);
466       }
467       else if (Abs(last-param)<tol) {
468         NewVertex = Standard_False;
469         Vsol = TopExp::LastVertex(E);
470       }
471       // check
472       if (!NewVertex) {
473         TopoDS_Vertex VRoot;
474         if (SearchRoot(Vsol,Map,VRoot)) NewVertex = Standard_True;
475       }
476     }
477     else {
478       TopoDS_Shape aLocalShape = DSS.SupportOnShape2(isol);
479       Vsol = TopoDS::Vertex(aLocalShape);
480 //      Vsol = TopoDS::Vertex(DSS.SupportOnShape2(isol));
481     }
482
483     // it is required to cut the edge
484     if (NewVertex) {
485       TopoDS_Shape aLocalShape = DSS.SupportOnShape2(isol);
486       TopoDS_Edge E = TopoDS::Edge(aLocalShape);
487 //      TopoDS_Edge E = TopoDS::Edge(DSS.SupportOnShape2(isol));
488       Standard_Real first,last,param;
489       DSS.ParOnEdgeS2(isol,param);
490       BRep_Tool::Range(E,first,last);
491       BRepLib_MakeWire MW;
492       for (anExp.Init(W); anExp.More(); anExp.Next()) {
493         if (E.IsSame(anExp.Current())) {
494           Standard_Boolean SO 
495             = (anExp.CurrentVertex().IsSame(TopExp::FirstVertex(E)));
496           TopTools_SequenceOfShape SE;
497           SE.Clear();
498           TColStd_SequenceOfReal SR;
499           SR.Clear();
500           SR.Append(param);
501           TrimEdge(E,SR,first,last,SO,SE);
502           TopoDS_Vertex VV1,VV2;
503           TopExp::Vertices(TopoDS::Edge(SE.Value(1)),VV1,VV2);
504           if (TopExp::FirstVertex(E).IsSame(VV1)
505               || TopExp::LastVertex(E).IsSame(VV1)) {
506             Vsol = VV2;
507           }
508           if (TopExp::FirstVertex(E).IsSame(VV2)
509               || TopExp::LastVertex(E).IsSame(VV2)) {
510             Vsol = VV1;
511           }
512           for (Standard_Integer k=1; k<=SE.Length(); k++) {
513             MW.Add(TopoDS::Edge(SE.Value(k)));
514           }
515         }
516         else {
517           MW.Add(anExp.Current());
518         }
519       }
520       newW = MW.Wire();
521     }
522     else {
523       newW = W;
524     }
525     
526     
527   }
528
529   return NewVertex;
530
531 }
532
533
534 static void Transform (const Standard_Boolean WithRotation,
535                        const gp_Pnt& P,
536                        const gp_Pnt& Pos1,
537                        const gp_Vec& Ax1,
538                        const gp_Pnt& Pos2,
539                        const gp_Vec& Ax2,
540                        gp_Pnt& Pnew)
541 {
542
543   Pnew = P.Translated (Pos1,Pos2);
544   gp_Vec axe1 = Ax1, axe2 = Ax2; 
545   if (!axe1.IsParallel(axe2,1.e-4)) {
546     gp_Vec Vtrans(Pos1,Pos2),Vsign;
547     Standard_Real alpha,beta,sign=1;
548     alpha = Vtrans.Dot(axe1);
549     beta = Vtrans.Dot(axe2);
550     if (alpha<-1.e-7) axe1 *=-1;
551     if (beta<1.e-7) axe2 *=-1;
552     alpha = Vtrans.Dot(axe1);
553     beta = Vtrans.Dot(axe2);
554     gp_Vec norm2 = axe1 ^ axe2;
555     Vsign.SetLinearForm(Vtrans.Dot(axe1),axe2,-Vtrans.Dot(axe2),axe1);
556     alpha = Vsign.Dot(axe1);
557     beta = Vsign.Dot(axe2);
558     Standard_Boolean pasnul = (Abs(alpha)>1.e-4 && Abs(beta)>1.e-4);
559     if ( alpha*beta>0.0 && pasnul ) sign=-1;
560     gp_Ax1 Norm(Pos2,norm2);
561     Standard_Real ang = axe1.AngleWithRef(axe2,norm2);
562     if (!WithRotation) {
563       if (ang>M_PI/2) ang = ang - M_PI;
564       if (ang<-M_PI/2) ang = ang + M_PI;
565     }
566     ang *= sign;
567     Pnew = Pnew.Rotated (Norm,ang);
568   }
569 }
570
571 static void BuildConnectedEdges(const TopoDS_Wire& aWire,
572                                 const TopoDS_Edge& StartEdge,
573                                 const TopoDS_Vertex& StartVertex,
574                                 TopTools_ListOfShape& ConnectedEdges)
575 {
576   TopTools_IndexedDataMapOfShapeListOfShape MapVE;
577   TopExp::MapShapesAndAncestors(aWire, TopAbs_VERTEX, TopAbs_EDGE, MapVE);
578   TopoDS_Edge CurEdge = StartEdge;
579   TopoDS_Vertex CurVertex = StartVertex;
580   TopoDS_Vertex Origin, V1, V2;
581   TopExp::Vertices(StartEdge, V1, V2);
582   Origin = (V1.IsSame(StartVertex))? V2 : V1;
583
584   for (;;)
585     {
586       TopTools_ListIteratorOfListOfShape itE( MapVE.FindFromKey(CurVertex) );
587       for (; itE.More(); itE.Next())
588         {
589           TopoDS_Edge anEdge = TopoDS::Edge(itE.Value());
590           if (!anEdge.IsSame(CurEdge))
591             {
592               ConnectedEdges.Append(anEdge);
593               TopExp::Vertices(anEdge, V1, V2);
594               CurVertex = (V1.IsSame(CurVertex))? V2 : V1;
595               CurEdge = anEdge;
596               break;
597             }
598         }
599       if (CurVertex.IsSame(Origin))
600         break;
601     }
602 }
603                                       
604 //=======================================================================
605 //function : BRepFill_CompatibleWires
606 //purpose  : 
607 //=======================================================================
608
609 BRepFill_CompatibleWires::BRepFill_CompatibleWires() 
610 :myIsDone(Standard_False)
611 {
612 }
613
614
615 //=======================================================================
616 //function : BRepFill_CompatibleWires
617 //purpose  : 
618 //=======================================================================
619
620 BRepFill_CompatibleWires::BRepFill_CompatibleWires(const TopTools_SequenceOfShape& Sections)
621 {
622   Init(Sections);
623 }
624
625
626 //=======================================================================
627 //function : Init
628 //purpose  : 
629 //=======================================================================
630
631 void BRepFill_CompatibleWires::Init(const TopTools_SequenceOfShape& Sections)
632 {
633   myInit = Sections;
634   myWork = Sections;
635   myPercent = 0.01;
636   myIsDone = Standard_False;
637   myMap.Clear();
638
639 }
640
641
642 //=======================================================================
643 //function : SetPercent
644 //purpose  : 
645 //=======================================================================
646
647 void BRepFill_CompatibleWires::SetPercent(const Standard_Real Percent)
648 {
649   if (0.<Percent && Percent<1.) myPercent = Percent;
650
651 }
652
653
654 //=======================================================================
655 //function : IsDone
656 //purpose  : 
657 //=======================================================================
658
659 Standard_Boolean BRepFill_CompatibleWires::IsDone() const 
660 {
661   return myIsDone;
662 }
663
664
665 //=======================================================================
666 //function : Shape
667 //purpose  : 
668 //=======================================================================
669
670 const TopTools_SequenceOfShape& BRepFill_CompatibleWires::Shape() const 
671 {
672   return myWork;
673 }
674
675
676 //=======================================================================
677 //function : GeneratedShapes
678 //purpose  : 
679 //=======================================================================
680
681 const TopTools_ListOfShape& BRepFill_CompatibleWires::GeneratedShapes
682 (const TopoDS_Edge& SubSection) const
683 {  
684
685   if (myMap.IsBound(SubSection)) {
686     return myMap(SubSection);
687   }
688   else {
689     static TopTools_ListOfShape Empty;
690     return Empty;
691   }
692 }
693
694
695 //=======================================================================
696 //function : Perform
697 //purpose  : 
698 //=======================================================================
699
700 void BRepFill_CompatibleWires::Perform (const Standard_Boolean WithRotation)
701 {
702   // compute origin and orientation on wires to avoid twisted results
703   // and update wires to have same number of edges
704
705   // determination of report:
706   // if the number of elements is the same and if the wires have discontinuities
707   // by tangency, the report is not carried out by curvilinear abscissa
708   Standard_Integer nbSects = myWork.Length(), i;
709   BRepTools_WireExplorer anExp;
710   Standard_Integer nbmax=0, nbmin=0;
711   TColStd_Array1OfInteger nbEdges(1,nbSects);
712   Standard_Boolean report;
713   GeomAbs_Shape contS=GeomAbs_CN;
714   GeomAbs_Shape cont;
715   for (i=1; i<=nbSects; i++) {
716     TopoDS_Shape aLocalShape = myWork(i).Oriented(TopAbs_FORWARD);
717     myWork(i) = TopoDS::Wire(aLocalShape);
718 //    myWork(i) = TopoDS::Wire(myWork(i).Oriented(TopAbs_FORWARD));
719     TopoDS_Wire W = TopoDS::Wire(myWork(i));
720     WireContinuity(W,cont);
721     if (cont<contS) contS=cont;
722     nbEdges(i) = 0;
723     for(anExp.Init(W); anExp.More(); anExp.Next() ) nbEdges(i)++;
724     if (i==1) nbmin = nbEdges(i);
725     if (nbmax<nbEdges(i)) nbmax = nbEdges(i);
726     if (nbmin>nbEdges(i)) nbmin = nbEdges(i);
727   } 
728   // if the number of elements is not the same or if all wires are at least
729   // C1, the report is carried out by curvilinear abscissa of cuts, otherwise 
730   // a report vertex / Vertex is done
731   report = (nbmax != nbmin || contS >= GeomAbs_C1 );
732   
733   // initialization of the map
734   Standard_Integer nbE = 0;
735   TopTools_ListOfShape Empty;
736   for (i=1; i<=nbSects; i++) {
737     TopoDS_Wire W = TopoDS::Wire(myWork(i));
738     for(anExp.Init(W); anExp.More(); anExp.Next() ) {
739       TopoDS_Edge E = TopoDS::Edge(anExp.Current());
740       myMap.Bind(E,Empty);
741       myMap(E).Append(E);
742       nbE++;
743     }
744   } 
745   
746   // open/closed sections
747   // initialisation of myDegen1, myDegen2
748   Standard_Integer ideb=1, ifin=myWork.Length();
749   // check if the first wire is punctual
750   myDegen1 = Standard_True;
751   for(anExp.Init(TopoDS::Wire(myWork(ideb))); anExp.More(); anExp.Next()) {
752     myDegen1 = myDegen1 && (BRep_Tool::Degenerated(anExp.Current()));
753   }
754   if (myDegen1) ideb++;
755   // check if the last wire is punctual
756   myDegen2 = Standard_True;
757   for(anExp.Init(TopoDS::Wire(myWork(ifin))); anExp.More(); anExp.Next()) {
758     myDegen2 = myDegen2 && (BRep_Tool::Degenerated(anExp.Current()));
759   }
760   if (myDegen2) ifin--;
761   
762   Standard_Boolean wClosed, allClosed = Standard_True, allOpen = Standard_True;
763   for (i=ideb; i<=ifin; i++) {
764     wClosed = myWork(i).Closed();
765     if (!wClosed) {
766       // check if the vertices are the same.
767       TopoDS_Vertex V1, V2;
768       TopExp::Vertices(TopoDS::Wire(myWork(i)),V1,V2);
769       if ( V1.IsSame(V2)) wClosed = Standard_True;
770     }
771     allClosed = (allClosed && wClosed);
772     allOpen = (allOpen && !wClosed);
773   }
774   
775   if (allClosed) {
776     // All sections are closed 
777     if (report) {
778       // same number of elements  
779       SameNumberByPolarMethod(WithRotation);
780     }
781     else {
782       // origin
783       ComputeOrigin(Standard_False);
784     }
785     myIsDone = Standard_True;
786   }
787   else if (allOpen) {
788     // All sections are open
789     // origin
790     SearchOrigin();
791     // same number of elements
792     if (report) {
793       SameNumberByACR(report);
794     }
795     myIsDone = Standard_True;
796   }
797   else {
798     // There are open and closed sections :
799     // not processed
800     Standard_DomainError::Raise("Sections must be all closed or all open");
801   }
802   
803 }
804
805
806
807
808 //=======================================================================
809 //function : Generated
810 //purpose  : 
811 //=======================================================================
812
813 const TopTools_DataMapOfShapeListOfShape&  BRepFill_CompatibleWires::Generated() const 
814 {
815   return myMap;
816 }
817
818
819 //=======================================================================
820 //function : SameNumberByPolarMethod
821 //purpose  : 
822 //=======================================================================
823
824 void BRepFill_CompatibleWires::
825               SameNumberByPolarMethod(const Standard_Boolean WithRotation)
826 {
827
828   // initialisation 
829   Standard_Integer NbSects=myWork.Length();
830   BRepTools_WireExplorer anExp;
831   TopoDS_Vertex V1, V2;
832   
833   Standard_Boolean allClosed = Standard_True;
834   Standard_Integer i,ii,ideb=1,ifin=NbSects;
835   for (i=1; i<=NbSects; i++) {
836     Handle(BRepCheck_Wire) Checker = new BRepCheck_Wire(TopoDS::Wire(myWork(i)));
837     allClosed = (allClosed && (Checker->Closed() == BRepCheck_NoError));
838     //allClosed = (allClosed && myWork(i).Closed());
839   }
840   if (!allClosed)
841     Standard_NoSuchObject::Raise("BRepFill_CompatibleWires::SameNumberByPolarMethod : the wires must be closed");
842   
843   // sections ponctuelles, sections bouclantes ?
844   if (myDegen1) ideb++;
845   if (myDegen2) ifin--;
846   Standard_Boolean vClosed = (!myDegen1) && (!myDegen2)
847                                 && (myWork(ideb).IsSame(myWork(ifin)));
848
849   //Removing degenerated edges
850   for (i = ideb; i <= ifin; i++)
851   {
852     Standard_Boolean hasDegEdge = Standard_False;
853     TopoDS_Iterator anItw(myWork(i));
854     for (; anItw.More(); anItw.Next())
855     {
856       const TopoDS_Edge& anEdge = TopoDS::Edge(anItw.Value());
857       if (BRep_Tool::Degenerated(anEdge))
858       {
859         hasDegEdge = Standard_True;
860         break;
861       }
862     }
863     if (hasDegEdge)
864     {
865       TopoDS_Wire aNewWire;
866       BRep_Builder aBBuilder;
867       aBBuilder.MakeWire(aNewWire);
868       for (anItw.Initialize(myWork(i)); anItw.More(); anItw.Next())
869       {
870         const TopoDS_Edge& anEdge = TopoDS::Edge(anItw.Value());
871         if (!BRep_Tool::Degenerated(anEdge))
872           aBBuilder.Add(aNewWire, anEdge);
873       }
874       myWork(i) = aNewWire;
875     }
876   }
877   
878   // Nombre max de decoupes possibles
879   Standard_Integer NbMaxV = 0;
880   for (i=1; i<=NbSects; i++) {
881     for(anExp.Init(TopoDS::Wire(myWork(i))); anExp.More(); anExp.Next()) {
882       NbMaxV++;
883     }
884   }
885   
886   // construction of tables of planes of wires 
887   gp_Pln P;
888   Handle(TColgp_HArray1OfPnt) Pos
889     = new (TColgp_HArray1OfPnt) (1,NbSects);
890   Handle(TColgp_HArray1OfVec) Axe
891     = new (TColgp_HArray1OfVec) (1,NbSects);
892   for (i=ideb;i<=ifin;i++) {
893     if (PlaneOfWire(TopoDS::Wire(myWork(i)),P)) {
894       Pos->SetValue(i,P.Location());
895       Axe->SetValue(i,gp_Vec(P.Axis().Direction()));
896     }
897   }
898   TopTools_SequenceOfShape SeqV;
899   if (myDegen1) {
900     SeqOfVertices(TopoDS::Wire(myWork(1)),SeqV);
901     Pos->SetValue(1,BRep_Tool::Pnt(TopoDS::Vertex(SeqV.Value(1))));
902     Axe->SetValue(1,Axe->Value(ideb));
903   }
904   if (myDegen2) {
905     SeqOfVertices(TopoDS::Wire(myWork(NbSects)),SeqV);
906     Pos->SetValue(NbSects,BRep_Tool::Pnt(TopoDS::Vertex(SeqV.Value(1))));
907     Axe->SetValue(NbSects,Axe->Value(ifin));
908   }
909   
910   // construction of RMap, map of reports of wire i to wire i-1
911   TopTools_DataMapOfShapeListOfShape RMap;
912   RMap.Clear();
913   
914   // loop on i
915   for (i=ifin; i>ideb; i--) {
916     
917     const TopoDS_Wire& wire1 = TopoDS::Wire(myWork(i));
918     
919     // sequence of vertices of the first wire
920     SeqOfVertices(wire1,SeqV);
921     if (SeqV.Length()>NbMaxV) 
922       Standard_NoSuchObject::Raise("BRepFill::SameNumberByPolarMethod failed");
923     
924     // extremity of the first wire
925     V1 = TopoDS::Vertex(SeqV.Value(1)); 
926     // loop on vertices of wire1
927     for (ii=1;ii<=SeqV.Length();ii++) {
928       
929       TopoDS_Vertex Vi = TopoDS::Vertex(SeqV.Value(ii));
930       
931       // init of RMap for Vi
932       TopTools_ListOfShape Init;
933       Init.Clear();
934       RMap.Bind(Vi,Init);
935       
936       // it is required to find intersection Vi - wire2
937       gp_Pnt Pi = BRep_Tool::Pnt(Vi);
938       
939       // return Pi in the current plane
940       gp_Pnt Pnew;
941       Transform(WithRotation,Pi,
942                 Pos->Value(i),Axe->Value(i), 
943                 Pos->Value(i-1),Axe->Value(i-1),Pnew);
944       
945       // calculate the intersection
946       TopoDS_Shape Support;
947       Standard_Boolean NewVertex;
948       TopoDS_Vertex Vsol;
949       TopoDS_Wire newwire;
950       if (Pnew.Distance(Pos->Value(i-1))>Precision::Confusion()) {
951         Standard_Real percent = myPercent;
952         NewVertex = EdgeIntersectOnWire(Pos->Value(i-1),Pnew,percent,
953                                     RMap,TopoDS::Wire(myWork(i-1)),
954                                     Vsol,newwire);
955         if (NewVertex) myWork(i-1) = newwire;
956         RMap(Vi).Append(Vsol);
957       }
958       
959     } // loop on  ii
960   }   // loop on  i
961   
962   // initialisation of MapVLV, map of correspondences vertex - list of vertices
963   TopTools_DataMapOfShapeListOfShape MapVLV;
964   SeqOfVertices(TopoDS::Wire(myWork(ideb)),SeqV);
965   Standard_Integer SizeMap = SeqV.Length();
966   MapVLV.Clear();
967   for (ii=1;ii<=SizeMap;ii++) {
968     TopoDS_Vertex Vi = TopoDS::Vertex(SeqV.Value(ii));
969     TopTools_ListOfShape Init;
970     Init.Clear();
971     Init.Append(Vi);
972     MapVLV.Bind(Vi,Init);
973     Standard_Integer NbV = 1;
974     TopoDS_Vertex V0,V1;
975     V0 = Vi;
976     Standard_Boolean tantque = SearchRoot(V0,RMap,V1);
977     while (tantque) {
978       MapVLV(Vi).Append(V1);
979       NbV++;
980       // test on NbV required for looping sections 
981       if (V1.IsSame(Vi) || NbV >= myWork.Length()) {
982         tantque = Standard_False;
983       }
984       else {
985         V0 = V1;
986         tantque = SearchRoot(V0,RMap,V1);
987       }
988     }
989   }
990   
991   // loop on i
992   for (i=ideb; i<ifin; i++) {
993     
994     const TopoDS_Wire& wire1 = TopoDS::Wire(myWork(i));
995     
996     // sequence of vertices of the first wire
997     SeqOfVertices(wire1,SeqV);
998     if ( SeqV.Length()>NbMaxV || SeqV.Length()>SizeMap ) 
999       Standard_NoSuchObject::Raise("BRepFill::SameNumberByPolarMethod failed");
1000     
1001     // extremity of the first wire
1002     V1 = TopoDS::Vertex(SeqV.Value(1));
1003
1004     // next wire 
1005     const TopoDS_Wire& wire2 = TopoDS::Wire(myWork(i+1));
1006     
1007     // loop on vertices of wire1
1008     for (ii=1;ii<=SeqV.Length();ii++) {
1009       
1010       TopoDS_Vertex Vi = TopoDS::Vertex(SeqV.Value(ii));
1011       TopoDS_Vertex VRoot;
1012       VRoot.Nullify();
1013       Standard_Boolean intersect = Standard_True;
1014       if (SearchRoot(Vi,MapVLV,VRoot)) {
1015         const TopTools_ListOfShape& LVi = MapVLV(VRoot);
1016         TopoDS_Vertex VonW;
1017         VonW.Nullify();
1018         intersect = (!SearchVertex(LVi,wire2,VonW));
1019       }
1020       
1021       if (intersect) {
1022         // it is necessary to find intersection Vi - wire2
1023         gp_Pnt Pi = BRep_Tool::Pnt(Vi);
1024         
1025         // return Pi in the current plane
1026         gp_Pnt Pnew;
1027         Transform(WithRotation,Pi,
1028                   Pos->Value(i),Axe->Value(i), 
1029                   Pos->Value(i+1),Axe->Value(i+1),Pnew);
1030         
1031         // calculate the intersection
1032         TopoDS_Shape Support;
1033         Standard_Boolean NewVertex;
1034         TopoDS_Vertex Vsol;
1035         TopoDS_Wire newwire;
1036         if (Pnew.Distance(Pos->Value(i+1))>Precision::Confusion()) {
1037           Standard_Real percent = myPercent;
1038           NewVertex = EdgeIntersectOnWire(Pos->Value(i+1),Pnew,percent,
1039                                       MapVLV,TopoDS::Wire(myWork(i+1)),
1040                                       Vsol,newwire);
1041           MapVLV(VRoot).Append(Vsol);
1042           if (NewVertex) myWork(i+1) = newwire;
1043         }
1044         
1045       }
1046     } // loop on ii
1047   }   // loop on i
1048   
1049   // regularize wires following MapVLV
1050   TopoDS_Wire wire = TopoDS::Wire(myWork(ideb));
1051
1052   // except for the last if the sections loop 
1053   Standard_Integer ibout = ifin;
1054   if (vClosed) ibout--;
1055
1056   for ( i=ideb+1; i<=ibout; i++) {
1057
1058     BRepLib_MakeWire MW;
1059
1060     anExp.Init(wire);
1061     TopoDS_Edge ECur = anExp.Current();
1062     TopoDS_Vertex VF,VL;
1063     TopExp::Vertices(ECur,VF,VL,Standard_True);
1064     Standard_Real U1 = BRep_Tool::Parameter(VF,ECur);
1065     Standard_Real U2 = BRep_Tool::Parameter(VL,ECur);
1066     BRepAdaptor_Curve Curve(ECur);
1067     gp_Pnt PPs = Curve.Value(0.1*(U1+9*U2));
1068     TopTools_ListIteratorOfListOfShape itF(MapVLV(VF)),itL(MapVLV(VL));
1069     Standard_Integer rang = ideb;
1070     while (rang < i) {
1071       itF.Next();
1072       itL.Next();
1073       rang++;
1074     }
1075     TopoDS_Vertex V1 = TopoDS::Vertex(itF.Value()), V2 = TopoDS::Vertex(itL.Value());
1076     TopoDS_Edge Esol;
1077     Standard_Real scalmax=0.;
1078     TopoDS_Iterator itW( myWork(i) );
1079     
1080     for(; itW.More(); itW.Next())
1081       {
1082         TopoDS_Edge E = TopoDS::Edge(itW.Value());
1083         TopoDS_Vertex VVF,VVL;
1084         TopExp::Vertices(E,VVF,VVL,Standard_True);
1085         
1086         // parse candidate edges
1087         Standard_Real scal1,scal2;
1088         if ( (V1.IsSame(VVF)&&V2.IsSame(VVL)) || (V2.IsSame(VVF)&&V1.IsSame(VVL)) ) {
1089           Standard_Real U1 = BRep_Tool::Parameter(VVF,E);
1090           Standard_Real U2 = BRep_Tool::Parameter(VVL,E);
1091           BRepAdaptor_Curve Curve(E);
1092           gp_Pnt PP1 = Curve.Value(0.1*(U1+9*U2));
1093           gp_Pnt PP2 = Curve.Value(0.1*(9*U1+U2));
1094   
1095           for (rang=i;rang>ideb;rang--) {
1096             Transform(WithRotation, PP1,
1097                       Pos->Value(rang), Axe->Value(rang),
1098                       Pos->Value(rang-1), Axe->Value(rang-1), PP1);
1099             Transform(WithRotation, PP2,
1100                       Pos->Value(rang), Axe->Value(rang),
1101                       Pos->Value(rang-1), Axe->Value(rang-1), PP2);
1102           }
1103           gp_Vec Ns(Pos->Value(ideb),PPs);
1104           Ns = Ns.Normalized();
1105           gp_Vec N1(Pos->Value(ideb),PP1);
1106           N1 = N1.Normalized();
1107           gp_Vec N2(Pos->Value(ideb),PP2);
1108           N2 = N2.Normalized();
1109           scal1 = N1.Dot(Ns);
1110           if (scal1>scalmax) {
1111             scalmax = scal1;
1112             Esol = E;
1113           }
1114           scal2 = N2.Dot(Ns);
1115           if (scal2>scalmax) {
1116             scalmax = scal2;
1117             TopoDS_Shape aLocalShape = E.Reversed();
1118             Esol = TopoDS::Edge(aLocalShape);
1119           }
1120         }
1121       } //end of for(; itW.More(); itW.Next())
1122     MW.Add(Esol);
1123
1124     TopTools_ListOfShape ConnectedEdges;
1125     BuildConnectedEdges( TopoDS::Wire(myWork(i)), Esol, V2, ConnectedEdges );
1126
1127     TopTools_ListIteratorOfListOfShape itCE(ConnectedEdges);
1128     for(; anExp.More(), itCE.More(); anExp.Next(), itCE.Next())
1129       {
1130         ECur = anExp.Current();
1131         TopExp::Vertices(ECur,VF,VL,Standard_True);
1132         U1 = BRep_Tool::Parameter(VF,ECur);
1133         U2 = BRep_Tool::Parameter(VL,ECur);
1134         Curve.Initialize(ECur);
1135         PPs = Curve.Value(0.1*(U1+9*U2));
1136         
1137         TopoDS_Edge E = TopoDS::Edge(itCE.Value());
1138         TopoDS_Vertex VVF,VVL;
1139         TopExp::Vertices(E,VVF,VVL,Standard_True);
1140
1141         // parse candidate edges
1142         Standard_Real scal1,scal2;
1143         U1 = BRep_Tool::Parameter(VVF,E);
1144         U2 = BRep_Tool::Parameter(VVL,E);
1145         Curve.Initialize(E);
1146         gp_Pnt PP1 = Curve.Value(0.1*(U1+9*U2));
1147         gp_Pnt PP2 = Curve.Value(0.1*(9*U1+U2));
1148         
1149         for (rang=i;rang>ideb;rang--) {
1150           Transform(WithRotation, PP1,
1151                     Pos->Value(rang), Axe->Value(rang),
1152                     Pos->Value(rang-1), Axe->Value(rang-1), PP1);
1153           Transform(WithRotation, PP2,
1154                     Pos->Value(rang), Axe->Value(rang),
1155                     Pos->Value(rang-1), Axe->Value(rang-1), PP2);
1156         }
1157         gp_Vec Ns(Pos->Value(ideb),PPs);
1158         Ns = Ns.Normalized();
1159         gp_Vec N1(Pos->Value(ideb),PP1);
1160         N1 = N1.Normalized();
1161         gp_Vec N2(Pos->Value(ideb),PP2);
1162         N2 = N2.Normalized();
1163         scal1 = N1.Dot(Ns);
1164         scal2 = N2.Dot(Ns);
1165         if (scal2>scal1)
1166           E.Reverse();
1167         MW.Add(E);
1168       }
1169     myWork(i) = MW.Wire();
1170   }
1171   
1172   // blocking sections?
1173   if (vClosed) myWork(myWork.Length()) = myWork(1);
1174
1175   // check the number of edges for debug
1176   Standard_Integer nbmax=0, nbmin=0;
1177   for ( i=ideb; i<=ifin; i++) {
1178     Standard_Integer nbEdges=0;
1179     for(anExp.Init(TopoDS::Wire(myWork(i))); anExp.More(); anExp.Next()) {
1180       nbEdges++;
1181     }
1182     if (i==ideb) nbmin = nbEdges;
1183     if (nbmax<nbEdges) nbmax = nbEdges;
1184     if (nbmin>nbEdges) nbmin = nbEdges;
1185   }
1186   if (nbmin!=nbmax) {
1187     Standard_NoSuchObject::Raise("BRepFill_CompatibleWires::SameNumberByPolarMethod failed");
1188   }
1189
1190 }
1191
1192 //=======================================================================
1193 //function : SameNumberByACR
1194 //purpose  : 
1195 //=======================================================================
1196
1197 void BRepFill_CompatibleWires::SameNumberByACR(const  Standard_Boolean  report)
1198 {
1199   // find the dimension
1200   Standard_Integer ideb=1, ifin=myWork.Length();
1201   BRepTools_WireExplorer anExp;
1202
1203   // point sections, blocking  sections?
1204   if (myDegen1) ideb++;
1205   if (myDegen2) ifin--;
1206   Standard_Boolean vClosed = (!myDegen1) && (!myDegen2)
1207                                 && (myWork(ideb).IsSame(myWork(ifin)));
1208
1209   Standard_Integer nbSects = myWork.Length(), i;
1210   Standard_Integer nbmax=0, nbmin=0;
1211   TColStd_Array1OfInteger nbEdges(1,nbSects);
1212   for (i=1; i<=nbSects; i++) {
1213     nbEdges(i) = 0;
1214     for(anExp.Init(TopoDS::Wire(myWork(i))); anExp.More(); anExp.Next()) {
1215       nbEdges(i)++;
1216     }
1217     if (i==1) nbmin = nbEdges(i);
1218     if (nbmax<nbEdges(i)) nbmax = nbEdges(i);
1219     if (nbmin>nbEdges(i)) nbmin = nbEdges(i);
1220   }
1221
1222   if (nbmax>1) {
1223     // several edges
1224
1225     if (report || nbmin<nbmax) {
1226       // insertion of cuts
1227       Standard_Integer nbdec=(nbmax-1)*nbSects+1;
1228       Standard_Real tol = 0.01;
1229       TColStd_Array1OfReal dec(1,nbdec);
1230       dec.Init(0);
1231       dec(2)=1;
1232       // calculate the table of cuts
1233       Standard_Integer j,k,l;
1234       for (i=1; i<=nbSects; i++) {
1235         // current wire
1236         const TopoDS_Wire& wire1 = TopoDS::Wire(myWork(i));
1237         Standard_Integer nbE = 0;
1238         for(anExp.Init(wire1); anExp.More(); anExp.Next()) {
1239           nbE++;
1240         }
1241         // length and ACR of the wire 
1242         TColStd_Array1OfReal ACR(0,nbE);
1243         ACR.Init(0);
1244         BRepFill::ComputeACR(wire1, ACR);
1245         // insertion of ACR of the wire in the table of cuts
1246         for (j=1; j<ACR.Length()-1; j++) {
1247           k=1;
1248           while (dec(k)<ACR(j)) {
1249             k++;
1250             if (k>nbdec) break;
1251           }
1252           if (dec(k-1)+tol<ACR(j)&& ACR(j)+tol<dec(k)) {
1253             for (l=nbdec-1;l>=k;l--) {
1254               dec(l+1)=dec(l);
1255             }
1256             dec(k) = ACR(j);
1257           }
1258         }
1259       }
1260       
1261       // table of cuts
1262       k=1;
1263       while (dec(k)<1) {
1264         k++;
1265         if (k>nbdec) break;
1266       }
1267       nbdec = k-1;
1268       TColStd_Array1OfReal dec2(1,nbdec);
1269       for (k=1;k<=nbdec;k++) {
1270         dec2(k) = dec(k);
1271       }
1272       
1273       // insertion of cuts in each wire
1274       for (i=1; i<=nbSects; i++) {
1275         const TopoDS_Wire& oldwire = TopoDS::Wire(myWork(i));
1276         TopoDS_Wire newwire = BRepFill::InsertACR(oldwire, dec2, tol);
1277         BRepTools_WireExplorer anExp1,anExp2;
1278         anExp1.Init(oldwire);
1279         anExp2.Init(newwire);
1280         for (;anExp1.More();anExp1.Next()) {
1281           const TopoDS_Edge& Ecur = anExp1.Current();
1282           if (!Ecur.IsSame(TopoDS::Edge(anExp2.Current()))) {
1283             TopTools_ListOfShape LE;
1284             LE.Clear();
1285             gp_Pnt P1,P2;
1286             const TopoDS_Vertex& V1 = anExp1.CurrentVertex();
1287             TopoDS_Vertex VF,VR;
1288             TopExp::Vertices(Ecur,VF,VR,Standard_True);
1289             if (V1.IsSame(VF)) P1 = BRep_Tool::Pnt(VR);
1290             if (V1.IsSame(VR)) P1 = BRep_Tool::Pnt(VF);
1291             TopoDS_Vertex V2 = anExp2.CurrentVertex();
1292             TopExp::Vertices(TopoDS::Edge(anExp2.Current()),
1293                              VF,VR,Standard_True);
1294             if (V2.IsSame(VF)) P2 = BRep_Tool::Pnt(VR);
1295             if (V2.IsSame(VR)) P2 = BRep_Tool::Pnt(VF);
1296             while (P1.Distance(P2)>1.e-3) {
1297               LE.Append(anExp2.Current());
1298               anExp2.Next();
1299               V2 = anExp2.CurrentVertex();
1300               TopExp::Vertices(TopoDS::Edge(anExp2.Current()),
1301                                VF,VR,Standard_True);
1302               if (V2.IsSame(VF)) P2 = BRep_Tool::Pnt(VR);
1303               if (V2.IsSame(VR)) P2 = BRep_Tool::Pnt(VF);
1304               if (P1.Distance(P2)<=1.e-3) {
1305                 LE.Append(anExp2.Current());
1306                 anExp2.Next();
1307               }
1308             }
1309
1310             TopTools_DataMapIteratorOfDataMapOfShapeListOfShape itmap;
1311             //TopTools_ListIteratorOfListOfShape itlist;
1312             TopoDS_Edge Ancestor;
1313             Standard_Integer nbedge, nblist=0;
1314             Standard_Boolean found = Standard_False;
1315
1316             for (itmap.Initialize(myMap);itmap.More()&&(!found);itmap.Next()) {
1317               nblist++;
1318               TopTools_ListIteratorOfListOfShape itlist(itmap.Value());
1319               nbedge = 0;
1320               while (itlist.More()&&(!found)) {
1321                 nbedge++;
1322                 TopoDS_Edge ECur = TopoDS::Edge(itlist.Value());
1323                     
1324                 if (Ecur.IsSame(ECur)) {
1325                   Ancestor = TopoDS::Edge(itmap.Key());
1326                   found = Standard_True;
1327                   myMap(Ancestor).InsertBefore(LE,itlist);
1328                   myMap(Ancestor).Remove(itlist);
1329                 }
1330                 if (itlist.More()) itlist.Next();
1331               }
1332               
1333             }
1334
1335           }
1336           else {
1337             anExp2.Next();
1338           }
1339           
1340         }
1341         myWork(i) = newwire;
1342       }
1343       
1344     }
1345   }
1346   
1347   // blocking sections ?
1348   if (vClosed) myWork(myWork.Length()) = myWork(1);
1349
1350   // check the number of edges for debug
1351   nbmax = 0;
1352   for (i=ideb; i<=ifin; i++) {
1353     nbEdges(i) = 0;
1354     for(anExp.Init(TopoDS::Wire(myWork(i))); anExp.More(); anExp.Next()) {
1355       nbEdges(i)++;
1356     }
1357     if (i==ideb) nbmin = nbEdges(i);
1358     if (nbmax<nbEdges(i)) nbmax = nbEdges(i);
1359     if (nbmin>nbEdges(i)) nbmin = nbEdges(i);
1360   }
1361   if (nbmax!=nbmin) 
1362     Standard_NoSuchObject::Raise("BRepFill_CompatibleWires::SameNumberByACR failed");
1363 }
1364
1365 //=======================================================================
1366 //function : ComputeOrigin
1367 //purpose  : 
1368 //=======================================================================
1369
1370 void BRepFill_CompatibleWires::ComputeOrigin(const  Standard_Boolean /*polar*/ )
1371 {
1372   // reorganize the wires respecting orientation and origin
1373   
1374   TopoDS_Vertex Vdeb, Vfin;
1375   gp_Pnt Pdeb, Psuiv, PPs;
1376
1377   BRepTools_WireExplorer anExp;
1378
1379   Standard_Boolean wClosed, allClosed = Standard_True;
1380
1381   Standard_Integer NbSects = myWork.Length();
1382   Standard_Integer i, ideb=1,ifin=NbSects;
1383
1384   // point sections, blocking sections 
1385   if (myDegen1) ideb++;
1386   if (myDegen2) ifin--;
1387   Standard_Boolean vClosed = (!myDegen1) && (!myDegen2)
1388                                 && (myWork(ideb).IsSame(myWork(ifin)));
1389   
1390   
1391   for (i=ideb; i<=ifin; i++) {
1392     wClosed = myWork(i).Closed();
1393     if (!wClosed) {
1394       // check if the vertices are the same.
1395       TopoDS_Vertex V1, V2;
1396       TopExp::Vertices(TopoDS::Wire(myWork(i)),V1,V2);
1397       if ( V1.IsSame(V2)) wClosed = Standard_True;
1398     }
1399     allClosed = (allClosed && wClosed);
1400   }
1401 /*
1402   for (i=ideb; i<=ifin; i++) {
1403     allClosed = (allClosed && myWork(i).Closed());
1404   }
1405 */
1406   if (!allClosed) 
1407     Standard_NoSuchObject::Raise("BRepFill_CompatibleWires::ComputeOrigin : the wires must be closed");
1408
1409 /*  
1410   // Max number of possible cuts
1411   Standard_Integer NbMaxV = 0;
1412   for (i=1; i<=NbSects; i++) {
1413     for(anExp.Init(TopoDS::Wire(myWork(i))); anExp.More(); anExp.Next()) {
1414       NbMaxV++;
1415     }
1416   }
1417   
1418   // construction of tables of planes of wires 
1419   gp_Pln P;  
1420   Handle(TColgp_HArray1OfPnt) Pos
1421     = new (TColgp_HArray1OfPnt) (1,NbSects);
1422   Handle(TColgp_HArray1OfVec) Axe
1423     = new (TColgp_HArray1OfVec) (1,NbSects);
1424   for (i=ideb;i<=ifin;i++) {
1425     if (PlaneOfWire(TopoDS::Wire(myWork(i)),P)) {
1426       Pos->SetValue(i,P.Location());
1427       Axe->SetValue(i,gp_Vec(P.Axis().Direction()));
1428     }
1429   }
1430   TopTools_SequenceOfShape SeqV;
1431   if (myDegen1) {
1432     SeqOfVertices(TopoDS::Wire(myWork(1)),SeqV);
1433     Pos->SetValue(1,BRep_Tool::Pnt(TopoDS::Vertex(SeqV.Value(1))));
1434     Axe->SetValue(1,Axe->Value(ideb));
1435   }
1436   if (myDegen2) {
1437     SeqOfVertices(TopoDS::Wire(myWork(NbSects)),SeqV);
1438     Pos->SetValue(NbSects,BRep_Tool::Pnt(TopoDS::Vertex(SeqV.Value(1))));
1439     Axe->SetValue(NbSects,Axe->Value(ifin));
1440   }
1441 */
1442
1443   //Consider that all wires have same number of edges (polar==Standard_False)
1444   TopTools_SequenceOfShape PrevSeq;
1445   TopTools_SequenceOfShape PrevEseq;
1446   Standard_Integer theLength = 0;
1447   const TopoDS_Wire& wire = TopoDS::Wire( myWork(ideb) );
1448   for (anExp.Init(wire); anExp.More(); anExp.Next())
1449     {
1450       PrevSeq.Append(anExp.CurrentVertex());
1451       PrevEseq.Append(anExp.Current());
1452       theLength++;
1453     }
1454
1455   Standard_Integer nbs, NbSamples = 0;
1456   if (theLength <= 2)
1457     NbSamples = 4;
1458   for (i = ideb+1; i <= ifin; i++)
1459     {
1460       const TopoDS_Wire& wire = TopoDS::Wire(myWork(i));
1461       TopoDS_Wire newwire;
1462       BRep_Builder BB;
1463       BB.MakeWire(newwire);
1464       
1465       TopTools_SequenceOfShape SeqVertices, SeqEdges;
1466       for (anExp.Init(wire); anExp.More(); anExp.Next())
1467         {
1468           SeqVertices.Append( anExp.CurrentVertex() );
1469           SeqEdges.Append( anExp.Current() );
1470         }
1471       
1472       Standard_Real MinSumDist = Precision::Infinite();
1473       Standard_Integer jmin = 1, j, k, n;
1474       Standard_Boolean forward = Standard_False;
1475       if (i == myWork.Length() && myDegen2)
1476         {
1477           // last point section
1478           jmin = 1;
1479           forward = Standard_True;
1480         }
1481       else
1482         for (j = 1; j <= theLength; j++)
1483           {
1484             // get a vector to superpose SeqVertices(j) on PrevSeq(1)
1485             const TopoDS_Vertex& Vprev = TopoDS::Vertex( PrevSeq(1) );
1486             const TopoDS_Vertex& V = TopoDS::Vertex( SeqVertices(j) );
1487             gp_Vec curToPrevVec( BRep_Tool::Pnt(V), BRep_Tool::Pnt(Vprev) );
1488
1489             //Forward
1490             Standard_Real SumDist = 0.;
1491             for (k = j, n = 1; k <= theLength; k++, n++)
1492               {
1493                 const TopoDS_Vertex& Vprev = TopoDS::Vertex( PrevSeq(n) );
1494                 gp_Pnt Pprev = BRep_Tool::Pnt(Vprev);
1495                 const TopoDS_Vertex& V = TopoDS::Vertex( SeqVertices(k) );
1496                 gp_Pnt P = BRep_Tool::Pnt(V).XYZ() + curToPrevVec.XYZ();
1497                 SumDist += Pprev.Distance(P);
1498                 if (NbSamples > 0)
1499                 {
1500                   const TopoDS_Edge& PrevEdge = TopoDS::Edge(PrevEseq(n));
1501                   const TopoDS_Edge& CurEdge = TopoDS::Edge(SeqEdges(k));
1502                   BRepAdaptor_Curve PrevEcurve(PrevEdge);
1503                   BRepAdaptor_Curve Ecurve(CurEdge);
1504                   Standard_Real SampleOnPrev = (PrevEcurve.LastParameter()-PrevEcurve.FirstParameter())/NbSamples;
1505                   Standard_Real SampleOnCur = (Ecurve.LastParameter()-Ecurve.FirstParameter())/NbSamples;
1506                   for (nbs = 1; nbs <= NbSamples-1; nbs++)
1507                   {
1508                     Standard_Real ParOnPrev = (PrevEdge.Orientation() == TopAbs_FORWARD)?
1509                       (PrevEcurve.FirstParameter() + nbs*SampleOnPrev) :
1510                       (PrevEcurve.FirstParameter() + (NbSamples-nbs)*SampleOnPrev);
1511                     Standard_Real ParOnCur = (CurEdge.Orientation() == TopAbs_FORWARD)?
1512                       (Ecurve.FirstParameter() + nbs*SampleOnCur) :
1513                       (Ecurve.FirstParameter() + (NbSamples-nbs)*SampleOnCur);
1514                     gp_Pnt PonPrev = PrevEcurve.Value(ParOnPrev);
1515                     gp_Pnt PonCur = Ecurve.Value(ParOnCur).XYZ() + curToPrevVec.XYZ();
1516                     SumDist += PonPrev.Distance(PonCur);
1517                   }
1518                 }
1519               }
1520             for (k = 1; k < j; k++, n++)
1521               {
1522                 const TopoDS_Vertex& Vprev = TopoDS::Vertex( PrevSeq(n) );
1523                 gp_Pnt Pprev = BRep_Tool::Pnt(Vprev);
1524                 const TopoDS_Vertex& V = TopoDS::Vertex( SeqVertices(k) );
1525                 gp_Pnt P = BRep_Tool::Pnt(V).XYZ() + curToPrevVec.XYZ();
1526                 SumDist += Pprev.Distance(P);
1527                 if (NbSamples > 0)
1528                 {
1529                   const TopoDS_Edge& PrevEdge = TopoDS::Edge(PrevEseq(n));
1530                   const TopoDS_Edge& CurEdge = TopoDS::Edge(SeqEdges(k));
1531                   BRepAdaptor_Curve PrevEcurve(PrevEdge);
1532                   BRepAdaptor_Curve Ecurve(CurEdge);
1533                   Standard_Real SampleOnPrev = (PrevEcurve.LastParameter()-PrevEcurve.FirstParameter())/NbSamples;
1534                   Standard_Real SampleOnCur = (Ecurve.LastParameter()-Ecurve.FirstParameter())/NbSamples;
1535                   for (nbs = 1; nbs <= NbSamples-1; nbs++)
1536                   {
1537                     Standard_Real ParOnPrev = (PrevEdge.Orientation() == TopAbs_FORWARD)?
1538                       (PrevEcurve.FirstParameter() + nbs*SampleOnPrev) :
1539                       (PrevEcurve.FirstParameter() + (NbSamples-nbs)*SampleOnPrev);
1540                     Standard_Real ParOnCur = (CurEdge.Orientation() == TopAbs_FORWARD)?
1541                       (Ecurve.FirstParameter() + nbs*SampleOnCur) :
1542                       (Ecurve.FirstParameter() + (NbSamples-nbs)*SampleOnCur);
1543                     gp_Pnt PonPrev = PrevEcurve.Value(ParOnPrev);
1544                     gp_Pnt PonCur = Ecurve.Value(ParOnCur).XYZ() + curToPrevVec.XYZ();
1545                     SumDist += PonPrev.Distance(PonCur);
1546                   }
1547                 }
1548               }
1549             if (SumDist < MinSumDist)
1550               {
1551                 MinSumDist = SumDist;
1552                 jmin = j;
1553                 forward = Standard_True;
1554               }
1555             
1556             //Backward
1557             SumDist = 0.;
1558             for (k = j, n = 1; k >= 1; k--, n++)
1559               {
1560                 const TopoDS_Vertex& Vprev = TopoDS::Vertex( PrevSeq(n) );
1561                 gp_Pnt Pprev = BRep_Tool::Pnt(Vprev);
1562                 const TopoDS_Vertex& V = TopoDS::Vertex( SeqVertices(k) );
1563                 gp_Pnt P = BRep_Tool::Pnt(V).XYZ() + curToPrevVec.XYZ();
1564                 SumDist += Pprev.Distance(P);
1565                 if (NbSamples > 0)
1566                 {
1567                   Standard_Integer k_cur = k-1;
1568                   if (k_cur == 0)
1569                     k_cur = theLength;
1570                   const TopoDS_Edge& PrevEdge = TopoDS::Edge(PrevEseq(n));
1571                   const TopoDS_Edge& CurEdge = TopoDS::Edge(SeqEdges(k_cur));
1572                   BRepAdaptor_Curve PrevEcurve(PrevEdge);
1573                   BRepAdaptor_Curve Ecurve(CurEdge);
1574                   Standard_Real SampleOnPrev = (PrevEcurve.LastParameter()-PrevEcurve.FirstParameter())/NbSamples;
1575                   Standard_Real SampleOnCur = (Ecurve.LastParameter()-Ecurve.FirstParameter())/NbSamples;
1576                   for (nbs = 1; nbs <= NbSamples-1; nbs++)
1577                   {
1578                     Standard_Real ParOnPrev = (PrevEdge.Orientation() == TopAbs_FORWARD)?
1579                       (PrevEcurve.FirstParameter() + nbs*SampleOnPrev) :
1580                       (PrevEcurve.FirstParameter() + (NbSamples-nbs)*SampleOnPrev);
1581                     Standard_Real ParOnCur = (CurEdge.Orientation() == TopAbs_FORWARD)?
1582                       (Ecurve.FirstParameter() + (NbSamples-nbs)*SampleOnCur) :
1583                       (Ecurve.FirstParameter() + nbs*SampleOnCur);
1584                     gp_Pnt PonPrev = PrevEcurve.Value(ParOnPrev);
1585                     gp_Pnt PonCur = Ecurve.Value(ParOnCur).XYZ() + curToPrevVec.XYZ();
1586                     SumDist += PonPrev.Distance(PonCur);
1587                   }
1588                 }
1589               }
1590             for (k = theLength; k > j; k--, n++)
1591               {
1592                 const TopoDS_Vertex& Vprev = TopoDS::Vertex( PrevSeq(n) );
1593                 gp_Pnt Pprev = BRep_Tool::Pnt(Vprev);
1594                 const TopoDS_Vertex& V = TopoDS::Vertex( SeqVertices(k) );
1595                 gp_Pnt P = BRep_Tool::Pnt(V).XYZ() + curToPrevVec.XYZ();
1596                 SumDist += Pprev.Distance(P);
1597                 if (NbSamples > 0)
1598                 {
1599                   const TopoDS_Edge& PrevEdge = TopoDS::Edge(PrevEseq(n));
1600                   const TopoDS_Edge& CurEdge = TopoDS::Edge(SeqEdges(k-1));
1601                   BRepAdaptor_Curve PrevEcurve(PrevEdge);
1602                   BRepAdaptor_Curve Ecurve(CurEdge);
1603                   Standard_Real SampleOnPrev = (PrevEcurve.LastParameter()-PrevEcurve.FirstParameter())/NbSamples;
1604                   Standard_Real SampleOnCur = (Ecurve.LastParameter()-Ecurve.FirstParameter())/NbSamples;
1605                   for (nbs = 1; nbs <= NbSamples-1; nbs++)
1606                   {
1607                     Standard_Real ParOnPrev = (PrevEdge.Orientation() == TopAbs_FORWARD)?
1608                       (PrevEcurve.FirstParameter() + nbs*SampleOnPrev) :
1609                       (PrevEcurve.FirstParameter() + (NbSamples-nbs)*SampleOnPrev);
1610                     Standard_Real ParOnCur = (CurEdge.Orientation() == TopAbs_FORWARD)?
1611                       (Ecurve.FirstParameter() + (NbSamples-nbs)*SampleOnCur) :
1612                       (Ecurve.FirstParameter() + nbs*SampleOnCur);
1613                     gp_Pnt PonPrev = PrevEcurve.Value(ParOnPrev);
1614                     gp_Pnt PonCur = Ecurve.Value(ParOnCur).XYZ() + curToPrevVec.XYZ();
1615                     SumDist += PonPrev.Distance(PonCur);
1616                   }
1617                 }
1618               }
1619             if (SumDist < MinSumDist)
1620               {
1621                 MinSumDist = SumDist;
1622                 jmin = j;
1623                 forward = Standard_False;
1624               }
1625           }
1626       
1627       PrevSeq.Clear();
1628       PrevEseq.Clear();
1629       if (forward)
1630         {
1631           for (j = jmin; j <= theLength; j++)
1632             {
1633               BB.Add( newwire, TopoDS::Edge(SeqEdges(j)) );
1634               PrevSeq.Append( SeqVertices(j) );
1635               PrevEseq.Append( SeqEdges(j) );
1636             }
1637           for (j = 1; j < jmin; j++)
1638             {
1639               BB.Add( newwire, TopoDS::Edge(SeqEdges(j)) );
1640               PrevSeq.Append( SeqVertices(j) );
1641               PrevEseq.Append( SeqEdges(j) );
1642             }
1643         }
1644       else
1645         {
1646           for (j = jmin-1; j >= 1; j--)
1647             {
1648               TopoDS_Shape aLocalShape = SeqEdges(j).Reversed();
1649               BB.Add( newwire, TopoDS::Edge(aLocalShape) );
1650               //PrevSeq.Append( SeqVertices(j) );
1651               PrevEseq.Append( SeqEdges(j).Reversed() );
1652             }
1653           for (j = theLength; j >= jmin; j--)
1654             {
1655               TopoDS_Shape aLocalShape = SeqEdges(j).Reversed();
1656               BB.Add( newwire, TopoDS::Edge(aLocalShape) );
1657               //PrevSeq.Append( SeqVertices(j) );
1658               PrevEseq.Append( SeqEdges(j).Reversed() );
1659             }
1660           for (j = jmin; j >= 1; j--)
1661             PrevSeq.Append( SeqVertices(j) );
1662           for (j = theLength; j > jmin; j--)
1663             PrevSeq.Append( SeqVertices(j) );
1664         }
1665       
1666       newwire.Closed( Standard_True );
1667       newwire.Orientation( TopAbs_FORWARD );
1668       myWork(i) = newwire;
1669     }
1670 #ifdef DEB_EFV
1671
1672   for ( i=ideb; i<=myWork.Length(); i++) {
1673     
1674     const TopoDS_Wire& wire = TopoDS::Wire(myWork(i));
1675     
1676     Standard_Integer nbEdges=0;
1677     for(anExp.Init(TopoDS::Wire(myWork(i))); anExp.More(); anExp.Next())
1678       nbEdges++;
1679     TopExp::Vertices(wire,Vdeb,Vfin);
1680     Standard_Boolean wClosed = wire.Closed();
1681     if (!wClosed) {
1682       // on regarde quand meme si les vertex sont les memes.
1683       if ( Vdeb.IsSame(Vfin)) wClosed = Standard_True;
1684     }
1685     
1686     
1687     TopoDS_Vertex Vsuiv, VF, VR;
1688     TopoDS_Wire newwire;
1689     BRep_Builder BW;
1690     BW.MakeWire(newwire);
1691     if (i==ideb) {
1692       anExp.Init(wire);
1693       const TopoDS_Edge Ecur = TopoDS::Edge(anExp.Current());
1694       TopExp::Vertices(Ecur,VF,VR);
1695       if (Vdeb.IsSame(VF)) Vsuiv=VR;
1696       else if (Vdeb.IsSame(VR)) Vsuiv=VF;
1697       else {
1698         // par defaut on prend l'origine sur cette arete
1699         if (VR.IsSame(TopoDS::Vertex(anExp.CurrentVertex()))) {
1700           Vdeb = VR;
1701           Vsuiv = VF;
1702         }
1703         else {
1704           Vdeb = VF;
1705           Vsuiv = VR;
1706         }
1707       }
1708       Pdeb=BRep_Tool::Pnt(Vdeb);
1709       Psuiv=BRep_Tool::Pnt(Vsuiv);
1710       Standard_Real U1 = BRep_Tool::Parameter(Vdeb,Ecur);
1711       Standard_Real U2 = BRep_Tool::Parameter(Vsuiv,Ecur);
1712       BRepAdaptor_Curve Curve(Ecur);
1713       PPs = Curve.Value(0.25*(U1+3*U2));
1714       myWork(ideb) = wire;
1715     }
1716     else {
1717       // on ramene Pdeb, Psuiv et PPs dans le plan courant
1718       gp_Pnt Pnew,Pnext,PPn; 
1719       Transform(Standard_True,Pdeb,Pos->Value(i-1),Axe->Value(i-1), 
1720                               Pos->Value(i),Axe->Value(i),Pnew);
1721       Transform(Standard_True,Psuiv,Pos->Value(i-1),Axe->Value(i-1), 
1722                               Pos->Value(i),Axe->Value(i),Pnext);
1723       Transform(Standard_True,PPs,Pos->Value(i-1),Axe->Value(i-1), 
1724                               Pos->Value(i),Axe->Value(i),PPn);
1725       
1726       Standard_Real distmini,dist;
1727       Standard_Integer rang=0,rangdeb=0;
1728       TopoDS_Vertex Vmini;
1729       gp_Pnt Pmini,P1,P2;
1730       SeqOfVertices(wire,SeqV);
1731       if (SeqV.Length()>NbMaxV) 
1732         Standard_NoSuchObject::Raise("BRepFill::ComputeOrigin failed");
1733       if (!polar) {
1734         // choix du vertex le plus proche comme origine
1735         distmini = Precision::Infinite();
1736         for (Standard_Integer ii=1;ii<=SeqV.Length();ii++) {
1737           P1 = BRep_Tool::Pnt(TopoDS::Vertex(SeqV.Value(ii)));
1738           dist = P1.Distance(Pnew);
1739           if (dist<distmini) {
1740             distmini = dist;
1741             Vmini = TopoDS::Vertex(SeqV.Value(ii));
1742           }
1743         }
1744         if (!Vmini.IsNull()) Pmini = BRep_Tool::Pnt(Vmini);
1745       }
1746       else {
1747         
1748         // recherche du vertex correspondant a la projection conique
1749         Standard_Real angmin, angV, eta = Precision::Angular();
1750         TopoDS_Vertex Vopti;
1751         angmin = M_PI/2;
1752         distmini = Precision::Infinite();
1753         gp_Dir dir0(gp_Vec(Pnew,P.Location()));
1754         for (Standard_Integer ii=1;ii<=SeqV.Length();ii++) {
1755           P1 = BRep_Tool::Pnt(TopoDS::Vertex(SeqV.Value(ii)));
1756           dist = Pnew.Distance(P1);
1757           if (dist<Precision::Confusion()) {
1758             angV = 0.0;
1759           }
1760           else {
1761             gp_Dir dir1(gp_Vec(Pnew,P1));
1762             angV = dir1.Angle(dir0);
1763           }
1764           if (angV>M_PI/2) angV = M_PI - angV;
1765           if (angmin>angV+eta) {
1766             distmini = dist;
1767             angmin = angV;
1768             Vopti = TopoDS::Vertex(SeqV.Value(ii));
1769           }
1770           else if (Abs(angmin-angV)<eta) {
1771             if (dist<distmini) {
1772               distmini = dist;
1773               angmin = angV;
1774               Vopti = TopoDS::Vertex(SeqV.Value(ii));
1775             }
1776           }
1777         }
1778         gp_Pnt Popti;
1779         if (!Vopti.IsNull()) Popti = BRep_Tool::Pnt(Vopti);
1780         Vmini = Vopti;
1781         
1782       }
1783
1784       distmini = Precision::Infinite();
1785       for (anExp.Init(wire); anExp.More(); anExp.Next()) {
1786         TopoDS_Edge Ecur = anExp.Current();
1787         TopoDS_Vertex Vcur = anExp.CurrentVertex();
1788         TopExp::Vertices(Ecur,VF,VR);
1789         if (VF.IsSame(Vmini)) {
1790           P1 = BRep_Tool::Pnt(VR);
1791           dist = P1.Distance(Pnext);
1792           if (dist<=distmini) {
1793             distmini = dist;
1794             Vsuiv = VR;
1795           }
1796         }
1797         if (VR.IsSame(Vmini)) {
1798           P1 = BRep_Tool::Pnt(VF);
1799           dist = P1.Distance(Pnext);
1800           if (dist<distmini) {
1801             distmini = dist;
1802             Vsuiv = VF;
1803           }
1804         }
1805       }
1806       
1807       // choix du sens de parcours en fonction de Pnext
1808       Standard_Boolean parcours = Standard_False;
1809       if (i==myWork.Length() && myDegen2) {
1810         // derniere section ponctuelle
1811         rangdeb = 1;
1812         parcours = Standard_True;
1813       }
1814       else {
1815         // cas general
1816         gp_Pnt Pbout = Pnext;
1817         TopoDS_Edge E1,E2;
1818         TopoDS_Vertex V1,V2;
1819         EdgesFromVertex(wire,Vmini,E1,E2);
1820         
1821         TopExp::Vertices(E1,V1,V2,Standard_True);
1822 #ifndef DEB
1823         Standard_Real U1=0, U2=0;
1824 #else
1825         Standard_Real U1, U2;
1826 #endif
1827         if (Vmini.IsSame(V1)) { 
1828           P1 = BRep_Tool::Pnt(V2);
1829           U1 = 0.25*(BRep_Tool::Parameter(V1,E1)+3*BRep_Tool::Parameter(V2,E1));
1830         }
1831         if (Vmini.IsSame(V2)) {
1832           P1 = BRep_Tool::Pnt(V1);
1833           U1 = 0.25*(3*BRep_Tool::Parameter(V1,E1)+BRep_Tool::Parameter(V2,E1));
1834         }
1835         
1836         TopExp::Vertices(E2,V1,V2,Standard_True);
1837         if (Vmini.IsSame(V1)) { 
1838           P2 = BRep_Tool::Pnt(V2);
1839           U2 = 0.25*(BRep_Tool::Parameter(V1,E2)+3*BRep_Tool::Parameter(V2,E2));
1840         }
1841         if (Vmini.IsSame(V2)) {
1842           P2 = BRep_Tool::Pnt(V1);
1843           U2 = 0.25*(3*BRep_Tool::Parameter(V1,E2)+BRep_Tool::Parameter(V2,E2));
1844         }
1845         
1846         if (Abs(Pbout.Distance(P1)-Pbout.Distance(P2))<Precision::Confusion()) {
1847           // cas limite ; on se decale un peu
1848           Pbout = PPn;
1849           BRepAdaptor_Curve Curve1(E1);
1850           P1 = Curve1.Value(U1);
1851           BRepAdaptor_Curve Curve2(E2);
1852           P2 = Curve2.Value(U2);
1853         }
1854         
1855         // calcul de rangdeb
1856         rangdeb = 0;
1857         if (Pbout.Distance(P1)<Pbout.Distance(P2)){
1858           // P1 est plus proche; parcours = False
1859           parcours = Standard_False;
1860           rang = 0;
1861           for (anExp.Init(wire); anExp.More(); anExp.Next()) {
1862             rang++;
1863             TopoDS_Edge Ecur = anExp.Current();
1864             if (E1.IsSame(Ecur)) {
1865               rangdeb = rang;
1866             }
1867           }
1868           BRepAdaptor_Curve Curve(E1);
1869           PPs = Curve.Value(U1);
1870         }
1871         else {
1872           // P2 est plus proche; parcours = True
1873           parcours = Standard_True;
1874           rang = 0;
1875           for (anExp.Init(wire); anExp.More(); anExp.Next()) {
1876             rang++;
1877             TopoDS_Edge Ecur = anExp.Current();
1878             if (E2.IsSame(Ecur)) {
1879               rangdeb = rang;
1880             }
1881           }
1882           BRepAdaptor_Curve Curve(E2);
1883           PPs = Curve.Value(U2);
1884         }
1885       }
1886
1887       // reconstruction du wire a partir de rangdeb
1888       TopTools_SequenceOfShape SeqEdges;
1889       SeqEdges.Clear();
1890       for (anExp.Init(TopoDS::Wire(wire)); anExp.More(); anExp.Next()) {
1891         SeqEdges.Append(anExp.Current());
1892       }
1893       if (parcours) {
1894         for (rang=rangdeb;rang<=nbEdges;rang++) {
1895           BW.Add(newwire,TopoDS::Edge(SeqEdges.Value(rang)));
1896         }
1897         for (rang=1;rang<rangdeb;rang++) {
1898           BW.Add(newwire,TopoDS::Edge(SeqEdges.Value(rang)));
1899         }
1900       }
1901       else {
1902         for (rang=rangdeb;rang>=1;rang--) {
1903           TopoDS_Shape aLocalShape = SeqEdges.Value(rang).Reversed();
1904           BW.Add(newwire,TopoDS::Edge(aLocalShape));
1905 //        BW.Add(newwire,TopoDS::Edge(SeqEdges.Value(rang).Reversed()));
1906         }
1907         for (rang=nbEdges;rang>rangdeb;rang--) {
1908           TopoDS_Shape aLocalShape = SeqEdges.Value(rang).Reversed();
1909           BW.Add(newwire,TopoDS::Edge(aLocalShape));
1910 //        BW.Add(newwire,TopoDS::Edge(SeqEdges.Value(rang).Reversed()));
1911         }
1912       }
1913       
1914       myWork(i) = newwire.Oriented(TopAbs_FORWARD);
1915       
1916       // on passe au wire suivant
1917       if (!Vmini.IsNull()) Pdeb=BRep_Tool::Pnt(Vmini);
1918       if (!Vsuiv.IsNull()) Psuiv=BRep_Tool::Pnt(Vsuiv);
1919     }
1920   }
1921 #endif
1922   
1923   // blocking sections ?
1924   if (vClosed) myWork(myWork.Length()) = myWork(1);
1925 }
1926
1927 //=======================================================================
1928 //function : SearchOrigin
1929 //purpose  : 
1930 //=======================================================================
1931
1932 void BRepFill_CompatibleWires::SearchOrigin()
1933 {
1934   // reorganize the open wires respecting orientation and origin
1935   
1936   gp_Pln P0,P;  
1937
1938   TopoDS_Vertex Vdeb, Vfin;
1939   gp_Pnt Pdeb,  Pfin;//,Psuiv;
1940
1941   BRepTools_WireExplorer anExp;
1942
1943   Standard_Boolean allOpen = Standard_True;
1944   Standard_Integer ideb=1, ifin=myWork.Length();
1945   if (myDegen1) ideb++;
1946   if (myDegen2) ifin--;
1947   Standard_Boolean vClosed = (!myDegen1) && (!myDegen2)
1948                                 && (myWork(ideb).IsSame(myWork(ifin)));
1949   
1950 //  for (Standard_Integer i=ideb; i<=ifin; i++) {
1951   Standard_Integer i;
1952   for  (i=ideb; i<=ifin; i++) {
1953     allOpen = (allOpen && !myWork(i).Closed());
1954   }
1955   if (!allOpen)
1956     Standard_NoSuchObject::Raise("BRepFill_CompatibleWires::SearchOrigin : the wires must be open");
1957
1958   // init
1959
1960   TopoDS_Wire wire1 = TopoDS::Wire(myWork(ideb));
1961   wire1.Orientation(TopAbs_FORWARD);
1962   TopExp::Vertices(wire1,Vdeb,Vfin);
1963   Pdeb = BRep_Tool::Pnt(Vdeb);
1964   Pfin = BRep_Tool::Pnt(Vfin);
1965   Standard_Boolean isline0 = (!PlaneOfWire(wire1,P0)), isline;
1966   myWork(ideb) = wire1;
1967   //OCC86
1968   anExp.Init(wire1);
1969   TopoDS_Edge E0 = anExp.Current(), E;
1970
1971   for ( i=ideb+1; i<=ifin; i++) {
1972
1973     TopoDS_Wire wire = TopoDS::Wire(myWork(i));
1974     wire.Orientation(TopAbs_FORWARD);
1975
1976     TopTools_SequenceOfShape SeqEdges;
1977     SeqEdges.Clear();
1978     Standard_Integer nbEdges=0;
1979     //OCC86  for(anExp.Init(wire); anExp.More(); anExp.Next()) {
1980     for(anExp.Init(wire), E = anExp.Current(); anExp.More(); anExp.Next()) {
1981       SeqEdges.Append(anExp.Current());
1982       nbEdges++;
1983     }
1984     TopExp::Vertices(wire,Vdeb,Vfin);
1985     isline = (!PlaneOfWire(wire,P));
1986
1987     TopoDS_Vertex Vmini;
1988     TopoDS_Wire newwire;
1989     BRep_Builder BW;
1990     BW.MakeWire(newwire);
1991     Standard_Boolean parcours = Standard_True;
1992
1993     if (isline0 || isline) {
1994       
1995       // particular case of straight segments 
1996       gp_Pnt P1 = BRep_Tool::Pnt(Vdeb),
1997              P2 = BRep_Tool::Pnt(Vfin);
1998       Standard_Real dist1, dist2;
1999       dist1 = Pdeb.Distance(P1)+Pfin.Distance(P2);
2000       dist2 = Pdeb.Distance(P2)+Pfin.Distance(P1);
2001       parcours = (dist2>=dist1);
2002     }
2003     
2004     else {
2005       //OCC86
2006       gp_Pnt P1 = BRep_Tool::Pnt(Vdeb), P1o = Pdeb,
2007              P2 = BRep_Tool::Pnt(Vfin), P2o = Pfin;
2008 /*    // return Pdeb in the current plane
2009       gp_Pnt Pnew = Pdeb.Translated (P0.Location(),P.Location());
2010       gp_Ax1 A0 = P0.Axis();
2011       gp_Ax1 A1 = P.Axis();
2012       
2013       if (!A0.IsParallel(A1,1.e-4)) {
2014         gp_Vec vec1(A0.Direction()), vec2(A1.Direction()), 
2015         norm = vec1 ^ vec2;
2016         gp_Ax1 Norm(P.Location(),norm);
2017         Standard_Real ang = vec1.AngleWithRef(vec2,norm);
2018         if (ang > M_PI/2.0)
2019           ang = M_PI - ang;
2020         if (ang < -M_PI/2.0)
2021           ang = -M_PI - ang;
2022         if (Abs(ang-M_PI/2.0)<Precision::Angular()) {
2023           // cas d'ambiguite
2024           gp_Vec Vtrans(P0.Location(),P.Location()),Vsign;
2025           Standard_Real alpha,beta,sign=1;
2026           Vsign.SetLinearForm(Vtrans.Dot(vec1),vec2,-Vtrans.Dot(vec2),vec1);
2027           alpha = Vsign.Dot(vec1);
2028           beta = Vsign.Dot(vec2);
2029           Standard_Boolean pasnul = (Abs(alpha)>1.e-4 && Abs(beta)>1.e-4);
2030           if ( alpha*beta>0.0 && pasnul ) sign=-1;
2031           ang *= sign;
2032         }
2033         Pnew = Pnew.Rotated (Norm,ang);
2034       }
2035       // choix entre Vdeb et Vfin
2036       Standard_Real dist = Pnew.Distance(P1);
2037       parcours = (dist<Pnew.Distance(P2));
2038 */      
2039       if(P1.IsEqual(P2,Precision::Confusion()) || P1o.IsEqual(P2o,Precision::Confusion())){
2040         BRepAdaptor_Curve Curve0(E0), Curve(E);
2041         Curve0.D0(Curve0.FirstParameter() + Precision::Confusion(), P2o);
2042         Curve.D0(Curve.FirstParameter() + Precision::Confusion(), P2);
2043       };
2044       gp_Vec VDebFin0(P1o,P2o), VDebFin(P1,P2);
2045       Standard_Real AStraight = VDebFin0.Angle(VDebFin);
2046       parcours = (AStraight < M_PI/2.0? Standard_True: Standard_False);
2047     }
2048     
2049     // reconstruction of the wire
2050     Standard_Integer rang;
2051     if (parcours) {
2052       for (rang=1;rang<=nbEdges;rang++) {
2053         TopoDS_Shape alocalshape = SeqEdges.Value(rang);
2054         BW.Add(newwire,TopoDS::Edge(alocalshape));
2055 //      BW.Add(newwire,TopoDS::Edge(SeqEdges.Value(rang)));
2056       }
2057     }
2058     else {
2059       for (rang=nbEdges;rang>=1;rang--) {
2060         TopoDS_Shape alocalshape = SeqEdges.Value(rang).Reversed();
2061         BW.Add(newwire,TopoDS::Edge(alocalshape));
2062 //      BW.Add(newwire,TopoDS::Edge(SeqEdges.Value(rang).Reversed()));
2063       }
2064     }
2065
2066     // orientation of the wire
2067     newwire.Oriented(TopAbs_FORWARD);
2068     myWork(i) = newwire;
2069
2070     // passe to the next wire 
2071     if (parcours) {
2072       Pdeb = BRep_Tool::Pnt(Vdeb);
2073       Pfin = BRep_Tool::Pnt(Vfin);
2074     }
2075     else {
2076       Pfin = BRep_Tool::Pnt(Vdeb);
2077       Pdeb = BRep_Tool::Pnt(Vfin);
2078     }
2079     P0 = P;
2080     isline0 = isline;
2081     //OCC86
2082     E0 = E;
2083   }
2084   
2085   // blocking sections ?
2086   if (vClosed) myWork(myWork.Length()) = myWork(1);
2087 }