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

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

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

revision 1.1 by molod, Fri Jun 4 16:23:37 2004 UTC revision 1.4 by molod, Tue Jun 8 22:26:08 2004 UTC
# Line 5  C $Name$ Line 5  C $Name$
5  c----------------------------------------------------------------------  c----------------------------------------------------------------------
6  c  Subroutine update_ocean_exports - 'Wrapper' routine to update  c  Subroutine update_ocean_exports - 'Wrapper' routine to update
7  c        the fields related to the ocean's surface that are needed  c        the fields related to the ocean's surface that are needed
8  c        by fizhi.  c        by fizhi (sst and sea ice extent).
 c        Also: Set up "bi, bj loop" and some timers and clocks here.  
9  c  c
10  c Call:  getsst  (Return the current sst field-read dataset if needed)  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)  c        getsice (Return the current sea ice field-read data if needed)
# Line 15  c--------------------------------------- Line 14  c---------------------------------------
14  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
15  #include "SIZE.h"  #include "SIZE.h"
16  #include "GRID.h"  #include "GRID.h"
17  #include "ocean_coms.h"  #include "fizhi_ocean_coms.h"
18  #include "EEPARAMS.h"  #include "EEPARAMS.h"
19    #include "chronos.h"
20    
21         integer myTime, myIter, myThid         integer myTime, myIter, myThid
22    
23         integer i, j, L, bi, bj         integer i, j, bi, bj, biglobal, bjglobal
24         integer im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2         integer im1, im2, jm1, jm2, idim1, idim2, jdim1, jdim2
25           integer nSxglobal, nSyglobal
26           integer ksst,kice
27           real        sstmin
28           parameter ( sstmin = 273.16 )
29    
30         im1 = 1-OLx         idim1 = 1-OLx
31         im2 = sNx+OLx         idim2 = sNx+OLx
32         jm1 = 1-OLy         jdim1 = 1-OLy
33         jm2 = sNy+OLy         jdim2 = sNy+OLy
34         idim1 = 1         im1 = 1
35         idim2 = sNx         im2 = sNx
36         jdim1 = 1         jm1 = 1
37         jdim2 = sNy         jm2 = sNy
38           nSxglobal = nSx*nPx
39           nSyglobal = nSy*nPy
40    
41         do bj = myByLo(myThid), myByHi(myThid)         call mdsfindunit( ksst, myThid )
42         do bi = myBxLo(myThid), myBxHi(myThid)         call mdsfindunit( kice, myThid )
43    
44    C***********************************************************************
45    
46  c      call getsst         DO BJ = myByLo(myThid),myByHi(myThid)
47  c      call getsice         DO BI = myBxLo(myThid),myBxHi(myThid)
48    
49           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    
57    c Check for Minimum Open-Water SST
58    c --------------------------------
59           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         enddo         enddo
64         enddo         enddo
65    
66           ENDDO
67           ENDDO
68    
69         return         return
70         end         end
71    
72           subroutine getsice(iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,
73         .            nSx,nSy,nPx,nPy,bi,bj,biglobal,bjglobal,nymd,nhms,sice)
74    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    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    C!      nSx       Number of processors in x-direction (local processor)
93    C!      nSy       Number of processors in y-direction (local processor)
94    C!      nPx       Number of processors in x-direction (global)
95    C!      nPy       Number of processors in y-direction (global)
96    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    C
103    C!OUTPUT PARAMETERS:
104    C!      sice(idim1:idim2,jdim1:jdim2,nSx,nSy) Sea ice depth in meters
105    C
106    C!ROUTINES CALLED:
107    C
108    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    C
112    C--------------------------------------------------------------------------
113    
114          implicit none
115    #include "CPP_OPTIONS.h"
116    
117          integer iunit,idim1,idim2,jdim1,jdim2,im1,im2,jm1,jm2,nSx,nSy
118          integer bi,bj,biglobal.bjglobal,nymd,nhms
119    
120          _RL sice(idim1:idim2,jdim1:jdim2,nSx,nSy)
121    
122    c MPI Utilities
123    c -------------
124          include 'mpif.h'
125          integer  ierror
126    
127    C Maximum number of dates in one year for the data
128          integer   ndmax
129          parameter (ndmax = 370)
130    
131          character*8  cname
132          character*80 cdscrip
133          real fac1, fac2, lat0, lon0, timebc1, timebc2, timemod, undef
134          logical first, found, error
135          integer i,j,n,nn,iyear,iyearbc,nd,ndby3,imbc,jmbc,ndatebc
136          integer nhmsbc(ndmax), nhmsbc1, nhmsbc2,nrec
137          integer nymdbc(ndmax),nymdbc1,nymdbc2,nymdmod
138    
139    C Define Allocatable Arrays
140          real sicebc1(im2,jm2,nPx,nPy),sicebc2(im2,jm2,nPx,nPy)
141    
142    C--------- Variable Initialization ---------------------------------
143    
144          data first /.true./
145          data error /.false./
146    
147    c  save header info
148          save imbc, jmbc, lat0, lon0, ndatebc, undef, nymdbc, nhmsbc
149          save nymdbc1, nymdbc2, nhmsbc1, nhmsbc2
150          save first
151          save sicebc1, sicebc2
152    
153    c  this only works for between 1950-2050
154          if (nymd .lt. 500101) then
155            nymdmod = 20000000 + nymd
156          else if (nymd .le. 991231) then
157            nymdmod = 19000000 + nymd
158          else
159            nymdmod = nymd
160          endif
161    
162    c  initialize so that first time through they have values for the check
163    c  these vaules make the iyear .ne. iyearbc true anyways for
164    c  for the first time so first isnt checked below.
165    
166          if (first) then
167            nymdbc(2) = 0
168            nymdbc1   = 0
169            nymdbc2   = 0
170            nhmsbc1   = 0
171            nhmsbc2   = 0
172            first = .false.
173          endif
174    
175    C---------- Read in Header file ----------------------------------
176    
177          iyear   = nymdmod/10000
178          iyearbc = nymdbc(2)/10000
179    
180          if( iyear.ne.iyearbc ) then
181    
182            close(iunit)
183            open (iunit, form='unformatted', access='direct',recl=im2*jm2*4)
184            nrec = 1
185            call bcheader (iunit, ndmax, nrec,
186         .                 cname, cdscrip, imbc, jmbc, lat0, lon0,
187         .                 ndatebc, nymdbc, nhmsbc, undef, error)
188    
189    C--------- Check data for Compatibility ------------------------------
190    
191    C Check for correct data in boundary condition file
192           if (.not.error .and. cname.ne.'SICE') then
193            write(6,*)'Wrong data in SICE boundary condition file => ',cname
194            error = .true.
195           endif
196    
197    C Check Horizontal Resolution
198           if (.not.error .and. imbc*jmbc.ne.im2*jm2) then
199            write(6,*) ' B.C. Resolution DOES NOT match Model Resolution!'
200            write(6,*) ' B.C. Resolution:  ',imbc*jmbc
201            write(6,*) 'Model Resolution:  ',im2*jm2
202            error = .true.
203           endif
204    
205    C Check Year
206           iyearbc = nymdbc(2)/10000
207           if (.not.error .and. iyear.ne.iyearbc .and. iyearbc.ne.0) then
208            write(6,*) '     B.C. Year DOES NOT match REQUESTED Year!'
209            write(6,*) '     B.C. Year:  ', iyearbc
210            write(6,*) 'Requested Year:  ', iyear
211            error = .true.
212           endif
213    
214           if (.not.error)   then
215    C if climatology, fill dates for data with current model year
216            if (iyearbc.eq.0) then          
217             write(6,*)
218             write(6,*) 'Climatological Dataset is being used.'  
219             write(6,*) 'Current model year to be used to fill Header Dates'
220             do n = 2, ndatebc-1
221              nymdbc(n) = nymdbc(n) +(nymdmod/10000)*10000
222             enddo
223    C  For the first date subtract 1 year from the current model NYMD
224             n = 1
225             nymdbc(n) = nymdbc(n) +(nymdmod/10000-1)*10000
226    C  For the last date add 1 year to the current model NYMD
227             n = ndatebc
228             nymdbc(n) = nymdbc(n) +(nymdmod/10000+1)*10000
229            endif
230    
231    C  Write out header info
232            write(6,*) ' Updated boundary condition data'
233            write(6,*) ' ---------------------------------'
234            write(6,*) ' Variable: ',cname
235            write(6,*) ' Description: ',cdscrip
236            write(6,*) ' Resolution: x= ',imbc,' y= ',jmbc,
237         .                                       ' Undefined value = ',undef
238            write(6,*) ' Starting latitude = ',lat0,' longitude =',lon0
239            write(6,*) ' Data valid at these times: '
240            ndby3 = ndatebc/3
241            do n = 1, ndby3*3,3
242             write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=n,n+2)
243     1000    format(3(2x,i3,':',i8,2x,i8))
244            enddo
245            write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=ndby3*3+1,ndatebc)
246           endif  
247    
248          endif
249    
250    C---------- Read sice data if necessary -------------------------------
251    
252          found = .false.
253          nd = 2
254    
255    c  If model time is not within the times of saved sice data
256    c  from previous call to getsice then read new data
257    
258          timemod = float(nymdmod) + float(nhms)   /1000000
259          timebc1 = float(nymdbc1) + float(nhmsbc1)/1000000
260          timebc2 = float(nymdbc2) + float(nhmsbc2)/1000000
261    
262          if (timemod .lt. timebc1 .or. timemod .ge. timebc2) then
263    
264           do while (.not.found .and. nd .le. ndatebc)
265            timebc2 = float(nymdbc(nd)) + float(nhmsbc(nd))/1000000
266            if (timebc2 .gt. timemod) then  
267              nymdbc1 = nymdbc(nd-1)
268              nymdbc2 = nymdbc(nd)
269              nhmsbc1 = nhmsbc(nd-1)
270              nhmsbc2 = nhmsbc(nd)
271              call bcdata (iunit, imbc, jmbc, nd, nd+1, sicebc1, sicebc2)
272              found = .true.
273            else
274              nd = nd + 1
275            endif
276           enddo
277    
278    c  Otherwise the data from the last time in getsice surrounds the
279    c  current model time.
280    
281          else
282           found = .true.
283          endif
284    
285          if (.not.found) then
286           print *, 'STOP: Could not find SICE dates for model time.'
287           call my_finalize
288           call my_exit (101)
289          endif
290    
291    C---------- Interpolate sice data ------------------------------------
292    
293          call interp_time(nymdmod,nhms,nymdbc1,nhmsbc1,nymdbc2,nhmsbc2,
294         .                                                       fac1,fac2)
295    
296          do j = jm1,jm2
297          do i = im1,im2
298           sice(i,j,bi,bj) = sicebc1(i,j,biglobal,bjglobal)*fac1
299         .                 + sicebc2(i,j,biglobal,bjglobal)*fac2
300    c average to 0 or 1
301    c -----------------
302           if (sice(i,j,bi,bj) .ge. 0.5) then
303            sice(i,j,bi,bj) = 1.
304           else
305            sice(i,j,bi,bj) = 0.
306           endif
307          enddo
308          enddo
309    
310    C---------- Fill sice with depth of ice ------------------------------------
311          do j = jm1,jm2
312          do i = im1,im2
313           if (sice(i,j,bi,bj) .eq. 1.) then                
314            sice(i,j,bi,bj) = 3.
315           endif
316          enddo
317          enddo
318    C---------------------------------------------------------------------------
319    
320          return
321          end
322          subroutine getsst ( iunit,nymd,nhms,sst,im,jm,lattice )
323    C************************************************************************
324    C!GETSST
325    C************************************************************************
326    C
327    C!ROUTINE:      GETSST
328    C!PROGRAMMER:   Sharon Nebuda
329    C!DATE CODED:   May 8, 1996
330    C!DESCRIPTION:  GETSST gets the SST data.
331    C!              This routine is adaptable for any frequency
332    C!              data upto a daily frequency.  
333    C!              note: for diurnal data ndmax should be increased.
334    C
335    C!INPUT PARAMETERS:
336    C!              iunit   Unit number assigned to the sst data file
337    C!              nymd    YYMMDD of the current model timestep
338    C!              nhms    HHMMSS of the model time
339    C!            im     Number of x points
340    C!            jm     Number of y points
341    C!       lattice     Grid Decomposition defined by Dynamics
342    C
343    C!OUTPUT PARAMETERS:
344    C!              sst(im,jm)      Sea surface temperature in Kelvin
345    C
346    C!ROUTINES CALLED:
347    C
348    C!      bcdata          Reads the data for a given unit number
349    C!      bcheader        Reads the header info for a given unit number
350    C!     interp_time   Returns weights for linear interpolation
351    C
352    C--------------------------------------------------------------------------
353    
354          use dynamics_lattice_module
355          implicit none
356          type ( dynamics_lattice_type ) lattice
357    
358    c MPI Utilities
359    c -------------
360          include 'mpif.h'
361          integer  ierror
362    
363    C  Parameter statements
364          integer   ndmax   ! Maximum number of dates in one year for the data
365          parameter (ndmax = 370)
366    
367    C  Variables passed to the routine:
368          integer   iunit   ! Unit number assigned to the SST data file
369          integer   nymd    ! YYMMDD of the current model timestep
370          integer   nhms    ! HHMMSS of the model time
371          integer        im     ! Number of x points
372          integer        jm     ! Number of y points
373    
374    C  Variables returned by the routine:
375          real      sst(im,jm)      ! Sea surface temperature in Kelvin
376    
377    C  Variables unique to the routine:
378          character*8  cname        ! Name of the data in the file header
379          character*80 cdscrip      ! Description of the data in the file header
380          real      fac1            ! Weighted value (fraction) of the data
381                                    ! before the model time
382          real      fac2            ! Weighted value (fraction) of the data
383                                    ! after the model time
384          logical   first           ! True for first time using the dates for the
385                                    ! BC data file.  Then read in the header file.
386          logical   found           ! If false, then the data surrounding the model
387                                    ! time was not found
388          logical error         ! TRUE if problem with data
389          integer   i,j,n,nn        ! DO loop counters
390          integer   iyear           ! Year of model
391          integer   iyearbc         ! Year of boundary condition data
392          real      lat0            ! Starting lat of the bc data set (future use)
393          real      lon0            ! Starting lon of the bc data set (future use)
394          integer   nd              ! Counter for record number of data to read
395          integer   ndby3           ! int(ndatebc/3) used for write statement
396          integer   imbc            ! IM read from the BC data
397          integer   jmbc            ! JM read from the BC data
398          integer   ndatebc         ! Number of dates in the BC file
399          integer   nhmsbc(ndmax)          ! HHMMSS of the data time (not needed currently)
400          integer   nhmsbc1         ! HHMMSS of the earlier data kept from last timestep
401          integer   nhmsbc2                ! HHMMSS of the later data kept from last timestep
402          integer nrec                    ! Record number of the header (set to 1)
403          integer   nymdbc(ndmax)          ! YYYYMMDD of each data
404          integer   nymdbc1         ! YYYYMMDD of the earlier data kept from last timestep
405          integer   nymdbc2                ! YYYYMMDD of the later data kept from last timestep
406          integer nymdmod           ! YYYYMMDD of the current model timestep
407          real      timebc1         ! YYYYMMDD.HHMMSS of the earlier bc data
408          real      timebc2         ! YYYYMMDD.HHMMSS of the later bc data
409          real      timemod         ! YYYYMMDD.HHMMSS of the current timestep
410          real      undef           ! Undefined value for missing data
411    
412    C Define Allocatable Arrays
413          real, allocatable, save :: sstbc1(:,:)     ! Sea surface temperature (K) from bc data
414                                                     ! of the date before the model time
415          real, allocatable, save :: sstbc2(:,:)     ! Sea surface temperature (K) from bc data
416                                                     ! of the date after the model time
417    
418    C--------- Variable Initialization ---------------------------------
419    
420          data first /.true./
421          data error /.false./
422    
423    c  save header info
424          save imbc, jmbc, lat0, lon0, ndatebc, undef, nymdbc, nhmsbc
425          save nymdbc1, nymdbc2, nhmsbc1, nhmsbc2, sstbc1
426          save first
427    
428    c  this only works for between 1950-2050
429          if (nymd .lt. 500101) then
430            nymdmod = 20000000 + nymd
431          else if (nymd .le. 991231) then
432            nymdmod = 19000000 + nymd
433          else
434            nymdmod = nymd
435          endif
436    
437    c  initialize so that first time through they have values for the check
438    c  these vaules make the iyear .ne. iyearbc true anyways for
439    c  for the first time so first isnt checked below.
440          if (first) then
441          allocate ( sstbc1(lattice%imglobal,lattice%jmglobal) )  ! Allocate Memory for sstbc1
442          allocate ( sstbc2(lattice%imglobal,lattice%jmglobal) )  ! Allocate Memory for sstbc2
443            nymdbc(2) = 0
444            nymdbc1   = 0
445            nymdbc2   = 0
446            nhmsbc1   = 0
447            nhmsbc2   = 0
448            first = .false.
449          endif
450    
451    C---------- Read in Header file ----------------------------------
452    
453          iyear   = nymdmod/10000
454          iyearbc = nymdbc(2)/10000
455    
456          if( iyear.ne.iyearbc ) then
457            if( lattice%myid.eq.0 ) then  
458    
459            close(iunit)
460            open (iunit, form='unformatted', access='direct',recl=lattice%imglobal*lattice%jmglobal*4)
461            nrec = 1
462            call bcheader (iunit, ndmax, nrec,
463         .                 cname, cdscrip, imbc, jmbc, lat0, lon0,
464         .                 ndatebc, nymdbc, nhmsbc, undef, error)
465    
466    C--------- Check data for Compatibility
467    
468    C Check for correct data in boundary condition file
469           if (.not.error .and. cname.ne.'SST') then
470                write(6,*) 'Wrong data in SST boundary condition file => ',cname
471                error = .true.
472           endif
473    
474    C Check Horizontal Resolution
475           if (.not.error .and. imbc*jmbc.ne.lattice%imglobal*lattice%jmglobal) then
476                write(6,*) 'Boundary Condition Resolution DOES NOT match Model Resolution!'
477                write(6,*) 'Boundary Condition Resolution:  ',imbc*jmbc
478                write(6,*) '             Model Resolution:  ',lattice%imglobal*lattice%jmglobal
479                error = .true.
480           endif
481    
482    C Check Year
483           iyearbc = nymdbc(2)/10000
484           if (.not.error .and. iyear.ne.iyearbc .and. iyearbc.ne.0) then
485                write(6,*) 'Boundary Condition Year DOES NOT match REQUESTED Year!'
486                write(6,*) 'Boundary Condition Year:  ', iyearbc
487                write(6,*) '         Requested Year:  ', iyear
488                error = .true.
489           endif
490    
491           if (.not.error)   then
492    C if climatology, fill dates for data with current model year
493                if (iyearbc.eq.0) then              
494                write(6,*)
495                write(6,*) 'Climatological Dataset is being used.'  
496                write(6,*) 'Current model year will be used to fill Header Dates'
497                  do n = 2, ndatebc-1
498                   nymdbc(n) = nymdbc(n) +(nymdmod/10000)*10000
499                  enddo
500    C  For the first date subtract 1 year from the current model NYMD
501                  n = 1
502                  nymdbc(n) = nymdbc(n) +(nymdmod/10000-1)*10000
503    C  For the last date add 1 year to the current model NYMD
504                  n = ndatebc
505                  nymdbc(n) = nymdbc(n) +(nymdmod/10000+1)*10000
506                endif
507    
508    C  Write out header info
509           write(6,*) ' Updated boundary condition data'
510           write(6,*) ' ---------------------------------'
511           write(6,*) ' Variable: ',cname
512           write(6,*) ' Description: ',cdscrip
513           write(6,*) ' Resolution: x= ',imbc,' y= ',jmbc,' Undefined value = ',undef
514           write(6,*) ' Starting latitude = ',lat0,' longitude =',lon0
515           write(6,*) ' Data valid at these times: '
516           ndby3 = ndatebc/3
517           do n = 1, ndby3*3,3
518            write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=n,n+2)
519     1000   format(3(2x,i3,':',i8,2x,i8))
520           enddo
521           write(6,1000) (nn,nymdbc(nn),nhmsbc(nn),nn=ndby3*3+1,ndatebc)
522          endif  ! End error  Check
523    
524          endif  ! End MYID=0 Check
525    
526    c Broadcast information to other PEs
527    c ----------------------------------
528    #if (mpi)
529           call mpi_bcast ( error,1,mpi_logical,0,lattice%comm,ierror )
530    #endif
531           if( error ) call my_exit (101)
532    
533    #if (mpi)
534           call mpi_bcast ( ndatebc,1     ,mpi_integer,0,lattice%comm,ierror )
535           call mpi_bcast ( nymdbc,ndatebc,mpi_integer,0,lattice%comm,ierror )
536           call mpi_bcast ( nhmsbc,ndatebc,mpi_integer,0,lattice%comm,ierror )
537    #endif
538    
539          endif  ! New Year Info Check
540    
541    C---------- Read SST data if necessary -------------------------------
542    
543            found = .false.
544            nd = 2
545    
546    c  If model time is not within the times of saved sst data
547    c  from previous call to getsst then read new data
548    
549            timemod = float(nymdmod) + float(nhms)   /1000000
550            timebc1 = float(nymdbc1) + float(nhmsbc1)/1000000
551            timebc2 = float(nymdbc2) + float(nhmsbc2)/1000000
552            if (timemod .lt. timebc1 .or. timemod .ge. timebc2) then
553    
554            do while (.not.found .and. nd .le. ndatebc)
555              timebc2 = float(nymdbc(nd)) + float(nhmsbc(nd))/1000000
556              if (timebc2 .gt. timemod) then        
557                nymdbc1 = nymdbc(nd-1)
558                nymdbc2 = nymdbc(nd)
559                nhmsbc1 = nhmsbc(nd-1)
560                nhmsbc2 = nhmsbc(nd)
561                if ( lattice%myid.eq.0 ) call bcdata (iunit, imbc, jmbc, nd, nd+1, sstbc1, sstbc2)
562    #if (mpi)
563                call mpi_bcast ( sstbc1,lattice%imglobal*lattice%jmglobal,mpi_double_precision,0,lattice%comm,ierror )
564                call mpi_bcast ( sstbc2,lattice%imglobal*lattice%jmglobal,mpi_double_precision,0,lattice%comm,ierror )
565    #endif
566                found = .true.
567              else
568                nd = nd + 1
569              endif
570            enddo
571    
572    c  Otherwise the data from the last time in getsst surrounds the
573    c  current model time.
574    
575            else
576              found = .true.
577            endif
578    
579            if (.not.found) then
580              if( lattice%myid.eq.0 ) print *, 'STOP: Could not find SST boundary condition dates surrounding the model time.'
581              call my_finalize
582              call my_exit (101)
583            endif
584    
585    C---------- Interpolate SST data ------------------------------------
586    
587              call interp_time ( nymdmod,nhms, nymdbc1,nhmsbc1, nymdbc2,nhmsbc2, fac1,fac2 )
588    
589              do j = 1, jm
590              do i = 1, im
591                sst(i,j) = sstbc1( lattice%iglobal(i),lattice%jglobal(j) )*fac1
592         .               + sstbc2( lattice%iglobal(i),lattice%jglobal(j) )*fac2
593              enddo
594              enddo
595    
596          return
597          end
598    
599          subroutine bcdata (iunit, im, jm, nrec1, nrec2, field1, field2)
600    C************************************************************************
601    C!BCDATA
602    C************************************************************************
603    C
604    C!ROUTINE:      BCDATA
605    C!PROGRAMMER:   Sharon Nebuda
606    C!DATE CODED:   April 29, 1996
607    C!DESCRIPTION:  BCDATA reads the data from the file assigned to the
608    C!              passed unit number and returns data from the two times
609    C!              surrounding the current model time.  The two record
610    C!              postitions are not assumed to be next to each other.
611    C
612    C!INPUT PARAMETERS:
613    C!      im      number of x points
614    C!      jm      number of y points
615    C!      nrec1   record number of the time before the model time
616    C!      nrec2   record number of the time after the model time
617    C
618    C!OUTPUT PARAMETERS:
619    C!      field1(im,jm)   data field before the model time
620    C!      field2(im,jm)   data field after the model time
621    C
622    C!REVISION HISTORY:    
623    C!      NEW
624    C
625    C!ROUTINES CALLED:
626    C
627    C!      none
628    C
629    C--------------------------------------------------------------------------
630    
631    
632    C--------------- Variable Declaration -------------------------------------
633          implicit none
634    
635    C  Variables passed to the routine:
636          integer   iunit   ! Unit number assigned to the data file
637          integer   im      ! Number of x points
638          integer   jm      ! Number of y points
639          integer   nrec1   ! Record number of the time before the model time
640          integer   nrec2   ! Record number of the time after the model time
641    
642    C  Variables returned by the routine:
643          real      field1(im,jm)   ! Real*8 Data before the model time
644          real      field2(im,jm)   ! Real*8 Data after  the model time
645    
646    C  Variables unique to the routine:
647          integer i,j               ! DO loop counters
648          real*4    f1(im,jm)       ! Real*4 Data before the model time
649          real*4    f2(im,jm)       ! Real*4 Data after  the model time
650    
651    C--------- Read file -----------------------------------------------
652    
653          read(iunit,rec=nrec1) f1
654          read(iunit,rec=nrec2) f2
655    
656          do j=1,jm
657          do i=1,im
658          field1(i,j) = f1(i,j)
659          field2(i,j) = f2(i,j)
660          enddo
661          enddo
662    
663          return
664          end
665          subroutine bcheader (iunit, ndmax, nrec,
666         .                     cname, cdscrip, im, jm, lat0, lon0, ndatebc,
667         .                     nymdbc, nhmsbc, undef, error)
668    C************************************************************************
669    C!BCHEADER
670    C************************************************************************
671    C
672    C!ROUTINE:      BCHEADER
673    C!PROGRAMMER:   Sharon Nebuda
674    C!DATE CODED:   April 29, 1996
675    C!DESCRIPTION:  BCHEADER reads the header info from the file assigned to the
676    C!              passed unit number and returns the info back.  
677    C
678    C!INPUT PARAMETERS:
679    C!      iunit   unit number assigned to the data file
680    C!      ndmax   maximum number of date/times of the data
681    C!      nrec    record number of the header info (or assume 1??)
682    C
683    C!OUTPUT PARAMETERS:
684    C!      cname           name of the data in the file header
685    C!      cdscrip         description of the data in the file header
686    C!      im              number of x points
687    C!      jm              number of y points
688    C!      lat0            starting latitude for the data grid
689    C!      lon0            starting longitude for the data grid
690    C!      ndatebc         number of date/times of the data in the file
691    C!      nymdbc(ndmax)   array of dates for the data including century
692    C!      nhmsbc(ndmax)   array of times for the data
693    C!      undef           value for undefined values in the data
694    C!      error           logical TRUE if dataset problem
695    C
696    C!REVISION HISTORY:    
697    C!      NEW
698    C
699    C!ROUTINES CALLED:
700    C!      none
701    C
702    C--------------------------------------------------------------------------
703    
704    C--------------- Variable Declaration -------------------------------------
705          implicit none
706    
707    C  Variables passed to the routine:
708          integer   iunit   ! Unit number assigned to the data file
709          integer   ndmax   ! Maximum number of dates for a given field
710          integer   nrec    ! Record number of the header info (or assume 1??)
711    
712    C  Variables returned by the routine:
713          character*8  cname        ! Name of the data in the file header
714          character*80 cdscrip      ! Description of the data in the file header
715          integer   im     ! Number of x points
716          integer   jm     ! Number of y points
717          real         lat0     ! Starting latitude of the data
718          real           lon0     ! Starting longitude of the data
719          integer   ndatebc ! Number of date/times of the data in the file
720          integer   nymdbc(ndmax)   ! array of dates for the data including century
721          integer   nhmsbc(ndmax)   ! array of times for the data
722          real      undef           ! value for undefined values in the data
723          logical error         ! logical TRUE if dataset problem
724    
725    C  Variables unique to the routine:
726          integer   i               ! DO loop counters
727          integer n
728          integer*4            im_32  ! Number of x points
729          integer*4               jm_32  ! Number of y points
730          real*4             lat0_32  ! Starting latitude of the data
731          real*4               lon0_32  ! Starting longitude of the data
732          integer*4       ndatebc_32  ! Number of date/times of the data in the file
733          integer*4 nymdbc_32(ndmax)  ! array of dates for the data including century
734          integer*4 nhmsbc_32(ndmax)  ! array of times for the data
735          real*4     undef_32         ! value for undefined values in the data
736    
737    C--------- Read file -----------------------------------------------
738    
739          read(iunit,rec=nrec,err=500) cname, cdscrip,
740         .                     im_32, jm_32, lat0_32, lon0_32,
741         .                     ndatebc_32, undef_32,
742         .                    (nymdbc_32(i), nhmsbc_32(i), i=1,ndatebc_32)
743    
744          im    =    im_32
745          jm    =    jm_32
746          lat0  =  lat0_32
747          lon0  =  lon0_32
748          undef = undef_32
749    
750          ndatebc = ndatebc_32
751          do i=1,ndatebc
752          nymdbc(i) = nymdbc_32(i)
753          nhmsbc(i) = nhmsbc_32(i)
754          enddo
755    
756          return
757      500 continue
758          print *, 'Error reading boundary condition from unit ',iunit
759          error = .true.
760          return
761          end

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.4

  ViewVC Help
Powered by ViewVC 1.1.22