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_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90 @ 3432

Last change on this file since 3432 was 3432, checked in by trackstand2, 12 years ago

Merge branch 'ksection_partition'

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