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