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 branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2011/dev_r2787_LOCEAN3_TRA_TRP/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90 @ 2789

Last change on this file since 2789 was 2789, checked in by cetlod, 13 years ago

Implementation of the merge of TRA/TRP : first guess, see ticket #842

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