/[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.12 - (hide annotations) (download)
Tue Jul 20 16:24:49 2004 UTC (19 years, 11 months ago) by molod
Branch: MAIN
Changes since 1.11: +12 -1 lines
Add logic for byteswapping of input data if needed

1 molod 1.12 C $Header: /u/gcmpack/MITgcm/pkg/fizhi/update_ocean_exports.F,v 1.11 2004/07/19 22:06:59 molod Exp $
2 molod 1.1 C $Name: $
3    
4     subroutine update_ocean_exports (myTime, myIter, myThid)
5     c----------------------------------------------------------------------
6     c Subroutine update_ocean_exports - 'Wrapper' routine to update
7     c the fields related to the ocean's surface that are needed
8 molod 1.3 c by fizhi (sst and sea ice extent).
9 molod 1.1 c
10     c Call: getsst (Return the current sst field-read dataset if needed)
11     c getsice (Return the current sea ice field-read data if needed)
12     c-----------------------------------------------------------------------
13     implicit none
14     #include "CPP_OPTIONS.h"
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     integer myTime, myIter, myThid
22    
23 molod 1.4 integer i, j, bi, bj, biglobal, bjglobal
24 molod 1.1 integer im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2
25 molod 1.4 integer nSxglobal, nSyglobal
26 molod 1.3 integer ksst,kice
27 molod 1.6 _RL sstmin
28 molod 1.3 parameter ( sstmin = 273.16 )
29 molod 1.1
30 molod 1.4 idim1 = 1-OLx
31     idim2 = sNx+OLx
32     jdim1 = 1-OLy
33     jdim2 = sNy+OLy
34     im1 = 1
35     im2 = sNx
36     jm1 = 1
37     jm2 = sNy
38     nSxglobal = nSx*nPx
39     nSyglobal = nSy*nPy
40    
41     call mdsfindunit( ksst, myThid )
42     call mdsfindunit( kice, myThid )
43    
44     C***********************************************************************
45 molod 1.3
46 molod 1.4 DO BJ = myByLo(myThid),myByHi(myThid)
47     DO BI = myBxLo(myThid),myBxHi(myThid)
48 molod 1.3
49 molod 1.4 biglobal=bi+(myXGlobalLo-1)/im2
50     bjglobal=bj+(myYGlobalLo-1)/jm2
51    
52     call getsst(ksst,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSx,
53     . nSy,nSxglobal,nSyglobal,bi,bj,biglobal,bjglobal,nymd,nhms,sst)
54     call getsice(kice,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSx,
55     . nSy,nSxglobal,nSyglobal,bi,bj,biglobal,bjglobal,nymd,nhms,sice)
56 molod 1.3
57     c Check for Minimum Open-Water SST
58     c --------------------------------
59 molod 1.4 do j=jm1,jm2
60     do i=im1,im2
61     if(sice(i,j,bi,bj).eq.0.0 .and. sst(i,j,bi,bj).lt.sstmin)
62     . sst(i,j,bi,bj) = sstmin
63 molod 1.1 enddo
64     enddo
65    
66 molod 1.4 ENDDO
67     ENDDO
68    
69 molod 1.1 return
70     end
71 molod 1.3
72 molod 1.4 subroutine getsice(iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,
73 molod 1.11 . nSumx,nSumy,nPgx,nPgy,bi,bj,biglobal,bjglobal,nymd,nhms,sice)
74 molod 1.3 C************************************************************************
75     C
76     C!ROUTINE: GETSICE
77     C!DESCRIPTION: GETSICE returns the sea ice depth.
78     C! This routine is adaptable for any frequency
79     C! data upto a daily frequency.
80     C! note: for diurnal data ndmax should be increased.
81     C
82     C!INPUT PARAMETERS:
83 molod 1.4 C! iunit Unit number assigned to the sice data file
84     C! idim1 Start dimension in x-direction
85     C! idim2 End dimension in x-direction
86     C! jdim1 Start dimension in y-direction
87     C! jdim2 End dimension in y-direction
88     C! im1 Begin of x-direction span for filling sice
89     C! im2 End of x-direction span for filling sice
90     C! jm1 Begin of y-direction span for filling sice
91     C! jm2 End of y-direction span for filling sice
92 molod 1.11 C! nSumx Number of processors in x-direction (local processor)
93     C! nSumy Number of processors in y-direction (local processor)
94     C! nPgx Number of processors in x-direction (global)
95     C! nPgx Number of processors in y-direction (global)
96 molod 1.4 C! bi Processor number in x-direction (local to processor)
97     C! bj Processor number in y-direction (local to processor)
98     C! biglobal Processor number in x-direction (global)
99     C! bjglobal Processor number in y-direction (global)
100     C! nymd YYMMDD of the current model timestep
101     C! nhms HHMMSS of the model time
102 molod 1.3 C
103     C!OUTPUT PARAMETERS:
104 molod 1.11 C! sice(idim1:idim2,jdim1:jdim2,nSumx,nSumy) Sea ice depth in meters
105 molod 1.3 C
106     C!ROUTINES CALLED:
107     C
108 molod 1.4 C! bcdata Reads the data for a given unit number
109     C! bcheader Reads the header info for a given unit number
110     C! interp_time Returns weights for linear interpolation
111 molod 1.3 C
112     C--------------------------------------------------------------------------
113    
114     implicit none
115 molod 1.7 #include "CPP_EEOPTIONS.h"
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.9 real 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.11 real sicebc1(sNx,sNy,nSx*nPx,nSy*nPy)
136     real 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.7 #include "CPP_EEOPTIONS.h"
363 molod 1.11 #include "SIZE.h"
364 molod 1.5
365 molod 1.11 integer iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSumx,nSumy
366     integer nPgx,nPgy,bi,bj,biglobal,bjglobal,nymd,nhms
367 molod 1.3
368 molod 1.11 _RL sst(idim1:idim2,jdim1:jdim2,nSumx,nSumy)
369 molod 1.3
370 molod 1.5 C Maximum number of dates in one year for the data
371     integer ndmax
372 molod 1.3 parameter (ndmax = 370)
373    
374 molod 1.5 character*8 cname
375     character*80 cdscrip
376 molod 1.9 real fac1, fac2, lat0, lon0, timebc1, timebc2, timemod, undef
377 molod 1.5 logical first, found, error
378 molod 1.9 integer i,j,n,nn,iyear,iyearbc,nd,ndby3,imbc,jmbc,npxbc,npybc
379 molod 1.5 integer ndatebc,nhmsbc(ndmax), nhmsbc1, nhmsbc2,nrec
380     integer nymdbc(ndmax),nymdbc1,nymdbc2,nymdmod
381    
382 molod 1.11 real sstbc1(sNx,sNy,nSx*nPx,nSy*nPy)
383     real sstbc2(sNx,sNy,nSx*nPx,nSy*nPy)
384 molod 1.3
385     C--------- Variable Initialization ---------------------------------
386    
387     data first /.true./
388     data error /.false./
389    
390     c save header info
391 molod 1.11 save imbc,jmbc,npxbc,npybc,lat0,lon0,ndatebc,undef,nymdbc,nhmsbc
392     save nymdbc1, nymdbc2, nhmsbc1, nhmsbc2
393     save first
394     save sstbc1, sstbc2
395 molod 1.3
396     c this only works for between 1950-2050
397     if (nymd .lt. 500101) then
398     nymdmod = 20000000 + nymd
399     else if (nymd .le. 991231) then
400     nymdmod = 19000000 + nymd
401     else
402     nymdmod = nymd
403     endif
404    
405     c initialize so that first time through they have values for the check
406     c these vaules make the iyear .ne. iyearbc true anyways for
407     c for the first time so first isnt checked below.
408     if (first) then
409     nymdbc(2) = 0
410     nymdbc1 = 0
411     nymdbc2 = 0
412     nhmsbc1 = 0
413     nhmsbc2 = 0
414     first = .false.
415     endif
416    
417     C---------- Read in Header file ----------------------------------
418    
419     iyear = nymdmod/10000
420     iyearbc = nymdbc(2)/10000
421    
422     if( iyear.ne.iyearbc ) then
423    
424 molod 1.5 close(iunit)
425     open (iunit,form='unformatted',access='direct',
426 molod 1.11 . recl=im2*jm2*nPgx*nPgy*4)
427 molod 1.5 nrec = 1
428     call bcheader (iunit, ndmax, nrec,
429     . cname, cdscrip, imbc, jmbc, npxbc, npybc, lat0, lon0,
430     . ndatebc, nymdbc, nhmsbc, undef, error)
431 molod 1.3
432     C--------- Check data for Compatibility
433    
434     C Check for correct data in boundary condition file
435     if (.not.error .and. cname.ne.'SST') then
436 molod 1.5 write(6,*)'Wrong data in SST boundary condition file => ',cname
437     error = .true.
438 molod 1.3 endif
439    
440     C Check Horizontal Resolution
441 molod 1.11 if(.not.error.and.imbc*jmbc*npxbc*npybc.ne.im2*jm2*npgx*npgy)then
442 molod 1.5 write(6,*) ' B.C. Resolution DOES NOT match Model Resolution!'
443     write(6,*) ' B.C. Resolution: ',imbc*jmbc*npxbc*npybc
444 molod 1.11 write(6,*) 'Model Resolution: ',im2*jm2*npgx*npgy
445 molod 1.5 error = .true.
446 molod 1.3 endif
447    
448     C Check Year
449     iyearbc = nymdbc(2)/10000
450     if (.not.error .and. iyear.ne.iyearbc .and. iyearbc.ne.0) then
451 molod 1.5 write(6,*)' B.C. Year DOES NOT match REQUESTED Year!'
452     write(6,*)' B.C. Year: ', iyearbc
453     write(6,*)'Requested Year: ', iyear
454     error = .true.
455 molod 1.3 endif
456    
457     if (.not.error) then
458     C if climatology, fill dates for data with current model year
459 molod 1.5 if (iyearbc.eq.0) then
460     write(6,*)
461 molod 1.9 write(6,*)'Climatological Dataset is being used.'
462     write(6,*)'Current model year is used to fill Header Dates'
463 molod 1.5 do n = 2, ndatebc-1
464     nymdbc(n) = nymdbc(n) +(nymdmod/10000)*10000
465     enddo
466 molod 1.3 C For the first date subtract 1 year from the current model NYMD
467 molod 1.5 n = 1
468     nymdbc(n) = nymdbc(n) +(nymdmod/10000-1)*10000
469 molod 1.3 C For the last date add 1 year to the current model NYMD
470 molod 1.5 n = ndatebc
471     nymdbc(n) = nymdbc(n) +(nymdmod/10000+1)*10000
472     endif
473 molod 1.3
474     C Write out header info
475 molod 1.5 write(6,*) ' Updated boundary condition data'
476     write(6,*) ' ---------------------------------'
477     write(6,*) ' Variable: ',cname
478     write(6,*) ' Description: ',cdscrip
479     write(6,*) ' Resolution: x= ',imbc,' y= ',jmbc,
480     . ' Undefined value = ',undef
481     write(6,*) ' Starting latitude = ',lat0,' longitude =',lon0
482     write(6,*) ' Data valid at these times: '
483     ndby3 = ndatebc/3
484     do n = 1, ndby3*3,3
485     write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=n,n+2)
486     1000 format(3(2x,i3,':',i8,2x,i8))
487     enddo
488     write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=ndby3*3+1,ndatebc)
489 molod 1.8 endif
490 molod 1.3
491     if( error ) call my_exit (101)
492    
493 molod 1.8 endif
494 molod 1.3
495     C---------- Read SST data if necessary -------------------------------
496    
497 molod 1.5 found = .false.
498     nd = 2
499 molod 1.3
500     c If model time is not within the times of saved sst data
501     c from previous call to getsst then read new data
502    
503 molod 1.5 timemod = float(nymdmod) + float(nhms) /1000000
504     timebc1 = float(nymdbc1) + float(nhmsbc1)/1000000
505     timebc2 = float(nymdbc2) + float(nhmsbc2)/1000000
506     if (timemod .lt. timebc1 .or. timemod .ge. timebc2) then
507    
508     do while (.not.found .and. nd .le. ndatebc)
509     timebc2 = float(nymdbc(nd)) + float(nhmsbc(nd))/1000000
510     if (timebc2 .gt. timemod) then
511     nymdbc1 = nymdbc(nd-1)
512     nymdbc2 = nymdbc(nd)
513     nhmsbc1 = nhmsbc(nd-1)
514     nhmsbc2 = nhmsbc(nd)
515 molod 1.11 call bcdata (iunit,imbc,jmbc,nPgx,nPgy,nd,nd+1,sstbc1,sstbc2)
516 molod 1.5 found = .true.
517     else
518     nd = nd + 1
519     endif
520     enddo
521 molod 1.3
522     c Otherwise the data from the last time in getsst surrounds the
523     c current model time.
524    
525 molod 1.5 else
526     found = .true.
527     endif
528 molod 1.3
529 molod 1.5 if (.not.found) then
530     print *, 'STOP: Could not find SST dates for model time.'
531     call my_finalize
532     call my_exit (101)
533     endif
534 molod 1.3
535     C---------- Interpolate SST data ------------------------------------
536    
537 molod 1.5 call interp_time(nymdmod,nhms,nymdbc1,nhmsbc1,nymdbc2,nhmsbc2,
538     . fac1,fac2)
539 molod 1.3
540 molod 1.5 do j = jm1,jm2
541     do i = im1,im2
542     sst(i,j,bi,bj) = sstbc1(i,j,biglobal,bjglobal)*fac1
543     . + sstbc2(i,j,biglobal,bjglobal)*fac2
544     enddo
545     enddo
546 molod 1.3
547     return
548     end
549    
550 molod 1.5 subroutine bcdata (iunit,im,jm,nPx,nPy,nrec1,nrec2,field1,field2)
551 molod 1.3 C************************************************************************
552     C
553 molod 1.5 C!ROUTINE: BCDATA
554     C!DESCRIPTION: BCDATA reads the data from the file assigned to the
555     C! passed unit number and returns data from the two times
556     C! surrounding the current model time. The two record
557     C! postitions are not assumed to be next to each other.
558 molod 1.3 C
559     C!INPUT PARAMETERS:
560 molod 1.5 C! im number of x points
561     C! im number of x points
562     C! nPx number of faces in x-direction
563     C! nPy number of faces in y-direction
564     C! nrec1 record number of the time before the model time
565     C! nrec2 record number of the time after the model time
566 molod 1.3 C
567     C!OUTPUT PARAMETERS:
568 molod 1.5 C! field1(im,jm,nPx,nPy) data field before the model time
569     C! field2(im,jm,nPx,nPy) data field after the model time
570 molod 1.3 C
571     C--------------------------------------------------------------------------
572 molod 1.5 implicit none
573 molod 1.12 #include "PACKAGES_CONFIG.h"
574 molod 1.7 #include "CPP_EEOPTIONS.h"
575 molod 1.3
576 molod 1.5 integer iunit,im,jm,nPx,nPy,nrec1,nrec2
577 molod 1.3
578 molod 1.9 real field1(im,jm,nPx,nPy)
579     real field2(im,jm,nPx,nPy)
580 molod 1.3
581 molod 1.5 integer i,j,n1,n2
582 molod 1.9 real*4 f1(im,jm,nPx,nPy), f2(im,jm,nPx,nPy)
583 molod 1.3
584     C--------- Read file -----------------------------------------------
585     read(iunit,rec=nrec1) f1
586     read(iunit,rec=nrec2) f2
587    
588 molod 1.5 do n2=1,nPy
589     do n1=1,nPx
590 molod 1.12 #ifdef _BYTESWAPIO
591     call MDS_BYTESWAPR4( im*jm, f1(1,1,n1,n2))
592     call MDS_BYTESWAPR4( im*jm, f2(1,1,n1,n2))
593     #endif
594 molod 1.3 do j=1,jm
595     do i=1,im
596 molod 1.5 field1(i,j,n1,n2) = f1(i,j,n1,n2)
597     field2(i,j,n1,n2) = f2(i,j,n1,n2)
598     enddo
599     enddo
600 molod 1.3 enddo
601     enddo
602    
603     return
604     end
605     subroutine bcheader (iunit, ndmax, nrec,
606 molod 1.5 . cname, cdscrip, im, jm, npx, npy, lat0, lon0, ndatebc,
607     . nymdbc, nhmsbc, undef, error)
608 molod 1.3 C************************************************************************
609     C
610 molod 1.5 C!ROUTINE: BCHEADER
611     C!DESCRIPTION: BCHEADER reads the header from a file and returns the info.
612 molod 1.3 C
613     C!INPUT PARAMETERS:
614 molod 1.5 C! iunit unit number assigned to the data file
615     C! ndmax maximum number of date/times of the data
616     C! nrec record number of the header info (or assume 1??)
617 molod 1.3 C
618     C!OUTPUT PARAMETERS:
619 molod 1.5 C! cname name of the data in the file header
620     C! cdscrip description of the data in the file header
621     C! im number of x points
622     C! jm number of y points
623     C! npx number of faces (processors) in x-direction
624     C! npy number of faces (processors) in x-direction
625     C! lat0 starting latitude for the data grid
626     C! lon0 starting longitude for the data grid
627     C! ndatebc number of date/times of the data in the file
628     C! nymdbc(ndmax) array of dates for the data including century
629     C! nhmsbc(ndmax) array of times for the data
630     C! undef value for undefined values in the data
631     C! error logical TRUE if dataset problem
632 molod 1.3 C
633     C--------------------------------------------------------------------------
634 molod 1.5 implicit none
635 molod 1.12 #include "PACKAGES_CONFIG.h"
636 molod 1.7 #include "CPP_EEOPTIONS.h"
637 molod 1.3
638 molod 1.5 integer iunit, ndmax, nrec
639 molod 1.3
640 molod 1.5 character*8 cname
641     character*80 cdscrip
642     integer im,jm,npx,npy,ndatebc,nymdbc(ndmax),nhmsbc(ndmax)
643 molod 1.9 real lat0,lon0,undef
644 molod 1.5 logical error
645    
646 molod 1.11 integer i
647 molod 1.5 integer*4 im_32,jm_32,npx_32,npy_32
648 molod 1.9 integer*4 ndatebc_32,nhmsbc_32(ndmax),nymdbc_32(ndmax)
649 molod 1.5 real*4 lat0_32,lon0_32,undef_32
650 molod 1.3
651     C--------- Read file -----------------------------------------------
652    
653     read(iunit,rec=nrec,err=500) cname, cdscrip,
654 molod 1.5 . im_32, jm_32, npx_32, npy_32, lat0_32, lon0_32,
655     . ndatebc_32, undef_32,
656     . (nymdbc_32(i), nhmsbc_32(i), i=1,ndatebc_32)
657 molod 1.12 #ifdef _BYTESWAPIO
658     call MDS_BYTESWAPR4( 1, lat0_32)
659     call MDS_BYTESWAPR4( 1, lon0_32)
660     call MDS_BYTESWAPR4( 1, undef_32)
661     #endif
662 molod 1.5
663     im = im_32
664     jm = jm_32
665     npx = npx_32
666     npy = npy_32
667     lat0 = lat0_32
668     lon0 = lon0_32
669 molod 1.3 undef = undef_32
670    
671     ndatebc = ndatebc_32
672     do i=1,ndatebc
673     nymdbc(i) = nymdbc_32(i)
674     nhmsbc(i) = nhmsbc_32(i)
675     enddo
676    
677     return
678     500 continue
679     print *, 'Error reading boundary condition from unit ',iunit
680     error = .true.
681     return
682     end

  ViewVC Help
Powered by ViewVC 1.1.22