/[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.4 - (hide annotations) (download)
Sat May 6 15:14:01 2006 UTC (18 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, checkpoint58h_post, checkpoint58j_post, checkpoint58f_post, checkpoint58i_post, checkpoint58g_post, checkpoint58k_post
Changes since 1.3: +4 -6 lines
One more round of packaging.

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

  ViewVC Help
Powered by ViewVC 1.1.22