/[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.14 - (hide annotations) (download)
Fri Oct 22 14:52:14 2004 UTC (19 years, 8 months ago) by molod
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint56c_post, checkpoint57a_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint57c_post, checkpoint56a_post
Changes since 1.13: +3 -2 lines
Change myTime from integer to real (_RL), change pressure0 calculation in ini_fixed
(Little bugs.....)

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

  ViewVC Help
Powered by ViewVC 1.1.22