/[MITgcm]/MITgcm/pkg/fizhi/update_ocean_exports.F
ViewVC logotype

Annotation of /MITgcm/pkg/fizhi/update_ocean_exports.F

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


Revision 1.15 - (hide annotations) (download)
Fri Feb 25 18:14:45 2005 UTC (19 years, 4 months ago) by molod
Branch: MAIN
Changes since 1.14: +7 -3 lines
Supply (set them for now....) data set names for veg, sst and sea ice

1 molod 1.15 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/update_ocean_exports.F,v 1.14 2004/10/22 14:52:14 molod Exp $
2 molod 1.1 C $Name: $
3    
4 molod 1.13 #include "FIZHI_OPTIONS.h"
5 molod 1.1 subroutine update_ocean_exports (myTime, myIter, myThid)
6     c----------------------------------------------------------------------
7     c Subroutine update_ocean_exports - 'Wrapper' routine to update
8     c the fields related to the ocean's surface that are needed
9 molod 1.3 c by fizhi (sst and sea ice extent).
10 molod 1.1 c
11     c Call: getsst (Return the current sst field-read dataset if needed)
12     c getsice (Return the current sea ice field-read data if needed)
13     c-----------------------------------------------------------------------
14     implicit none
15     #include "SIZE.h"
16     #include "GRID.h"
17 molod 1.2 #include "fizhi_ocean_coms.h"
18 molod 1.1 #include "EEPARAMS.h"
19 molod 1.3 #include "chronos.h"
20 molod 1.1
21 molod 1.14 integer myIter, myThid
22     _RL myTime
23 molod 1.1
24 molod 1.4 integer i, j, bi, bj, biglobal, bjglobal
25 molod 1.1 integer im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2
26 molod 1.4 integer nSxglobal, nSyglobal
27 molod 1.3 integer ksst,kice
28 molod 1.6 _RL sstmin
29 molod 1.3 parameter ( sstmin = 273.16 )
30 molod 1.1
31 molod 1.4 idim1 = 1-OLx
32     idim2 = sNx+OLx
33     jdim1 = 1-OLy
34     jdim2 = sNy+OLy
35     im1 = 1
36     im2 = sNx
37     jm1 = 1
38     jm2 = sNy
39     nSxglobal = nSx*nPx
40     nSyglobal = nSy*nPy
41    
42     call mdsfindunit( ksst, myThid )
43     call mdsfindunit( kice, myThid )
44    
45     C***********************************************************************
46 molod 1.3
47 molod 1.4 DO BJ = myByLo(myThid),myByHi(myThid)
48     DO BI = myBxLo(myThid),myBxHi(myThid)
49 molod 1.3
50 molod 1.4 biglobal=bi+(myXGlobalLo-1)/im2
51     bjglobal=bj+(myYGlobalLo-1)/jm2
52    
53     call getsst(ksst,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSx,
54     . nSy,nSxglobal,nSyglobal,bi,bj,biglobal,bjglobal,nymd,nhms,sst)
55     call getsice(kice,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSx,
56     . nSy,nSxglobal,nSyglobal,bi,bj,biglobal,bjglobal,nymd,nhms,sice)
57 molod 1.3
58     c Check for Minimum Open-Water SST
59     c --------------------------------
60 molod 1.4 do j=jm1,jm2
61     do i=im1,im2
62     if(sice(i,j,bi,bj).eq.0.0 .and. sst(i,j,bi,bj).lt.sstmin)
63     . sst(i,j,bi,bj) = sstmin
64 molod 1.1 enddo
65     enddo
66    
67 molod 1.4 ENDDO
68     ENDDO
69    
70 molod 1.1 return
71     end
72 molod 1.3
73 molod 1.4 subroutine getsice(iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,
74 molod 1.11 . nSumx,nSumy,nPgx,nPgy,bi,bj,biglobal,bjglobal,nymd,nhms,sice)
75 molod 1.3 C************************************************************************
76     C
77     C!ROUTINE: GETSICE
78     C!DESCRIPTION: GETSICE returns the sea ice depth.
79     C! This routine is adaptable for any frequency
80     C! data upto a daily frequency.
81     C! note: for diurnal data ndmax should be increased.
82     C
83     C!INPUT PARAMETERS:
84 molod 1.4 C! iunit Unit number assigned to the sice data file
85     C! idim1 Start dimension in x-direction
86     C! idim2 End dimension in x-direction
87     C! jdim1 Start dimension in y-direction
88     C! jdim2 End dimension in y-direction
89     C! im1 Begin of x-direction span for filling sice
90     C! im2 End of x-direction span for filling sice
91     C! jm1 Begin of y-direction span for filling sice
92     C! jm2 End of y-direction span for filling sice
93 molod 1.11 C! nSumx Number of processors in x-direction (local processor)
94     C! nSumy Number of processors in y-direction (local processor)
95     C! nPgx Number of processors in x-direction (global)
96     C! nPgx Number of processors in y-direction (global)
97 molod 1.4 C! bi Processor number in x-direction (local to processor)
98     C! bj Processor number in y-direction (local to processor)
99     C! biglobal Processor number in x-direction (global)
100     C! bjglobal Processor number in y-direction (global)
101     C! nymd YYMMDD of the current model timestep
102     C! nhms HHMMSS of the model time
103 molod 1.3 C
104     C!OUTPUT PARAMETERS:
105 molod 1.11 C! sice(idim1:idim2,jdim1:jdim2,nSumx,nSumy) Sea ice depth in meters
106 molod 1.3 C
107     C!ROUTINES CALLED:
108     C
109 molod 1.4 C! bcdata Reads the data for a given unit number
110     C! bcheader Reads the header info for a given unit number
111     C! interp_time Returns weights for linear interpolation
112 molod 1.3 C
113     C--------------------------------------------------------------------------
114    
115     implicit none
116 molod 1.11 #include "SIZE.h"
117 molod 1.4
118 molod 1.11 integer iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSumx,nSumy
119     integer nPgx,nPgy,bi,bj,biglobal,bjglobal,nymd,nhms
120 molod 1.4
121 molod 1.11 _RL sice(idim1:idim2,jdim1:jdim2,nSumx,nSumy)
122 molod 1.3
123 molod 1.4 C Maximum number of dates in one year for the data
124     integer ndmax
125 molod 1.3 parameter (ndmax = 370)
126    
127 molod 1.4 character*8 cname
128     character*80 cdscrip
129 molod 1.15 character*40 sicedata
130 molod 1.13 _RL fac1, fac2, lat0, lon0, timebc1, timebc2, timemod, undef
131 molod 1.4 logical first, found, error
132 molod 1.9 integer i,j,n,nn,iyear,iyearbc,nd,ndby3,imbc,jmbc,npxbc,npybc
133 molod 1.5 integer ndatebc,nhmsbc(ndmax), nhmsbc1, nhmsbc2,nrec
134 molod 1.4 integer nymdbc(ndmax),nymdbc1,nymdbc2,nymdmod
135 molod 1.3
136 molod 1.13 _RL sicebc1(sNx,sNy,nSx*nPx,nSy*nPy)
137     _RL sicebc2(sNx,sNy,nSx*nPx,nSy*nPy)
138 molod 1.3
139     C--------- Variable Initialization ---------------------------------
140    
141     data first /.true./
142     data error /.false./
143 molod 1.15 sicedata='sice19232.weekly.clim'
144 molod 1.3
145     c save header info
146 molod 1.11 save imbc,jmbc,npxbc,npybc,lat0,lon0,ndatebc,undef,nymdbc,nhmsbc
147     save nymdbc1, nymdbc2, nhmsbc1, nhmsbc2
148     save first
149     save sicebc1, sicebc2
150 molod 1.3
151     c this only works for between 1950-2050
152     if (nymd .lt. 500101) then
153     nymdmod = 20000000 + nymd
154     else if (nymd .le. 991231) then
155     nymdmod = 19000000 + nymd
156     else
157     nymdmod = nymd
158     endif
159    
160     c initialize so that first time through they have values for the check
161     c these vaules make the iyear .ne. iyearbc true anyways for
162     c for the first time so first isnt checked below.
163    
164     if (first) then
165     nymdbc(2) = 0
166     nymdbc1 = 0
167     nymdbc2 = 0
168     nhmsbc1 = 0
169     nhmsbc2 = 0
170     first = .false.
171     endif
172    
173     C---------- Read in Header file ----------------------------------
174    
175     iyear = nymdmod/10000
176     iyearbc = nymdbc(2)/10000
177    
178     if( iyear.ne.iyearbc ) then
179    
180 molod 1.5 close(iunit)
181 molod 1.15 open (iunit,file=sicedata,form='unformatted',access='direct',
182 molod 1.11 . recl=im2*jm2*nPgx*nPgy*4)
183 molod 1.5 nrec = 1
184     call bcheader (iunit, ndmax, nrec,
185     . cname, cdscrip, imbc, jmbc, npxbc, npybc, lat0, lon0,
186     . ndatebc, nymdbc, nhmsbc, undef, error)
187 molod 1.3
188     C--------- Check data for Compatibility ------------------------------
189    
190     C Check for correct data in boundary condition file
191     if (.not.error .and. cname.ne.'SICE') then
192 molod 1.4 write(6,*)'Wrong data in SICE boundary condition file => ',cname
193     error = .true.
194 molod 1.3 endif
195    
196     C Check Horizontal Resolution
197 molod 1.11 if(.not.error.and.imbc*jmbc*npxbc*npybc.ne.im2*jm2*npgx*npgy)then
198 molod 1.4 write(6,*) ' B.C. Resolution DOES NOT match Model Resolution!'
199 molod 1.5 write(6,*) ' B.C. Resolution: ',imbc*jmbc*npxbc*npybc
200 molod 1.11 write(6,*) 'Model Resolution: ',im2*jm2*npgx*npgy
201 molod 1.4 error = .true.
202 molod 1.3 endif
203    
204     C Check Year
205     iyearbc = nymdbc(2)/10000
206     if (.not.error .and. iyear.ne.iyearbc .and. iyearbc.ne.0) then
207 molod 1.5 write(6,*)' B.C. Year DOES NOT match REQUESTED Year!'
208     write(6,*)' B.C. Year: ', iyearbc
209     write(6,*)'Requested Year: ', iyear
210 molod 1.4 error = .true.
211 molod 1.3 endif
212    
213 molod 1.4 if (.not.error) then
214 molod 1.3 C if climatology, fill dates for data with current model year
215 molod 1.4 if (iyearbc.eq.0) then
216     write(6,*)
217     write(6,*) 'Climatological Dataset is being used.'
218     write(6,*) 'Current model year to be used to fill Header Dates'
219     do n = 2, ndatebc-1
220     nymdbc(n) = nymdbc(n) +(nymdmod/10000)*10000
221     enddo
222 molod 1.3 C For the first date subtract 1 year from the current model NYMD
223 molod 1.4 n = 1
224     nymdbc(n) = nymdbc(n) +(nymdmod/10000-1)*10000
225 molod 1.3 C For the last date add 1 year to the current model NYMD
226 molod 1.4 n = ndatebc
227     nymdbc(n) = nymdbc(n) +(nymdmod/10000+1)*10000
228     endif
229 molod 1.3
230     C Write out header info
231 molod 1.4 write(6,*) ' Updated boundary condition data'
232     write(6,*) ' ---------------------------------'
233     write(6,*) ' Variable: ',cname
234     write(6,*) ' Description: ',cdscrip
235     write(6,*) ' Resolution: x= ',imbc,' y= ',jmbc,
236     . ' Undefined value = ',undef
237     write(6,*) ' Starting latitude = ',lat0,' longitude =',lon0
238     write(6,*) ' Data valid at these times: '
239     ndby3 = ndatebc/3
240     do n = 1, ndby3*3,3
241     write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=n,n+2)
242     1000 format(3(2x,i3,':',i8,2x,i8))
243     enddo
244     write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=ndby3*3+1,ndatebc)
245     endif
246 molod 1.3
247 molod 1.4 endif
248 molod 1.3
249     C---------- Read sice data if necessary -------------------------------
250    
251 molod 1.4 found = .false.
252     nd = 2
253 molod 1.3
254     c If model time is not within the times of saved sice data
255     c from previous call to getsice then read new data
256    
257 molod 1.4 timemod = float(nymdmod) + float(nhms) /1000000
258     timebc1 = float(nymdbc1) + float(nhmsbc1)/1000000
259     timebc2 = float(nymdbc2) + float(nhmsbc2)/1000000
260    
261     if (timemod .lt. timebc1 .or. timemod .ge. timebc2) then
262    
263     do while (.not.found .and. nd .le. ndatebc)
264     timebc2 = float(nymdbc(nd)) + float(nhmsbc(nd))/1000000
265     if (timebc2 .gt. timemod) then
266 molod 1.5 nymdbc1 = nymdbc(nd-1)
267     nymdbc2 = nymdbc(nd)
268     nhmsbc1 = nhmsbc(nd-1)
269     nhmsbc2 = nhmsbc(nd)
270 molod 1.11 call bcdata (iunit,imbc,jmbc,nPgx,nPgy,nd,nd+1,sicebc1,sicebc2)
271 molod 1.5 found = .true.
272 molod 1.4 else
273 molod 1.5 nd = nd + 1
274 molod 1.4 endif
275     enddo
276 molod 1.3
277     c Otherwise the data from the last time in getsice surrounds the
278     c current model time.
279    
280 molod 1.4 else
281     found = .true.
282     endif
283    
284     if (.not.found) then
285     print *, 'STOP: Could not find SICE dates for model time.'
286     call my_finalize
287     call my_exit (101)
288     endif
289 molod 1.3
290     C---------- Interpolate sice data ------------------------------------
291    
292 molod 1.4 call interp_time(nymdmod,nhms,nymdbc1,nhmsbc1,nymdbc2,nhmsbc2,
293     . fac1,fac2)
294 molod 1.3
295 molod 1.4 do j = jm1,jm2
296     do i = im1,im2
297     sice(i,j,bi,bj) = sicebc1(i,j,biglobal,bjglobal)*fac1
298     . + sicebc2(i,j,biglobal,bjglobal)*fac2
299 molod 1.3 c average to 0 or 1
300     c -----------------
301 molod 1.4 if (sice(i,j,bi,bj) .ge. 0.5) then
302     sice(i,j,bi,bj) = 1.
303     else
304     sice(i,j,bi,bj) = 0.
305     endif
306     enddo
307     enddo
308 molod 1.3
309     C---------- Fill sice with depth of ice ------------------------------------
310 molod 1.4 do j = jm1,jm2
311     do i = im1,im2
312     if (sice(i,j,bi,bj) .eq. 1.) then
313     sice(i,j,bi,bj) = 3.
314     endif
315     enddo
316     enddo
317 molod 1.3 C---------------------------------------------------------------------------
318    
319     return
320     end
321 molod 1.5 subroutine getsst(iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,
322 molod 1.11 . nSumx,nSumy,nPgx,nPgy,bi,bj,biglobal,bjglobal,nymd,nhms,sst)
323 molod 1.3 C************************************************************************
324     C
325     C!ROUTINE: GETSST
326     C!DESCRIPTION: GETSST gets the SST data.
327     C! This routine is adaptable for any frequency
328     C! data upto a daily frequency.
329     C! note: for diurnal data ndmax should be increased.
330     C
331     C!INPUT PARAMETERS:
332 molod 1.5 C! iunit Unit number assigned to the sice data file
333     C! idim1 Start dimension in x-direction
334     C! idim2 End dimension in x-direction
335     C! jdim1 Start dimension in y-direction
336     C! jdim2 End dimension in y-direction
337     C! im1 Begin of x-direction span for filling sice
338     C! im2 End of x-direction span for filling sice
339     C! jm1 Begin of y-direction span for filling sice
340     C! jm2 End of y-direction span for filling sice
341 molod 1.11 C! nSumx Number of processors in x-direction (local processor)
342     C! nSumy Number of processors in y-direction (local processor)
343     C! nPgx Number of processors in x-direction (global)
344     C! nPgy Number of processors in y-direction (global)
345 molod 1.5 C! bi Processor number in x-direction (local to processor)
346     C! bj Processor number in y-direction (local to processor)
347     C! biglobal Processor number in x-direction (global)
348     C! bjglobal Processor number in y-direction (global)
349     C! nymd YYMMDD of the current model timestep
350     C! nhms HHMMSS of the model time
351 molod 1.3 C
352     C!OUTPUT PARAMETERS:
353 molod 1.11 C! sst(idim1:idim2,jdim1:jdim2,nSumx,nSumy) Sea surface temperature (K)
354 molod 1.3 C
355     C!ROUTINES CALLED:
356     C
357     C! bcdata Reads the data for a given unit number
358     C! bcheader Reads the header info for a given unit number
359     C! interp_time Returns weights for linear interpolation
360     C
361     C--------------------------------------------------------------------------
362    
363     implicit none
364 molod 1.11 #include "SIZE.h"
365 molod 1.5
366 molod 1.11 integer iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSumx,nSumy
367     integer nPgx,nPgy,bi,bj,biglobal,bjglobal,nymd,nhms
368 molod 1.3
369 molod 1.11 _RL sst(idim1:idim2,jdim1:jdim2,nSumx,nSumy)
370 molod 1.3
371 molod 1.5 C Maximum number of dates in one year for the data
372     integer ndmax
373 molod 1.3 parameter (ndmax = 370)
374    
375 molod 1.5 character*8 cname
376     character*80 cdscrip
377 molod 1.15 character*40 sstdata
378 molod 1.13 _RL fac1, fac2, lat0, lon0, timebc1, timebc2, timemod, undef
379 molod 1.5 logical first, found, error
380 molod 1.9 integer i,j,n,nn,iyear,iyearbc,nd,ndby3,imbc,jmbc,npxbc,npybc
381 molod 1.5 integer ndatebc,nhmsbc(ndmax), nhmsbc1, nhmsbc2,nrec
382     integer nymdbc(ndmax),nymdbc1,nymdbc2,nymdmod
383    
384 molod 1.13 _RL sstbc1(sNx,sNy,nSx*nPx,nSy*nPy)
385     _RL sstbc2(sNx,sNy,nSx*nPx,nSy*nPy)
386 molod 1.3
387     C--------- Variable Initialization ---------------------------------
388    
389     data first /.true./
390     data error /.false./
391 molod 1.15 sstdata='sst19232.weekly.clim'
392 molod 1.3
393     c save header info
394 molod 1.11 save imbc,jmbc,npxbc,npybc,lat0,lon0,ndatebc,undef,nymdbc,nhmsbc
395     save nymdbc1, nymdbc2, nhmsbc1, nhmsbc2
396     save first
397     save sstbc1, sstbc2
398 molod 1.3
399     c this only works for between 1950-2050
400     if (nymd .lt. 500101) then
401     nymdmod = 20000000 + nymd
402     else if (nymd .le. 991231) then
403     nymdmod = 19000000 + nymd
404     else
405     nymdmod = nymd
406     endif
407    
408     c initialize so that first time through they have values for the check
409     c these vaules make the iyear .ne. iyearbc true anyways for
410     c for the first time so first isnt checked below.
411     if (first) then
412     nymdbc(2) = 0
413     nymdbc1 = 0
414     nymdbc2 = 0
415     nhmsbc1 = 0
416     nhmsbc2 = 0
417     first = .false.
418     endif
419    
420     C---------- Read in Header file ----------------------------------
421    
422     iyear = nymdmod/10000
423     iyearbc = nymdbc(2)/10000
424    
425     if( iyear.ne.iyearbc ) then
426    
427 molod 1.5 close(iunit)
428 molod 1.15 open (iunit,file=sstdata,form='unformatted',access='direct',
429 molod 1.11 . recl=im2*jm2*nPgx*nPgy*4)
430 molod 1.5 nrec = 1
431     call bcheader (iunit, ndmax, nrec,
432     . cname, cdscrip, imbc, jmbc, npxbc, npybc, lat0, lon0,
433     . ndatebc, nymdbc, nhmsbc, undef, error)
434 molod 1.3
435     C--------- Check data for Compatibility
436    
437     C Check for correct data in boundary condition file
438     if (.not.error .and. cname.ne.'SST') then
439 molod 1.5 write(6,*)'Wrong data in SST boundary condition file => ',cname
440     error = .true.
441 molod 1.3 endif
442    
443     C Check Horizontal Resolution
444 molod 1.11 if(.not.error.and.imbc*jmbc*npxbc*npybc.ne.im2*jm2*npgx*npgy)then
445 molod 1.5 write(6,*) ' B.C. Resolution DOES NOT match Model Resolution!'
446     write(6,*) ' B.C. Resolution: ',imbc*jmbc*npxbc*npybc
447 molod 1.11 write(6,*) 'Model Resolution: ',im2*jm2*npgx*npgy
448 molod 1.5 error = .true.
449 molod 1.3 endif
450    
451     C Check Year
452     iyearbc = nymdbc(2)/10000
453     if (.not.error .and. iyear.ne.iyearbc .and. iyearbc.ne.0) then
454 molod 1.5 write(6,*)' B.C. Year DOES NOT match REQUESTED Year!'
455     write(6,*)' B.C. Year: ', iyearbc
456     write(6,*)'Requested Year: ', iyear
457     error = .true.
458 molod 1.3 endif
459    
460     if (.not.error) then
461     C if climatology, fill dates for data with current model year
462 molod 1.5 if (iyearbc.eq.0) then
463     write(6,*)
464 molod 1.9 write(6,*)'Climatological Dataset is being used.'
465     write(6,*)'Current model year is used to fill Header Dates'
466 molod 1.5 do n = 2, ndatebc-1
467     nymdbc(n) = nymdbc(n) +(nymdmod/10000)*10000
468     enddo
469 molod 1.3 C For the first date subtract 1 year from the current model NYMD
470 molod 1.5 n = 1
471     nymdbc(n) = nymdbc(n) +(nymdmod/10000-1)*10000
472 molod 1.3 C For the last date add 1 year to the current model NYMD
473 molod 1.5 n = ndatebc
474     nymdbc(n) = nymdbc(n) +(nymdmod/10000+1)*10000
475     endif
476 molod 1.3
477     C Write out header info
478 molod 1.5 write(6,*) ' Updated boundary condition data'
479     write(6,*) ' ---------------------------------'
480     write(6,*) ' Variable: ',cname
481     write(6,*) ' Description: ',cdscrip
482     write(6,*) ' Resolution: x= ',imbc,' y= ',jmbc,
483     . ' Undefined value = ',undef
484     write(6,*) ' Starting latitude = ',lat0,' longitude =',lon0
485     write(6,*) ' Data valid at these times: '
486     ndby3 = ndatebc/3
487     do n = 1, ndby3*3,3
488     write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=n,n+2)
489     1000 format(3(2x,i3,':',i8,2x,i8))
490     enddo
491     write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=ndby3*3+1,ndatebc)
492 molod 1.8 endif
493 molod 1.3
494     if( error ) call my_exit (101)
495    
496 molod 1.8 endif
497 molod 1.3
498     C---------- Read SST data if necessary -------------------------------
499    
500 molod 1.5 found = .false.
501     nd = 2
502 molod 1.3
503     c If model time is not within the times of saved sst data
504     c from previous call to getsst then read new data
505    
506 molod 1.5 timemod = float(nymdmod) + float(nhms) /1000000
507     timebc1 = float(nymdbc1) + float(nhmsbc1)/1000000
508     timebc2 = float(nymdbc2) + float(nhmsbc2)/1000000
509     if (timemod .lt. timebc1 .or. timemod .ge. timebc2) then
510    
511     do while (.not.found .and. nd .le. ndatebc)
512     timebc2 = float(nymdbc(nd)) + float(nhmsbc(nd))/1000000
513     if (timebc2 .gt. timemod) then
514     nymdbc1 = nymdbc(nd-1)
515     nymdbc2 = nymdbc(nd)
516     nhmsbc1 = nhmsbc(nd-1)
517     nhmsbc2 = nhmsbc(nd)
518 molod 1.11 call bcdata (iunit,imbc,jmbc,nPgx,nPgy,nd,nd+1,sstbc1,sstbc2)
519 molod 1.5 found = .true.
520     else
521     nd = nd + 1
522     endif
523     enddo
524 molod 1.3
525     c Otherwise the data from the last time in getsst surrounds the
526     c current model time.
527    
528 molod 1.5 else
529     found = .true.
530     endif
531 molod 1.3
532 molod 1.5 if (.not.found) then
533     print *, 'STOP: Could not find SST dates for model time.'
534     call my_finalize
535     call my_exit (101)
536     endif
537 molod 1.3
538     C---------- Interpolate SST data ------------------------------------
539    
540 molod 1.5 call interp_time(nymdmod,nhms,nymdbc1,nhmsbc1,nymdbc2,nhmsbc2,
541     . fac1,fac2)
542 molod 1.3
543 molod 1.5 do j = jm1,jm2
544     do i = im1,im2
545     sst(i,j,bi,bj) = sstbc1(i,j,biglobal,bjglobal)*fac1
546     . + sstbc2(i,j,biglobal,bjglobal)*fac2
547     enddo
548     enddo
549 molod 1.3
550     return
551     end
552    
553 molod 1.5 subroutine bcdata (iunit,im,jm,nPx,nPy,nrec1,nrec2,field1,field2)
554 molod 1.3 C************************************************************************
555     C
556 molod 1.5 C!ROUTINE: BCDATA
557     C!DESCRIPTION: BCDATA reads the data from the file assigned to the
558     C! passed unit number and returns data from the two times
559     C! surrounding the current model time. The two record
560     C! postitions are not assumed to be next to each other.
561 molod 1.3 C
562     C!INPUT PARAMETERS:
563 molod 1.5 C! im number of x points
564     C! im number of x points
565     C! nPx number of faces in x-direction
566     C! nPy number of faces in y-direction
567     C! nrec1 record number of the time before the model time
568     C! nrec2 record number of the time after the model time
569 molod 1.3 C
570     C!OUTPUT PARAMETERS:
571 molod 1.5 C! field1(im,jm,nPx,nPy) data field before the model time
572     C! field2(im,jm,nPx,nPy) data field after the model time
573 molod 1.3 C
574     C--------------------------------------------------------------------------
575 molod 1.5 implicit none
576 molod 1.3
577 molod 1.5 integer iunit,im,jm,nPx,nPy,nrec1,nrec2
578 molod 1.3
579 molod 1.13 _RL field1(im,jm,nPx,nPy)
580     _RL field2(im,jm,nPx,nPy)
581 molod 1.3
582 molod 1.5 integer i,j,n1,n2
583 molod 1.9 real*4 f1(im,jm,nPx,nPy), f2(im,jm,nPx,nPy)
584 molod 1.3
585     C--------- Read file -----------------------------------------------
586     read(iunit,rec=nrec1) f1
587     read(iunit,rec=nrec2) f2
588    
589 molod 1.5 do n2=1,nPy
590     do n1=1,nPx
591 molod 1.12 #ifdef _BYTESWAPIO
592     call MDS_BYTESWAPR4( im*jm, f1(1,1,n1,n2))
593     call MDS_BYTESWAPR4( im*jm, f2(1,1,n1,n2))
594     #endif
595 molod 1.3 do j=1,jm
596     do i=1,im
597 molod 1.5 field1(i,j,n1,n2) = f1(i,j,n1,n2)
598     field2(i,j,n1,n2) = f2(i,j,n1,n2)
599     enddo
600     enddo
601 molod 1.3 enddo
602     enddo
603    
604     return
605     end
606     subroutine bcheader (iunit, ndmax, nrec,
607 molod 1.5 . cname, cdscrip, im, jm, npx, npy, lat0, lon0, ndatebc,
608     . nymdbc, nhmsbc, undef, error)
609 molod 1.3 C************************************************************************
610     C
611 molod 1.5 C!ROUTINE: BCHEADER
612     C!DESCRIPTION: BCHEADER reads the header from a file and returns the info.
613 molod 1.3 C
614     C!INPUT PARAMETERS:
615 molod 1.5 C! iunit unit number assigned to the data file
616     C! ndmax maximum number of date/times of the data
617     C! nrec record number of the header info (or assume 1??)
618 molod 1.3 C
619     C!OUTPUT PARAMETERS:
620 molod 1.5 C! cname name of the data in the file header
621     C! cdscrip description of the data in the file header
622     C! im number of x points
623     C! jm number of y points
624     C! npx number of faces (processors) in x-direction
625     C! npy number of faces (processors) in x-direction
626     C! lat0 starting latitude for the data grid
627     C! lon0 starting longitude for the data grid
628     C! ndatebc number of date/times of the data in the file
629     C! nymdbc(ndmax) array of dates for the data including century
630     C! nhmsbc(ndmax) array of times for the data
631     C! undef value for undefined values in the data
632     C! error logical TRUE if dataset problem
633 molod 1.3 C
634     C--------------------------------------------------------------------------
635 molod 1.5 implicit none
636 molod 1.3
637 molod 1.5 integer iunit, ndmax, nrec
638 molod 1.3
639 molod 1.5 character*8 cname
640     character*80 cdscrip
641     integer im,jm,npx,npy,ndatebc,nymdbc(ndmax),nhmsbc(ndmax)
642 molod 1.13 _RL lat0,lon0,undef
643 molod 1.5 logical error
644    
645 molod 1.11 integer i
646 molod 1.5 integer*4 im_32,jm_32,npx_32,npy_32
647 molod 1.9 integer*4 ndatebc_32,nhmsbc_32(ndmax),nymdbc_32(ndmax)
648 molod 1.5 real*4 lat0_32,lon0_32,undef_32
649 molod 1.3
650     C--------- Read file -----------------------------------------------
651    
652     read(iunit,rec=nrec,err=500) cname, cdscrip,
653 molod 1.5 . im_32, jm_32, npx_32, npy_32, lat0_32, lon0_32,
654     . ndatebc_32, undef_32,
655     . (nymdbc_32(i), nhmsbc_32(i), i=1,ndatebc_32)
656 molod 1.12 #ifdef _BYTESWAPIO
657     call MDS_BYTESWAPR4( 1, lat0_32)
658     call MDS_BYTESWAPR4( 1, lon0_32)
659     call MDS_BYTESWAPR4( 1, undef_32)
660     #endif
661 molod 1.5
662     im = im_32
663     jm = jm_32
664     npx = npx_32
665     npy = npy_32
666     lat0 = lat0_32
667     lon0 = lon0_32
668 molod 1.3 undef = undef_32
669    
670     ndatebc = ndatebc_32
671     do i=1,ndatebc
672     nymdbc(i) = nymdbc_32(i)
673     nhmsbc(i) = nhmsbc_32(i)
674     enddo
675    
676     return
677     500 continue
678     print *, 'Error reading boundary condition from unit ',iunit
679     error = .true.
680     return
681     end

  ViewVC Help
Powered by ViewVC 1.1.22