/[lmdze]/trunk/IOIPSL/Histcom/histend.f90
ViewVC logotype

Contents of /trunk/IOIPSL/Histcom/histend.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 6289 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 module histend_m
2
3 use histcom_var, only: nb_files_max, nb_var_max
4
5 implicit none
6
7 INTEGER, SAVE:: ncvar_ids(nb_files_max, nb_var_max)
8 private nb_files_max, nb_var_max
9
10 contains
11
12 SUBROUTINE histend(fileid)
13
14 ! This subroutine ends the declaration of variables, sets the time
15 ! axes in the NetCDF file and puts it into write mode.
16
17 USE errioipsl, ONLY: histerr
18 use histbeg_totreg_m, ONLY: date0, regular
19 USE histcom_var, ONLY: freq_opp, freq_wrt, fullop, missing_val, name, &
20 nb_tax, nb_var, ncdf_ids, tax_name, tdimid, tid, title, topp, &
21 unit_name, var_axid, var_zaxid, xid, yid, zax_ids, zax_name
22 USE ioget_calendar_m, ONLY: ioget_calendar_str
23 USE ju2ymds_m, ONLY: ju2ymds
24 USE netcdf, ONLY: nf90_float, nf90_unlimited
25 use netcdf95, only: nf95_def_dim, nf95_def_var, nf95_put_att, nf95_enddef
26
27 INTEGER, INTENT(IN):: fileid ! ID of the file to be worked on
28
29 ! Local:
30 INTEGER ncid, varid
31 INTEGER ndim, iv, itx, ziv
32 INTEGER itax
33 INTEGER dims(4), dim_cnt
34 INTEGER year, month, day, hours, minutes
35 REAL sec
36 REAL rtime0
37 CHARACTER(len=20) tname, tunit
38 CHARACTER(len=42) str30
39 CHARACTER(len=80) ttitle
40 CHARACTER(len=120) assoc
41 CHARACTER(len=70) str70
42 CHARACTER(len=3):: cal(12) = (/ 'JAN', 'FEB', 'MAR', 'APR', 'MAY', 'JUN', &
43 'JUL', 'AUG', 'SEP', 'OCT', 'NOV', 'DEC'/)
44 CHARACTER(len=7) tmp_opp
45
46 !---------------------------------------------------------------------
47
48 ncid = ncdf_ids(fileid)
49
50 ! 1.0 Create the time axes
51
52 call nf95_def_dim(ncid, 'time_counter', nf90_unlimited, tid(fileid))
53
54 ! 1.1 Define all the time axes needed for this file
55
56 DO itx = 1, nb_tax(fileid)
57 IF (nb_tax(fileid)>1) THEN
58 str30 = 't_' // tax_name(fileid, itx)
59 ELSE
60 str30 = 'time_counter'
61 END IF
62 call nf95_def_var(ncid, str30, nf90_float, tid(fileid), &
63 tdimid(fileid, itx))
64
65 rtime0 = date0(fileid)
66 CALL ju2ymds(rtime0, year, month, day, sec)
67
68 ! Catch any error induced by a change in calendar
69
70 IF (year < 0) THEN
71 year = 2000 + year
72 END IF
73
74 hours = int(sec/(60.*60.))
75 minutes = int((sec-hours*60.*60.)/60.)
76 sec = sec - (hours*60.*60.+minutes*60.)
77
78 WRITE(str70, 7000) year, month, day, hours, minutes, int(sec)
79 call nf95_put_att(ncid, tdimid(fileid, itx), 'units', trim(str70))
80
81 CALL ioget_calendar_str(str30)
82 call nf95_put_att(ncid, tdimid(fileid, itx), 'calendar', trim(str30))
83
84 call nf95_put_att(ncid, tdimid(fileid, itx), 'title', 'Time')
85
86 call nf95_put_att(ncid, tdimid(fileid, itx), 'long_name', &
87 'Time axis')
88
89 WRITE(str70, 7001) year, cal(month), day, hours, minutes, int(sec)
90 call nf95_put_att(ncid, tdimid(fileid, itx), 'time_origin', &
91 trim(str70))
92 END DO
93
94 ! 2.0 declare the variables
95
96 DO iv = 1, nb_var(fileid)
97
98 itax = var_axid(fileid, iv)
99
100 tname = name(fileid, iv)
101 tunit = unit_name(fileid, iv)
102 ttitle = title(fileid, iv)
103
104 IF (regular(fileid)) THEN
105 dims(1:2) = (/ xid(fileid), yid(fileid) /)
106 dim_cnt = 2
107 ELSE
108 dims(1) = xid(fileid)
109 dim_cnt = 1
110 END IF
111
112 tmp_opp = topp(fileid, iv)
113 ziv = var_zaxid(fileid, iv)
114
115 ! 2.1 dimension of field
116
117 IF ((trim(tmp_opp)/='never')) THEN
118 IF ((trim(tmp_opp)/='once') .AND. (trim( &
119 tmp_opp)/='l_max') .AND. (trim(tmp_opp)/='l_min')) THEN
120 IF (ziv==-99) THEN
121 ndim = dim_cnt + 1
122 dims(dim_cnt+1:dim_cnt+2) = (/ tid(fileid), 0 /)
123 ELSE
124 ndim = dim_cnt + 2
125 dims(dim_cnt+1:dim_cnt+2) = (/ zax_ids(fileid, ziv), &
126 tid(fileid) /)
127 END IF
128 ELSE
129 IF (ziv==-99) THEN
130 ndim = dim_cnt
131 dims(dim_cnt+1:dim_cnt+2) = (/ 0, 0 /)
132 ELSE
133 ndim = dim_cnt + 1
134 dims(dim_cnt+1:dim_cnt+2) = (/ zax_ids(fileid, ziv), 0 /)
135 END IF
136 END IF
137
138 call nf95_def_var(ncid, trim(tname), nf90_float, dims(1:abs(ndim)), &
139 varid)
140
141 ncvar_ids(fileid, iv) = varid
142
143 call nf95_put_att(ncid, varid, 'units', trim(tunit))
144 call nf95_put_att(ncid, varid, 'missing_value', missing_val)
145 call nf95_put_att(ncid, varid, 'long_name', trim(ttitle))
146 call nf95_put_att(ncid, varid, 'short_name', trim(tname))
147 call nf95_put_att(ncid, varid, 'online_operation', trim(fullop( &
148 fileid, iv)))
149
150 SELECT CASE (ndim)
151 CASE (-3)
152 str30 = 'ZYX'
153 CASE (2)
154 str30 = 'YX'
155 CASE (3)
156 str30 = 'TYX'
157 CASE (4)
158 str30 = 'TZYX'
159 CASE DEFAULT
160 CALL histerr(3, 'histend', &
161 'less than 2 or more than 4 dimensions are not', &
162 'allowed at this stage', ' ')
163 END SELECT
164
165 call nf95_put_att(ncid, varid, 'axis', trim(str30))
166
167 assoc = 'nav_lat nav_lon'
168 ziv = var_zaxid(fileid, iv)
169 IF (ziv>0) THEN
170 str30 = zax_name(fileid, ziv)
171 assoc = trim(str30) // ' ' // trim(assoc)
172 END IF
173
174 IF (itax>0) THEN
175 IF (nb_tax(fileid)>1) THEN
176 str30 = 't_' // tax_name(fileid, itax)
177 ELSE
178 str30 = 'time_counter'
179 END IF
180 assoc = trim(str30) // ' ' // trim(assoc)
181
182 call nf95_put_att(ncid, varid, 'interval_operation', &
183 real(freq_opp(fileid, iv)))
184 call nf95_put_att(ncid, varid, 'interval_write', &
185 real(freq_wrt(fileid, iv)))
186 END IF
187 call nf95_put_att(ncid, varid, 'associate', trim(assoc))
188 END IF
189 END DO
190
191 ! 3.0 Put the netcdf file into write mode
192 call nf95_enddef(ncid)
193
194 7000 FORMAT ('seconds since ', I4.4, '-', I2.2, '-', I2.2, ' ', I2.2, ':', &
195 I2.2, ':', I2.2)
196 7001 FORMAT (' ', I4.4, '-', A3, '-', I2.2, ' ', I2.2, ':', I2.2, ':', I2.2)
197
198 END SUBROUTINE histend
199
200 end module histend_m

  ViewVC Help
Powered by ViewVC 1.1.21