0023404: Create SquareConfusion function in Precision package for speed and convenience
[occt.git] / src / Precision / Precision.cdl
1 -- Created on: 1993-02-17
2 -- Created by: Remi LEQUETTE
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
22
23 package Precision 
24
25         ---Purpose: The Precision package offers a set of functions defining precision criteria
26         -- for use in conventional situations when comparing two numbers.
27         -- Generalities
28         -- It is not advisable to use floating number equality. Instead, the difference
29         -- between numbers must be compared with a given precision, i.e. :
30         -- Standard_Real x1, x2 ;
31         -- x1 = ...
32         -- x2 = ...
33         -- If ( x1 == x2 ) ...
34         -- should not be used and must be written as indicated below:
35         -- Standard_Real x1, x2 ;
36         -- Standard_Real Precision = ...
37         -- x1 = ...
38         -- x2 = ...
39         -- If ( Abs ( x1 - x2 ) < Precision ) ...
40         -- Likewise, when ordering floating numbers, you must take the following into account :
41         -- Standard_Real x1, x2 ;
42         -- Standard_Real Precision = ...
43         -- x1 = ...       ! a large number
44         -- x2 = ...       ! another large number
45         -- If ( x1 < x2 - Precision ) ...
46         -- is incorrect when x1 and x2 are large numbers ; it is better to write :
47         -- Standard_Real x1, x2 ;
48         -- Standard_Real Precision = ...
49         -- x1 = ...       ! a large number
50         -- x2 = ...       ! another large number
51         -- If ( x2 - x1 > Precision ) ...
52         -- Precision in Cas.Cade
53         -- Generally speaking, the precision criterion is not implicit in Cas.Cade. Low-level geometric algorithms accept
54         -- precision criteria as arguments. As a rule, they should not refer directly to the precision criteria provided by the
55         -- Precision package.
56         -- On the other hand, high-level modeling algorithms have to provide the low-level geometric algorithms that they
57         -- call, with a precision criteria. One way of doing this is to use the above precision criteria.
58         -- Alternatively, the high-level algorithms can have their own system for precision management. For example, the
59         -- Topology Data Structure stores precision criteria for each elementary shape (as a vertex, an edge or a face). When
60         -- a new topological object is constructed, the precision criteria are taken from those provided by the Precision
61         -- package, and stored in the related data structure. Later, a topological algorithm which analyses these objects will
62         -- work with the values stored in the data structure. Also, if this algorithm is to build a new topological object, from
63         -- these precision criteria, it will compute a new precision criterion for the new topological object, and write it into the
64         -- data structure of the new topological object.
65         -- The different precision criteria offered by the Precision package, cover the most common requirements of
66         -- geometric algorithms, such as intersections, approximations, and so on.
67         -- The choice of precision depends on the algorithm and on the geometric space. The geometric space may be :
68         -- -   a "real" 2D or 3D space, where the lengths are measured in meters, millimeters, microns, inches, etc ..., or
69         -- -   a "parametric" space, 1D on a curve or 2D on a surface, where lengths have no dimension.
70         -- The choice of precision criteria for real space depends on the choice of the product, as it is based on the accuracy
71         -- of the machine and the unit of measurement.
72         -- The choice of precision criteria for parametric space depends on both the accuracy of the machine and the
73         -- dimensions of the curve or the surface, since the parametric precision criterion and the real precision criterion are
74         -- linked : if the curve is defined by the equation P(t), the inequation :
75         -- Abs ( t2 - t1 ) < ParametricPrecision
76         -- means that the parameters t1 and t2 are considered to be equal, and the inequation :
77         -- Distance ( P(t2) , P(t1) ) < RealPrecision
78         -- means that the points P(t1) and P(t2) are considered to be coincident. It seems to be the same idea, and it
79         -- would be wonderful if these two inequations were equivalent. Note that this is rarely the case !
80         -- What is provided in this package?
81         -- The Precision package provides :
82         -- -   a set of real space precision criteria for the algorithms, in view of checking distances and angles,
83         -- -   a set of parametric space precision criteria for the algorithms, in view of checking both :
84         --   -   the equality of parameters in a parametric space,
85         --   -   or the coincidence of points in the real space, by using parameter values,
86         -- -   the notion of infinite value, composed of a value assumed to be infinite, and checking tests designed to verify
87         --   if any value could be considered as infinite.
88         --  All the provided functions are very simple. The returned values result from the adaptation of the applications
89         -- developed by the Open CASCADE company to Open CASCADE algorithms. The main interest of these functions
90         -- lies in that it incites engineers developing applications to ask questions on precision factors. Which one is to be
91         -- used in such or such case ? Tolerance criteria are context dependent. They must first choose :
92         -- -   either to work in real space,
93         -- -   or to work in parametric space,
94         -- -   or to work in a combined real and parametric space.
95         --   They must next decide which precision factor will give the best answer to the current problem. Within an application
96         -- environment, it is crucial to master precision even though this process may take a great deal of time.
97     
98 uses
99     Standard
100
101 is
102
103     Angular returns Real from Standard;
104         ---Purpose:  Returns the recommended precision value
105         --  when checking the equality of two angles (given in radians).
106         -- Standard_Real Angle1 = ... , Angle2 = ... ;
107         -- If ( Abs( Angle2 - Angle1 ) < Precision::Angular() ) ...
108         -- The tolerance of angular equality may be used to check the parallelism of two vectors :
109         -- gp_Vec V1, V2 ;
110         -- V1 = ...
111         -- V2 = ...
112         -- If ( V1.IsParallel (V2, Precision::Angular() ) ) ...
113         -- The tolerance of angular equality is equal to 1.e-12.
114         -- Note : The tolerance of angular equality can be used when working with scalar products or
115         -- cross products since sines and angles are equivalent for small angles. Therefore, in order to
116         -- check whether two unit vectors are perpendicular :
117         -- gp_Dir D1, D2 ;
118         -- D1 = ...
119         -- D2 = ...
120         -- you can use :
121         -- If ( Abs( D1.D2 ) < Precision::Angular() ) ...
122         -- (although the function IsNormal does exist).
123         
124     Confusion returns Real from Standard;
125         ---Purpose: 
126         -- Returns the recommended precision value when
127         -- checking coincidence of two points in real space.
128         -- The tolerance of confusion is used for testing a 3D
129         -- distance :
130         -- -   Two points are considered to be coincident if their
131         --   distance is smaller than the tolerance of confusion.
132         --  gp_Pnt P1, P2 ;
133         -- P1 = ...
134         -- P2 = ...
135         -- if ( P1.IsEqual ( P2 , Precision::Confusion() ) )
136         --     then ...
137         -- -   A vector is considered to be null if it has a null length :
138         --   gp_Vec V ;
139         -- V = ...
140         -- if ( V.Magnitude() < Precision::Confusion() ) then ...
141         -- The tolerance of confusion is equal to 1.e-7.
142         -- The value of the tolerance of confusion is also used to
143         -- define :
144         -- -   the tolerance of intersection, and
145         -- -   the tolerance of approximation.
146         --   Note : As a rule, coordinate values in Cas.Cade are not
147         -- dimensioned, so 1. represents one user unit, whatever
148         -- value the unit may have : the millimeter, the meter, the
149         -- inch, or any other unit. Let's say that Cas.Cade
150         -- algorithms are written to be tuned essentially with
151         -- mechanical design applications, on the basis of the
152         -- millimeter. However, these algorithms may be used with
153         -- any other unit but the tolerance criterion does no longer
154         -- have the same signification.
155         -- So pay particular attention to the type of your application,
156         -- in relation with the impact of your unit on the precision criterion.
157         -- -   For example in mechanical design, if the unit is the
158         --   millimeter, the tolerance of confusion corresponds to a
159         --   distance of 1 / 10000 micron, which is rather difficult to measure.
160         -- -   However in other types of applications, such as
161         --   cartography, where the kilometer is frequently used,
162         --   the tolerance of confusion corresponds to a greater
163         --   distance (1 / 10 millimeter). This distance
164         --   becomes easily measurable, but only within a restricted
165         -- space which contains some small objects of the complete scene.
166         
167     SquareConfusion returns Real from Standard;
168         ---Purpose:
169         -- Returns square of Confusion.
170         -- Created for speed and convenience.
171
172     Intersection returns Real from Standard;
173         ---Purpose:Returns the precision value in real space, frequently
174         -- used by intersection algorithms to decide that a solution is reached.
175         -- This function provides an acceptable level of precision
176         -- for an intersection process to define the adjustment limits.
177         -- The tolerance of intersection is designed to ensure
178         -- that a point computed by an iterative algorithm as the
179         -- intersection between two curves is indeed on the
180         -- intersection. It is obvious that two tangent curves are
181         -- close to each other, on a large distance. An iterative
182         -- algorithm of intersection may find points on these
183         -- curves within the scope of the confusion tolerance, but
184         -- still far from the true intersection point. In order to force
185         -- the intersection algorithm to continue the iteration
186         -- process until a correct point is found on the tangent
187         -- objects, the tolerance of intersection must be smaller
188         -- than the tolerance of confusion.
189         -- On the other hand, the tolerance of intersection must
190         -- be large enough to minimize the time required by the
191         -- process to converge to a solution.
192         -- The tolerance of intersection is equal to :
193         -- Precision::Confusion() / 100.
194         -- (that is, 1.e-9).
195
196     Approximation returns Real from Standard;
197         ---Purpose: Returns the precision value in real space, frequently used
198         -- by approximation algorithms.
199         -- This function provides an acceptable level of precision for
200         -- an approximation process to define adjustment limits.
201         -- The tolerance of approximation is designed to ensure
202         -- an acceptable computation time when performing an
203         -- approximation process. That is why the tolerance of
204         -- approximation is greater than the tolerance of confusion.
205         -- The tolerance of approximation is equal to :
206         -- Precision::Confusion() * 10.
207         -- (that is, 1.e-6).
208         -- You may use a smaller tolerance in an approximation
209         -- algorithm, but this option might be costly.
210
211     Parametric(P : Real from Standard; T : Real from Standard) 
212     returns Real from Standard;
213         ---Purpose: Convert a real  space precision  to  a  parametric
214         --          space precision.   <T>  is the mean  value  of the
215         --          length of the tangent of the curve or the surface.
216         --          
217         --          Value is P / T
218         --          
219         ---C++: inline
220         
221     PConfusion(T : Real from Standard) returns Real from Standard;
222         ---Purpose: 
223         -- Returns a precision value in parametric space, which may be used :
224         -- -   to test the coincidence of two points in the real space,
225         --   by using parameter values, or
226         -- -   to test the equality of two parameter values in a parametric space.
227         --  The parametric tolerance of confusion is designed to
228         -- give a mean value in relation with the dimension of
229         -- the curve or the surface. It considers that a variation of
230         -- parameter equal to 1. along a curve (or an
231         -- isoparametric curve of a surface) generates a segment
232         -- whose length is equal to 100. (default value), or T.
233         --   The parametric tolerance of confusion is equal to :
234         -- -   Precision::Confusion() / 100., or Precision::Confusion() / T.
235         --   The value of the parametric tolerance of confusion is also used to define :
236         -- -   the parametric tolerance of intersection, and
237         -- -   the parametric tolerance of approximation.
238         --   Warning
239         -- It is rather difficult to define a unique precision value in parametric space.
240         -- -   First consider a curve (c) ; if M is the point of
241         --   parameter u and M' the point of parameter u+du on
242         --   the curve, call 'parametric tangent' at point M, for the
243         --   variation du of the parameter, the quantity :
244         --   T(u,du)=MM'/du (where MM' represents the
245         --   distance between the two points M and M', in the real space).
246         -- -   Consider the other curve resulting from a scaling
247         --   transformation of (c) with a scale factor equal to
248         --   10. The 'parametric tangent' at the point of
249         --   parameter u of this curve is ten times greater than the
250         --   previous one. This shows that for two different curves,
251         --   the distance between two points on the curve, resulting
252         --   from the same variation of parameter du, may vary   considerably.
253         -- -   Moreover, the variation of the parameter along the
254         --   curve is generally not proportional to the curvilinear
255         --   abscissa along the curve. So the distance between two
256         --   points resulting from the same variation of parameter
257         --   du, at two different points of a curve, may completely differ.
258         -- -   Moreover, the parameterization of a surface may
259         --   generate two quite different 'parametric tangent' values
260         --   in the u or in the v parametric direction.
261         -- -   Last, close to the poles of a sphere (the points which
262         --   correspond to the values -Pi/2. and Pi/2. of the
263         --   v parameter) the u parameter may change from 0 to
264         --   2.Pi without impacting on the resulting point.
265         --   Therefore, take great care when adjusting a parametric
266         -- tolerance to your own algorithm.
267         
268     PIntersection(T : Real from Standard) returns Real from Standard;
269         ---Purpose: 
270         -- Returns a precision value in parametric space, which
271         -- may be used by intersection algorithms, to decide that
272         -- a solution is reached. The purpose of this function is to
273         -- provide an acceptable level of precision in parametric
274         -- space, for an intersection process to define the adjustment limits.
275         -- The parametric tolerance of intersection is
276         -- designed to give a mean value in relation with the
277         -- dimension of the curve or the surface. It considers
278         -- that a variation of parameter equal to 1. along a curve
279         -- (or an isoparametric curve of a surface) generates a
280         -- segment whose length is equal to 100. (default value), or T.
281         --   The parametric tolerance of intersection is equal to :
282         -- -   Precision::Intersection() / 100., or Precision::Intersection() / T.
283  
284     PApproximation(T : Real from Standard) returns Real from Standard;
285         ---Purpose: Returns a precision value in parametric space, which may
286         -- be used by approximation algorithms. The purpose of this
287         -- function is to provide an acceptable level of precision in
288         -- parametric space, for an approximation process to define
289         -- the adjustment limits.
290         -- The parametric tolerance of approximation is
291         -- designed to give a mean value in relation with the
292         -- dimension of the curve or the surface. It considers
293         -- that a variation of parameter equal to 1. along a curve
294         -- (or an isoparametric curve of a surface) generates a
295         -- segment whose length is equal to 100. (default value), or T.
296         -- The parametric tolerance of intersection is equal to :
297         -- -   Precision::Approximation() / 100., or Precision::Approximation() / T.
298
299     Parametric(P : Real from Standard)
300     returns Real from Standard;
301         ---Purpose: Convert a real  space precision  to  a  parametric
302         --          space precision on a default curve.
303         --          
304         --          Value is Parametric(P,1.e+2)
305         --          
306         
307     PConfusion returns Real from Standard;
308         ---Purpose: Used  to test distances  in parametric  space on a
309         --          default curve.
310         --          
311         --          This is Precision::Parametric(Precision::Confusion())
312         --          
313         ---C++: inline
314         
315     PIntersection returns Real from Standard;
316         ---Purpose: Used for Intersections  in parametric  space  on a
317         --          default curve.
318         --          
319         --          This is Precision::Parametric(Precision::Intersection())
320         --          
321         ---C++: inline
322
323     PApproximation returns Real from Standard;
324         ---Purpose: Used for  Approximations  in parametric space on a
325         --          default curve.
326         --          
327         --          This is Precision::Parametric(Precision::Approximation())
328         --          
329         ---C++: inline
330
331     IsInfinite(R : Real from Standard) returns Boolean;
332         ---Purpose: Returns True if R may be considered as an infinite
333         --          number. Currently Abs(R) > 1e100
334
335     IsPositiveInfinite(R : Real from Standard) returns Boolean;
336         ---Purpose: Returns True if R may be considered as  a positive
337         --          infinite number. Currently R > 1e100
338
339     IsNegativeInfinite(R : Real from Standard) returns Boolean;
340         ---Purpose: Returns True if R may  be considered as a negative
341         --          infinite number. Currently R < -1e100
342         
343
344     Infinite returns Real;
345         ---Purpose: Returns a  big number that  can  be  considered as
346         --          infinite. Use -Infinite() for a negative big number.
347         
348 end Precision;
349