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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 67 - (show annotations)
Tue Oct 2 15:50:56 2012 UTC (11 years, 7 months ago) by guez
File size: 6951 byte(s)
Cleaning.
1 module histwrite_real_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE histwrite_real(fileid, varid, itau, nbdpt, buff_tmp, nbindex, &
8 nindex, do_oper, do_write)
9
10 ! This subroutine is internal and does the calculations and writing
11 ! if needed. At a later stage it should be split into an operation
12 ! and writing subroutines.
13
14 USE histcom_var, ONLY: buffer, buff_pos, datasz_max, deltat, &
15 last_opp, last_wrt, missing_val, nbopp, nb_opp, nb_wrt, ncdf_ids, &
16 ncvar_ids, point, regular, scal, scsize, sopps, tax_last, tdimid, &
17 topp, var_axid, zorig, zsize
18 USE mathelp, ONLY: trans_buff, moycum
19 USE mathop_m, ONLY: mathop
20 use netcdf, only: NF90_PUT_VAR
21
22 INTEGER, INTENT(IN):: fileid, varid, itau, nbdpt
23 REAL buff_tmp(:)
24
25 INTEGER, INTENT(IN):: nbindex
26 ! number of indices provided
27 ! If it is equal to the size of the full field as provided in histdef
28 ! then nothing is done.
29
30 INTEGER, INTENT(IN):: nindex(nbindex)
31 ! The indices used to expand the variable (pdata) onto the full field
32
33 LOGICAL, INTENT(IN):: do_oper, do_write
34
35 ! Local:
36
37 INTEGER:: tsz, ncid, ncvarid
38 INTEGER:: i, iret, ipt, itax
39 INTEGER:: io, nbin, nbout
40 INTEGER, DIMENSION(4):: corner, edges
41 INTEGER:: itime
42
43 REAL:: rtime
44 CHARACTER(LEN=7):: tmp_opp
45
46 REAL, ALLOCATABLE, SAVE:: buff_tmp2(:)
47 INTEGER, SAVE:: buff_tmp2_sz
48 REAL, ALLOCATABLE, SAVE:: buffer_used(:)
49 INTEGER, SAVE:: buffer_sz
50
51 !--------------------------------------------------------------------
52
53 ! The sizes which can be encoutered
54
55 tsz = zsize(fileid, varid, 1) * zsize(fileid, varid, 2) &
56 * zsize(fileid, varid, 3)
57
58 ! 1.0 We allocate the memory needed to store the data between write
59 ! and the temporary space needed for operations.
60 ! We have to keep precedent buffer if needed
61
62 IF (.NOT. ALLOCATED(buffer)) THEN
63 ALLOCATE(buffer(buff_pos))
64 buffer_sz = buff_pos
65 buffer(:)=0.0
66 ELSE IF (buffer_sz < buff_pos) THEN
67 IF (SUM(buffer)/=0.0) THEN
68 ALLOCATE(buffer_used(buffer_sz))
69 buffer_used(:)=buffer(:)
70 DEALLOCATE(buffer)
71 ALLOCATE(buffer(buff_pos))
72 buffer_sz = buff_pos
73 buffer(:SIZE(buffer_used))=buffer_used
74 DEALLOCATE(buffer_used)
75 ELSE
76 DEALLOCATE(buffer)
77 ALLOCATE(buffer(buff_pos))
78 buffer_sz = buff_pos
79 buffer(:)=0.0
80 ENDIF
81 ENDIF
82
83 ! The buffers are only deallocated when more space is needed. This
84 ! reduces the umber of allocates but increases memory needs.
85
86 IF (.NOT.ALLOCATED(buff_tmp2)) THEN
87 ALLOCATE(buff_tmp2(datasz_max(fileid, varid)))
88 buff_tmp2_sz = datasz_max(fileid, varid)
89 ELSE IF (datasz_max(fileid, varid) > buff_tmp2_sz) THEN
90 DEALLOCATE(buff_tmp2)
91 ALLOCATE(buff_tmp2(datasz_max(fileid, varid)))
92 buff_tmp2_sz = datasz_max(fileid, varid)
93 ENDIF
94
95 rtime = itau * deltat(fileid)
96 tmp_opp = topp(fileid, varid)
97
98 ! 3.0 Do the operations or transfer the slab of data into buff_tmp
99
100 ! 3.1 DO the Operations only if needed
101
102 IF (do_oper) THEN
103 i = fileid
104 nbout = nbdpt
105
106 ! 3.4 We continue the sequence of operations
107 ! we started in the interface routine
108
109 DO io = 2, nbopp(i, varid), 2
110 nbin = nbout
111 nbout = datasz_max(i, varid)
112 CALL mathop(sopps(i, varid, io), nbin, buff_tmp, missing_val, &
113 nbindex, nindex, scal(i, varid, io), nbout, buff_tmp2)
114
115 nbin = nbout
116 nbout = datasz_max(i, varid)
117 CALL mathop(sopps(i, varid, io+1), nbin, buff_tmp2, missing_val, &
118 nbindex, nindex, scal(i, varid, io+1), nbout, buff_tmp)
119 ENDDO
120
121 ! 3.5 Zoom into the data
122
123 CALL trans_buff(zorig(i, varid, 1), zsize(i, varid, 1), &
124 zorig(i, varid, 2), zsize(i, varid, 2), zorig(i, varid, 3), &
125 zsize(i, varid, 3), scsize(i, varid, 1), scsize(i, varid, 2), &
126 scsize(i, varid, 3), buff_tmp, buff_tmp2_sz, buff_tmp2)
127
128 ! 5.0 Do the operations if needed. In the case of instantaneous
129 ! output we do not transfer to the buffer.
130
131 ipt = point(fileid, varid)
132
133 IF ((TRIM(tmp_opp) /= "inst") &
134 .AND.(TRIM(tmp_opp) /= "once")) THEN
135 CALL moycum(tmp_opp, tsz, buffer(ipt:), &
136 buff_tmp2, nb_opp(fileid, varid))
137 ENDIF
138
139 last_opp(fileid, varid) = itau
140 nb_opp(fileid, varid) = nb_opp(fileid, varid)+1
141
142 ENDIF
143
144 ! 6.0 Write to file if needed
145
146 IF (do_write) THEN
147 ncvarid = ncvar_ids(fileid, varid)
148 ncid = ncdf_ids(fileid)
149
150 ! 6.1 Do the operations that are needed before writting
151 IF ((TRIM(tmp_opp) /= "inst") .AND. (TRIM(tmp_opp) /= "once")) THEN
152 rtime = (rtime + last_wrt(fileid, varid)*deltat(fileid)) / 2.
153 ENDIF
154
155 ! 6.2 Add a value to the time axis of this variable if needed
156 IF (TRIM(tmp_opp) /= "l_max" .AND. TRIM(tmp_opp) /= "l_min" &
157 .AND. TRIM(tmp_opp) /= "once") THEN
158 itax = var_axid(fileid, varid)
159 itime = nb_wrt(fileid, varid) + 1
160
161 IF (tax_last(fileid, itax) < itime) THEN
162 iret = NF90_PUT_VAR(ncid, tdimid(fileid, itax), (/rtime/), &
163 start=(/itime/))
164 tax_last(fileid, itax) = itime
165 ENDIF
166 ELSE
167 itime=1
168 ENDIF
169
170 ! 6.3 Write the data. Only in the case of instantaneous output
171 ! we do not write the buffer.
172
173 IF (scsize(fileid, varid, 3) == 1) THEN
174 IF (regular(fileid)) THEN
175 corner(1:4) = (/1, 1, itime, 0/)
176 edges(1:4) = (/zsize(fileid, varid, 1), &
177 zsize(fileid, varid, 2), &
178 1, 0/)
179 ELSE
180 corner(1:4) = (/1, itime, 0, 0/)
181 edges(1:4) = (/zsize(fileid, varid, 1), 1, 0, 0/)
182 ENDIF
183 ELSE
184 IF (regular(fileid)) THEN
185 corner(1:4) = (/1, 1, 1, itime/)
186 edges(1:4) = (/zsize(fileid, varid, 1), &
187 zsize(fileid, varid, 2), &
188 zsize(fileid, varid, 3), 1/)
189 ELSE
190 corner(1:4) = (/1, 1, itime, 0/)
191 edges(1:4) = (/zsize(fileid, varid, 1), &
192 zsize(fileid, varid, 3), 1, 0/)
193 ENDIF
194 ENDIF
195
196 ipt = point(fileid, varid)
197
198 IF ((TRIM(tmp_opp) /= "inst") .AND. (TRIM(tmp_opp) /= "once")) THEN
199 iret = NF90_PUT_VAR(ncid, ncvarid, buffer(ipt:), &
200 start=corner(1:4), count=edges(1:4))
201 ELSE
202 iret = NF90_PUT_VAR(ncid, ncvarid, buff_tmp2, &
203 start=corner(1:4), count=edges(1:4))
204 ENDIF
205
206 last_wrt(fileid, varid) = itau
207 nb_wrt(fileid, varid) = nb_wrt(fileid, varid)+1
208 nb_opp(fileid, varid) = 0
209 ENDIF
210
211 END SUBROUTINE histwrite_real
212
213 end module histwrite_real_m

  ViewVC Help
Powered by ViewVC 1.1.21