0022939: Make B-Spline internal cache thread-safe to be used in multy-threaded mode
[occt.git] / src / Geom / Geom_BSplineCurve.cdl
1 -- Created on: 1993-03-09
2 -- Created by: JCV
3 -- Copyright (c) 1993-1999 Matra Datavision
4 -- Copyright (c) 1999-2012 OPEN CASCADE SAS
5 --
6 -- The content of this file is subject to the Open CASCADE Technology Public
7 -- License Version 6.5 (the "License"). You may not use the content of this file
8 -- except in compliance with the License. Please obtain a copy of the License
9 -- at http://www.opencascade.org and read it completely before using this file.
10 --
11 -- The Initial Developer of the Original Code is Open CASCADE S.A.S., having its
12 -- main offices at: 1, place des Freres Montgolfier, 78280 Guyancourt, France.
13 --
14 -- The Original Code and all software distributed under the License is
15 -- distributed on an "AS IS" basis, without warranty of any kind, and the
16 -- Initial Developer hereby disclaims all such warranties, including without
17 -- limitation, any warranties of merchantability, fitness for a particular
18 -- purpose or non-infringement. Please see the License for the specific terms
19 -- and conditions governing the rights and limitations under the License.
20
21 -- xab : modified 15-Mar-95 : added cache mecanism to speed up evaluation
22 -- mei : modified 08-Jun-95 : added method MovePoint
23
24
25 class BSplineCurve from Geom inherits BoundedCurve from Geom
26
27         ---Purpose : Definition of the B_spline curve.
28         --       A B-spline curve can be  
29         --         Uniform  or non-uniform
30         --         Rational or non-rational
31         --         Periodic or non-periodic
32         --  
33         --  a b-spline curve is defined by :
34         --  its degree; the degree for a
35         --   Geom_BSplineCurve is limited to a value (25)
36         --   which is defined and controlled by the system.
37         --   This value is returned by the function MaxDegree;
38         -- - its periodic or non-periodic nature;
39         -- - a table of poles (also called control points), with
40         --   their associated weights if the BSpline curve is
41         --   rational. The poles of the curve are "control
42         --   points" used to deform the curve. If the curve is
43         --   non-periodic, the first pole is the start point of
44         --   the curve, and the last pole is the end point of
45         --   the curve. The segment which joins the first pole
46         --   to the second pole is the tangent to the curve at
47         --   its start point, and the segment which joins the
48         --   last pole to the second-from-last pole is the
49         --   tangent to the curve at its end point. If the curve
50         --   is periodic, these geometric properties are not
51         --   verified. It is more difficult to give a geometric
52         --   signification to the weights but are useful for
53         --   providing exact representations of the arcs of a
54         --   circle or ellipse. Moreover, if the weights of all the
55         --   poles are equal, the curve has a polynomial
56         --   equation; it is therefore a non-rational curve.
57         -- - a table of knots with their multiplicities. For a
58         --   Geom_BSplineCurve, the table of knots is an
59         --   increasing sequence of reals without repetition;
60         --   the multiplicities define the repetition of the knots.
61         --   A BSpline curve is a piecewise polynomial or
62         --   rational curve. The knots are the parameters of
63         --   junction points between two pieces. The
64         --   multiplicity Mult(i) of the knot Knot(i) of
65         --   the BSpline curve is related to the degree of
66         --   continuity of the curve at the knot Knot(i),
67         --   which is equal to Degree - Mult(i)
68         --   where Degree is the degree of the BSpline curve.
69         --   If the knots are regularly spaced (i.e. the difference
70         --   between two consecutive knots is a constant), three
71         --   specific and frequently used cases of knot
72         --   distribution can be identified:
73         -- - "uniform" if all multiplicities are equal to 1,
74         -- - "quasi-uniform" if all multiplicities are equal to 1,
75         --   except the first and the last knot which have a
76         --   multiplicity of Degree + 1, where Degree is
77         --   the degree of the BSpline curve,
78         -- - "Piecewise Bezier" if all multiplicities are equal to
79         --   Degree except the first and last knot which
80         --   have a multiplicity of Degree + 1, where
81         --   Degree is the degree of the BSpline curve. A
82         --   curve of this type is a concatenation of arcs of Bezier curves.
83         -- If the BSpline curve is not periodic:
84         -- - the bounds of the Poles and Weights tables are 1
85         --   and NbPoles, where NbPoles is the number
86         --   of poles of the BSpline curve,
87         -- - the bounds of the Knots and Multiplicities tables
88         --   are 1 and NbKnots, where NbKnots is the
89         --   number of knots of the BSpline curve.
90         -- If the BSpline curve is periodic, and if there are k
91         -- periodic knots and p periodic poles, the period is:
92         -- period = Knot(k + 1) - Knot(1)
93         -- and the poles and knots tables can be considered
94         -- as infinite tables, verifying:
95         -- - Knot(i+k) = Knot(i) + period
96         -- - Pole(i+p) = Pole(i)
97         -- Note: data structures of a periodic BSpline curve
98         -- are more complex than those of a non-periodic one.
99         -- Warning
100         -- In this class, weight value is considered to be zero if
101         -- the weight is less than or equal to gp::Resolution().
102         --    
103         -- References :
104         --  . A survey of curve and surface methods in CADG Wolfgang BOHM
105         --    CAGD 1 (1984)
106         --  . On de Boor-like algorithms and blossoming Wolfgang BOEHM
107         --    cagd 5 (1988)
108         --  . Blossoming and knot insertion algorithms for B-spline curves
109         --    Ronald N. GOLDMAN
110         --  . Modelisation des surfaces en CAO, Henri GIAUME Peugeot SA   
111         --  . Curves and Surfaces for Computer Aided Geometric Design,
112         --    a practical guide Gerald Farin
113
114 uses  Array1OfInteger      from TColStd,
115       Array1OfReal         from TColStd,
116       HArray1OfInteger     from TColStd,
117       HArray1OfReal        from TColStd,
118       Array1OfPnt          from TColgp,
119       Ax1                  from gp,
120       Ax2                  from gp, 
121       Pnt                  from gp,
122       HArray1OfPnt         from TColgp,
123       Trsf                 from gp,
124       Vec                  from gp,
125       BSplKnotDistribution from GeomAbs,
126       Geometry             from Geom,
127       Shape                from GeomAbs,
128       Mutex                from Standard
129
130
131 raises ConstructionError   from Standard,
132        DimensionError      from Standard,
133        DomainError         from Standard,
134        OutOfRange          from Standard,
135        RangeError          from Standard,
136        NoSuchObject        from Standard,
137        UndefinedDerivative from Geom
138
139 is
140  
141   Create (Poles          : Array1OfPnt     from TColgp; 
142           Knots          : Array1OfReal    from TColStd; 
143           Multiplicities : Array1OfInteger from TColStd; 
144           Degree         : Integer;
145           Periodic       : Boolean = Standard_False)
146           
147   returns mutable BSplineCurve from Geom
148
149         ---Purpose :  Creates a  non-rational B_spline curve   on  the
150         --         basis <Knots, Multiplicities> of degree <Degree>.
151
152   raises ConstructionError;
153
154         -- The following conditions must be verified.
155
156         --  0 < Degree <= MaxDegree.
157         --  
158         --  Knots.Length() == Mults.Length() >= 2
159         --  
160         --  Knots(i) < Knots(i+1) (Knots are increasing)
161         --  
162         --  1 <= Mults(i) <= Degree
163         --  
164         --   On a non periodic curve the first and last multiplicities
165         --   may be Degree+1 (this is even recommanded if you want the
166         --   curve to start and finish on the first and last pole).
167         --   
168         --   On a periodic  curve the first  and  the last multicities
169         --   must be the same.
170         --   
171         --   on non-periodic curves
172         --   
173         --     Poles.Length() == Sum(Mults(i)) - Degree - 1 >= 2
174         --     
175         --   on periodic curves 
176         --   
177         --     Poles.Length() == Sum(Mults(i)) except the first or last
178
179
180   Create (Poles          : Array1OfPnt     from TColgp; 
181           Weights        : Array1OfReal    from TColStd;
182           Knots          : Array1OfReal    from TColStd; 
183           Multiplicities : Array1OfInteger from TColStd; 
184           Degree         : Integer;
185           Periodic       : Boolean = Standard_False; 
186           CheckRational  : Boolean = Standard_True)
187           
188   returns mutable BSplineCurve from Geom
189
190         ---Purpose : Creates  a rational B_spline  curve  on the basis
191         --         <Knots, Multiplicities> of degree <Degree>.
192         --  Raises ConstructionError subject to the following conditions 
193         --  0 < Degree <= MaxDegree.
194         --  
195         --  Weights.Length() == Poles.Length()
196         --  
197         --  Knots.Length() == Mults.Length() >= 2
198         --  
199         --  Knots(i) < Knots(i+1) (Knots are increasing)
200         --  
201         --  1 <= Mults(i) <= Degree
202         --  
203         --   On a non periodic curve the first and last multiplicities
204         --   may be Degree+1 (this is even recommanded if you want the
205         --   curve to start and finish on the first and last pole).
206         --   
207         --   On a periodic  curve the first  and  the last multicities
208         --   must be the same.
209         --   
210         --   on non-periodic curves
211         --   
212         --     Poles.Length() == Sum(Mults(i)) - Degree - 1 >= 2
213         --     
214         --   on periodic curves 
215         --   
216         --     Poles.Length() == Sum(Mults(i)) except the first or last
217
218   raises ConstructionError;
219
220         
221
222
223   IncreaseDegree (me : mutable; Degree : Integer)
224   
225         ---Purpose: Increases the degree of this BSpline curve to
226         -- Degree. As a result, the poles, weights and
227         -- multiplicities tables are modified; the knots table is
228         -- not changed. Nothing is done if Degree is less than
229         -- or equal to the current degree.
230         -- Exceptions
231         -- Standard_ConstructionError if Degree is greater than
232         -- Geom_BSplineCurve::MaxDegree().
233   raises ConstructionError;
234
235  IncreaseMultiplicity (me : mutable; Index : Integer; M : Integer)
236  
237         ---Purpose :Increases the multiplicity  of the knot <Index> to
238         --         <M>.   
239         --         
240         --         If   <M>   is   lower   or  equal   to  the current
241         --         multiplicity nothing is done. If <M> is higher than
242         --         the degree the degree is used.
243
244  raises OutOfRange;
245         
246         ---Purpose: If <Index> is not in [FirstUKnotIndex, LastUKnotIndex]
247
248
249   IncreaseMultiplicity (me : mutable; I1, I2 : Integer; M : Integer) 
250   
251         ---Purpose :Increases  the  multiplicities   of  the knots  in
252         --         [I1,I2] to <M>.
253         --         
254         --         For each knot if  <M>  is  lower  or equal  to  the
255         --         current multiplicity  nothing  is  done. If <M>  is
256         --         higher than the degree the degree is used.
257
258  raises OutOfRange;
259         
260         ---Purpose: If <I1,I2> are not in [FirstUKnotIndex, LastUKnotIndex]
261
262   IncrementMultiplicity (me : mutable; I1, I2 : Integer; M : Integer) 
263   
264         ---Purpose :Increment  the  multiplicities   of  the knots  in
265         --         [I1,I2] by <M>.
266         --         
267         --         If <M> is not positive nithing is done.
268         --         
269         --         For   each  knot   the resulting   multiplicity  is
270         --         limited to the Degree.
271
272  raises OutOfRange;
273         
274         ---Purpose: If <I1,I2> are not in [FirstUKnotIndex, LastUKnotIndex]
275
276
277
278
279   InsertKnot (me : mutable; 
280               U : Real; 
281               M : Integer = 1; 
282               ParametricTolerance : Real = 0.0;
283               Add : Boolean = Standard_True); 
284   
285         ---Purpose: Inserts a knot value in the sequence of knots.  If
286         --          <U>  is an  existing knot     the multiplicity  is
287         --          increased by <M>.
288         --          
289         --          If U  is  not  on the parameter  range  nothing is
290         --          done.
291         --          
292         --          If the multiplicity is negative or null nothing is
293         --          done. The  new   multiplicity  is limited  to  the
294         --          degree.
295         --          
296         --          The  tolerance criterion  for  knots  equality  is
297         --          the max of Epsilon(U) and ParametricTolerance.
298
299
300   InsertKnots (me : mutable; Knots : Array1OfReal    from TColStd; 
301                              Mults : Array1OfInteger from TColStd;
302                              ParametricTolerance : Real = 0.0;
303                              Add : Boolean = Standard_False);
304                              
305         ---Purpose: Inserts a set of knots  values in  the sequence of
306         --          knots.    
307         --          
308         --          For each U = Knots(i), M = Mults(i)
309         --          
310         --          If <U>  is an existing  knot  the  multiplicity is
311         --          increased by  <M> if  <Add>  is True, increased to
312         --          <M> if <Add> is False.
313         --          
314         --          If U  is  not  on the parameter  range  nothing is
315         --          done.
316         --          
317         --          If the multiplicity is negative or null nothing is
318         --          done. The  new   multiplicity  is limited  to  the
319         --          degree.
320         --          
321         --          The  tolerance criterion  for  knots  equality  is
322         --          the max of Epsilon(U) and ParametricTolerance.
323
324
325                              
326
327
328   RemoveKnot(me : mutable; Index     : Integer; 
329                            M         : Integer;
330                            Tolerance : Real) returns Boolean
331                            
332         ---Purpose : Reduces the multiplicity of the knot of index Index
333         -- to M. If M is equal to 0, the knot is removed.
334         -- With a modification of this type, the array of poles is also modified.
335         -- Two different algorithms are systematically used to
336         -- compute the new poles of the curve. If, for each
337         -- pole, the distance between the pole calculated
338         -- using the first algorithm and the same pole
339         -- calculated using the second algorithm, is less than
340         -- Tolerance, this ensures that the curve is not
341         -- modified by more than Tolerance. Under these
342         -- conditions, true is returned; otherwise, false is returned.
343         -- A low tolerance is used to prevent modification of
344         -- the curve. A high tolerance is used to "smooth" the curve.
345         -- Exceptions
346         -- Standard_OutOfRange if Index is outside the
347         -- bounds of the knots table.
348      raises OutOfRange;
349      
350
351         ---Purpose : pole insertion and pole removing
352         --  this operation is limited to the Uniform or QuasiUniform
353         --  BSplineCurve. The knot values are modified . If the BSpline is
354         --  NonUniform or Piecewise Bezier an exception Construction error
355         --  is raised.
356
357
358   Reverse (me : mutable);
359         ---Purpose :
360         --  Changes the direction of parametrization of <me>. The Knot
361         --  sequence is modified, the FirstParameter and the 
362         --  LastParameter are not modified. The StartPoint of the 
363         --  initial curve becomes the EndPoint of the reversed curve 
364         --  and the EndPoint of the initial curve becomes the StartPoint
365         --  of the reversed curve.
366
367
368   ReversedParameter(me; U : Real) returns Real;
369         ---Purpose: Returns the  parameter on the  reversed  curve for
370         --          the point of parameter U on <me>.
371         --          
372         --          returns UFirst + ULast - U
373
374   Segment (me : mutable; U1, U2 : Real)
375         ---Purpose : Modifies this BSpline curve by segmenting it between
376         -- U1 and U2. Either of these values can be outside the
377         -- bounds of the curve, but U2 must be greater than U1.
378         -- All data structure tables of this BSpline curve are
379         -- modified, but the knots located between U1 and U2
380         -- are retained. The degree of the curve is not modified.
381         --  Warnings :
382         --  Even if <me> is not closed it can become closed after the 
383         --  segmentation for example if U1 or U2 are out of the bounds 
384         --  of the curve <me> or if the curve makes loop.
385         --  After the segmentation the length of a curve can be null.
386     raises DomainError from Standard;
387         ---Purpose: raises if U2 < U1.
388
389
390   SetKnot (me : mutable; Index : Integer; K : Real)
391         ---Purpose : Modifies this BSpline curve by assigning the value K
392         -- to the knot of index Index in the knots table. This is a
393         -- relatively local modification because K must be such that:
394         -- Knots(Index - 1) < K < Knots(Index + 1)
395         -- The second syntax allows you also to increase the
396         -- multiplicity of the knot to M (but it is not possible to
397         -- decrease the multiplicity of the knot with this function).
398         -- Standard_ConstructionError if:
399         -- - K is not such that:
400         -- Knots(Index - 1) < K < Knots(Index + 1)
401         -- - M is greater than the degree of this BSpline curve
402         --   or lower than the previous multiplicity of knot of
403         --   index Index in the knots table.
404         --  Standard_OutOfRange if Index is outside the bounds of the knots table.
405      raises ConstructionError,
406                     OutOfRange;
407
408
409   SetKnots (me : mutable; K : Array1OfReal from TColStd)
410         ---Purpose :  Modifies this BSpline curve by assigning the array
411         -- K to its knots table. The multiplicity of the knots is not modified.
412         -- Exceptions
413         -- Standard_ConstructionError if the values in the
414         -- array K are not in ascending order.
415         -- Standard_OutOfRange if the bounds of the array
416         -- K are not respectively 1 and the number of knots of this BSpline curve.
417      raises ConstructionError,
418                     OutOfRange;
419   
420   SetKnot (me : mutable; Index : Integer; K : Real; M : Integer)
421         ---Purpose :
422         --  Changes the knot of range Index with its multiplicity.
423         --  You can increase the multiplicity of a knot but it is
424         --  not allowed to decrease the multiplicity of an existing knot.
425      raises ConstructionError,
426         ---Purpose :
427         --  Raised if K >= Knots(Index+1) or K <= Knots(Index-1).
428         --  Raised if M is greater than Degree or lower than the previous
429         --  multiplicity of knot of range Index. 
430             OutOfRange;
431         ---Purpose : Raised if Index < 1 || Index > NbKnots
432
433   PeriodicNormalization(me ;  U : in out Real) ; 
434        
435         ---Purpose : returns the parameter normalized within
436         --         the period if the curve is periodic : otherwise
437         --         does not do anything
438     
439   SetPeriodic (me : mutable)
440         ---Purpose : Changes this BSpline curve into a periodic curve.
441         -- To become periodic, the curve must first be closed.
442         -- Next, the knot sequence must be periodic. For this,
443         -- FirstUKnotIndex and LastUKnotIndex are used
444         -- to compute I1 and I2, the indexes in the knots
445         -- array of the knots corresponding to the first and
446         -- last parameters of this BSpline curve.
447         -- The period is therefore: Knots(I2) - Knots(I1).
448         -- Consequently, the knots and poles tables are modified.
449         -- Exceptions
450         -- Standard_ConstructionError if this BSpline curve is not closed.
451      raises ConstructionError;
452
453
454   SetOrigin (me : mutable; Index : Integer)
455         ---Purpose: Assigns the knot of index Index in the knots table as
456         -- the origin of this periodic BSpline curve. As a
457         -- consequence, the knots and poles tables are modified.
458         -- Exceptions
459         -- Standard_NoSuchObject if this curve is not periodic.
460         -- Standard_DomainError if Index is outside the bounds of the knots table.
461     raises NoSuchObject,
462            DomainError;
463         
464   SetOrigin (me  : mutable; 
465              U   : Real from Standard;
466              Tol : Real from Standard)
467         ---Purpose: Set the origin of a periodic curve at Knot U. If U
468         --          is  not a  knot  of  the  BSpline  a  new knot  is
469         --          inseted. KnotVector and poles are modified.
470     raises NoSuchObject;
471         ---Purpose: Raised if the curve is not periodic
472
473
474   SetNotPeriodic (me : mutable);
475         ---Purpose : Changes this BSpline curve into a non-periodic
476         -- curve. If this curve is already non-periodic, it is not modified.
477         -- Note: the poles and knots tables are modified.
478         -- Warning
479         -- If this curve is periodic, as the multiplicity of the first
480         -- and last knots is not modified, and is not equal to
481         -- Degree + 1, where Degree is the degree of
482         -- this BSpline curve, the start and end points of the
483         -- curve are not its first and last poles.
484    
485                 
486  
487   SetPole (me : mutable; Index : Integer; P : Pnt)
488         ---Purpose : Modifies this BSpline curve by assigning P to the pole
489         -- of index Index in the poles table.
490         -- Exceptions
491         -- Standard_OutOfRange if Index is outside the
492         -- bounds of the poles table.
493         -- Standard_ConstructionError if Weight is negative or null.
494      raises OutOfRange;
495      
496   SetPole (me : mutable; Index : Integer; P : Pnt; Weight : Real)
497         ---Purpose: Modifies this BSpline curve by assigning P to the pole
498         -- of index Index in the poles table.
499         -- This syntax also allows you to modify the
500         -- weight of the modified pole, which becomes Weight.
501         -- In this case, if this BSpline curve is non-rational, it
502         -- can become rational and vice versa.
503         -- Exceptions
504         -- Standard_OutOfRange if Index is outside the
505         -- bounds of the poles table.
506         -- Standard_ConstructionError if Weight is negative or null.
507      raises OutOfRange,
508                ConstructionError;
509
510
511   SetWeight (me : mutable; Index : Integer; Weight : Real)
512         ---Purpose :
513         --  Changes the weight for the pole of range Index.
514         --  If the curve was non rational it can become rational.
515         --  If the curve was rational it can become non rational.
516      raises OutOfRange,
517         ---Purpose:
518         --  Raised if Index < 1 || Index > NbPoles
519             ConstructionError;
520         ---Purpose : Raised if Weight <= 0.0
521
522   MovePoint (me : mutable; U: Real; P: Pnt; Index1, Index2: Integer;
523              FirstModifiedPole, LastModifiedPole: out Integer)
524         ---Purpose : Moves the point of parameter U of this BSpline curve
525         -- to P. Index1 and Index2 are the indexes in the table
526         -- of poles of this BSpline curve of the first and last
527         -- poles designated to be moved.
528         -- FirstModifiedPole and LastModifiedPole are the
529         -- indexes of the first and last poles which are effectively modified.
530         -- In the event of incompatibility between Index1, Index2 and the value U:
531         -- - no change is made to this BSpline curve, and
532         -- - the FirstModifiedPole and LastModifiedPole are returned null.
533         --   Exceptions
534         -- Standard_OutOfRange if:
535         -- - Index1 is greater than or equal to Index2, or
536         -- - Index1 or Index2 is less than 1 or greater than the
537         --   number of poles of this BSpline curve.
538          raises OutOfRange;
539       
540   MovePointAndTangent (me : mutable; 
541                        U                 : Real; 
542                        P                 : Pnt; 
543                        Tangent           : Vec ;
544                        Tolerance         : Real ; 
545                        StartingCondition, 
546                        EndingCondition   : Integer; 
547                        ErrorStatus       : out Integer) 
548
549         ---Purpose : 
550         -- Move a point with parameter U to P.
551         -- and makes it tangent at U be Tangent.
552         -- StartingCondition = -1 means first can move
553         -- EndingCondition   = -1 means last point can move
554         -- StartingCondition = 0 means the first point cannot move
555         -- EndingCondition   = 0 means the last point cannot move
556         -- StartingCondition = 1 means the first point and tangent cannot move
557         -- EndingCondition   = 1 means the last point and tangent cannot move  
558         -- and so forth
559         -- ErrorStatus != 0 means that there are not enought degree of freedom
560         -- with the constrain to deform the curve accordingly
561         -- 
562      raises OutOfRange;
563      
564   IsCN (me; N : Integer)   returns Boolean
565         ---Purpose :
566         --  Returns the continuity of the curve, the curve is at least C0.
567      raises RangeError;
568         ---Purpose : Raised if N < 0.
569
570
571   IsClosed (me)  returns Boolean;
572         ---Purpose :
573         --  Returns true if the distance between the first point and the 
574         --  last point of the curve is lower or equal to Resolution 
575         --  from package gp.
576         --- Warnings :
577         --  The first and the last point can be different from the first
578         --  pole and the last pole of the curve.
579
580
581   IsPeriodic (me)  returns Boolean;
582         ---Purpose : Returns True if the curve is periodic.
583
584
585   IsRational (me)  returns Boolean;
586         ---Purpose :
587         --  Returns True if the weights are not identical.
588         --  The tolerance criterion is Epsilon of the class Real.
589     
590   IsCacheValid(me;  Parameter : Real) returns Boolean
591   
592         ---Purpose :
593         --           Tells whether the Cache is valid for the
594         --           given parameter 
595         -- Warnings : the parameter must be normalized within
596         -- the period if the curve is periodic. Otherwise
597         -- the answer will be false
598         -- 
599         is static private;
600   
601   Continuity (me)  returns Shape from GeomAbs;
602         ---Purpose :
603         --  Returns the global continuity of the curve :
604         --  C0 : only geometric continuity,
605         --  C1 : continuity of the first derivative all along the Curve,
606         --  C2 : continuity of the second derivative all along the Curve,
607         --  C3 : continuity of the third derivative all along the Curve,
608         --  CN : the order of continuity is infinite.
609         --  For a B-spline curve of degree d if a knot Ui has a
610         --  multiplicity p the B-spline curve is only Cd-p continuous 
611         --  at Ui. So the global continuity of the curve can't be greater 
612         --  than Cd-p where p is the maximum multiplicity of the interior
613         --  Knots. In the interior of a knot span the curve is infinitely
614         --  continuously differentiable.
615
616
617   Degree (me)  returns Integer;
618         ---Purpose: Returns the degree of this BSpline curve.
619         -- The degree of a Geom_BSplineCurve curve cannot
620         -- be greater than Geom_BSplineCurve::MaxDegree().
621
622         ---Purpose : Computation of value and derivatives
623
624   D0 (me ; U : Real; P : out Pnt);
625         ---Purpose: Returns in P the point of parameter U.
626
627   D1 (me; U : Real; P : out Pnt; V1 : out Vec)
628      raises UndefinedDerivative;
629         ---Purpose : Raised if the continuity of the curve is not C1.
630
631
632   D2 (me; U : Real; P : out Pnt; V1, V2 : out Vec)
633      raises UndefinedDerivative;
634         ---Purpose : Raised if the continuity of the curve is not C2.
635
636
637   D3 (me; U : Real; P : out Pnt; V1, V2, V3 : out Vec)
638      raises UndefinedDerivative;
639         ---Purpose : Raised if the continuity of the curve is not C3.
640         
641
642   DN (me; U : Real; N : Integer)  returns Vec
643         ---Purpose : For the point of parameter U of this BSpline curve,
644         -- computes the vector corresponding to the Nth derivative.
645         -- Warning
646         -- On a point where the continuity of the curve is not the
647         -- one requested, this function impacts the part defined
648         -- by the parameter with a value greater than U, i.e. the
649         -- part of the curve to the "right" of the singularity.
650         -- Exceptions
651         -- Standard_RangeError if N is less than 1.
652      raises  UndefinedDerivative,
653                     RangeError;
654
655         ---Purpose  :
656         --  The following functions compute the point of parameter U 
657         --  and the derivatives at this point on the B-spline curve 
658         --  arc defined between the knot FromK1 and the knot ToK2. 
659         --  U can be out of bounds [Knot (FromK1),  Knot (ToK2)] but
660         --  for the computation we only use the definition of the curve
661         --  between these two knots. This method is useful to compute 
662         --  local derivative, if the order of continuity of the whole 
663         --  curve is not greater enough.    Inside the parametric
664         --  domain Knot (FromK1), Knot (ToK2) the evaluations are
665         --  the same as if we consider the whole definition of the
666         --  curve. Of course the evaluations are different outside
667         --  this parametric domain.
668
669
670   LocalValue (me; U : Real; FromK1, ToK2 : Integer)   returns Pnt
671      raises DomainError,
672         ---Purpose : Raised if FromK1 = ToK2.
673             OutOfRange;
674         ---Purpose :
675         --  Raised if FromK1 and ToK2 are not in the range 
676         --  [FirstUKnotIndex, LastUKnotIndex].
677
678   LocalD0 (me; U : Real; FromK1, ToK2 : Integer; P : out Pnt)
679      raises DomainError,
680         ---Purpose : Raised if FromK1 = ToK2.
681             OutOfRange;
682         ---Purpose :
683         --  Raised if FromK1 and ToK2 are not in the range 
684         --  [FirstUKnotIndex, LastUKnotIndex].
685
686   LocalD1 (me; U : Real; FromK1, ToK2 : Integer; P : out Pnt; V1 : out Vec)
687      raises UndefinedDerivative,
688         ---Purpose :
689         --  Raised if the local continuity of the curve is not C1 
690         --  between the knot K1 and the knot K2. 
691             DomainError,
692         ---Purpose : Raised if FromK1 = ToK2.
693             OutOfRange;
694         ---Purpose :
695         --  Raised if FromK1 and ToK2 are not in the range 
696         --  [FirstUKnotIndex, LastUKnotIndex].
697
698
699   LocalD2 (me; U : Real; FromK1, ToK2 : Integer; P : out Pnt; V1, V2 : out Vec)
700      raises UndefinedDerivative,
701         ---Purpose :
702         --  Raised if the local continuity of the curve is not C2 
703         --  between the knot K1 and the knot K2. 
704             DomainError,
705         ---Purpose : Raised if FromK1 = ToK2.
706             OutOfRange;
707         ---Purpose :
708         --  Raised if FromK1 and ToK2 are not in the range 
709         --  [FirstUKnotIndex, LastUKnotIndex].
710
711
712
713   LocalD3 (me; U : Real;  FromK1, ToK2 : Integer;
714            P : out Pnt; V1, V2, V3 : out Vec)
715      raises UndefinedDerivative,
716         ---Purpose :
717         --  Raised if the local continuity of the curve is not C3
718         --  between the knot K1 and the knot K2. 
719             DomainError,
720         ---Purpose : Raised if FromK1 = ToK2.
721             OutOfRange;
722         ---Purpose :
723         --  Raised if FromK1 and ToK2 are not in the range
724         --  [FirstUKnotIndex, LastUKnotIndex].
725
726
727   LocalDN (me; U : Real;  FromK1, ToK2 : Integer; N : Integer)  returns Vec
728      raises  UndefinedDerivative,
729         ---Purpose :
730         --  Raised if the local continuity of the curve is not CN
731         --  between the knot K1 and the knot K2. 
732             DomainError,
733         ---Purpose : Raised if FromK1 = ToK2.
734              RangeError,
735         ---Purpose : Raised if N < 1.
736              OutOfRange;
737         ---Purpose :
738         --  Raises if FromK1 and ToK2 are not in the range 
739         --  [FirstUKnotIndex, LastUKnotIndex].
740
741
742   EndPoint (me)   returns Pnt;
743         ---Purpose :
744         --  Returns the last point of the curve.
745         -- Warnings :
746         --  The last point of the curve is different from the last 
747         --  pole of the curve if the multiplicity of the last knot
748         --  is lower than Degree.
749
750
751   FirstUKnotIndex (me)   returns Integer;
752         ---Purpose : Returns the index in the knot array of the knot
753         -- corresponding to the first or last parameter of this BSpline curve.
754         -- For a BSpline curve, the first (or last) parameter
755         -- (which gives the start (or end) point of the curve) is a
756         -- knot value. However, if the multiplicity of the first (or
757         -- last) knot is less than Degree + 1, where
758         -- Degree is the degree of the curve, it is not the first
759         -- (or last) knot of the curve.
760       
761
762   FirstParameter (me)   returns Real;
763         ---Purpose : Returns the value of the first parameter of this
764         -- BSpline curve. This is a knot value.
765         -- The first parameter is the one of the start point of the BSpline curve. 
766        
767
768
769   Knot (me; Index : Integer)   returns Real
770         ---Purpose :
771         --  Returns the knot of range Index. When there is a knot 
772         --  with a multiplicity greater than 1 the knot is not repeated.
773         --  The method Multiplicity can be used to get the multiplicity 
774         --  of the Knot.
775      raises OutOfRange;
776         ---Purpose : Raised if Index < 1 or Index > NbKnots
777
778
779   Knots (me; K : out Array1OfReal from TColStd)
780         ---Purpose : returns the knot values of the B-spline curve; 
781         -- Warning
782         -- A knot with a multiplicity greater than 1 is not
783         -- repeated in the knot table. The Multiplicity function
784         -- can be used to obtain the multiplicity of each knot.
785      raises DimensionError;
786         ---Purpose :
787         --  Raised if the length of K is not equal to the number of knots.
788
789
790   KnotSequence (me; K : out Array1OfReal from TColStd)
791         ---Purpose : Returns K, the knots sequence of this BSpline curve.
792         -- In this sequence, knots with a multiplicity greater than 1 are repeated.
793         -- In the case of a non-periodic curve the length of the
794         -- sequence must be equal to the sum of the NbKnots
795         -- multiplicities of the knots of the curve (where
796         -- NbKnots is the number of knots of this BSpline
797         -- curve). This sum is also equal to : NbPoles + Degree + 1
798         -- where NbPoles is the number of poles and
799         -- Degree the degree of this BSpline curve.
800         -- In the case of a periodic curve, if there are k periodic
801         -- knots, the period is Knot(k+1) - Knot(1).
802         -- The initial sequence is built by writing knots 1 to k+1,
803         -- which are repeated according to their corresponding multiplicities.
804         -- If Degree is the degree of the curve, the degree of
805         -- continuity of the curve at the knot of index 1 (or k+1)
806         -- is equal to c = Degree + 1 - Mult(1). c
807         -- knots are then inserted at the beginning and end of
808         -- the initial sequence:
809         -- - the c values of knots preceding the first item
810         --   Knot(k+1) in the initial sequence are inserted
811         --   at the beginning; the period is subtracted from these c values;
812         -- - the c values of knots following the last item
813         --   Knot(1) in the initial sequence are inserted at
814         --   the end; the period is added to these c values.
815         -- The length of the sequence must therefore be equal to:
816         -- NbPoles + 2*Degree - Mult(1) + 2.
817         -- Example
818         -- For a non-periodic BSpline curve of degree 2 where:
819         -- - the array of knots is: { k1 k2 k3 k4 },
820         -- - with associated multiplicities: { 3 1 2 3 },
821         -- the knot sequence is:
822         -- K = { k1 k1 k1 k2 k3 k3 k4 k4 k4 }
823         -- For a periodic BSpline curve of degree 4 , which is
824         -- "C1" continuous at the first knot, and where :
825         -- - the periodic knots are: { k1 k2 k3 (k4) }
826         --   (3 periodic knots: the points of parameter k1 and k4
827         --   are identical, the period is p = k4 - k1),
828         -- - with associated multiplicities: { 3 1 2 (3) },
829         -- the degree of continuity at knots k1 and k4 is:
830         -- Degree + 1 - Mult(i) = 2.
831         -- 2 supplementary knots are added at the beginning
832         -- and end of the sequence:
833         -- - at the beginning: the 2 knots preceding k4 minus
834         --   the period; in this example, this is k3 - p both times;
835         -- - at the end: the 2 knots following k1 plus the period;
836         --   in this example, this is k2 + p and k3 + p.
837         -- The knot sequence is therefore:
838         -- K = { k3-p k3-p k1 k1 k1 k2 k3 k3
839         -- k4 k4 k4 k2+p k3+p }
840         -- Exceptions
841         -- Standard_DimensionError if the array K is not of
842         -- the appropriate length.Returns the knots sequence.
843              raises DimensionError;
844        
845
846
847   KnotDistribution (me)   returns BSplKnotDistribution from GeomAbs;
848         ---Purpose :
849         --  Returns NonUniform or Uniform or QuasiUniform or PiecewiseBezier.
850         --  If all the knots differ by a positive constant from the 
851         --  preceding knot the BSpline Curve can be :
852         --  - Uniform if all the knots are of multiplicity 1,
853         --  - QuasiUniform if all the knots are of multiplicity 1 except for
854         --    the first and last knot which are of multiplicity Degree + 1,
855         --  - PiecewiseBezier if the first and last knots have multiplicity
856         --    Degree + 1 and if interior knots have multiplicity Degree
857         --    A piecewise Bezier with only two knots is a BezierCurve. 
858         --  else the curve is non uniform.
859         --  The tolerance criterion is Epsilon from class Real.
860
861
862   LastUKnotIndex (me)  returns Integer;
863         ---Purpose :
864         --  For a BSpline curve the last parameter (which gives the 
865         --  end point of the curve) is a knot value but if the 
866         --  multiplicity of the last knot index is lower than 
867         --  Degree + 1 it is not the last knot of the curve. This
868         --  method computes the index of the knot corresponding to
869         --  the last parameter.
870
871
872   LastParameter (me)   returns Real;
873         ---Purpose :
874         --  Computes the parametric value of the end point of the curve.
875         --  It is a knot value.
876
877
878   LocateU (me;
879            U                   : Real; 
880            ParametricTolerance : Real; 
881            I1, I2              : in out Integer;
882            WithKnotRepetition  : Boolean = Standard_False);
883         ---Purpose :
884         --  Locates the parametric value U in the sequence of knots.
885         --  If "WithKnotRepetition" is True we consider the knot's
886         --  representation with repetition of multiple knot value,
887         --  otherwise  we consider the knot's representation with
888         --  no repetition of multiple knot values.
889         --  Knots (I1) <= U <= Knots (I2)
890         --  . if I1 = I2  U is a knot value (the tolerance criterion 
891         --    ParametricTolerance is used).
892         --  . if I1 < 1  => U < Knots (1) - Abs(ParametricTolerance)
893         --  . if I2 > NbKnots => U > Knots (NbKnots) + Abs(ParametricTolerance)
894
895
896   Multiplicity (me; Index : Integer)   returns Integer
897         ---Purpose :
898         --  Returns the multiplicity of the knots of range Index.
899      raises OutOfRange;
900         ---Purpose : Raised if Index < 1 or Index > NbKnots
901
902
903   Multiplicities (me; M : out Array1OfInteger from TColStd)
904         ---Purpose :
905         --  Returns the multiplicity of the knots of the curve.
906      raises DimensionError;
907         ---Purpose :
908         --  Raised if the length of M is not equal to NbKnots.
909
910
911   NbKnots (me)  returns Integer;
912         ---Purpose :
913         --  Returns the number of knots. This method returns the number of 
914         --  knot without repetition of multiple knots.
915
916
917   NbPoles (me)  returns Integer;
918         ---Purpose : Returns the number of poles
919
920
921   Pole (me; Index : Integer)   returns Pnt
922         ---Purpose : Returns the pole of range Index.
923      raises OutOfRange;
924         ---Purpose : Raised if Index < 1 or Index > NbPoles.
925
926
927   Poles (me; P : out Array1OfPnt from TColgp)
928         ---Purpose : Returns the poles of the B-spline curve;
929      raises DimensionError;
930         ---Purpose : 
931         --  Raised if the length of P is not equal to the number of poles.
932
933
934   StartPoint (me)  returns Pnt;
935         ---Purpose :
936         --  Returns the start point of the curve.
937         -- Warnings :
938         --  This point is different from the first pole of the curve if the
939         --  multiplicity of the first knot is lower than Degree.
940
941
942   Weight (me; Index : Integer)  returns Real  
943         ---Purpose : Returns the weight of the pole of range Index .
944      raises OutOfRange;
945         ---Purpose : Raised if Index < 1 or Index > NbPoles.
946
947
948   Weights (me; W : out Array1OfReal from TColStd)
949         ---Purpose : Returns the weights of the B-spline curve;
950      raises DimensionError;
951         ---Purpose :
952         --  Raised if the length of W is not equal to NbPoles.
953
954
955
956
957
958
959
960   Transform (me : mutable; T : Trsf);
961         ---Purpose: Applies the transformation T to this BSpline curve.
962   MaxDegree (myclass)  returns Integer;
963         ---Purpose :
964         --  Returns the value of the maximum degree of the normalized 
965         --  B-spline basis functions in this package.
966
967   Resolution(me          : mutable; 
968              Tolerance3D : Real;
969              UTolerance  : out Real) 
970         ---Purpose:  Computes for this BSpline curve the parametric
971         -- tolerance UTolerance for a given 3D tolerance Tolerance3D.
972         -- If f(t) is the equation of this BSpline curve,
973         -- UTolerance ensures that:
974         --           | t1 - t0| < Utolerance ===> 
975         --           |f(t1) - f(t0)| < Tolerance3D
976   ;
977
978   Copy (me)  returns mutable like me;
979         ---Purpose: Creates a new object which is a copy of this BSpline curve.
980     
981   InvalidateCache(me : mutable)
982         ---Purpose : Invalidates the cache. This has to be private
983         -- this has to be private
984       is static private;
985
986   UpdateKnots(me : mutable)
987         ---Purpose : Recompute  the  flatknots,  the knotsdistribution, the continuity.
988     is static private;
989   
990   ValidateCache(me : mutable ; Parameter : Real) 
991   
992     is static private;
993         ---Purpose : updates the cache and validates it
994
995   
996         
997
998
999 fields
1000
1001   rational        : Boolean;
1002   periodic        : Boolean;
1003   knotSet         : BSplKnotDistribution from GeomAbs; 
1004   smooth          : Shape from GeomAbs;
1005   deg             : Integer;
1006   poles           : HArray1OfPnt     from TColgp;
1007   weights         : HArray1OfReal    from TColStd;
1008   flatknots       : HArray1OfReal    from TColStd;
1009   knots           : HArray1OfReal    from TColStd;
1010   mults           : HArray1OfInteger from TColStd;
1011   cachepoles      : HArray1OfPnt     from TColgp;
1012   -- Taylor expansion of the poles function, in homogeneous
1013   -- form if the curve is rational. The taylor expansion
1014   -- is normalized so that the span corresponds to
1015   -- [0 1] see below
1016   cacheweights    : HArray1OfReal    from TColStd;
1017   -- Taylor expansion of the poles function, in homogeneous
1018   -- form if the curve is rational. The taylor expansion
1019   -- is normalized so that the span corresponds to
1020   -- [0 1] see below
1021   validcache      : Integer;
1022   -- = 1 the cache is valid 
1023   -- = 0 the cache is invalid
1024   parametercache    : Real;
1025   -- Parameter at which the Taylor expension is stored in 
1026   -- the cache
1027   spanlenghtcache   : Real;
1028   -- Since the Taylor expansion is normalized in the 
1029   -- cache to evaluate the cache one has to use
1030   -- (Parameter - parametercache) / nspanlenghtcache
1031   spanindexcache : Integer;
1032   -- the span for which the cache is valid if 
1033   -- validcache is 1 
1034
1035   -- usefull to evaluate the parametric resolution
1036   maxderivinv   : Real from Standard;
1037   maxderivinvok : Boolean from Standard;
1038
1039   myMutex       : Mutex from Standard;
1040   -- protected bspline-cache
1041 end;