/[lmdze]/trunk/IOIPSL/histwrite.f
ViewVC logotype

Contents of /trunk/IOIPSL/histwrite.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 92 - (show annotations)
Wed Mar 26 18:16:05 2014 UTC (10 years, 1 month ago) by guez
File size: 15041 byte(s)
Extracted procedures that were in module calendar into separate files.

1 MODULE histwrite_m
2
3 ! From histcom.f90, version 2.1 2004/04/21 09:27:10
4
5 USE errioipsl, ONLY: histerr
6 USE histcom_var, ONLY: datasz_in, datasz_max, date0, deltat, &
7 freq_opp, freq_wrt, fuchnbout, last_opp, last_opp_chk, last_wrt, &
8 last_wrt_chk, missing_val, nbopp, nb_files, scal, scsize, sopps, &
9 topp
10 use histvar_seq_m, only: histvar_seq
11 use histwrite_real_m, only: histwrite_real
12 use isittime_m, only: isittime
13 USE mathop_m, ONLY: mathop
14
15 implicit none
16
17 INTERFACE histwrite
18 ! The "histwrite" procedures give the data to the input-output system.
19 ! They trigger the operations to be performed and the writing to
20 ! the file if needed.
21
22 ! We test the work to be done at this time here so that at a
23 ! later stage we can call different operations and write subroutines
24 ! for the REAL and INTEGER interfaces.
25
26 ! INTEGER, INTENT(IN):: fileid
27 ! The ID of the file on which this variable is to be written.
28 ! The variable should have been defined in this file before.
29
30 ! CHARACTER(LEN=*), INTENT(IN):: varname
31 ! short name of the variable
32
33 ! INTEGER, INTENT(IN):: itau
34 ! current timestep
35
36 ! REAL, INTENT(IN):: pdata(:) or (:, :) or (:, :, :)
37 ! values of the variable
38
39 ! The difference between the procedures is the rank of "pdata".
40
41 MODULE PROCEDURE histwrite_r1d, histwrite_r2d, histwrite_r3d
42 END INTERFACE histwrite
43
44 PRIVATE
45 public histwrite
46
47 CONTAINS
48
49 SUBROUTINE histwrite_r1d(fileid, varname, itau, pdata)
50
51 INTEGER, INTENT(IN):: fileid, itau
52 CHARACTER(LEN=*), INTENT(IN):: varname
53 REAL, INTENT(IN):: pdata(:)
54
55 ! Variables local to the procedure:
56 integer nbindex, nindex(size(pdata))
57 LOGICAL:: do_oper, do_write, largebuf
58 INTEGER:: varid, io, nbpt_in, nbpt_out
59 REAL, ALLOCATABLE, SAVE:: buff_tmp(:)
60 INTEGER, SAVE:: buff_tmp_sz
61 CHARACTER(LEN=7):: tmp_opp
62
63 !--------------------------------------------------------------------
64
65 nbindex = size(nindex)
66 nindex = 0
67
68 ! 1.0 Try to catch errors like specifying the wrong file ID.
69
70 IF ((fileid < 1) .OR. (fileid > nb_files)) THEN
71 CALL histerr(3, "histwrite", &
72 'Illegal file ID in the histwrite of variable', varname, ' ')
73 ENDIF
74
75 ! 1.1 Find the id of the variable to be written and the real time
76
77 CALL histvar_seq(fileid, varname, varid)
78
79 ! 2.0 do nothing for never operation
80
81 tmp_opp = topp(fileid, varid)
82
83 IF (TRIM(tmp_opp) == "never") THEN
84 last_opp_chk(fileid, varid) = -99
85 last_wrt_chk(fileid, varid) = -99
86 ENDIF
87
88 ! 3.0 We check if we need to do an operation
89
90 IF (last_opp_chk(fileid, varid) == itau) THEN
91 CALL histerr(3, "histwrite", &
92 'This variable as already been analysed at the present', &
93 'time step', ' ')
94 ENDIF
95
96 CALL isittime(itau, date0(fileid), deltat(fileid), &
97 freq_opp(fileid, varid), last_opp(fileid, varid), &
98 last_opp_chk(fileid, varid), do_oper)
99
100 ! 4.0 We check if we need to write the data
101
102 IF (last_wrt_chk(fileid, varid) == itau) THEN
103 CALL histerr(3, "histwrite", &
104 'This variable as already been written for the present', &
105 'time step', ' ')
106 ENDIF
107
108 CALL isittime(itau, date0(fileid), deltat(fileid), &
109 freq_wrt(fileid, varid), last_wrt(fileid, varid), &
110 last_wrt_chk(fileid, varid), do_write)
111
112 ! 5.0 histwrite called
113
114 IF (do_oper .OR. do_write) THEN
115 ! 5.1 Get the sizes of the data we will handle
116
117 IF (datasz_in(fileid, varid, 1) <= 0) THEN
118 ! There is the risk here that the user has over-sized the array.
119 ! But how can we catch this ?
120 ! In the worst case we will do impossible operations
121 ! on part of the data !
122 datasz_in(fileid, varid, 1) = SIZE(pdata)
123 datasz_in(fileid, varid, 2) = -1
124 datasz_in(fileid, varid, 3) = -1
125 ENDIF
126
127 ! 5.2 The maximum size of the data will give the size of the buffer
128
129 IF (datasz_max(fileid, varid) <= 0) THEN
130 largebuf = .FALSE.
131 DO io=1, nbopp(fileid, varid)
132 IF (INDEX(fuchnbout, sopps(fileid, varid, io)) > 0) THEN
133 largebuf = .TRUE.
134 ENDIF
135 ENDDO
136 IF (largebuf) THEN
137 datasz_max(fileid, varid) = scsize(fileid, varid, 1) &
138 * scsize(fileid, varid, 2) *scsize(fileid, varid, 3)
139 ELSE
140 datasz_max(fileid, varid) = datasz_in(fileid, varid, 1)
141 ENDIF
142 ENDIF
143
144 IF (.NOT.ALLOCATED(buff_tmp)) THEN
145 ALLOCATE(buff_tmp(datasz_max(fileid, varid)))
146 buff_tmp_sz = datasz_max(fileid, varid)
147 ELSE IF (datasz_max(fileid, varid) > buff_tmp_sz) THEN
148 DEALLOCATE(buff_tmp)
149 ALLOCATE(buff_tmp(datasz_max(fileid, varid)))
150 buff_tmp_sz = datasz_max(fileid, varid)
151 ENDIF
152
153 ! We have to do the first operation anyway. Thus we do it here
154 ! and change the ranke of the data at the same time. This
155 ! should speed up things.
156
157 nbpt_in = datasz_in(fileid, varid, 1)
158 nbpt_out = datasz_max(fileid, varid)
159 CALL mathop(sopps(fileid, varid, 1), nbpt_in, pdata, missing_val, &
160 nbindex, nindex, scal(fileid, varid, 1), nbpt_out, buff_tmp)
161 CALL histwrite_real(fileid, varid, itau, nbpt_out, buff_tmp, nbindex, &
162 nindex, do_oper, do_write)
163 ENDIF
164
165 ! 6.0 Manage time steps
166
167 IF ((TRIM(tmp_opp) /= "once") .AND. (TRIM(tmp_opp) /= "never")) THEN
168 last_opp_chk(fileid, varid) = itau
169 last_wrt_chk(fileid, varid) = itau
170 ELSE
171 last_opp_chk(fileid, varid) = -99
172 last_wrt_chk(fileid, varid) = -99
173 ENDIF
174
175 END SUBROUTINE histwrite_r1d
176
177 !************************************************************************
178
179 SUBROUTINE histwrite_r2d (fileid, varname, itau, pdata)
180
181 INTEGER, INTENT(IN):: fileid, itau
182 REAL, INTENT(IN):: pdata(:, :)
183 CHARACTER(LEN=*), INTENT(IN):: varname
184
185 integer nbindex, nindex(size(pdata))
186 LOGICAL:: do_oper, do_write, largebuf
187 INTEGER:: varid, io, nbpt_in(1:2), nbpt_out
188 REAL, ALLOCATABLE, SAVE:: buff_tmp(:)
189 INTEGER, SAVE:: buff_tmp_sz
190 CHARACTER(LEN=7):: tmp_opp
191
192 !--------------------------------------------------------------------
193
194 nbindex = size(nindex)
195 nindex = 0
196
197 ! 1.0 Try to catch errors like specifying the wrong file ID.
198
199 IF ( (fileid < 1).OR.(fileid > nb_files) ) THEN
200 CALL histerr (3, "histwrite", &
201 'Illegal file ID in the histwrite of variable', varname, ' ')
202 ENDIF
203
204 ! 1.1 Find the id of the variable to be written and the real time
205
206 CALL histvar_seq (fileid, varname, varid)
207
208 ! 2.0 do nothing for never operation
209
210 tmp_opp = topp(fileid, varid)
211
212 IF (TRIM(tmp_opp) == "never") THEN
213 last_opp_chk(fileid, varid) = -99
214 last_wrt_chk(fileid, varid) = -99
215 ENDIF
216
217 ! 3.0 We check if we need to do an operation
218
219 IF (last_opp_chk(fileid, varid) == itau) CALL histerr (3, "histwrite", &
220 'This variable as already been analysed at the present', &
221 'time step', ' ')
222
223 CALL isittime(itau, date0(fileid), deltat(fileid), &
224 freq_opp(fileid, varid), last_opp(fileid, varid), &
225 last_opp_chk(fileid, varid), do_oper)
226
227 ! 4.0 We check if we need to write the data
228
229 IF (last_wrt_chk(fileid, varid) == itau) THEN
230 CALL histerr (3, "histwrite", &
231 'This variable as already been written for the present', &
232 'time step', ' ')
233 ENDIF
234
235 CALL isittime &
236 (itau, date0(fileid), deltat(fileid), freq_wrt(fileid, varid), &
237 last_wrt(fileid, varid), last_wrt_chk(fileid, varid), do_write)
238
239 ! 5.0 histwrite called
240
241 IF (do_oper.OR.do_write) THEN
242
243 !- 5.1 Get the sizes of the data we will handle
244
245 IF (datasz_in(fileid, varid, 1) <= 0) THEN
246 !--- There is the risk here that the user has over-sized the array.
247 !--- But how can we catch this ?
248 !--- In the worst case we will do impossible operations
249 !--- on part of the data !
250 datasz_in(fileid, varid, 1) = SIZE(pdata, DIM=1)
251 datasz_in(fileid, varid, 2) = SIZE(pdata, DIM=2)
252 datasz_in(fileid, varid, 3) = -1
253 ENDIF
254
255 !- 5.2 The maximum size of the data will give the size of the buffer
256
257 IF (datasz_max(fileid, varid) <= 0) THEN
258 largebuf = .FALSE.
259 DO io=1, nbopp(fileid, varid)
260 IF (INDEX(fuchnbout, sopps(fileid, varid, io)) > 0) THEN
261 largebuf = .TRUE.
262 ENDIF
263 ENDDO
264 IF (largebuf) THEN
265 datasz_max(fileid, varid) = &
266 scsize(fileid, varid, 1) &
267 *scsize(fileid, varid, 2) &
268 *scsize(fileid, varid, 3)
269 ELSE
270 datasz_max(fileid, varid) = &
271 datasz_in(fileid, varid, 1) &
272 *datasz_in(fileid, varid, 2)
273 ENDIF
274 ENDIF
275
276 IF (.NOT.ALLOCATED(buff_tmp)) THEN
277 ALLOCATE (buff_tmp(datasz_max(fileid, varid)))
278 buff_tmp_sz = datasz_max(fileid, varid)
279 ELSE IF (datasz_max(fileid, varid) > buff_tmp_sz) THEN
280 DEALLOCATE (buff_tmp)
281 ALLOCATE (buff_tmp(datasz_max(fileid, varid)))
282 buff_tmp_sz = datasz_max(fileid, varid)
283 ENDIF
284
285 !- We have to do the first operation anyway.
286 !- Thus we do it here and change the ranke
287 !- of the data at the same time. This should speed up things.
288
289 nbpt_in(1:2) = datasz_in(fileid, varid, 1:2)
290 nbpt_out = datasz_max(fileid, varid)
291 CALL mathop (sopps(fileid, varid, 1), nbpt_in, pdata, &
292 missing_val, nbindex, nindex, &
293 scal(fileid, varid, 1), nbpt_out, buff_tmp)
294 CALL histwrite_real (fileid, varid, itau, nbpt_out, &
295 buff_tmp, nbindex, nindex, do_oper, do_write)
296 ENDIF
297
298 ! 6.0 Manage time steps
299
300 IF ((TRIM(tmp_opp) /= "once").AND.(TRIM(tmp_opp) /= "never")) THEN
301 last_opp_chk(fileid, varid) = itau
302 last_wrt_chk(fileid, varid) = itau
303 ELSE
304 last_opp_chk(fileid, varid) = -99
305 last_wrt_chk(fileid, varid) = -99
306 ENDIF
307
308 END SUBROUTINE histwrite_r2d
309
310 !************************************************************************
311
312 SUBROUTINE histwrite_r3d (fileid, varname, itau, pdata)
313
314 INTEGER, INTENT(IN):: fileid, itau
315 REAL, DIMENSION(:, :, :), INTENT(IN):: pdata
316 CHARACTER(LEN=*), INTENT(IN):: varname
317
318 integer nbindex, nindex(size(pdata))
319 LOGICAL:: do_oper, do_write, largebuf
320 INTEGER:: varid, io, nbpt_in(1:3), nbpt_out
321 REAL, ALLOCATABLE, SAVE:: buff_tmp(:)
322 INTEGER, SAVE:: buff_tmp_sz
323 CHARACTER(LEN=7):: tmp_opp
324
325 !--------------------------------------------------------------------
326
327 nbindex = size(nindex)
328 nindex = 0
329
330 ! 1.0 Try to catch errors like specifying the wrong file ID.
331 ! Thanks Marine for showing us what errors users can make !
332
333 IF ( (fileid < 1).OR.(fileid > nb_files) ) THEN
334 CALL histerr (3, "histwrite", &
335 'Illegal file ID in the histwrite of variable', varname, ' ')
336 ENDIF
337
338 ! 1.1 Find the id of the variable to be written and the real time
339
340 CALL histvar_seq (fileid, varname, varid)
341
342 ! 2.0 do nothing for never operation
343
344 tmp_opp = topp(fileid, varid)
345
346 IF (TRIM(tmp_opp) == "never") THEN
347 last_opp_chk(fileid, varid) = -99
348 last_wrt_chk(fileid, varid) = -99
349 ENDIF
350
351 ! 3.0 We check if we need to do an operation
352
353 IF (last_opp_chk(fileid, varid) == itau) THEN
354 CALL histerr (3, "histwrite", &
355 'This variable as already been analysed at the present', &
356 'time step', ' ')
357 ENDIF
358
359 CALL isittime &
360 (itau, date0(fileid), deltat(fileid), freq_opp(fileid, varid), &
361 last_opp(fileid, varid), last_opp_chk(fileid, varid), do_oper)
362
363 ! 4.0 We check if we need to write the data
364
365 IF (last_wrt_chk(fileid, varid) == itau) THEN
366 CALL histerr (3, "histwrite", &
367 'This variable as already been written for the present', &
368 'time step', ' ')
369 ENDIF
370
371 CALL isittime &
372 (itau, date0(fileid), deltat(fileid), freq_wrt(fileid, varid), &
373 last_wrt(fileid, varid), last_wrt_chk(fileid, varid), do_write)
374
375 ! 5.0 histwrite called
376
377 IF (do_oper.OR.do_write) THEN
378
379 !- 5.1 Get the sizes of the data we will handle
380
381 IF (datasz_in(fileid, varid, 1) <= 0) THEN
382 !--- There is the risk here that the user has over-sized the array.
383 !--- But how can we catch this ?
384 !--- In the worst case we will do impossible operations
385 !--- on part of the data !
386 datasz_in(fileid, varid, 1) = SIZE(pdata, DIM=1)
387 datasz_in(fileid, varid, 2) = SIZE(pdata, DIM=2)
388 datasz_in(fileid, varid, 3) = SIZE(pdata, DIM=3)
389 ENDIF
390
391 !- 5.2 The maximum size of the data will give the size of the buffer
392
393 IF (datasz_max(fileid, varid) <= 0) THEN
394 largebuf = .FALSE.
395 DO io =1, nbopp(fileid, varid)
396 IF (INDEX(fuchnbout, sopps(fileid, varid, io)) > 0) THEN
397 largebuf = .TRUE.
398 ENDIF
399 ENDDO
400 IF (largebuf) THEN
401 datasz_max(fileid, varid) = &
402 scsize(fileid, varid, 1) &
403 *scsize(fileid, varid, 2) &
404 *scsize(fileid, varid, 3)
405 ELSE
406 datasz_max(fileid, varid) = &
407 datasz_in(fileid, varid, 1) &
408 *datasz_in(fileid, varid, 2) &
409 *datasz_in(fileid, varid, 3)
410 ENDIF
411 ENDIF
412
413 IF (.NOT.ALLOCATED(buff_tmp)) THEN
414 ALLOCATE (buff_tmp(datasz_max(fileid, varid)))
415 buff_tmp_sz = datasz_max(fileid, varid)
416 ELSE IF (datasz_max(fileid, varid) > buff_tmp_sz) THEN
417 DEALLOCATE (buff_tmp)
418 ALLOCATE (buff_tmp(datasz_max(fileid, varid)))
419 buff_tmp_sz = datasz_max(fileid, varid)
420 ENDIF
421
422 !- We have to do the first operation anyway.
423 !- Thus we do it here and change the ranke
424 !- of the data at the same time. This should speed up things.
425
426 nbpt_in(1:3) = datasz_in(fileid, varid, 1:3)
427 nbpt_out = datasz_max(fileid, varid)
428 CALL mathop (sopps(fileid, varid, 1), nbpt_in, pdata, &
429 missing_val, nbindex, nindex, &
430 scal(fileid, varid, 1), nbpt_out, buff_tmp)
431 CALL histwrite_real (fileid, varid, itau, nbpt_out, &
432 buff_tmp, nbindex, nindex, do_oper, do_write)
433 ENDIF
434
435 ! 6.0 Manage time steps
436
437 IF ((TRIM(tmp_opp) /= "once").AND.(TRIM(tmp_opp) /= "never")) THEN
438 last_opp_chk(fileid, varid) = itau
439 last_wrt_chk(fileid, varid) = itau
440 ELSE
441 last_opp_chk(fileid, varid) = -99
442 last_wrt_chk(fileid, varid) = -99
443 ENDIF
444
445 END SUBROUTINE histwrite_r3d
446
447 END MODULE histwrite_m

  ViewVC Help
Powered by ViewVC 1.1.21