0025468: GeomConvert_ApproxSurface should have a constructor for adaptors
[occt.git] / src / GeomConvert / GeomConvert.cdl
1 -- Created on: 1991-10-03
2 -- Created by: JeanClaude VAUTHIER 
3 -- Copyright (c) 1991-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 --  Modified : 07/10/97 : JPI/RBV/SMN  : traitement des courbes offset
18 --  et surfaces offset par approximation 
19
20
21 package GeomConvert
22
23         --- Purpose : The GeomConvert package provides some global functions as follows
24         -- -   converting classical Geom curves into BSpline curves,
25         -- -   segmenting BSpline curves, particularly at knots
26         --   values: this function may be used in conjunction with the
27         --   GeomConvert_BSplineCurveKnotSplitting
28         --   class to segment a BSpline curve into arcs which
29         --   comply with required continuity levels,
30         -- -   converting classical Geom surfaces into BSpline surfaces, and
31         -- -   segmenting BSpline surfaces, particularly at
32         --   knots values: this function may be used in conjunction with the
33         --   GeomConvert_BSplineSurfaceKnotSplitting
34         --   class to segment a BSpline surface into patches
35         --   which comply with required continuity levels.
36         --  All geometric entities used in this package are bounded.
37         --  
38         -- References :
39         --  . Generating the Bezier Points of B-spline curves and surfaces
40         --    (Wolfgang Bohm) CAGD volume 13 number 6 november 1981
41         --  . On NURBS: A Survey  (Leslie Piegl) IEEE Computer Graphics and
42         --    Application January 1991
43         --  . Curve and surface construction using rational B-splines 
44         --    (Leslie Piegl and Wayne Tiller) CAD Volume 19 number 9 november
45         --    1987
46         --  . A survey of curve and surface methods in CAGD (Wolfgang BOHM)
47         --    CAGD 1 1984
48
49
50 uses    Standard, 
51         TColStd,
52         TColGeom, 
53         TColgp,
54         GeomAbs,
55         gp, 
56         Geom,
57         Geom2d,
58         Convert, 
59         AdvApp2Var,
60         Adaptor3d
61             
62
63 is
64  
65   class BSplineCurveKnotSplitting;
66
67   class BSplineSurfaceKnotSplitting;
68
69   class BSplineCurveToBezierCurve;
70
71   class CompCurveToBSplineCurve;
72
73   class BSplineSurfaceToBezierSurface;
74
75  class CompBezierSurfacesToBSplineSurface;
76
77  class  ApproxSurface;  
78
79  class  ApproxCurve;  
80         ---Purpose: Convert a curve from Geom by an approximation method
81             --
82   SplitBSplineCurve (C               : BSplineCurve from Geom; 
83                      FromK1, ToK2    : Integer;
84                      SameOrientation : Boolean = Standard_True)
85      returns BSplineCurve from Geom
86          --- Purpose : 
87          --  This method computes the arc of B-spline curve between the two 
88          --  knots FromK1 and ToK2.  If C is periodic the arc has the same
89          --  orientation as C if SameOrientation = Standard_True.  
90          --  If C is not periodic  SameOrientation is not used for the
91          --  computation and C is oriented from the knot fromK1 to the knot toK2.  
92          --  We just keep the local definition of C between the knots
93          --  FromK1 and ToK2.  The returned B-spline curve has its first
94          --  and last knots with a multiplicity equal to degree + 1, where
95          --  degree is the polynomial degree of C.
96          --  The indexes of the knots FromK1 and ToK2 doesn't include the
97          --  repetition of multiple knots in their definition.
98      raises  DomainError from Standard;
99          --- Purpose :  Raised if FromK1 = ToK2
100          --             Raised if FromK1 or ToK2 are out of the bounds 
101          --             [FirstUKnotIndex, LastUKnotIndex]
102
103
104
105   SplitBSplineCurve (C                   : BSplineCurve from Geom; 
106                      FromU1, ToU2        : Real;
107                      ParametricTolerance : Real;
108                      SameOrientation     : Boolean = Standard_True)
109      returns BSplineCurve from Geom
110         --- Purpose :
111         --  This function computes the segment of B-spline curve between the 
112         --  parametric values FromU1, ToU2.
113         --  If C is periodic the arc has the same orientation as C if
114         --  SameOrientation = True.  
115         --  If C is not periodic SameOrientation is not used for the 
116         --  computation and C is oriented fromU1 toU2. 
117         --  If U1 and U2 and two parametric values we consider that 
118         --  U1 = U2 if Abs (U1 - U2) <= ParametricTolerance and 
119         --  ParametricTolerance must  be greater or equal to Resolution
120         --  from package gp.
121      raises DomainError from Standard;
122         --- Purpose :
123         --  Raised if FromU1 or ToU2 are out of the parametric bounds of the
124         --  curve (The tolerance criterion is ParametricTolerance).
125         --  Raised if Abs (FromU1 - ToU2) <= ParametricTolerance
126         --  Raised if ParametricTolerance < Resolution from gp.
127
128
129
130   SplitBSplineSurface (S : BSplineSurface from Geom; 
131                        FromUK1, ToUK2, FromVK1, ToVK2 : Integer; 
132                        SameUOrientation : Boolean = Standard_True;
133                        SameVOrientation : Boolean = Standard_True)
134      returns BSplineSurface from Geom
135         --- Purpose : 
136         --  Computes the B-spline surface patche between the knots values
137         --  FromUK1, ToUK2, FromVK1, ToVK2.
138         --  If S is periodic in one direction the patche has the same 
139         --  orientation as S in this direction if the flag is true in this
140         --  direction (SameUOrientation, SameVOrientation).
141         --  If S is not periodic SameUOrientation and SameVOrientation are not
142         --  used for the computation and S is oriented FromUK1 ToUK2 and 
143         --  FromVK1 ToVK2.
144      raises DomainError from Standard;
145         --- Purpose :  Raised if 
146         --             FromUK1 = ToUK2 or FromVK1 = ToVK2
147         --             FromUK1 or ToUK2 are out of the bounds 
148         --             [FirstUKnotIndex, LastUKnotIndex]
149         --             FromVK1 or ToVK2 are out of the bounds 
150         --             [FirstVKnotIndex, LastVKnotIndex]
151
152
153
154   SplitBSplineSurface (S : BSplineSurface from Geom; 
155                        FromK1, ToK2    : Integer;
156                        USplit          : Boolean;
157                        SameOrientation : Boolean = Standard_True)
158      returns BSplineSurface from Geom
159         --- Purpose : 
160         --  This method splits a B-spline surface patche between the
161         --  knots values FromK1, ToK2 in one direction.
162         --  If USplit = True then the splitting direction is the U parametric
163         --  direction else it is the V parametric direction.
164         --  If S is periodic in the considered direction the patche has the
165         --  same orientation as S in this direction if SameOrientation is True
166         --  If S is not periodic in this direction SameOrientation is not used
167         --  for the computation and S is oriented FromK1 ToK2.
168      raises  DomainError from Standard;
169         --- Purpose : Raised if FromK1 = ToK2 or if
170         --            FromK1 or ToK2 are out of the bounds 
171         --            [FirstUKnotIndex, LastUKnotIndex] in the 
172         --            considered parametric direction.
173
174
175   SplitBSplineSurface (S : BSplineSurface from Geom; 
176                        FromU1, ToU2, FromV1, ToV2 : Real; 
177                        ParametricTolerance        : Real;
178                        SameUOrientation           : Boolean = Standard_True;
179                        SameVOrientation           : Boolean = Standard_True)
180      returns BSplineSurface from Geom
181         --- Purpose :
182         --  This method computes the B-spline surface patche between the
183         --  parametric values FromU1, ToU2, FromV1, ToV2.
184         --  If S is periodic in one direction the patche has the same 
185         --  orientation as S in this direction if the flag is True in this
186         --  direction (SameUOrientation, SameVOrientation).
187         --  If S is not periodic SameUOrientation and SameVOrientation are not
188         --  used for the computation and S is oriented FromU1 ToU2 and 
189         --  FromV1 ToV2.
190         --  If U1 and U2 and two parametric values we consider that U1 = U2 if
191         --  Abs (U1 - U2) <= ParametricTolerance and ParametricTolerance must
192         --  be greater or equal to Resolution from package gp.
193      raises DomainError from Standard;
194         --- Purpose :
195         --  Raised if FromU1 or ToU2 or FromV1 or ToU2 are out of the 
196         --  parametric bounds of the surface (the tolerance criterion is
197         --  ParametricTolerance).
198         --  Raised if Abs (FromU1 - ToU2) <= ParametricTolerance or
199         --  Abs (FromV1 - ToV2) <= ParametricTolerance.
200         --  Raised if ParametricTolerance < Resolution.
201
202
203
204   SplitBSplineSurface (S : BSplineSurface from Geom; 
205                        FromParam1, ToParam2 : Real;
206                        USplit               : Boolean; 
207                        ParametricTolerance  : Real;
208                        SameOrientation      : Boolean = Standard_True)
209      returns BSplineSurface from Geom
210         --- Purpose : 
211         --  This method splits the B-spline surface S in one direction
212         --  between the parametric values FromParam1, ToParam2.
213         --  If USplit = True then the Splitting direction is the U parametric
214         --  direction else it is the V parametric direction.
215         --  If S is periodic in the considered direction the patche has 
216         --  the same orientation as S in this direction if SameOrientation 
217         --  is true.
218         --  If S is not periodic in the considered direction SameOrientation 
219         --  is not used for the computation and S is oriented FromParam1 
220         --  ToParam2.
221         --  If U1 and U2 and two parametric values we consider that U1 = U2 
222         --  if Abs (U1 - U2) <= ParametricTolerance and ParametricTolerance
223         --  must be greater or equal to Resolution from package gp.
224      raises DomainError from Standard;
225         --- Purpose :
226         --  Raises if FromParam1 or ToParam2 are out of the parametric bounds
227         --  of the surface in the considered direction.
228         --  Raises if Abs (FromParam1 - ToParam2) <= ParametricTolerance.
229
230
231   CurveToBSplineCurve (C                : Curve from Geom ;
232                        Parameterisation : ParameterisationType from Convert 
233                        =  Convert_TgtThetaOver2)
234      returns BSplineCurve from Geom
235         --- Purpose : This function converts a non infinite curve from
236         --  Geom into a  B-spline curve.  C must be   an ellipse or  a
237         --  circle  or a trimmed conic  or a trimmed  line or a Bezier
238         --  curve or a trimmed  Bezier curve or a  BSpline curve or  a
239         --  trimmed  BSpline curve or  an  OffsetCurve.  The returned  B-spline is
240         --  not periodic except  if C is a Circle  or an  Ellipse.  If
241         --   the  Parameterisation is  QuasiAngular than  the returned
242         --   curve is NOT periodic  in case a  periodic Geom_Circle or
243         --  Geom_Ellipse.  For TgtThetaOver2_1 and TgtThetaOver2_2 the
244         --   method   raises  an exception  in    case  of a  periodic
245         --  Geom_Circle or a Geom_Ellipse ParameterisationType applies
246         --   only    if  the curve  is   a  Circle  or  an   ellipse :
247         --  TgtThetaOver2,  -- TgtThetaOver2_1, -- TgtThetaOver2_2, --
248         --  TgtThetaOver2_3, -- TgtThetaOver2_4,
249         --    
250         -- Purpose: this is the classical rational parameterisation
251         --                    2
252         --               1 - t
253         --  cos(theta) = ------
254         --                    2
255         --               1 + t
256         --                   
257         --                 2t
258         --  sin(theta) = ------
259         --                     2
260         --                1 + t
261         --                   
262         --  t = tan (theta/2)        
263         -- 
264         --  with TgtThetaOver2  the routine will compute the number of spans
265         --  using the rule num_spans = [ (ULast - UFirst) / 1.2 ] + 1 
266         --  with TgtThetaOver2_N, N  spans will be forced: an error will 
267         --  be raized if (ULast - UFirst) >= PI and N = 1,
268         --  ULast - UFirst >= 2 PI and N = 2
269         --   
270         -- QuasiAngular,
271         --  here t is a rational function that approximates  
272         --  theta ----> tan(theta/2).
273         --  Neverthless the composing with above function yields exact
274         --  functions whose square sum up to 1
275         -- RationalC1 ;
276         --  t is replaced by a polynomial function of u so as to grant
277         --  C1 contiuity across knots.
278         -- Exceptions 
279         --        Standard_DomainError:
280         -- -   if the curve C is infinite, or
281         -- -   if C is a (complete) circle or ellipse, and Parameterisation is equal to
282         --   Convert_TgtThetaOver2_1 or Convert_TgtThetaOver2_2.
283         --   Standard_ConstructionError:
284         -- -   if C is a (complete) circle or ellipse, and if Parameterisation is not equal to
285         --   Convert_TgtThetaOver2, Convert_RationalC1,
286         --   Convert_QuasiAngular (the curve is converted
287         --   in these three cases) or to Convert_TgtThetaOver2_1 or
288         --   Convert_TgtThetaOver2_2 (another exception is raised in these two cases).
289         -- -   if C is a trimmed circle or ellipse, if Parameterisation is equal to
290         --   Convert_TgtThetaOver2_1 and if U2 - U1 > 0.9999 * Pi, where U1 and U2 are
291         --   respectively the first and the last parameters of the
292         --   trimmed curve (this method of parameterization
293         --   cannot be used to convert a half-circle or a half-ellipse, for example), or
294         -- -   if C is a trimmed circle or ellipse, if
295         --   Parameterisation is equal to Convert_TgtThetaOver2_2 and U2 - U1 >
296         --   1.9999 * Pi where U1 and U2 are
297         --   respectively the first and the last parameters of the
298         --   trimmed curve (this method of parameterization
299         --   cannot be used to convert a quasi-complete circle or ellipse). 
300      raises DomainError,
301             ConstructionError;
302         
303   SurfaceToBSplineSurface (S : Surface from Geom)
304      returns BSplineSurface from Geom
305         --- Purpose : 
306         --  This algorithm converts a non infinite surface from Geom
307         --  into a B-spline surface.
308         --  S must be a trimmed plane or a trimmed cylinder or a trimmed cone
309         --  or a trimmed sphere or a trimmed torus or a sphere or a torus or
310         --  a Bezier surface of a trimmed Bezier surface or a trimmed swept
311         --  surface with a corresponding basis curve which can be turned into
312         --  a B-spline curve   (see the method CurveToBSplineCurve).
313         --  Raises DomainError if the type of the surface is not previously defined.
314      raises DomainError;
315       
316   ConcatG1(ArrayOfCurves  : in out Array1OfBSplineCurve from TColGeom;
317            ArrayOfToler   : in           Array1OfReal   from TColStd;
318            ArrayOfConcatenated    : out  HArray1OfBSplineCurve from TColGeom;
319            ClosedG1Flag           : in   Boolean                from Standard ;
320            ClosedTolerance        : in   Real                   from Standard) ;
321            
322         --- Purpose : This Method concatenates G1 the ArrayOfCurves as far
323         --  as it  is possible.  
324         --  ArrayOfCurves[0..N-1]
325         --  ArrayOfToler contains the  biggest tolerance of the two
326         --               points shared by two consecutives curves.
327         --               Its dimension: [0..N-2]
328         --  ClosedG1     indicates if the ArrayOfCurves is closed.
329         --               In this case ClosedG1 contains the biggest tolerance
330         --               of the two points which are at the closure.
331         --               Otherwise its value is 0.0
332
333
334   ConcatC1(ArrayOfCurves  : in out Array1OfBSplineCurve from TColGeom;
335            ArrayOfToler   : in           Array1OfReal   from TColStd;
336            ArrayOfIndices : out        HArray1OfInteger from TColStd;
337            ArrayOfConcatenated    : out  HArray1OfBSplineCurve from TColGeom;
338            ClosedG1Flag           : in   Boolean                 from Standard ;
339            ClosedTolerance        : in   Real                   from Standard) ;
340
341         --- Purpose : This Method concatenates C1 the ArrayOfCurves as far
342         --  as it is possible.
343         --  ArrayOfCurves[0..N-1]
344         --  ArrayOfToler contains the  biggest tolerance of the two
345         --               points shared by two consecutives curves.
346         --               Its dimension: [0..N-2]
347         --  ClosedG1     indicates if the ArrayOfCurves is closed.
348         --               In this case ClosedG1 contains the biggest tolerance
349         --               of the two points which are at the closure.
350         --               Otherwise its value is 0.0
351
352    ConcatC1(ArrayOfCurves         : in out Array1OfBSplineCurve from TColGeom;
353            ArrayOfToler           : in           Array1OfReal   from TColStd;
354            ArrayOfIndices         : out        HArray1OfInteger from TColStd;
355            ArrayOfConcatenated    : out  HArray1OfBSplineCurve from TColGeom;
356            ClosedG1Flag           : in   Boolean              from Standard ;
357            ClosedTolerance        : in   Real               from Standard ;
358            AngularTolerance       : in Real                  from Standard) ;
359            
360         --- Purpose : This Method concatenates C1 the ArrayOfCurves as far
361         --  as it is possible.
362         --  ArrayOfCurves[0..N-1]
363         --  ArrayOfToler contains the  biggest tolerance of the two
364         --               points shared by two consecutives curves.
365         --               Its dimension: [0..N-2]
366         --  ClosedG1     indicates if the ArrayOfCurves is closed.
367         --               In this case ClosedG1 contains the biggest tolerance
368         --               of the two points which are at the closure.
369         --               Otherwise its value is 0.0
370         -- 
371
372   C0BSplineToC1BSplineCurve(BS              : in out BSplineCurve from Geom;
373                             tolerance       : in Real from Standard; 
374                             AngularTolerance: in Real =  1.0e-7);
375         ---Purpose : This  Method reduces as far as   it is possible the
376         --  multiplicities of  the  knots of  the BSpline BS.(keeping  the
377         --  geometry).  It returns a new BSpline which  could still be C0.
378         --  tolerance is a  geometrical tolerance.   
379         --  The  Angular toleranceis in radians  and mesures  the angle of
380         --  the tangents  on  the left and on  the right  to decide if  the
381         -- curve is G1 or not at a given point
382
383
384   C0BSplineToArrayOfC1BSplineCurve(BS        : in  BSplineCurve from Geom;
385                                    tabBS     : out HArray1OfBSplineCurve from TColGeom;
386                                    tolerance : in Real from Standard);
387         --- Purpose : This Method   reduces as far  as  it is possible  the
388         --  multiplicities  of  the knots  of the BSpline  BS.(keeping the geometry).
389         --  It returns an array of BSpline C1. tolerance is a geometrical tolerance.
390  
391   C0BSplineToArrayOfC1BSplineCurve(BS               : in  BSplineCurve from Geom;
392                                    tabBS            : out HArray1OfBSplineCurve from TColGeom;
393                                    AngularTolerance : in Real from Standard ;
394                                    tolerance        : in Real from Standard);
395         --- Purpose :This   Method reduces as far   as it is  possible the
396         --  multiplicities of  the  knots of  the  BSpline BS.(keeping the
397         --  geometry).  It returns an array of BSpline C1.  tolerance is a
398         --  geometrical tolerance : it  allows for the maximum deformation
399         --  The  Angular tolerance is in  radians and mesures the angle of
400         --  the tangents on the left and on the right to decide if the curve
401         --  is C1 or not at a given point
402
403 end GeomConvert;
404
405
406
407
408
409
410
411
412
413