Annotation of OpenXM_contrib/PHC/Ada/Continuation/predictors.ads, Revision 1.1.1.1
1.1 maekawa 1: with Standard_Floating_Numbers; use Standard_Floating_Numbers;
2: with Standard_Complex_Numbers; use Standard_Complex_Numbers;
3: with Standard_Complex_Vectors; use Standard_Complex_Vectors;
4: with Standard_Complex_Matrices; use Standard_Complex_Matrices;
5: with Standard_Complex_Solutions; use Standard_Complex_Solutions;
6: with Continuation_Data; use Continuation_Data;
7:
8: package Predictors is
9:
10: -- DESCRIPTION :
11: -- This package contains several implementations for the predictor
12: -- in an increment-and-fix continuation.
13:
14: -- The predictor provides a prediction both for the continuation parameter t
15: -- and for the solution(s) x.
16:
17: -- For the continuation paramter t the following options can be made :
18: -- Real : linear prediction, simply adds the step size;
19: -- Complex : can make predictions in complex space;
20: -- Circular : to perform a circular sample, for winding numbers;
21: -- Geometric : distances to target form geometric series.
22:
23: -- For the solution vector x the following options are provided :
24: -- Secant : linear extrapolation using differences;
25: -- Tangent : linear extrapolation using the first derivatives;
26: -- Hermite : third-order extrapolation using first derivatives.
27: -- Furthermore, these predictors for x can be applied
28: -- for one solution (Single) or for an array of solutions (Multiple).
29:
30: -- By combining these options, the following 13 predictors are provided :
31:
32: -- Secant_Single_Real_Predictor
33: -- Secant_Single_Complex_Predictor
34: -- Secant_Multiple_Real_Predictor
35: -- Secant_Multiple_Complex_Predictor
36: -- Tangent_Single_Real_Predictor
37: -- Tangent_Single_Complex_Predictor
38: -- Tangent_Multiple_Real_Predictor
39: -- Tangent_Multiple_Complex_Predictor
40:
41: -- Secant_Circular_Predictor
42: -- Secant_Geometric_Predictor
43: -- Tangent_Circular_Predictor
44: -- Tangent_Geometric_Predictor
45:
46: -- Hermite_Single_Real_Predictor
47:
48: -- The order in which these predictors are listed depends on their mutual
49: -- resemblances of the specified parameters.
50:
51: procedure Secant_Single_Real_Predictor
52: ( x : in out Vector; prev_x : in Vector;
53: t : in out Complex_Number; prev_t,target : in Complex_Number;
54: h,tol : in double_float; pow : in positive := 1 );
55:
56: procedure Secant_Multiple_Real_Predictor
57: ( x : in out Solution_Array; prev_x : in Solution_Array;
58: t : in out Complex_Number; prev_t,target : in Complex_Number;
59: h,tol,dist_x : in double_float; pow : in positive := 1 );
60:
61: -- DESCRIPTION :
62: -- Secant predictor for x and a linear predictor for t.
63:
64: -- ON ENTRY :
65: -- x the current approximation(s) for t;
66: -- prev_x the approximation(s) for a previous t;
67: -- t the current value of the continuation parameter;
68: -- prev_t is the previous value for t;
69: -- target is the target value for t;
70: -- h is the step size;
71: -- tol tolerance to decide when t = target;
72: -- dist_x for all i /= j : |x(i)(k) - x(j)(k)| > d, for k in 1..n;
73: -- pow power of t in the homotopy towards 1.
74:
75: -- ON RETURN :
76: -- x the predicted approximation(s);
77: -- t the predicted value of the continuation parameter.
78:
79: procedure Secant_Single_Complex_Predictor
80: ( x : in out Vector; prev_x : in Vector;
81: t : in out Complex_Number; prev_t,target : in Complex_Number;
82: h,tol,dist_t : in double_float; trial : in natural );
83:
84: procedure Secant_Multiple_Complex_Predictor
85: ( x : in out Solution_Array; prev_x : in Solution_Array;
86: t : in out Complex_Number; prev_t,target : in Complex_Number;
87: h,tol,dist_x,dist_t : in double_float;
88: trial : in natural);
89:
90: -- DESCRIPTION :
91: -- Secant predictor for x and complex predictor for t.
92:
93: -- ON ENTRY :
94: -- x the current approximation(s) for t;
95: -- prev_x the approximation(s) for a previous t;
96: -- t the current value of the continuation parameter;
97: -- prev_t is the previous value for t;
98: -- target is the target value for t;
99: -- h is the step size;
100: -- tol tolerance to decide when two numbers are equal;
101: -- dist_x for all i /= j : |x(i)(k) - x(j)(k)| > d, for k in 1..n;
102: -- dist_t t must keep a distance to the target;
103: -- trial indicates the number of trials for starting out of
104: -- the previous value for t.
105:
106: -- ON RETURN :
107: -- x the predicted approximation(s);
108: -- t the predicted value of the continuation parameter.
109:
110: procedure Secant_Circular_Predictor
111: ( x : in out Vector; prev_x : in Vector;
112: t : in out Complex_Number; theta : in out double_float;
113: prev_t,t0_min_target,target : in Complex_Number;
114: h,tol : in double_float );
115:
116: -- DESCRIPTION :
117: -- Secant predictor for x and circular predictor for t, around target.
118:
119: -- NOTE : This is the link between t and theta :
120: -- t = target + t0_min_target * ( cos(theta) + i sin(theta) )
121:
122: -- ON ENTRY :
123: -- x,prev_x,t,prev_t,target as before;
124: -- theta the angle for t.
125: -- t0_min_target is t0-target, where t0 is the start point;
126: -- h is step size for theta !!
127:
128: -- ON RETURN :
129: -- x the predicted approximation;
130: -- t the predicted value of the continuation parameter;
131: -- theta the predicted angle.
132:
133: procedure Secant_Geometric_Predictor
134: ( x : in out Vector; prev_x : in Vector;
135: t : in out Complex_Number; prev_t,target : in Complex_Number;
136: h,tol : in double_float );
137:
138: -- DESCRIPTION :
139: -- Secant predictor for x and a geometric predictor for t.
140:
141: -- ON ENTRY :
142: -- x the current approximation(s) for t;
143: -- prev_x the approximation(s) for a previous t;
144: -- t the current value of the continuation parameter;
145: -- prev_t is the previous value for t;
146: -- target is the target value for t;
147: -- h ratio between two consecutive distance to target, 0<h<1;
148: -- tol tolerance to decide when t = target;
149:
150: -- ON RETURN :
151: -- x the predicted approximation;
152: -- t the predicted value of the continuation parameter.
153:
154: generic
155:
156: with function Norm ( x : Vector ) return double_float;
157: with function dH ( x : Vector; t : Complex_Number ) return Vector;
158: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
159: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
160: -- returns the Jacobian matrix of H(x,t) at (x,t)
161:
162: procedure Tangent_Single_Real_Predictor
163: ( x : in out Vector; t : in out Complex_Number;
164: target : in Complex_Number; h,tol : in double_float;
165: pow : in positive := 1 );
166:
167: generic
168:
169: with function Norm ( x : Vector ) return double_float;
170: with function dH ( x : Vector; t : Complex_Number ) return Vector;
171: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
172: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
173: -- returns the Jacobian matrix of H(x,t) at (x,t)
174:
175: procedure Tangent_Multiple_Real_Predictor
176: ( x : in out Solution_Array; t : in out Complex_Number;
177: target : in Complex_Number; h,tol,dist_x : in double_float;
178: nsys : in out natural; pow : in positive := 1 );
179:
180: -- DESCRIPTION :
181: -- Tangent predictor for x and a linear predictor for t.
182:
183: -- ON ENTRY :
184: -- x current approximation for the solution;
185: -- t current value of the continuation parameter;
186: -- target target value for the continuation parameter;
187: -- h steplength;
188: -- tol tolerance to decide when t = target;
189: -- dist_x for all i /= j : |x(i)(k) - x(j)(k)| > dist_x, for k in 1..n;
190: -- nsys must be initally equal to zero, used for counting;
191: -- pow power of t in the homotopy.
192:
193: -- ON RETURN :
194: -- x predicted approximation for the solution;
195: -- t new value of the continuation parameter;
196: -- nsys the number of linear systems solved.
197:
198: generic
199:
200: with function Norm ( x : Vector ) return double_float;
201: with function dH ( x : Vector; t : Complex_Number ) return Vector;
202: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
203: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
204: -- returns the Jacobian matrix of H(x,t) at (x,t)
205:
206: procedure Tangent_Single_Complex_Predictor
207: ( x : in out Vector; t : in out Complex_Number;
208: target : in Complex_Number;
209: h,tol,dist_t : in double_float; trial : in natural );
210:
211: generic
212:
213: with function Norm ( x : Vector) return double_float;
214: with function dH ( x : Vector; t : Complex_Number ) return Vector;
215: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
216: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
217: -- returns the Jacobian matrix of H(x,t) at (x,t)
218:
219: procedure Tangent_Multiple_Complex_Predictor
220: ( x : in out Solution_Array; t : in out Complex_Number;
221: target : in Complex_Number;
222: h,tol,dist_x,dist_t : in double_float;
223: trial : in natural; nsys : in out natural );
224:
225: -- DESCRIPTION :
226: -- Tangent predictor for x and a complex predictor for t.
227:
228: -- ON ENTRY :
229: -- x current approximation for the solution;
230: -- t current value of the continuation parameter;
231: -- target target value for the continuation parameter;
232: -- h steplength;
233: -- tol tolerance to decide when two numbers are equal;
234: -- dist_x for all i /= j : |x(i)(k) - x(j)(k)| > d, for k in 1..n;
235: -- dist_t t must keep distance to the target;
236: -- trial indicates the number of trials for starting out of
237: -- the previous value for t;
238: -- nsys must be initially equal to zero.
239:
240: -- ON RETURN :
241: -- x predicted approximation for the solution;
242: -- t new value of the continuation parameter;
243: -- nsys the number of linear systems solved.
244:
245: generic
246:
247: with function Norm ( x : Vector) return double_float;
248: with function dH ( x : Vector; t : Complex_Number ) return Vector;
249: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
250: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
251: -- returns the Jacobian matrix of H(x,t) at (x,t)
252:
253: procedure Tangent_Circular_Predictor
254: ( x : in out Vector; t : in out Complex_Number;
255: theta : in out double_float;
256: t0_min_target,target : in Complex_Number;
257: h,tol : in double_float );
258:
259: -- DESCRIPTION :
260: -- This is a tangent predictor for x and a circular predictor for t
261: -- For information on the parameters, see Secant_Circular_Predictor.
262:
263: generic
264:
265: with function Norm ( x : Vector) return double_float;
266: with function dH ( x : Vector; t : Complex_Number ) return Vector;
267: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
268: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
269: -- returns the Jacobian matrix of H(x,t) at (x,t)
270:
271: procedure Tangent_Geometric_Predictor
272: ( x : in out Vector; t : in out Complex_Number;
273: target : in Complex_Number; h,tol : in double_float );
274:
275: -- DESCRIPTION :
276: -- Tangent predictor for x and a geometric predictor for t.
277: -- For information on the parameters, see Secant_Geometric_Predictor.
278:
279: generic
280:
281: with function Norm ( x : Vector) return double_float;
282: with function dH ( x : Vector; t : Complex_Number ) return Vector;
283: -- returns the derivatives of H(x,t) w.r.t. t in (x,t)
284: with function dH ( x : Vector; t : Complex_Number ) return Matrix;
285: -- returns the Jacobian matrix of H(x,t) at (x,t)
286:
287: procedure Hermite_Single_Real_Predictor
288: ( x : in out Vector; prev_x : in Vector;
289: t : in out Complex_Number; prev_t,target : in Complex_Number;
290: v : in out Vector; prev_v : in Vector;
291: h,tol : in double_float; pow : in positive := 1 );
292:
293: -- DESCRIPTION :
294: -- Third-order extrapolation based on previous values of the solution
295: -- paths along with corresponding first derivatives.
296:
297: -- ON ENTRY :
298: -- x current approximation for the solution;
299: -- prev_x previous approximation of the solution at prev_t;
300: -- t current value of the continuation parameter;
301: -- prev_t previous value of the continuation parameter;
302: -- target target value for the continuation parameter;
303: -- v will be used at work space;
304: -- prev_v direction of the path at prev_t;
305: -- h steplength;
306: -- tol tolerance to decide when t = target;
307: -- dist_x for all i /= j : |x(i)(k) - x(j)(k)| > dist_x, for k in 1..n;
308: -- pow power of t in the homotopy.
309:
310: -- ON RETURN :
311: -- x predicted approximation for the solution;
312: -- t new value of the continuation parameter;
313: -- v direction of the path computed for value of t on entry.
314:
315: end Predictors;
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>