New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
bdydta.F90 in tags/nemo_v3_2/nemo_v3_2/NEMO/OPA_SRC/BDY – NEMO

source: tags/nemo_v3_2/nemo_v3_2/NEMO/OPA_SRC/BDY/bdydta.F90 @ 1878

Last change on this file since 1878 was 1878, checked in by flavoni, 14 years ago

initial test for nemogcm

File size: 45.5 KB
Line 
1MODULE bdydta
2   !!======================================================================
3   !!                       ***  MODULE bdydta  ***
4   !! Open boundary data : read the data for the unstructured open boundaries.
5   !!======================================================================
6   !! History :  1.0  !  2005-01  (J. Chanut, A. Sellar)  Original code
7   !!             -   !  2007-01  (D. Storkey) Update to use IOM module
8   !!             -   !  2007-07  (D. Storkey) add bdy_dta_bt
9   !!            3.0  !  2008-04  (NEMO team)  add in the reference version
10   !!----------------------------------------------------------------------
11#if defined key_bdy
12   !!----------------------------------------------------------------------
13   !!   'key_bdy'                     Unstructured Open Boundary Conditions
14   !!----------------------------------------------------------------------
15   !!   bdy_dta    : read u, v, t, s data along open boundaries
16   !!   bdy_dta_bt : read depth-mean velocities and elevation along open
17   !!                boundaries       
18   !!----------------------------------------------------------------------
19   USE oce             ! ocean dynamics and tracers
20   USE dom_oce         ! ocean space and time domain
21   USE phycst          ! physical constants
22   USE bdy_oce         ! ocean open boundary conditions
23   USE bdytides        ! tidal forcing at boundaries
24   USE iom
25   USE ioipsl
26   USE in_out_manager  ! I/O logical units
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   bdy_dta      ! routines called by step.F90
32   PUBLIC   bdy_dta_bt 
33
34   INTEGER ::   numbdyt, numbdyu, numbdyv                      !: logical units for T-, U-, & V-points data file, resp.
35   INTEGER ::   ntimes_bdy                                     !: exact number of time dumps in data files
36   INTEGER ::   nbdy_b, nbdy_a                                 !: record of bdy data file for before and after model time step
37   INTEGER ::   numbdyt_bt, numbdyu_bt, numbdyv_bt             !: logical unit for T-, U- & V-points data file, resp.
38   INTEGER ::   ntimes_bdy_bt                                  !: exact number of time dumps in data files
39   INTEGER ::   nbdy_b_bt, nbdy_a_bt                           !: record of bdy data file for before and after model time step
40
41   INTEGER, DIMENSION (jpbtime) ::   istep, istep_bt           !: time array in seconds in each data file
42
43   REAL(wp) ::  zoffset                                        !: time offset between time origin in file & start time of model run
44
45   REAL(wp), DIMENSION(jpbdim,jpk,2) ::   tbdydta, sbdydta     !: time interpolated values of T and S bdy data   
46   REAL(wp), DIMENSION(jpbdim,jpk,2) ::   ubdydta, vbdydta     !: time interpolated values of U and V bdy data
47   REAL(wp), DIMENSION(jpbdim,2)     ::   ubtbdydta, vbtbdydta !: Arrays used for time interpolation of bdy data   
48   REAL(wp), DIMENSION(jpbdim,2)     ::   sshbdydta            !: bdy data of ssh
49
50   !!----------------------------------------------------------------------
51   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
52   !! $Id: bdydta.F90 1715 2009-11-05 15:18:26Z smasson $
53   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
54   !!----------------------------------------------------------------------
55
56CONTAINS
57
58   SUBROUTINE bdy_dta( kt )
59      !!----------------------------------------------------------------------
60      !!                   ***  SUBROUTINE bdy_dta  ***
61      !!                   
62      !! ** Purpose :   Read unstructured boundary data for FRS condition.
63      !!
64      !! ** Method  :   At the first timestep, read in boundary data for two
65      !!                times from the file and time-interpolate. At other
66      !!                timesteps, check to see if we need another time from
67      !!                the file. If so read it in. Time interpolate.
68      !!----------------------------------------------------------------------
69      INTEGER, INTENT( in ) ::   kt                             ! ocean time-step index (for timesplitting option, otherwise zero)
70      !!
71      CHARACTER(LEN=80), DIMENSION(3) ::   clfile               ! names of input files
72      CHARACTER(LEN=70 )              ::   clunits              ! units attribute of time coordinate
73      LOGICAL ::   lect                                         ! flag for reading
74      INTEGER ::   it, ib, ik, igrd                             ! dummy loop indices
75      INTEGER ::   igrd_start, igrd_end                         ! start and end of loops on igrd
76      INTEGER ::   idvar                                        ! netcdf var ID
77      INTEGER ::   iman, i15, imois                             ! Time variables for monthly clim forcing
78      INTEGER ::   ntimes_bdyt, ntimes_bdyu, ntimes_bdyv
79      INTEGER ::   itimer, totime
80      INTEGER ::   ii, ij                                       ! array addresses
81      INTEGER ::   ipi, ipj, ipk, inum                          ! temporary integers (NetCDF read)
82      INTEGER ::   iyear0, imonth0, iday0
83      INTEGER ::   ihours0, iminutes0, isec0
84      INTEGER ::   iyear, imonth, iday, isecs
85      INTEGER, DIMENSION(jpbtime) ::   istept, istepu, istepv   ! time arrays from data files
86      REAL(wp) ::   dayfrac, zxy, zoffsett
87      REAL(wp) ::   zoffsetu, zoffsetv
88      REAL(wp) ::   dayjul0, zdayjulini
89      REAL(wp), DIMENSION(jpbtime)      ::   zstepr             ! REAL time array from data files
90      REAL(wp), DIMENSION(jpbdta,1,jpk) ::   zdta               ! temporary array for data fields
91      !!---------------------------------------------------------------------------
92
93      IF( ln_bdy_dyn_frs .OR. ln_bdy_tra_frs ) THEN  ! If these are both false then this routine
94                                                     ! does nothing.
95
96      ! -------------------- !
97      !    Initialization    !
98      ! -------------------- !
99
100      lect   = .false.           ! If true, read a time record
101
102      ! Some time variables for monthly climatological forcing:
103      ! *******************************************************
104 !!gm  here  use directely daymod variables
105 
106      iman = INT( raamo )      ! Number of months in a year
107
108      i15 = INT( 2*REAL( nday, wp ) / ( REAL( nmonth_len(nmonth), wp ) + 0.5 ) )
109      ! i15=0 if the current day is in the first half of the month, else i15=1
110
111      imois = nmonth + i15 - 1            ! imois is the first month record
112      IF( imois == 0 )   imois = iman
113
114      ! Time variable for non-climatological forcing:
115      ! *********************************************
116      itimer = (kt-nit000+1)*rdt      ! current time in seconds for interpolation
117
118
119      !                                                !-------------------!
120      IF( kt == nit000 ) THEN                          !  First call only  !
121         !                                             !-------------------!
122         istep(:) = 0
123         nbdy_b    = 0
124         nbdy_a    = 0
125
126         ! Get time information from bdy data file
127         ! ***************************************
128
129         IF(lwp) WRITE(numout,*)
130         IF(lwp) WRITE(numout,*)    'bdy_dta : Initialize unstructured boundary data'
131         IF(lwp) WRITE(numout,*)    '~~~~~~~' 
132
133         IF     ( nbdy_dta == 0 ) THEN
134            !
135            IF(lwp) WRITE(numout,*) '          Bdy data are taken from initial conditions'
136            !
137         ELSEIF (nbdy_dta == 1) THEN
138            !
139            IF(lwp) WRITE(numout,*) '          Bdy data are read in netcdf files'
140            !
141            dayfrac = adatrj  - REAL( itimer, wp ) / 86400.   ! day fraction at time step kt-1
142            dayfrac = dayfrac - INT ( dayfrac )               !
143            totime  = ( nitend - nit000 + 1 ) * rdt           ! Total time of the run to verify that all the
144            !                                                 ! necessary time dumps in file are included
145            !
146            clfile(1) = filbdy_data_T
147            clfile(2) = filbdy_data_U
148            clfile(3) = filbdy_data_V
149            !                                                 
150            ! how many files are we to read in?
151            igrd_start = 1
152            igrd_end   = 3
153            IF(.NOT. ln_bdy_tra_frs .AND. .NOT. ln_bdy_ice_frs) THEN
154               ! No T-grid file.
155               igrd_start = 2
156            ELSEIF ( .NOT. ln_bdy_dyn_frs ) THEN
157               ! No U-grid or V-grid file.
158               igrd_end   = 1         
159            ENDIF
160
161            DO igrd = igrd_start, igrd_end                     !  loop over T, U & V grid  !
162               !                                               !---------------------------!
163               CALL iom_open( clfile(igrd), inum )
164               CALL iom_gettime( inum, zstepr, kntime=ntimes_bdy, cdunits=clunits ) 
165
166               SELECT CASE( igrd )
167                  CASE (1) 
168                     numbdyt = inum
169                  CASE (2) 
170                     numbdyu = inum
171                  CASE (3) 
172                     numbdyv = inum
173               END SELECT
174
175               ! Calculate time offset
176               READ(clunits,7000) iyear0, imonth0, iday0, ihours0, iminutes0, isec0
177               ! Convert time origin in file to julian days
178               isec0 = isec0 + ihours0*60.*60. + iminutes0*60.
179               CALL ymds2ju(iyear0, imonth0, iday0, REAL(isec0, wp), dayjul0)
180               ! Compute model initialization time
181               iyear  = ndastp / 10000
182               imonth = ( ndastp - iyear * 10000 ) / 100
183               iday   = ndastp - iyear * 10000 - imonth * 100
184               isecs  = dayfrac * 86400
185               CALL ymds2ju(iyear, imonth, iday, REAL(isecs, wp) , zdayjulini)
186               ! offset from initialization date:
187               zoffset = (dayjul0-zdayjulini)*86400
188               !
1897000           FORMAT('seconds since ', I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
190
191               !! TO BE DONE... Check consistency between calendar from file
192               !! (available optionally from iom_gettime) and calendar in model
193               !! when calendar in model available outside of IOIPSL.
194
195               IF(lwp) WRITE(numout,*) 'number of times: ',ntimes_bdy
196               IF(lwp) WRITE(numout,*) 'offset: ',zoffset
197               IF(lwp) WRITE(numout,*) 'totime: ',totime
198               IF(lwp) WRITE(numout,*) 'zstepr: ',zstepr
199
200               ! Check that there are not too many times in the file.
201               IF( ntimes_bdy > jpbtime ) THEN
202                  WRITE(ctmp1,*) 'Check file: ', clfile(igrd), 'jpbtime= ', jpbtime, ' ntimes_bdy= ', ntimes_bdy
203                  CALL ctl_stop( 'Number of time dumps in files exceed jpbtime parameter', ctmp1 )
204               ENDIF
205
206               ! Check that time array increases:
207       
208               it = 1
209               DO WHILE( zstepr(it+1) > zstepr(it) .AND. it /= ntimes_bdy - 1 )
210                 it = it + 1
211               END DO
212
213               IF( it.NE.ntimes_bdy-1 .AND. ntimes_bdy > 1 ) THEN
214                     WRITE(ctmp1,*) 'Check file: ', clfile(igrd)
215                     CALL ctl_stop( 'Time array in unstructured boundary data files',   &
216                        &           'does not continuously increase.'               , ctmp1 )
217               ENDIF
218               !
219               ! Check that times in file span model run time:
220               IF( zstepr(1) + zoffset > 0 ) THEN
221                     WRITE(ctmp1,*) 'Check file: ', clfile(igrd)
222                     CALL ctl_stop( 'First time dump in bdy file is after model initial time', ctmp1 )
223               END IF
224               IF( zstepr(ntimes_bdy) + zoffset < totime ) THEN
225                     WRITE(ctmp1,*) 'Check file: ', clfile(igrd)
226                     CALL ctl_stop( 'Last time dump in bdy file is before model final time', ctmp1 )
227               END IF
228               !
229               IF    ( igrd == 1 ) THEN
230                 ntimes_bdyt = ntimes_bdy
231                 zoffsett = zoffset
232                 istept(:) = INT( zstepr(:) + zoffset )
233               ELSEIF(igrd == 2 ) THEN
234                 ntimes_bdyu = ntimes_bdy
235                 zoffsetu = zoffset
236                 istepu(:) = INT( zstepr(:) + zoffset )
237               ELSEIF(igrd == 3 ) THEN
238                 ntimes_bdyv = ntimes_bdy
239                 zoffsetv = zoffset
240                 istepv(:) = INT( zstepr(:) + zoffset )
241               ENDIF
242               !
243            END DO                                         ! end loop over T, U & V grid
244
245            IF (igrd_start == 1 .and. igrd_end == 3) THEN
246               ! Only test differences if we are reading in 3 files
247               ! Verify time consistency between files 
248               IF( ntimes_bdyu /= ntimes_bdyt .OR. ntimes_bdyv /= ntimes_bdyt ) THEN
249                  CALL ctl_stop( 'Bdy data files must have the same number of time dumps',   &
250                  &           'Multiple time frequencies not implemented yet'  )
251               ENDIF
252               ntimes_bdy = ntimes_bdyt
253               !
254               IF( zoffsetu /= zoffsett .OR. zoffsetv /= zoffsett ) THEN
255                  CALL ctl_stop( 'Bdy data files must have the same time origin',   &
256                  &           'Multiple time frequencies not implemented yet' )
257               ENDIF
258               zoffset = zoffsett
259            ENDIF
260
261            IF( igrd_start == 1 ) THEN
262               istep(:) = istept(:)
263            ELSE
264               istep(:) = istepu(:)
265            ENDIF
266
267            ! Check number of time dumps:             
268            IF( ntimes_bdy == 1 .AND. .NOT. ln_bdy_clim ) THEN
269              CALL ctl_stop( 'There is only one time dump in data files',   &
270                 &           'Choose ln_bdy_clim=.true. in namelist for constant bdy forcing.' )
271            ENDIF
272
273            IF( ln_bdy_clim ) THEN
274              IF( ntimes_bdy /= 1 .AND. ntimes_bdy /= 12 ) THEN
275                 CALL ctl_stop( 'For climatological boundary forcing (ln_bdy_clim=.true.),',   &
276                    &           'bdy data files must contain 1 or 12 time dumps.' )
277              ELSEIF( ntimes_bdy ==  1 ) THEN
278                IF(lwp) WRITE(numout,*)
279                IF(lwp) WRITE(numout,*) 'We assume constant boundary forcing from bdy data files'
280              ELSEIF( ntimes_bdy == 12 ) THEN
281                IF(lwp) WRITE(numout,*)
282                IF(lwp) WRITE(numout,*) 'We assume monthly (and cyclic) boundary forcing from bdy data files'
283              ENDIF
284            ENDIF
285
286            ! Find index of first record to read (before first model time).
287            it = 1
288            DO WHILE( istep(it+1) <= 0 .AND. it <= ntimes_bdy - 1 )
289              it = it + 1
290            END DO
291            nbdy_b = it
292            !
293            WRITE(numout,*) 'Time offset is ',zoffset
294            WRITE(numout,*) 'First record to read is ',nbdy_b
295
296         ENDIF ! endif (nbdy_dta == 1)
297
298
299         ! 1.2  Read first record in file if necessary (ie if nbdy_dta == 1)
300         ! *****************************************************************
301
302         IF( nbdy_dta == 0) THEN      ! boundary data arrays are filled with initial conditions
303            !
304            IF (ln_bdy_tra_frs) THEN
305              igrd = 1            ! T-points data
306              DO ib = 1, nblen(igrd)
307                ii = nbi(ib,igrd)
308                ij = nbj(ib,igrd)
309                DO ik = 1, jpkm1
310                  tbdy(ib,ik) = tn(ii, ij, ik)
311                  sbdy(ib,ik) = sn(ii, ij, ik)
312                ENDDO
313              END DO
314            ENDIF
315
316            IF(ln_bdy_dyn_frs) THEN
317              igrd = 2            ! U-points data
318              DO ib = 1, nblen(igrd)
319                ii = nbi(ib,igrd)
320                ij = nbj(ib,igrd)
321                DO ik = 1, jpkm1
322                  ubdy(ib,ik) = un(ii, ij, ik)
323                ENDDO
324              END DO
325
326              igrd = 3            ! V-points data
327              DO ib = 1, nblen(igrd)           
328                ii = nbi(ib,igrd)
329                ij = nbj(ib,igrd)
330                DO ik = 1, jpkm1
331                  vbdy(ib,ik) = vn(ii, ij, ik)
332                ENDDO
333              END DO
334            ENDIF
335            !
336         ELSEIF( nbdy_dta == 1 ) THEN    ! Set first record in the climatological case:   
337            !
338            IF( ln_bdy_clim .AND. ntimes_bdy == 1 ) THEN
339               nbdy_a = 1
340            ELSEIF( ln_bdy_clim .AND. ntimes_bdy == iman ) THEN
341               nbdy_b = 0
342               nbdy_a = imois
343            ELSE
344               nbdy_a = nbdy_b
345            ENDIF
346   
347            ! Read first record:
348            ipj  = 1
349            ipk  = jpk
350            igrd = 1
351            ipi  = nblendta(igrd)
352
353            IF(ln_bdy_tra_frs) THEN
354               igrd = 1                                           ! Temperature
355               IF( nblendta(igrd) <=  0 ) THEN
356                  idvar = iom_varid( numbdyt, 'votemper' )
357                  nblendta(igrd) = iom_file(numbdyt)%dimsz(1,idvar)
358               ENDIF
359               WRITE(numout,*) 'Dim size for votemper is ', nblendta(igrd)
360               ipi = nblendta(igrd)
361               CALL iom_get ( numbdyt, jpdom_unknown, 'votemper', zdta(1:ipi,1:ipj,1:ipk), nbdy_a )
362
363               DO ib = 1, nblen(igrd)
364                  DO ik = 1, jpkm1
365                     tbdydta(ib,ik,2) =  zdta(nbmap(ib,igrd),1,ik)
366                  END DO
367               END DO
368               !
369               igrd = 1                                           ! salinity
370               IF( nblendta(igrd) .le. 0 ) THEN
371                  idvar = iom_varid( numbdyt, 'vosaline' )
372                  nblendta(igrd) = iom_file(numbdyt)%dimsz(1,idvar)
373               ENDIF
374               WRITE(numout,*) 'Dim size for vosaline is ', nblendta(igrd)
375               ipi = nblendta(igrd)
376               CALL iom_get ( numbdyt, jpdom_unknown, 'vosaline', zdta(1:ipi,1:ipj,1:ipk), nbdy_a )
377
378               DO ib = 1, nblen(igrd)
379                  DO ik = 1, jpkm1
380                     sbdydta(ib,ik,2) =  zdta(nbmap(ib,igrd),1,ik)
381                  END DO
382               END DO
383            ENDIF  ! ln_bdy_tra_frs
384 
385            IF(ln_bdy_dyn_frs) THEN
386
387               igrd = 2                                           ! u-velocity
388               IF ( nblendta(igrd) .le. 0 ) THEN
389                 idvar = iom_varid( numbdyu,'vozocrtx' )
390                 nblendta(igrd) = iom_file(numbdyu)%dimsz(1,idvar)
391               ENDIF
392               WRITE(numout,*) 'Dim size for vozocrtx is ', nblendta(igrd)
393               ipi = nblendta(igrd)
394               CALL iom_get ( numbdyu, jpdom_unknown,'vozocrtx',zdta(1:ipi,1:ipj,1:ipk),nbdy_a )
395               DO ib = 1, nblen(igrd)
396                  DO ik = 1, jpkm1
397                     ubdydta(ib,ik,2) =  zdta(nbmap(ib,igrd),1,ik)
398                  END DO
399               END DO
400               !
401               igrd = 3                                           ! v-velocity
402               IF ( nblendta(igrd) .le. 0 ) THEN
403                 idvar = iom_varid( numbdyv,'vomecrty' )
404                 nblendta(igrd) = iom_file(numbdyv)%dimsz(1,idvar)
405               ENDIF
406               WRITE(numout,*) 'Dim size for vomecrty is ', nblendta(igrd)
407               ipi = nblendta(igrd)
408               CALL iom_get ( numbdyv, jpdom_unknown,'vomecrty',zdta(1:ipi,1:ipj,1:ipk),nbdy_a )
409               DO ib = 1, nblen(igrd)
410                  DO ik = 1, jpkm1
411                     vbdydta(ib,ik,2) =  zdta(nbmap(ib,igrd),1,ik)
412                  END DO
413               END DO
414            ENDIF ! ln_bdy_dyn_frs
415
416
417            IF ((.NOT.ln_bdy_clim) .AND. (istep(1) > 0)) THEN
418               ! First data time is after start of run
419               ! Put first value in both time levels
420               nbdy_b = nbdy_a
421               IF(ln_bdy_tra_frs) THEN
422                 tbdydta(:,:,1) = tbdydta(:,:,2)
423                 sbdydta(:,:,1) = sbdydta(:,:,2)
424               ENDIF
425               IF(ln_bdy_dyn_frs) THEN
426                 ubdydta(:,:,1) = ubdydta(:,:,2)
427                 vbdydta(:,:,1) = vbdydta(:,:,2)
428               ENDIF
429            END IF
430
431         END IF ! nbdy_dta == 0/1
432 
433         ! In the case of constant boundary forcing fill bdy arrays once for all
434         IF ((ln_bdy_clim).AND.(ntimes_bdy==1)) THEN
435            IF(ln_bdy_tra_frs) THEN
436              tbdy  (:,:) = tbdydta  (:,:,2)
437              sbdy  (:,:) = sbdydta  (:,:,2)
438            ENDIF
439            IF(ln_bdy_dyn_frs) THEN
440              ubdy  (:,:) = ubdydta  (:,:,2)
441              vbdy  (:,:) = vbdydta  (:,:,2)
442            ENDIF
443
444            IF(ln_bdy_tra_frs .or. ln_bdy_ice_frs) CALL iom_close( numbdyt )
445            IF(ln_bdy_dyn_frs) CALL iom_close( numbdyu )
446            IF(ln_bdy_dyn_frs) CALL iom_close( numbdyv )
447         END IF
448
449      ENDIF                                            ! End if nit000
450
451
452      !                                                !---------------------!
453      !                                                !  at each time step  !
454      !                                                !---------------------!
455
456      IF( nbdy_dta == 1 .AND. ntimes_bdy > 1 ) THEN 
457         !
458         ! Read one more record if necessary
459         !**********************************
460
461        IF( ln_bdy_clim .AND. imois /= nbdy_b ) THEN      ! remember that nbdy_b=0 for kt=nit000
462           nbdy_b = imois
463           nbdy_a = imois + 1
464           nbdy_b = MOD( nbdy_b, iman )   ;   IF( nbdy_b == 0 ) nbdy_b = iman
465           nbdy_a = MOD( nbdy_a, iman )   ;   IF( nbdy_a == 0 ) nbdy_a = iman
466           lect=.true.
467        ELSEIF( .NOT.ln_bdy_clim .AND. itimer >= istep(nbdy_a) ) THEN
468
469           IF ( nbdy_a < ntimes_bdy ) THEN
470              nbdy_b = nbdy_a
471              nbdy_a = nbdy_a + 1
472              lect  =.true.
473           ELSE
474              ! We have reached the end of the file
475              ! put the last data time into both time levels
476              nbdy_b = nbdy_a
477              IF(ln_bdy_tra_frs) THEN
478                tbdydta(:,:,1) =  tbdydta(:,:,2)
479                sbdydta(:,:,1) =  sbdydta(:,:,2)
480              ENDIF
481              IF(ln_bdy_dyn_frs) THEN
482                ubdydta(:,:,1) =  ubdydta(:,:,2)
483                vbdydta(:,:,1) =  vbdydta(:,:,2)
484              ENDIF
485            END IF ! nbdy_a < ntimes_bdy
486
487        END IF
488         
489        IF( lect ) THEN
490           ! Swap arrays
491           IF(ln_bdy_tra_frs) THEN
492             tbdydta(:,:,1) =  tbdydta(:,:,2)
493             sbdydta(:,:,1) =  sbdydta(:,:,2)
494           ENDIF
495           IF(ln_bdy_dyn_frs) THEN
496             ubdydta(:,:,1) =  ubdydta(:,:,2)
497             vbdydta(:,:,1) =  vbdydta(:,:,2)
498           ENDIF
499 
500           ! read another set
501           ipj  = 1
502           ipk  = jpk
503
504           IF(ln_bdy_tra_frs) THEN
505              !
506              igrd = 1                                   ! temperature
507              ipi  = nblendta(igrd)
508              CALL iom_get ( numbdyt, jpdom_unknown, 'votemper', zdta(1:ipi,1:ipj,1:ipk), nbdy_a )
509              DO ib = 1, nblen(igrd)
510                 DO ik = 1, jpkm1
511                    tbdydta(ib,ik,2) = zdta(nbmap(ib,igrd),1,ik)
512                 END DO
513              END DO
514              !
515              igrd = 1                                   ! salinity
516              ipi  = nblendta(igrd)
517              CALL iom_get ( numbdyt, jpdom_unknown, 'vosaline', zdta(1:ipi,1:ipj,1:ipk), nbdy_a )
518              DO ib = 1, nblen(igrd)
519                 DO ik = 1, jpkm1
520                    sbdydta(ib,ik,2) = zdta(nbmap(ib,igrd),1,ik)
521                 END DO
522              END DO
523           ENDIF ! ln_bdy_tra_frs
524
525           IF(ln_bdy_dyn_frs) THEN
526              !
527              igrd = 2                                   ! u-velocity
528              ipi  = nblendta(igrd)
529              CALL iom_get ( numbdyu, jpdom_unknown,'vozocrtx',zdta(1:ipi,1:ipj,1:ipk),nbdy_a )
530              DO ib = 1, nblen(igrd)
531                DO ik = 1, jpkm1
532                  ubdydta(ib,ik,2) =  zdta(nbmap(ib,igrd),1,ik)
533                END DO
534              END DO
535              !
536              igrd = 3                                   ! v-velocity
537              ipi  = nblendta(igrd)
538              CALL iom_get ( numbdyv, jpdom_unknown,'vomecrty',zdta(1:ipi,1:ipj,1:ipk),nbdy_a )
539              DO ib = 1, nblen(igrd)
540                 DO ik = 1, jpkm1
541                    vbdydta(ib,ik,2) =  zdta(nbmap(ib,igrd),1,ik)
542                 END DO
543              END DO
544           ENDIF ! ln_bdy_dyn_frs
545
546           !
547           IF(lwp) WRITE(numout,*) 'bdy_dta : first record file used nbdy_b ',nbdy_b
548           IF(lwp) WRITE(numout,*) '~~~~~~~~  last  record file used nbdy_a ',nbdy_a
549           IF (.NOT.ln_bdy_clim) THEN
550              IF(lwp) WRITE(numout,*) 'first  record time (s): ', istep(nbdy_b)
551              IF(lwp) WRITE(numout,*) 'model time (s)        : ', itimer
552              IF(lwp) WRITE(numout,*) 'second record time (s): ', istep(nbdy_a)
553           ENDIF
554           !
555       ENDIF ! end lect=.true.
556
557
558       ! Interpolate linearly
559       ! ********************
560       !
561       IF( ln_bdy_clim ) THEN   ;   zxy = REAL( nday                  , wp ) / REAL( nmonth_len(nbdy_b), wp ) + 0.5 - i15
562       ELSE                     ;   zxy = REAL( istep(nbdy_b) - itimer, wp ) / REAL( istep(nbdy_b) - istep(nbdy_a), wp )
563       END IF
564
565          IF(ln_bdy_tra_frs) THEN
566             igrd = 1                                   ! temperature & salinity
567             DO ib = 1, nblen(igrd)
568               DO ik = 1, jpkm1
569                 tbdy(ib,ik) = zxy * tbdydta(ib,ik,2) + (1.-zxy) * tbdydta(ib,ik,1)
570                 sbdy(ib,ik) = zxy * sbdydta(ib,ik,2) + (1.-zxy) * sbdydta(ib,ik,1)
571               END DO
572             END DO
573          ENDIF
574
575          IF(ln_bdy_dyn_frs) THEN
576             igrd = 2                                   ! u-velocity
577             DO ib = 1, nblen(igrd)
578               DO ik = 1, jpkm1
579                 ubdy(ib,ik) = zxy * ubdydta(ib,ik,2) + (1.-zxy) * ubdydta(ib,ik,1)   
580               END DO
581             END DO
582             !
583             igrd = 3                                   ! v-velocity
584             DO ib = 1, nblen(igrd)
585               DO ik = 1, jpkm1
586                 vbdy(ib,ik) = zxy * vbdydta(ib,ik,2) + (1.-zxy) * vbdydta(ib,ik,1)   
587               END DO
588             END DO
589          ENDIF
590
591      END IF                       !end if ((nbdy_dta==1).AND.(ntimes_bdy>1))
592   
593
594      !                                                !---------------------!
595      !                                                !     last call       !
596      !                                                !---------------------!
597      IF( kt == nitend ) THEN
598          IF(ln_bdy_tra_frs .or. ln_bdy_ice_frs) CALL iom_close( numbdyt )              ! Closing of the 3 files
599          IF(ln_bdy_dyn_frs) CALL iom_close( numbdyu )
600          IF(ln_bdy_dyn_frs) CALL iom_close( numbdyv )
601      ENDIF
602      !
603      ENDIF ! ln_bdy_dyn_frs .OR. ln_bdy_tra_frs
604
605   END SUBROUTINE bdy_dta
606
607
608   SUBROUTINE bdy_dta_bt( kt, jit )
609      !!---------------------------------------------------------------------------
610      !!                      ***  SUBROUTINE bdy_dta_bt  ***
611      !!                   
612      !! ** Purpose :   Read unstructured boundary data for Flather condition
613      !!
614      !! ** Method  :  At the first timestep, read in boundary data for two
615      !!               times from the file and time-interpolate. At other
616      !!               timesteps, check to see if we need another time from
617      !!               the file. If so read it in. Time interpolate.
618      !!---------------------------------------------------------------------------
619!!gm DOCTOR names :   argument integer :  start with "k"
620      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index
621      INTEGER, INTENT( in ) ::   jit         ! barotropic time step index
622      !                                      ! (for timesplitting option, otherwise zero)
623      !!
624      LOGICAL ::   lect                      ! flag for reading
625      INTEGER ::   it, ib, igrd              ! dummy loop indices
626      INTEGER ::   idvar                     ! netcdf var ID
627      INTEGER ::   iman, i15, imois          ! Time variables for monthly clim forcing
628      INTEGER ::   ntimes_bdyt, ntimes_bdyu, ntimes_bdyv
629      INTEGER ::   itimer, totime
630      INTEGER ::   ipi, ipj, ipk, inum       ! temporary integers (NetCDF read)
631      INTEGER ::   iyear0, imonth0, iday0
632      INTEGER ::   ihours0, iminutes0, isec0
633      INTEGER ::   iyear, imonth, iday, isecs
634      INTEGER, DIMENSION(jpbtime) ::   istept, istepu, istepv   ! time arrays from data files
635      REAL(wp) ::   dayfrac, zxy, zoffsett
636      REAL(wp) ::   zoffsetu, zoffsetv
637      REAL(wp) ::   dayjul0, zdayjulini
638      REAL(wp) ::   zinterval_s, zinterval_e                    ! First and last interval in time axis
639      REAL(wp), DIMENSION(jpbtime)      ::   zstepr             ! REAL time array from data files
640      REAL(wp), DIMENSION(jpbdta,1)     ::   zdta               ! temporary array for data fields
641      CHARACTER(LEN=80), DIMENSION(3)   ::   clfile
642      CHARACTER(LEN=70 )                ::   clunits            ! units attribute of time coordinate
643      !!---------------------------------------------------------------------------
644
645!!gm   add here the same style as in bdy_dta
646!!gm      clearly bdy_dta_bt and bdy_dta  can be combined...   
647!!gm      too many things duplicated in the read of data...   simplification can be done
648
649      ! -------------------- !
650      !    Initialization    !
651      ! -------------------- !
652
653      lect   = .false.           ! If true, read a time record
654
655      ! Some time variables for monthly climatological forcing:
656      ! *******************************************************
657 !!gm  here  use directely daymod variables
658 
659      iman  = INT( raamo ) ! Number of months in a year
660
661      i15 = INT( 2*REAL( nday, wp ) / ( REAL( nmonth_len(nmonth), wp ) + 0.5 ) )
662      ! i15=0 if the current day is in the first half of the month, else i15=1
663
664      imois = nmonth + i15 - 1            ! imois is the first month record
665      IF( imois == 0 ) imois = iman
666
667      ! Time variable for non-climatological forcing:
668      ! *********************************************
669
670      itimer = ((kt-1)-nit000+1)*rdt                      ! current time in seconds for interpolation
671      itimer = itimer + jit*rdt/REAL(nn_baro,wp)      ! in non-climatological case
672
673      IF ( ln_bdy_tides ) THEN
674
675         ! -------------------------------------!
676         ! Update BDY fields with tidal forcing !
677         ! -------------------------------------! 
678
679         CALL tide_update( kt, jit ) 
680 
681      ENDIF
682
683      IF ( ln_bdy_dyn_fla ) THEN
684
685         ! -------------------------------------!
686         ! Update BDY fields with model data    !
687         ! -------------------------------------! 
688
689      !                                                !-------------------!
690      IF( kt == nit000 ) THEN                          !  First call only  !
691         !                                             !-------------------!
692         istep_bt(:) = 0
693         nbdy_b_bt    = 0
694         nbdy_a_bt    = 0
695
696         ! Get time information from bdy data file
697         ! ***************************************
698
699        IF(lwp) WRITE(numout,*)
700        IF(lwp) WRITE(numout,*)    'bdy_dta_bt :Initialize unstructured boundary data for barotropic variables.'
701        IF(lwp) WRITE(numout,*)    '~~~~~~~' 
702
703        IF( nbdy_dta == 0 ) THEN
704          IF(lwp) WRITE(numout,*)  'Bdy data are taken from initial conditions'
705
706        ELSEIF (nbdy_dta == 1) THEN
707          IF(lwp) WRITE(numout,*)  'Bdy data are read in netcdf files'
708
709          dayfrac = adatrj  - REAL(itimer,wp)/86400. ! day fraction at time step kt-1
710          dayfrac = dayfrac - INT (dayfrac)          !
711          totime = (nitend-nit000+1)*rdt             ! Total time of the run to verify that all the
712                                                     ! necessary time dumps in file are included
713
714          clfile(1) = filbdy_data_bt_T
715          clfile(2) = filbdy_data_bt_U
716          clfile(3) = filbdy_data_bt_V
717
718          DO igrd = 1,3
719
720            CALL iom_open( clfile(igrd), inum )
721            CALL iom_gettime( inum, zstepr, kntime=ntimes_bdy, cdunits=clunits ) 
722
723            SELECT CASE( igrd )
724               CASE (1) 
725                  numbdyt = inum
726               CASE (2) 
727                  numbdyu = inum
728               CASE (3) 
729                  numbdyv = inum
730            END SELECT
731
732            ! Calculate time offset
733            READ(clunits,7000) iyear0, imonth0, iday0, ihours0, iminutes0, isec0
734            ! Convert time origin in file to julian days
735            isec0 = isec0 + ihours0*60.*60. + iminutes0*60.
736            CALL ymds2ju(iyear0, imonth0, iday0, REAL(isec0, wp), dayjul0)
737            ! Compute model initialization time
738            iyear  = ndastp / 10000
739            imonth = ( ndastp - iyear * 10000 ) / 100
740            iday   = ndastp - iyear * 10000 - imonth * 100
741            isecs  = dayfrac * 86400
742            CALL ymds2ju(iyear, imonth, iday, REAL(isecs, wp) , zdayjulini)
743            ! zoffset from initialization date:
744            zoffset = (dayjul0-zdayjulini)*86400
745            !
746
7477000 FORMAT('seconds since ', I4.4,'-',I2.2,'-',I2.2,' ',I2.2,':',I2.2,':',I2.2)
748
749            !! TO BE DONE... Check consistency between calendar from file
750            !! (available optionally from iom_gettime) and calendar in model
751            !! when calendar in model available outside of IOIPSL.
752
753            ! Check that there are not too many times in the file.
754            IF (ntimes_bdy_bt > jpbtime) CALL ctl_stop( &
755                 'Number of time dumps in bdy file exceed jpbtime parameter', &
756                 'Check file:' // TRIM(clfile(igrd))  )
757
758            ! Check that time array increases (or interp will fail):
759            DO it = 2, ntimes_bdy
760               IF ( zstepr(it-1) >= zstepr(it) ) THEN
761                  CALL ctl_stop('Time array in unstructured boundary data file', &
762                       'does not continuously increase.',               &
763                       'Check file:' // TRIM(clfile(igrd))  )
764                  EXIT
765               END IF
766            END DO
767
768            IF ( .NOT. ln_bdy_clim ) THEN
769               ! Check that times in file span model run time:
770
771               ! Note: the fields may be time means, so we allow nit000 to be before
772               ! first time in the file, provided that it falls inside the meaning
773               ! period of the first field.  Until we can get the meaning period
774               ! from the file, use the interval between fields as a proxy.
775               ! If nit000 is before the first time, use the value at first time
776               ! instead of extrapolating.  This is done by putting time 1 into
777               ! both time levels.
778               ! The same applies to the last time level: see setting of lect below.
779
780               IF ( ntimes_bdy == 1 ) CALL ctl_stop( &
781                    'There is only one time dump in data files', &
782                    'Set ln_bdy_clim=.true. in namelist for constant bdy forcing.' )
783
784               zinterval_s = zstepr(2) - zstepr(1)
785               zinterval_e = zstepr(ntimes_bdy) - zstepr(ntimes_bdy-1)
786
787               IF ( zstepr(1) - zinterval_s / 2.0 > 0 ) THEN             
788                  IF(lwp) WRITE(numout,*) 'First bdy time relative to nit000:', zstepr(1)
789                  IF(lwp) WRITE(numout,*) 'Interval between first two times: ', zinterval_s
790                  CALL ctl_stop( 'First data time is after start of run', & 
791                       'by more than half a meaning period', &
792                       'Check file: ' // TRIM(clfile(igrd)) )
793               END IF
794
795               IF ( zstepr(ntimes_bdy) + zinterval_e / 2.0 < totime ) THEN
796                  IF(lwp) WRITE(numout,*) 'Last bdy time relative to nit000:', zstepr(ntimes_bdy)
797                  IF(lwp) WRITE(numout,*) 'Interval between last two times: ', zinterval_e
798                  CALL ctl_stop( 'Last data time is before end of run', & 
799                       'by more than half a meaning period', &
800                       'Check file: ' // TRIM(clfile(igrd))  )
801               END IF
802
803            END IF ! .NOT. ln_bdy_clim
804
805            IF ( igrd .EQ. 1) THEN
806              ntimes_bdyt = ntimes_bdy_bt
807              zoffsett = zoffset
808              istept(:) = INT( zstepr(:) + zoffset )
809            ELSE IF (igrd .EQ. 2) THEN
810              ntimes_bdyu = ntimes_bdy_bt
811              zoffsetu = zoffset
812              istepu(:) = INT( zstepr(:) + zoffset )
813            ELSE IF (igrd .EQ. 3) THEN
814              ntimes_bdyv = ntimes_bdy_bt
815              zoffsetv = zoffset
816              istepv(:) = INT( zstepr(:) + zoffset )
817            ENDIF
818
819          ENDDO
820
821      ! Verify time consistency between files 
822
823          IF ( ntimes_bdyu /= ntimes_bdyt .OR. ntimes_bdyv /= ntimes_bdyt ) THEN
824             CALL ctl_stop( &
825             'Time axis lengths differ between bdy data files', &
826             'Multiple time frequencies not implemented yet' )
827          ELSE
828            ntimes_bdy_bt = ntimes_bdyt
829          ENDIF
830
831          IF (zoffsetu.NE.zoffsett .OR. zoffsetv.NE.zoffsett) THEN
832            CALL ctl_stop( & 
833            'Bdy data files must have the same time origin', &
834            'Multiple time frequencies not implemented yet'  )
835          ENDIF
836          zoffset = zoffsett
837
838      !! Check that times are the same in the three files... HERE.
839          istep_bt(:) = istept(:)
840
841      ! Check number of time dumps:             
842          IF (ln_bdy_clim) THEN
843            SELECT CASE ( ntimes_bdy_bt )
844            CASE( 1 )
845              IF(lwp) WRITE(numout,*)
846              IF(lwp) WRITE(numout,*) 'We assume constant boundary forcing from bdy data files'
847              IF(lwp) WRITE(numout,*)             
848            CASE( 12 )
849              IF(lwp) WRITE(numout,*)
850              IF(lwp) WRITE(numout,*) 'We assume monthly (and cyclic) boundary forcing from bdy data files'
851              IF(lwp) WRITE(numout,*) 
852            CASE DEFAULT
853              CALL ctl_stop( &
854                'For climatological boundary forcing (ln_bdy_clim=.true.),',&
855                'bdy data files must contain 1 or 12 time dumps.' )
856            END SELECT
857          ENDIF
858
859      ! Find index of first record to read (before first model time).
860
861          it=1
862          DO WHILE ( ((istep_bt(it+1)) <= 0 ).AND.(it.LE.(ntimes_bdy_bt-1)))
863            it=it+1
864          END DO
865          nbdy_b_bt = it
866
867          WRITE(numout,*) 'Time offset is ',zoffset
868          WRITE(numout,*) 'First record to read is ',nbdy_b_bt
869
870        ENDIF ! endif (nbdy_dta == 1)
871
872      ! 1.2  Read first record in file if necessary (ie if nbdy_dta == 1)
873      ! *****************************************************************
874
875        IF ( nbdy_dta == 0) THEN
876          ! boundary data arrays are filled with initial conditions
877          igrd = 2            ! U-points data
878          DO ib = 1, nblen(igrd)             
879            ubtbdy(ib) = un(nbi(ib,igrd), nbj(ib,igrd), 1)
880          END DO
881
882          igrd = 3            ! V-points data
883          DO ib = 1, nblen(igrd)             
884            vbtbdy(ib) = vn(nbi(ib,igrd), nbj(ib,igrd), 1)
885          END DO
886
887          igrd = 1            ! T-points data
888          DO ib = 1, nblen(igrd)             
889            sshbdy(ib) = sshn(nbi(ib,igrd), nbj(ib,igrd))
890          END DO
891
892        ELSEIF (nbdy_dta == 1) THEN
893 
894        ! Set first record in the climatological case:   
895          IF ((ln_bdy_clim).AND.(ntimes_bdy_bt==1)) THEN
896            nbdy_a_bt = 1
897          ELSEIF ((ln_bdy_clim).AND.(ntimes_bdy_bt==iman)) THEN
898            nbdy_b_bt = 0
899            nbdy_a_bt = imois
900          ELSE
901            nbdy_a_bt = nbdy_b_bt
902          END IF
903 
904         ! Open Netcdf files:
905
906          CALL iom_open ( filbdy_data_bt_T, numbdyt_bt )
907          CALL iom_open ( filbdy_data_bt_U, numbdyu_bt )
908          CALL iom_open ( filbdy_data_bt_V, numbdyv_bt )
909
910         ! Read first record:
911          ipj=1
912          igrd=1
913          ipi=nblendta(igrd)
914
915          ! ssh
916          igrd=1
917          IF ( nblendta(igrd) .le. 0 ) THEN
918            idvar = iom_varid( numbdyt_bt,'sossheig' )
919            nblendta(igrd) = iom_file(numbdyt_bt)%dimsz(1,idvar)
920          ENDIF
921          WRITE(numout,*) 'Dim size for sossheig is ',nblendta(igrd)
922          ipi=nblendta(igrd)
923
924          CALL iom_get ( numbdyt_bt, jpdom_unknown,'sossheig',zdta(1:ipi,1:ipj),nbdy_a_bt )
925
926          DO ib=1, nblen(igrd)
927            sshbdydta(ib,2) =  zdta(nbmap(ib,igrd),1)
928          END DO
929 
930          ! u-velocity
931          igrd=2
932          IF ( nblendta(igrd) .le. 0 ) THEN
933            idvar = iom_varid( numbdyu_bt,'vobtcrtx' )
934            nblendta(igrd) = iom_file(numbdyu_bt)%dimsz(1,idvar)
935          ENDIF
936          WRITE(numout,*) 'Dim size for vobtcrtx is ',nblendta(igrd)
937          ipi=nblendta(igrd)
938
939          CALL iom_get ( numbdyu_bt, jpdom_unknown,'vobtcrtx',zdta(1:ipi,1:ipj),nbdy_a_bt )
940
941          DO ib=1, nblen(igrd)
942            ubtbdydta(ib,2) =  zdta(nbmap(ib,igrd),1)
943          END DO
944
945          ! v-velocity
946          igrd=3
947          IF ( nblendta(igrd) .le. 0 ) THEN
948            idvar = iom_varid( numbdyv_bt,'vobtcrty' )
949            nblendta(igrd) = iom_file(numbdyv_bt)%dimsz(1,idvar)
950          ENDIF
951          WRITE(numout,*) 'Dim size for vobtcrty is ',nblendta(igrd)
952          ipi=nblendta(igrd)
953
954          CALL iom_get ( numbdyv_bt, jpdom_unknown,'vobtcrty',zdta(1:ipi,1:ipj),nbdy_a_bt )
955
956          DO ib=1, nblen(igrd)
957            vbtbdydta(ib,2) =  zdta(nbmap(ib,igrd),1)
958          END DO
959
960        END IF
961 
962        ! In the case of constant boundary forcing fill bdy arrays once for all
963        IF ((ln_bdy_clim).AND.(ntimes_bdy_bt==1)) THEN
964
965          ubtbdy  (:) = ubtbdydta  (:,2)
966          vbtbdy  (:) = vbtbdydta  (:,2)
967          sshbdy  (:) = sshbdydta  (:,2)
968
969          CALL iom_close( numbdyt_bt )
970          CALL iom_close( numbdyu_bt )
971          CALL iom_close( numbdyv_bt )
972
973        END IF
974
975      ENDIF ! End if nit000
976
977      ! -------------------- !
978      ! 2. At each time step !
979      ! -------------------- !
980
981      IF ((nbdy_dta==1).AND.(ntimes_bdy_bt>1)) THEN 
982
983      ! 2.1 Read one more record if necessary
984      !**************************************
985
986        IF ( (ln_bdy_clim).AND.(imois/=nbdy_b_bt) ) THEN ! remember that nbdy_b_bt=0 for kt=nit000
987         nbdy_b_bt = imois
988         nbdy_a_bt = imois+1
989         nbdy_b_bt = MOD( nbdy_b_bt, iman )
990         IF( nbdy_b_bt == 0 ) nbdy_b_bt = iman
991         nbdy_a_bt = MOD( nbdy_a_bt, iman )
992         IF( nbdy_a_bt == 0 ) nbdy_a_bt = iman
993         lect=.true.
994
995        ELSEIF ((.NOT.ln_bdy_clim).AND.(itimer >= istep_bt(nbdy_a_bt))) THEN
996          nbdy_b_bt=nbdy_a_bt
997          nbdy_a_bt=nbdy_a_bt+1
998          lect=.true.
999        END IF
1000         
1001        IF (lect) THEN
1002
1003        ! Swap arrays
1004          sshbdydta(:,1) =  sshbdydta(:,2)
1005          ubtbdydta(:,1) =  ubtbdydta(:,2)
1006          vbtbdydta(:,1) =  vbtbdydta(:,2)
1007 
1008        ! read another set
1009
1010          ipj=1
1011          ipk=jpk
1012          igrd=1
1013          ipi=nblendta(igrd)
1014
1015         
1016          ! ssh
1017          igrd=1
1018          ipi=nblendta(igrd)
1019
1020          CALL iom_get ( numbdyt_bt, jpdom_unknown,'sossheig',zdta(1:ipi,1:ipj),nbdy_a_bt )
1021
1022          DO ib=1, nblen(igrd)
1023            sshbdydta(ib,2) =  zdta(nbmap(ib,igrd),1)
1024          END DO
1025
1026          ! u-velocity
1027          igrd=2
1028          ipi=nblendta(igrd)
1029
1030          CALL iom_get ( numbdyu_bt, jpdom_unknown,'vobtcrtx',zdta(1:ipi,1:ipj),nbdy_a_bt )
1031
1032          DO ib=1, nblen(igrd)
1033            ubtbdydta(ib,2) =  zdta(nbmap(ib,igrd),1)
1034          END DO
1035
1036          ! v-velocity
1037          igrd=3
1038          ipi=nblendta(igrd)
1039
1040          CALL iom_get ( numbdyv_bt, jpdom_unknown,'vobtcrty',zdta(1:ipi,1:ipj),nbdy_a_bt )
1041
1042          DO ib=1, nblen(igrd)
1043            vbtbdydta(ib,2) =  zdta(nbmap(ib,igrd),1)
1044          END DO
1045
1046
1047         IF(lwp) WRITE(numout,*) 'bdy_dta : first record file used nbdy_b_bt ',nbdy_b_bt
1048         IF(lwp) WRITE(numout,*) '~~~~~~~~  last  record file used nbdy_a_bt ',nbdy_a_bt
1049         IF (.NOT.ln_bdy_clim) THEN
1050           IF(lwp) WRITE(numout,*) 'first  record time (s): ', istep_bt(nbdy_b_bt)
1051           IF(lwp) WRITE(numout,*) 'model time (s)        : ', itimer
1052           IF(lwp) WRITE(numout,*) 'second record time (s): ', istep_bt(nbdy_a_bt)
1053         ENDIF
1054        END IF ! end lect=.true.
1055
1056
1057      ! 2.2   Interpolate linearly:
1058      ! ***************************
1059   
1060        IF (ln_bdy_clim) THEN
1061          zxy = REAL( nday, wp ) / REAL( nmonth_len(nbdy_b_bt), wp ) + 0.5 - i15
1062        ELSE         
1063          zxy = REAL(istep_bt(nbdy_b_bt)-itimer, wp) / REAL(istep_bt(nbdy_b_bt)-istep_bt(nbdy_a_bt), wp)
1064        END IF
1065
1066          igrd=1
1067          DO ib=1, nblen(igrd)
1068            sshbdy(ib) = zxy      * sshbdydta(ib,2) + &
1069                       (1.-zxy) * sshbdydta(ib,1)   
1070          END DO
1071
1072          igrd=2
1073          DO ib=1, nblen(igrd)
1074            ubtbdy(ib) = zxy      * ubtbdydta(ib,2) + &
1075                         (1.-zxy) * ubtbdydta(ib,1)   
1076          END DO
1077
1078          igrd=3
1079          DO ib=1, nblen(igrd)
1080            vbtbdy(ib) = zxy      * vbtbdydta(ib,2) + &
1081                         (1.-zxy) * vbtbdydta(ib,1)   
1082          END DO
1083
1084
1085      END IF !end if ((nbdy_dta==1).AND.(ntimes_bdy_bt>1))
1086   
1087      ! ------------------- !
1088      ! Last call kt=nitend !
1089      ! ------------------- !
1090
1091      ! Closing of the 3 files
1092      IF( kt == nitend ) THEN
1093          CALL iom_close( numbdyt_bt )
1094          CALL iom_close( numbdyu_bt )
1095          CALL iom_close( numbdyv_bt )
1096      ENDIF
1097
1098      ENDIF ! ln_bdy_dyn_frs
1099
1100      END SUBROUTINE bdy_dta_bt
1101
1102
1103#else
1104   !!----------------------------------------------------------------------
1105   !!   Dummy module                   NO Unstruct Open Boundary Conditions
1106   !!----------------------------------------------------------------------
1107CONTAINS
1108   SUBROUTINE bdy_dta( kt )              ! Empty routine
1109      WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt
1110   END SUBROUTINE bdy_dta
1111   SUBROUTINE bdy_dta_bt( kt, kit )      ! Empty routine
1112      WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt, kit
1113   END SUBROUTINE bdy_dta_bt
1114#endif
1115
1116   !!==============================================================================
1117END MODULE bdydta
Note: See TracBrowser for help on using the repository browser.