/[lmdze]/trunk/libf/IOIPSL/mathop.f90
ViewVC logotype

Contents of /trunk/libf/IOIPSL/mathop.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 62 - (show annotations)
Thu Jul 26 14:37:37 2012 UTC (11 years, 9 months ago) by guez
File size: 18814 byte(s)
Changed handling of compiler in compilation system.

Removed the prefix letters "y", "p", "t" or "z" in some names of variables.

Replaced calls to NetCDF by calls to NetCDF95.

Extracted "ioget_calendar" procedures from "calendar.f90" into a
separate file.

Extracted to a separate file, "mathop2.f90", procedures that were not
part of the generic interface "mathop" in "mathop.f90".

Removed computation of "dq" in "bilan_dyn", which was not used.

In "iniadvtrac", removed schemes 20 Slopes and 30 Prather. Was not
compatible with declarations of array sizes.

In "clcdrag", "ustarhb", "vdif_kcay", "yamada4" and "coefkz", changed
the size of some arrays from "klon" to "knon".

Removed possible call to "conema3" in "physiq".

Removed unused argument "cd" in "yamada".

1 MODULE mathop_m
2
3 ! From mathelp.f90, version 2.0 2004/04/05 14:47:50
4
5 implicit none
6
7 PRIVATE
8 PUBLIC :: mathop
9
10 INTERFACE mathop
11 MODULE PROCEDURE mathop_r11, mathop_r21, mathop_r31
12 END INTERFACE mathop
13
14 ! Variables used to detect and identify the operations
15 CHARACTER(LEN=120):: indexfu = 'gather, scatter, fill, coll, undef, only'
16
17 CONTAINS
18
19 SUBROUTINE mathop_r11(fun, nb, work_in, miss_val, nb_index, nindex, scal, &
20 nb_max, work_out)
21
22 ! This subroutine gives an interface to the various operations
23 ! which are allowed. The interface is general enough to allow its
24 ! use for other cases.
25
26 ! INPUT
27
28 ! fun : function to be applied to the vector of data
29 ! nb : Length of input vector
30 ! work_in : Input vector of data (REAL)
31 ! miss_val : The value of the missing data flag (it has to be a
32 ! maximum value, in f90 : huge( a real ))
33 ! nb_index : Length of index vector
34 ! nindex : Vector of indices
35 ! scal : A scalar value for vector/scalar operations
36 ! nb_max : maximum length of output vector
37
38 ! OUTPUT
39
40 ! nb_max : Actual length of output variable
41 ! work_out : Output vector after the operation was applied
42 USE errioipsl, ONLY : histerr
43 USE mathop2, ONLY : ma_abs_r11, ma_acos_r11, ma_add_r11, ma_alog_r11, &
44 ma_asin_r11, ma_atan_r11, ma_cels_r11, ma_chs_r11, ma_cos_r11, &
45 ma_deg_r11, ma_divi_r11, ma_div_r11, ma_exp_r11, ma_fucoll_r11, &
46 ma_fufill_r11, ma_fugath_r11, ma_fumax_r11, ma_fumin_r11, &
47 ma_fuonly_r11, ma_fuscat_r11, ma_fuundef_r11, ma_ident_r11, &
48 ma_kelv_r11, ma_mult_r11, ma_power_r11, ma_rad_r11, ma_sin_r11, &
49 ma_sqrt_r11, ma_subi_r11, ma_sub_r11, ma_tan_r11
50
51 CHARACTER(LEN=7) :: fun
52 INTEGER :: nb, nb_max, nb_index
53 INTEGER :: nindex(nb_index)
54 REAL :: work_in(nb), scal, miss_val
55 REAL :: work_out(nb_max)
56
57 INTEGER :: ierr
58
59 INTRINSIC SIN, COS, TAN, ASIN, ACOS, ATAN, EXP, ALOG, SQRT, ABS
60 !--------------------------------------------------------------------
61 ierr = 0
62
63 IF (scal >= miss_val-1.) THEN
64 IF (INDEX(indexfu, fun(1:LEN_TRIM(fun))) == 0) THEN
65 SELECT CASE (fun)
66 CASE('sin')
67 ierr = ma_sin_r11(nb, work_in, nb_max, work_out)
68 CASE('cos')
69 ierr = ma_cos_r11(nb, work_in, nb_max, work_out)
70 CASE('tan')
71 ierr = ma_tan_r11(nb, work_in, nb_max, work_out)
72 CASE('asin')
73 ierr = ma_asin_r11(nb, work_in, nb_max, work_out)
74 CASE('acos')
75 ierr = ma_acos_r11(nb, work_in, nb_max, work_out)
76 CASE('atan')
77 ierr = ma_atan_r11(nb, work_in, nb_max, work_out)
78 CASE('exp')
79 ierr = ma_exp_r11(nb, work_in, nb_max, work_out)
80 CASE('log')
81 ierr = ma_alog_r11(nb, work_in, nb_max, work_out)
82 CASE('sqrt')
83 ierr = ma_sqrt_r11(nb, work_in, nb_max, work_out)
84 CASE('chs')
85 ierr = ma_chs_r11(nb, work_in, nb_max, work_out)
86 CASE('abs')
87 ierr = ma_abs_r11(nb, work_in, nb_max, work_out)
88 CASE('cels')
89 ierr = ma_cels_r11(nb, work_in, nb_max, work_out)
90 CASE('kelv')
91 ierr = ma_kelv_r11(nb, work_in, nb_max, work_out)
92 CASE('deg')
93 ierr = ma_deg_r11(nb, work_in, nb_max, work_out)
94 CASE('rad')
95 ierr = ma_rad_r11(nb, work_in, nb_max, work_out)
96 CASE('ident')
97 ierr = ma_ident_r11(nb, work_in, nb_max, work_out)
98 CASE DEFAULT
99 CALL histerr(3, "mathop", &
100 'scalar variable undefined and no indexing', &
101 'but still unknown function', fun)
102 END SELECT
103 IF (ierr > 0) THEN
104 CALL histerr(3, "mathop", &
105 'Error while executing a simple function', fun, ' ')
106 ENDIF
107 ELSE
108 SELECT CASE (fun)
109 CASE('gather')
110 ierr = ma_fugath_r11(nb, work_in, nb_index, nindex, &
111 miss_val, nb_max, work_out)
112 CASE('scatter')
113 IF (nb_index > nb) THEN
114 work_out(1:nb_max) = miss_val
115 ierr=1
116 ELSE
117 ierr = ma_fuscat_r11(nb, work_in, nb_index, nindex, &
118 miss_val, nb_max, work_out)
119 ENDIF
120 CASE('coll')
121 ierr = ma_fucoll_r11(nb, work_in, nb_index, nindex, &
122 miss_val, nb_max, work_out)
123 CASE('fill')
124 ierr = ma_fufill_r11(nb, work_in, nb_index, nindex, &
125 miss_val, nb_max, work_out)
126 CASE('undef')
127 ierr = ma_fuundef_r11(nb, work_in, nb_index, nindex, &
128 miss_val, nb_max, work_out)
129 CASE('only')
130 ierr = ma_fuonly_r11(nb, work_in, nb_index, nindex, &
131 miss_val, nb_max, work_out)
132 CASE DEFAULT
133 CALL histerr(3, "mathop", &
134 'scalar variable undefined and indexing', &
135 'was requested but with unknown function', fun)
136 END SELECT
137 IF (ierr > 0) THEN
138 CALL histerr(3, "mathop_r11", &
139 'Error while executing an indexing function', fun, ' ')
140 ENDIF
141 ENDIF
142 ELSE
143 SELECT CASE (fun)
144 CASE('fumin')
145 ierr = ma_fumin_r11(nb, work_in, scal, nb_max, work_out)
146 CASE('fumax')
147 ierr = ma_fumax_r11(nb, work_in, scal, nb_max, work_out)
148 CASE('add')
149 ierr = ma_add_r11(nb, work_in, scal, nb_max, work_out)
150 CASE('subi')
151 ierr = ma_subi_r11(nb, work_in, scal, nb_max, work_out)
152 CASE('sub')
153 ierr = ma_sub_r11(nb, work_in, scal, nb_max, work_out)
154 CASE('mult')
155 ierr = ma_mult_r11(nb, work_in, scal, nb_max, work_out)
156 CASE('div')
157 ierr = ma_div_r11(nb, work_in, scal, nb_max, work_out)
158 CASE('divi')
159 ierr = ma_divi_r11(nb, work_in, scal, nb_max, work_out)
160 CASE('power')
161 ierr = ma_power_r11(nb, work_in, scal, nb_max, work_out)
162 CASE DEFAULT
163 CALL histerr(3, "mathop", &
164 'Unknown operation with a scalar', fun, ' ')
165 END SELECT
166 IF (ierr > 0) THEN
167 CALL histerr(3, "mathop", &
168 'Error while executing a scalar function', fun, ' ')
169 ENDIF
170 ENDIF
171 !-----------------------
172 END SUBROUTINE mathop_r11
173 !
174 SUBROUTINE mathop_r21(fun, nb, work_in, miss_val, nb_index, nindex, scal, &
175 nb_max, work_out)
176
177 ! This subroutines gives an interface to the various operations
178 ! which are allowed. The interface is general enough to allow its use
179 ! for other cases.
180
181 ! INPUT
182
183 ! fun : function to be applied to the vector of data
184 ! nb : Length of input vector
185 ! work_in : Input vector of data (REAL)
186 ! miss_val : The value of the missing data flag (it has to be a
187 ! maximum value, in f90 : huge( a real ))
188 ! nb_index : Length of index vector
189 ! nindex : Vector of indices
190 ! scal : A scalar value for vector/scalar operations
191 ! nb_max : maximum length of output vector
192
193 ! OUTPUT
194
195 ! nb_max : Actual length of output variable
196 ! work_out : Output vector after the operation was applied
197 USE errioipsl, ONLY : histerr
198 USE mathop2, ONLY : ma_abs_r21, ma_acos_r21, ma_add_r21, ma_alog_r21, &
199 ma_asin_r21, ma_atan_r21, ma_cels_r21, ma_chs_r21, ma_cos_r21, &
200 ma_deg_r21, ma_divi_r21, ma_div_r21, ma_exp_r21, ma_fucoll_r21, &
201 ma_fufill_r21, ma_fugath_r21, ma_fumax_r21, ma_fumin_r21, &
202 ma_fuonly_r21, ma_fuscat_r21, ma_fuundef_r21, ma_ident_r21, &
203 ma_kelv_r21, ma_mult_r21, ma_power_r21, ma_rad_r21, ma_sin_r21, &
204 ma_sqrt_r21, ma_subi_r21, ma_sub_r21, ma_tan_r21
205
206 CHARACTER(LEN=7) :: fun
207 INTEGER :: nb(2), nb_max, nb_index
208 INTEGER :: nindex(nb_index)
209 REAL :: work_in(nb(1), nb(2)), scal, miss_val
210 REAL :: work_out(nb_max)
211
212 INTEGER :: ierr
213
214 INTRINSIC SIN, COS, TAN, ASIN, ACOS, ATAN, EXP, ALOG, SQRT, ABS
215 !--------------------------------------------------------------------
216 ierr = 0
217
218 IF (scal >= miss_val-1.) THEN
219 IF (INDEX(indexfu, fun(1:LEN_TRIM(fun))) == 0) THEN
220 SELECT CASE (fun)
221 CASE('sin')
222 ierr = ma_sin_r21(nb, work_in, nb_max, work_out)
223 CASE('cos')
224 ierr = ma_cos_r21(nb, work_in, nb_max, work_out)
225 CASE('tan')
226 ierr = ma_tan_r21(nb, work_in, nb_max, work_out)
227 CASE('asin')
228 ierr = ma_asin_r21(nb, work_in, nb_max, work_out)
229 CASE('acos')
230 ierr = ma_acos_r21(nb, work_in, nb_max, work_out)
231 CASE('atan')
232 ierr = ma_atan_r21(nb, work_in, nb_max, work_out)
233 CASE('exp')
234 ierr = ma_exp_r21(nb, work_in, nb_max, work_out)
235 CASE('log')
236 ierr = ma_alog_r21(nb, work_in, nb_max, work_out)
237 CASE('sqrt')
238 ierr = ma_sqrt_r21(nb, work_in, nb_max, work_out)
239 CASE('chs')
240 ierr = ma_chs_r21(nb, work_in, nb_max, work_out)
241 CASE('abs')
242 ierr = ma_abs_r21(nb, work_in, nb_max, work_out)
243 CASE('cels')
244 ierr = ma_cels_r21(nb, work_in, nb_max, work_out)
245 CASE('kelv')
246 ierr = ma_kelv_r21(nb, work_in, nb_max, work_out)
247 CASE('deg')
248 ierr = ma_deg_r21(nb, work_in, nb_max, work_out)
249 CASE('rad')
250 ierr = ma_rad_r21(nb, work_in, nb_max, work_out)
251 CASE('ident')
252 ierr = ma_ident_r21(nb, work_in, nb_max, work_out)
253 CASE DEFAULT
254 CALL histerr(3, "mathop", &
255 'scalar variable undefined and no indexing', &
256 'but still unknown function', fun)
257 END SELECT
258 IF (ierr > 0) THEN
259 CALL histerr(3, "mathop", &
260 'Error while executing a simple function', fun, ' ')
261 ENDIF
262 ELSE
263 SELECT CASE (fun)
264 CASE('gather')
265 ierr = ma_fugath_r21(nb, work_in, nb_index, nindex, &
266 miss_val, nb_max, work_out)
267 CASE('scatter')
268 IF (nb_index > (nb(1)*nb(2)) ) THEN
269 work_out(1:nb_max) = miss_val
270 ierr=1
271 ELSE
272 ierr = ma_fuscat_r21(nb, work_in, nb_index, nindex, &
273 miss_val, nb_max, work_out)
274 ENDIF
275 CASE('coll')
276 ierr = ma_fucoll_r21(nb, work_in, nb_index, nindex, &
277 miss_val, nb_max, work_out)
278 CASE('fill')
279 ierr = ma_fufill_r21(nb, work_in, nb_index, nindex, &
280 miss_val, nb_max, work_out)
281 CASE('undef')
282 ierr = ma_fuundef_r21(nb, work_in, nb_index, nindex, &
283 miss_val, nb_max, work_out)
284 CASE('only')
285 ierr = ma_fuonly_r21(nb, work_in, nb_index, nindex, &
286 miss_val, nb_max, work_out)
287 CASE DEFAULT
288 CALL histerr(3, "mathop", &
289 'scalar variable undefined and indexing', &
290 'was requested but with unknown function', fun)
291 END SELECT
292 IF (ierr > 0) THEN
293 CALL histerr(3, "mathop_r21", &
294 'Error while executing an indexing function', fun, ' ')
295 ENDIF
296 ENDIF
297 ELSE
298 SELECT CASE (fun)
299 CASE('fumin')
300 ierr = ma_fumin_r21(nb, work_in, scal, nb_max, work_out)
301 CASE('fumax')
302 ierr = ma_fumax_r21(nb, work_in, scal, nb_max, work_out)
303 CASE('add')
304 ierr = ma_add_r21(nb, work_in, scal, nb_max, work_out)
305 CASE('subi')
306 ierr = ma_subi_r21(nb, work_in, scal, nb_max, work_out)
307 CASE('sub')
308 ierr = ma_sub_r21(nb, work_in, scal, nb_max, work_out)
309 CASE('mult')
310 ierr = ma_mult_r21(nb, work_in, scal, nb_max, work_out)
311 CASE('div')
312 ierr = ma_div_r21(nb, work_in, scal, nb_max, work_out)
313 CASE('divi')
314 ierr = ma_divi_r21(nb, work_in, scal, nb_max, work_out)
315 CASE('power')
316 ierr = ma_power_r21(nb, work_in, scal, nb_max, work_out)
317 CASE DEFAULT
318 CALL histerr(3, "mathop", &
319 'Unknown operation with a scalar', fun, ' ')
320 END SELECT
321 IF (ierr > 0) THEN
322 CALL histerr(3, "mathop", &
323 'Error while executing a scalar function', fun, ' ')
324 ENDIF
325 ENDIF
326 !-----------------------
327 END SUBROUTINE mathop_r21
328 !
329 SUBROUTINE mathop_r31(fun, nb, work_in, miss_val, nb_index, nindex, scal, &
330 nb_max, work_out)
331
332 ! This subroutines gives an interface to the various operations
333 ! which are allowed. The interface is general enough to allow its use
334 ! for other cases.
335
336 ! INPUT
337
338 ! fun : function to be applied to the vector of data
339 ! nb : Length of input vector
340 ! work_in : Input vector of data (REAL)
341 ! miss_val : The value of the missing data flag (it has to be a
342 ! maximum value, in f90 : huge( a real ))
343 ! nb_index : Length of index vector
344 ! nindex : Vector of indices
345 ! scal : A scalar value for vector/scalar operations
346 ! nb_max : maximum length of output vector
347
348 ! OUTPUT
349
350 ! nb_max : Actual length of output variable
351 ! work_out : Output vector after the operation was applied
352 USE errioipsl, ONLY : histerr
353 USE mathop2, ONLY : ma_abs_r31, ma_acos_r31, ma_add_r31, ma_alog_r31, &
354 ma_asin_r31, ma_atan_r31, ma_cels_r31, ma_chs_r31, ma_cos_r31, &
355 ma_deg_r31, ma_divi_r31, ma_div_r31, ma_exp_r31, ma_fucoll_r31, &
356 ma_fufill_r31, ma_fugath_r31, ma_fumax_r31, ma_fumin_r31, &
357 ma_fuonly_r31, ma_fuscat_r31, ma_fuundef_r31, ma_ident_r31, &
358 ma_kelv_r31, ma_mult_r31, ma_power_r31, ma_rad_r31, ma_sin_r31, &
359 ma_sqrt_r31, ma_subi_r31, ma_sub_r31, ma_tan_r31
360
361 CHARACTER(LEN=7) :: fun
362 INTEGER :: nb(3), nb_max, nb_index
363 INTEGER :: nindex(nb_index)
364 REAL :: work_in(nb(1), nb(2), nb(3)), scal, miss_val
365 REAL :: work_out(nb_max)
366
367 INTEGER :: ierr
368
369 INTRINSIC SIN, COS, TAN, ASIN, ACOS, ATAN, EXP, ALOG, SQRT, ABS
370 !--------------------------------------------------------------------
371 ierr = 0
372
373 IF (scal >= miss_val-1.) THEN
374 IF (INDEX(indexfu, fun(1:LEN_TRIM(fun))) == 0) THEN
375 SELECT CASE (fun)
376 CASE('sin')
377 ierr = ma_sin_r31(nb, work_in, nb_max, work_out)
378 CASE('cos')
379 ierr = ma_cos_r31(nb, work_in, nb_max, work_out)
380 CASE('tan')
381 ierr = ma_tan_r31(nb, work_in, nb_max, work_out)
382 CASE('asin')
383 ierr = ma_asin_r31(nb, work_in, nb_max, work_out)
384 CASE('acos')
385 ierr = ma_acos_r31(nb, work_in, nb_max, work_out)
386 CASE('atan')
387 ierr = ma_atan_r31(nb, work_in, nb_max, work_out)
388 CASE('exp')
389 ierr = ma_exp_r31(nb, work_in, nb_max, work_out)
390 CASE('log')
391 ierr = ma_alog_r31(nb, work_in, nb_max, work_out)
392 CASE('sqrt')
393 ierr = ma_sqrt_r31(nb, work_in, nb_max, work_out)
394 CASE('chs')
395 ierr = ma_chs_r31(nb, work_in, nb_max, work_out)
396 CASE('abs')
397 ierr = ma_abs_r31(nb, work_in, nb_max, work_out)
398 CASE('cels')
399 ierr = ma_cels_r31(nb, work_in, nb_max, work_out)
400 CASE('kelv')
401 ierr = ma_kelv_r31(nb, work_in, nb_max, work_out)
402 CASE('deg')
403 ierr = ma_deg_r31(nb, work_in, nb_max, work_out)
404 CASE('rad')
405 ierr = ma_rad_r31(nb, work_in, nb_max, work_out)
406 CASE('ident')
407 ierr = ma_ident_r31(nb, work_in, nb_max, work_out)
408 CASE DEFAULT
409 CALL histerr(3, "mathop", &
410 'scalar variable undefined and no indexing', &
411 'but still unknown function', fun)
412 END SELECT
413 IF (ierr > 0) THEN
414 CALL histerr(3, "mathop", &
415 'Error while executing a simple function', fun, ' ')
416 ENDIF
417 ELSE
418 SELECT CASE (fun)
419 CASE('gather')
420 ierr = ma_fugath_r31(nb, work_in, nb_index, nindex, &
421 miss_val, nb_max, work_out)
422 CASE('scatter')
423 IF (nb_index > (nb(1)*nb(2)*nb(3))) THEN
424 work_out(1:nb_max) = miss_val
425 ierr=1
426 ELSE
427 ierr = ma_fuscat_r31(nb, work_in, nb_index, nindex, &
428 miss_val, nb_max, work_out)
429 ENDIF
430 CASE('coll')
431 ierr = ma_fucoll_r31(nb, work_in, nb_index, nindex, &
432 miss_val, nb_max, work_out)
433 CASE('fill')
434 ierr = ma_fufill_r31(nb, work_in, nb_index, nindex, &
435 miss_val, nb_max, work_out)
436 CASE('undef')
437 ierr = ma_fuundef_r31(nb, work_in, nb_index, nindex, &
438 miss_val, nb_max, work_out)
439 CASE('only')
440 ierr = ma_fuonly_r31(nb, work_in, nb_index, nindex, &
441 miss_val, nb_max, work_out)
442 CASE DEFAULT
443 CALL histerr(3, "mathop", &
444 'scalar variable undefined and indexing', &
445 'was requested but with unknown function', fun)
446 END SELECT
447 IF (ierr > 0) THEN
448 CALL histerr(3, "mathop_r31", &
449 'Error while executing an indexing function', fun, ' ')
450 ENDIF
451 ENDIF
452 ELSE
453 SELECT CASE (fun)
454 CASE('fumin')
455 ierr = ma_fumin_r31(nb, work_in, scal, nb_max, work_out)
456 CASE('fumax')
457 ierr = ma_fumax_r31(nb, work_in, scal, nb_max, work_out)
458 CASE('add')
459 ierr = ma_add_r31(nb, work_in, scal, nb_max, work_out)
460 CASE('subi')
461 ierr = ma_subi_r31(nb, work_in, scal, nb_max, work_out)
462 CASE('sub')
463 ierr = ma_sub_r31(nb, work_in, scal, nb_max, work_out)
464 CASE('mult')
465 ierr = ma_mult_r31(nb, work_in, scal, nb_max, work_out)
466 CASE('div')
467 ierr = ma_div_r31(nb, work_in, scal, nb_max, work_out)
468 CASE('divi')
469 ierr = ma_divi_r31(nb, work_in, scal, nb_max, work_out)
470 CASE('power')
471 ierr = ma_power_r31(nb, work_in, scal, nb_max, work_out)
472 CASE DEFAULT
473 CALL histerr(3, "mathop", &
474 'Unknown operation with a scalar', fun, ' ')
475 END SELECT
476 IF (ierr > 0) THEN
477 CALL histerr(3, "mathop", &
478 'Error while executing a scalar function', fun, ' ')
479 ENDIF
480 ENDIF
481
482 END SUBROUTINE mathop_r31
483
484 END MODULE mathop_m

  ViewVC Help
Powered by ViewVC 1.1.21