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

Annotation of /trunk/IOIPSL/histwrite.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 178 - (hide annotations)
Fri Mar 11 18:47:26 2016 UTC (8 years, 3 months ago) by guez
Original Path: trunk/Sources/IOIPSL/histwrite.f
File size: 15171 byte(s)
Moved variables date0, deltat, datasz_max, ncvar_ids, point, buff_pos,
buffer, regular from module histcom_var to modules where they are
defined.

Removed procedure ioipslmpp, useless for a sequential program.

Added argument datasz_max to histwrite_real (to avoid circular
dependency with histwrite).

Removed useless variables and computations everywhere.

Changed real litteral constants from default kind to double precision
in lwb, lwu, lwvn, sw1s, swtt, swtt1, swu.

Removed unused arguments: paer of sw, sw1s, sw2s, swclr; pcldsw of
sw1s, sw2s; pdsig, prayl of swr; co2_ppm of clmain, clqh; tsol of
transp_lay; nsrf of screenp; kcrit and kknu of gwstress; pstd of
orosetup.

Added output of relative humidity.

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

  ViewVC Help
Powered by ViewVC 1.1.21