/[MITgcm]/MITgcm/pkg/profiles/profiles_init_fixed.F
ViewVC logotype

Annotation of /MITgcm/pkg/profiles/profiles_init_fixed.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Fri Mar 24 22:58:25 2006 UTC (18 years, 2 months ago) by heimbach
Branch: MAIN
o package cost profiles routines to better modularize them.

1 heimbach 1.1 #include "COST_CPPOPTIONS.h"
2    
3     C o==========================================================o
4     C | subroutine profiles_init_fixed |
5     C | o initialization for netcdf profiles data |
6     C | started: Gael Forget 15-March-2006 |
7     C o==========================================================o
8    
9     SUBROUTINE profiles_init_fixed( myThid )
10    
11     implicit none
12    
13     C ==================== Global Variables ===========================
14     #include "SIZE.h"
15     #include "EEPARAMS.h"
16     #include "PARAMS.h"
17     #include "GRID.h"
18     #include "DYNVARS.h"
19     #include "cal.h"
20     #include "ecco_cost.h"
21     #include "ctrl.h"
22     #include "ctrl_dummy.h"
23     #include "optim.h"
24     #ifdef ALLOW_PROFILES_CONTRIBUTION
25     # include "profiles.h"
26     # include "netcdf.inc"
27     #endif
28     C ==================== Routine Variables ==========================
29    
30     integer k,l,m,bi,bj,iG,jG, myThid,num_file,length_for_tile
31     integer fid, dimid, varid1, varid1a, varid1b
32     integer varid2,varid3
33     _RL tmpyymmdd(1000),tmphhmmss(1000),diffsecs
34     integer tmpdate(4),tmpdiff(4)
35     _RL tmp_lon, tmp_lon2(1000), tmp_lat2(1000)
36     integer vec_start(2), vec_count(2), profno_div1000, kk
37     character*(80) profilesfile, fnamedatanc
38     character*(80) fnameequinc, adfnameequinc
39     integer IL, err
40     logical exst
41    
42     #ifdef ALLOW_PROFILES_CONTRIBUTION
43    
44     c == external functions ==
45     integer ILNBLNK
46    
47     c-- == end of interface ==
48    
49     prof_names(1)='prof_T'
50     prof_names(2)='prof_S'
51     prof_names(3)='prof_U'
52     prof_names(4)='prof_V'
53     prof_namesmask(1)='prof_Tmask'
54     prof_namesmask(2)='prof_Smask'
55     prof_namesmask(3)='prof_Umask'
56     prof_namesmask(4)='prof_Vmask'
57     prof_namesweight(1)='prof_Tweight'
58     prof_namesweight(2)='prof_Sweight'
59     prof_namesweight(3)='prof_Uweight'
60     prof_namesweight(4)='prof_Vweight'
61     profiles_curfile_buff=0
62     profilesfile_equi_type=2
63    
64     do m=1,NLEVELMAX
65     do l=1,1000
66     do k=1,4
67     profiles_data_buff(m,l,k)=0
68     profiles_weight_buff(m,l,k)=0
69     enddo
70     enddo
71     enddo
72    
73     c remplacer par une boucle ensuite :
74     do num_file=1,NFILESPROFMAX
75    
76     IL = ILNBLNK( profilesfiles(num_file) )
77     if (IL.NE.0) then
78     write(profilesfile(1:80),'(1a)') profilesfiles(num_file)(1:IL)
79     else
80     write(profilesfile(1:80),'(1a)') ' '
81     endif
82    
83     IL = ILNBLNK( profilesfile )
84     if (IL.NE.0) then
85    
86     C===========================================================
87     c open data files and read the position vectors
88     C===========================================================
89    
90     write(fnamedatanc(1:80),'(2a)') profilesfile(1:IL),'.nc'
91     err = NF_OPEN(fnamedatanc, 0, fiddata(num_file))
92    
93     c1) read the number of profiles :
94     cgf err = NF_OPEN(filename, 0, fid)
95     fid=fiddata(num_file)
96     err = NF_INQ_DIMID(fid,'iPROF', dimid )
97     err = NF_INQ_DIMLEN(fid, dimid, ProfNo(num_file) )
98     err = NF_INQ_DIMID(fid,'iDEPTH', dimid )
99     if (err.NE.NF_NOERR) then
100     err = NF_INQ_DIMID(fid,'Z', dimid )
101     endif
102     err = NF_INQ_DIMLEN(fid, dimid, ProfDepthNo(num_file) )
103     print*,"fid num_file ProfNo(num_file) ProfDepthNo(num_file)",
104     &fid,num_file,ProfNo(num_file),ProfDepthNo(num_file)
105    
106     c2) read the dates and positions :
107     err = NF_INQ_VARID(fid,'depth', varid1a )
108     do k=1,ProfDepthNo(num_file)
109     err = NF_GET_VAR1_DOUBLE(fid,varid1a,k,
110     & prof_depth(num_file,k))
111     enddo
112    
113     err = NF_INQ_VARID(fid,'prof_YYYYMMDD', varid1a )
114     err = NF_INQ_VARID(fid,'prof_HHMMSS', varid1b )
115     err = NF_INQ_VARID(fid,'prof_lon', varid2 )
116     err = NF_INQ_VARID(fid,'prof_lat', varid3 )
117    
118     DO bi = myBxLo(myThid), myBxHi(myThid)
119     DO bj = myByLo(myThid), myByHi(myThid)
120    
121     do k=1,NOBSGLOB
122     prof_time(num_file,k)=-999
123     prof_lon(num_file,k)=-999
124     prof_lat(num_file,k)=-999
125     prof_ind_glob(num_file,k)=-999
126     enddo
127    
128    
129     length_for_tile=0
130     profno_div1000=max(1,int(profno(num_file)/1000))
131    
132     do kk=1,profno_div1000
133    
134     if (min(ProfNo(num_file), 1000*kk).GE.
135     & 1+1000*(kk-1)) then
136    
137     vec_start(1)=1
138     vec_start(2)=1+1000*(kk-1)
139     vec_count(1)=1
140     vec_count(2)=min(1000,ProfNo(num_file)-1000*(kk-1))
141    
142     if ( (vec_count(2).LE.0).OR.(vec_count(2).GT.1000).OR.
143     & (vec_start(2).LE.0).OR.
144     & (vec_count(2)+vec_start(2)-1.GT.ProfNo(num_file)) )
145     & then
146     print*,"stop 1",vec_start, vec_count
147     stop
148     endif
149    
150     err = NF_GET_VARA_DOUBLE(fid,varid1a,vec_start(2),
151     & vec_count(2), tmpyymmdd)
152     err = NF_GET_VARA_DOUBLE(fid,varid1b,vec_start(2),
153     & vec_count(2), tmphhmmss)
154     err = NF_GET_VARA_DOUBLE(fid,varid2,vec_start(2),
155     & vec_count(2), tmp_lon2)
156     err = NF_GET_VARA_DOUBLE(fid,varid3,vec_start(2),
157     & vec_count(2), tmp_lat2)
158    
159     if (err.NE.NF_NOERR) then
160     print*,"stop 2",vec_start(2),vec_count(2),
161     & kk,min(1000,ProfNo(num_file)-1000*(kk-1))
162     stop
163     endif
164    
165     do k=1,min(1000,ProfNo(num_file)-1000*(kk-1))
166    
167     call cal_FullDate( int(tmpyymmdd(k)),int(tmphhmmss(k)),
168     & tmpdate,mythid )
169     call cal_TimePassed( modelstartdate,tmpdate,tmpdiff,mythid )
170     call cal_ToSeconds (tmpdiff,diffsecs,mythid)
171     diffsecs=diffsecs+nIter0*deltaTclock
172    
173     if (xC(sNx+1,1,bi,bj).LT.xC(sNx+1,1,bi,bj)) then
174     tmp_lon=2*xC(sNx,1,bi,bj)-xC(sNx-1,1,bi,bj)
175     else
176     tmp_lon=xC(sNx+1,1,bi,bj)
177     endif
178     if ((xC(1,1,bi,bj).LE.tmp_lon2(k)).AND.
179     & (tmp_lon.GT.tmp_lon2(k)).AND.
180     & (yC(1,1,bi,bj).LE.tmp_lat2(k)).AND.
181     & (yC(1,sNy+1,bi,bj).GT.tmp_lat2(k))
182     & ) then
183     length_for_tile=length_for_tile+1
184     prof_time(num_file,length_for_tile)=diffsecs
185     prof_lon(num_file,length_for_tile)=tmp_lon2(k)
186     prof_lat(num_file,length_for_tile)=tmp_lat2(k)
187     prof_ind_glob(num_file,length_for_tile)=k+1000*(kk-1)
188     if (length_for_tile.GT.NOBSGLOB) then
189     print*,"too much profiles: need to increase NOBSGLOB,"
190     print*," or split the data file (less memory cost)"
191     stop
192     endif
193     endif
194     enddo
195     endif
196     enddo
197    
198     ProfNo(num_file)=length_for_tile
199     print*,"fid dimid ProfNo(num_file)",fid, dimid,
200     & num_file, ProfNo(num_file)
201    
202     do k=1,4
203     prof_num_var_cur(num_file,k)=0
204     enddo
205     prof_num_var_tot(num_file)=0
206    
207     c3) detect available data types
208     err = NF_INQ_VARID(fid,'prof_T', varid1 )
209     if (err.EQ.NF_NOERR) then
210     vec_quantities(num_file,1)=.TRUE.
211     prof_num_var_tot(num_file)=prof_num_var_tot(num_file)+1
212     prof_num_var_cur(num_file,1)=prof_num_var_tot(num_file)
213     else
214     vec_quantities(num_file,1)=.FALSE.
215     endif
216     err = NF_INQ_VARID(fid,'prof_S', varid1 )
217     if (err.EQ.NF_NOERR) then
218     vec_quantities(num_file,2)=.TRUE.
219     prof_num_var_tot(num_file)=prof_num_var_tot(num_file)+1
220     prof_num_var_cur(num_file,2)=prof_num_var_tot(num_file)
221     else
222     vec_quantities(num_file,2)=.FALSE.
223     endif
224     err = NF_INQ_VARID(fid,'prof_U', varid1 )
225     if (err.EQ.NF_NOERR) then
226     vec_quantities(num_file,3)=.TRUE.
227     prof_num_var_tot(num_file)=prof_num_var_tot(num_file)+1
228     prof_num_var_cur(num_file,3)=prof_num_var_tot(num_file)
229     else
230     vec_quantities(num_file,3)=.FALSE.
231     endif
232     err = NF_INQ_VARID(fid,'prof_V', varid1 )
233     if (err.EQ.NF_NOERR) then
234     vec_quantities(num_file,4)=.TRUE.
235     prof_num_var_tot(num_file)=prof_num_var_tot(num_file)+1
236     prof_num_var_cur(num_file,4)=prof_num_var_tot(num_file)
237     else
238     vec_quantities(num_file,4)=.FALSE.
239     endif
240    
241    
242     C===========================================================
243     c create files for model counterparts to observations
244     C===========================================================
245    
246     if (profno(num_file).GT.0) then
247     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
248     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
249    
250     if (profilesfile_equi_type.EQ.1) then
251    
252     write(fnameequinc(1:80),'(2a,i3.3,a,i3.3,a)')
253     & profilesfile(1:IL),'.',iG,'.',jG,'.equi.nc'
254     write(adfnameequinc(1:80),'(3a,i3.3,a,i3.3,a)') 'ad',
255     & profilesfile(1:IL),'.',iG,'.',jG,'.equi.nc'
256    
257     inquire( file=fnameequinc, exist=exst )
258     if (.NOT.exst) then
259     call profiles_init_ncfile(num_file,fiddata(num_file),fnameequinc,
260     & fidforward(num_file),profno(num_file),profdepthno(num_file),
261     & myThid)
262     call profiles_init_ncfile(num_file,fiddata(num_file),
263     & adfnameequinc, fidadjoint(num_file),profno(num_file),
264     & profdepthno(num_file), myThid)
265     else
266     err = NF_OPEN(fnameequinc , NF_WRITE , fidforward(num_file) )
267     err = NF_OPEN(adfnameequinc , NF_WRITE , fidadjoint(num_file) )
268     endif
269    
270     else
271    
272     write(fnameequinc(1:80),'(2a,i3.3,a,i3.3,a)')
273     & profilesfile(1:IL),'.',iG,'.',jG,'.equi.bin'
274     write(adfnameequinc(1:80),'(3a,i3.3,a,i3.3,a)') 'ad',
275     & profilesfile(1:IL),'.',iG,'.',jG,'.equi.bin'
276    
277     inquire( file=fnameequinc, exist=exst )
278     if (.NOT.exst) then
279     call profiles_init_ncfile(num_file,fiddata(num_file),fnameequinc,
280     & fidforward(num_file),profno(num_file),profdepthno(num_file),
281     & myThid)
282     call profiles_init_ncfile(num_file,fiddata(num_file),
283     & adfnameequinc, fidadjoint(num_file),profno(num_file),
284     & profdepthno(num_file), myThid)
285     else
286     call MDSFINDUNIT( fidforward(num_file) , mythid )
287     open( fidforward(num_file),file=fnameequinc,
288     & form ='unformatted',status='unknown', access='direct',
289     & recl= (profdepthno(num_file)+1)*WORDLENGTH*2 )
290     call MDSFINDUNIT( fidadjoint(num_file) , mythid )
291     open( fidadjoint(num_file),file=adfnameequinc,
292     & form ='unformatted',status='unknown', access='direct',
293     & recl= (profdepthno(num_file)+1)*WORDLENGTH*2 )
294     endif
295    
296     endif
297    
298     endif
299    
300     ENDDO
301     ENDDO
302    
303    
304     C===========================================================
305     else
306     ProfNo(num_file)=0
307     do k=1,4
308     prof_num_var_cur(num_file,k)=0
309     vec_quantities(num_file,k)=.FALSE.
310     enddo
311     prof_num_var_tot(num_file)=0
312     do k=1,NOBSGLOB
313     prof_time(num_file,k)=-999
314     prof_lon(num_file,k)=-999
315     prof_lat(num_file,k)=-999
316     prof_ind_glob(num_file,k)=-999
317     enddo
318    
319     endif !if (IL.NE.0) then
320     enddo ! do num_file=1,NFILESPROFMAX
321     C===========================================================
322    
323     #endif
324    
325     END
326    

  ViewVC Help
Powered by ViewVC 1.1.22