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.
Changeset 2128 for branches/devukmo2010/NEMO/OPA_SRC/BDY/bdydta.F90 – NEMO

Ignore:
Timestamp:
2010-09-28T14:29:51+02:00 (14 years ago)
Author:
rfurner
Message:

merged branches OBS, ASM, Rivers, BDY & mixed_dynldf ready for vn3.3 merge

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/devukmo2010/NEMO/OPA_SRC/BDY/bdydta.F90

    r1715 r2128  
    88   !!             -   !  2007-07  (D. Storkey) add bdy_dta_bt 
    99   !!            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 
    1012   !!---------------------------------------------------------------------- 
    1113#if defined key_bdy 
     
    2527   USE ioipsl 
    2628   USE in_out_manager  ! I/O logical units 
     29#if defined key_lim2 
     30   USE ice_2 
     31#endif 
    2732 
    2833   IMPLICIT NONE 
     
    4752   REAL(wp), DIMENSION(jpbdim,2)     ::   ubtbdydta, vbtbdydta !: Arrays used for time interpolation of bdy data    
    4853   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 interpolation of bdy data for ice variables 
     58   REAL(wp), DIMENSION(jpbdim,2)     ::   hsnif_bdydta         !: } 
     59#endif 
    4960 
    5061   !!---------------------------------------------------------------------- 
     
    196207               IF(lwp) WRITE(numout,*) 'offset: ',zoffset 
    197208               IF(lwp) WRITE(numout,*) 'totime: ',totime 
    198                IF(lwp) WRITE(numout,*) 'zstepr: ',zstepr 
     209               IF(lwp) WRITE(numout,*) 'zstepr: ',zstepr(1:ntimes_bdy) 
    199210 
    200211               ! Check that there are not too many times in the file.  
     
    227238               END IF 
    228239               ! 
    229                IF    ( igrd == 1 ) THEN 
    230                  ntimes_bdyt = ntimes_bdy 
    231                  zoffsett = zoffset 
    232                  istept(:) = INT( zstepr(:) + zoffset ) 
    233                ELSEIF(igrd == 2 ) THEN 
    234                  ntimes_bdyu = ntimes_bdy 
    235                  zoffsetu = zoffset 
    236                  istepu(:) = INT( zstepr(:) + zoffset ) 
    237                ELSEIF(igrd == 3 ) THEN 
    238                  ntimes_bdyv = ntimes_bdy 
    239                  zoffsetv = zoffset 
    240                  istepv(:) = INT( zstepr(:) + zoffset ) 
    241                ENDIF 
     240               SELECT CASE( igrd ) 
     241                  CASE (1) 
     242                    ntimes_bdyt = ntimes_bdy 
     243                    zoffsett = zoffset 
     244                    istept(:) = INT( zstepr(:) + zoffset ) 
     245                    numbdyt = inum 
     246                  CASE (2) 
     247                    ntimes_bdyu = ntimes_bdy 
     248                    zoffsetu = zoffset 
     249                    istepu(:) = INT( zstepr(:) + zoffset ) 
     250                    numbdyu = inum 
     251                  CASE (3) 
     252                    ntimes_bdyv = ntimes_bdy 
     253                    zoffsetv = zoffset 
     254                    istepv(:) = INT( zstepr(:) + zoffset ) 
     255                    numbdyv = inum 
     256               END SELECT 
    242257               ! 
    243258            END DO                                         ! end loop over T, U & V grid  
     
    291306            nbdy_b = it 
    292307            ! 
    293             WRITE(numout,*) 'Time offset is ',zoffset 
    294             WRITE(numout,*) 'First record to read is ',nbdy_b 
     308            IF(lwp) WRITE(numout,*) 'Time offset is ',zoffset 
     309            IF(lwp) WRITE(numout,*) 'First record to read is ',nbdy_b 
    295310 
    296311         ENDIF ! endif (nbdy_dta == 1) 
     
    334349            ENDIF 
    335350            ! 
     351#if defined key_lim2 
     352            IF (ln_bdy_ice_frs) THEN 
     353               igrd = 1            ! T-points data 
     354               DO ib = 1, nblen(igrd) 
     355                  frld_bdy(ib)  =  frld(nbi(ib,igrd), nbj(ib,igrd)) 
     356                  hicif_bdy(ib) = hicif(nbi(ib,igrd), nbj(ib,igrd)) 
     357                  hsnif_bdy(ib) = hsnif(nbi(ib,igrd), nbj(ib,igrd)) 
     358               END DO 
     359            ENDIF 
     360#endif 
    336361         ELSEIF( nbdy_dta == 1 ) THEN    ! Set first record in the climatological case:    
    337362            ! 
     
    357382                  nblendta(igrd) = iom_file(numbdyt)%dimsz(1,idvar) 
    358383               ENDIF 
    359                WRITE(numout,*) 'Dim size for votemper is ', nblendta(igrd) 
     384               IF(lwp) WRITE(numout,*) 'Dim size for votemper is ', nblendta(igrd) 
    360385               ipi = nblendta(igrd) 
    361386               CALL iom_get ( numbdyt, jpdom_unknown, 'votemper', zdta(1:ipi,1:ipj,1:ipk), nbdy_a ) 
     
    372397                  nblendta(igrd) = iom_file(numbdyt)%dimsz(1,idvar) 
    373398               ENDIF 
    374                WRITE(numout,*) 'Dim size for vosaline is ', nblendta(igrd) 
     399               IF(lwp) WRITE(numout,*) 'Dim size for vosaline is ', nblendta(igrd) 
    375400               ipi = nblendta(igrd) 
    376401               CALL iom_get ( numbdyt, jpdom_unknown, 'vosaline', zdta(1:ipi,1:ipj,1:ipk), nbdy_a ) 
     
    390415                 nblendta(igrd) = iom_file(numbdyu)%dimsz(1,idvar) 
    391416               ENDIF 
    392                WRITE(numout,*) 'Dim size for vozocrtx is ', nblendta(igrd) 
     417               IF(lwp) WRITE(numout,*) 'Dim size for vozocrtx is ', nblendta(igrd) 
    393418               ipi = nblendta(igrd) 
    394419               CALL iom_get ( numbdyu, jpdom_unknown,'vozocrtx',zdta(1:ipi,1:ipj,1:ipk),nbdy_a ) 
     
    404429                 nblendta(igrd) = iom_file(numbdyv)%dimsz(1,idvar) 
    405430               ENDIF 
    406                WRITE(numout,*) 'Dim size for vomecrty is ', nblendta(igrd) 
     431               IF(lwp) WRITE(numout,*) 'Dim size for vomecrty is ', nblendta(igrd) 
    407432               ipi = nblendta(igrd) 
    408433               CALL iom_get ( numbdyv, jpdom_unknown,'vomecrty',zdta(1:ipi,1:ipj,1:ipk),nbdy_a ) 
     
    414439            ENDIF ! ln_bdy_dyn_frs 
    415440 
     441#if defined key_lim2 
     442            IF(ln_bdy_ice_frs) THEN 
     443              ! 
     444              igrd=1                                              ! leads fraction 
     445              IF(lwp) WRITE(numout,*) 'Dim size for ildsconc is ',nblendta(igrd) 
     446              ipi=nblendta(igrd) 
     447              CALL iom_get ( numbdyt, jpdom_unknown,'ildsconc',zdta(1:ipi,:,1),nbdy_a ) 
     448              DO ib=1, nblen(igrd) 
     449                frld_bdydta(ib,2) =  zdta(nbmap(ib,igrd),1,1) 
     450              END DO 
     451              ! 
     452              igrd=1                                              ! ice thickness 
     453              IF(lwp) WRITE(numout,*) 'Dim size for iicethic is ',nblendta(igrd) 
     454              ipi=nblendta(igrd) 
     455              CALL iom_get ( numbdyt, jpdom_unknown,'iicethic',zdta(1:ipi,:,1),nbdy_a ) 
     456              DO ib=1, nblen(igrd) 
     457                hicif_bdydta(ib,2) =  zdta(nbmap(ib,igrd),1,1) 
     458              END DO 
     459              ! 
     460              igrd=1                                              ! snow thickness 
     461              IF(lwp) WRITE(numout,*) 'Dim size for isnowthi is ',nblendta(igrd) 
     462              ipi=nblendta(igrd) 
     463              CALL iom_get ( numbdyt, jpdom_unknown,'isnowthi',zdta(1:ipi,:,1),nbdy_a ) 
     464              DO ib=1, nblen(igrd) 
     465                hsnif_bdydta(ib,2) =  zdta(nbmap(ib,igrd),1,1) 
     466              END DO 
     467            ENDIF ! just if ln_bdy_ice_frs is set 
     468#endif 
    416469 
    417470            IF ((.NOT.ln_bdy_clim) .AND. (istep(1) > 0)) THEN 
     
    427480                 vbdydta(:,:,1) = vbdydta(:,:,2) 
    428481               ENDIF 
     482#if defined key_lim2 
     483             IF( ln_bdy_ice_frs ) THEN 
     484               frld_bdydta (:,1) =  frld_bdydta(:,2) 
     485               hicif_bdydta(:,1) = hicif_bdydta(:,2) 
     486               hsnif_bdydta(:,1) = hsnif_bdydta(:,2) 
     487             ENDIF 
     488#endif 
    429489            END IF 
    430490 
     
    441501              vbdy  (:,:) = vbdydta  (:,:,2) 
    442502            ENDIF 
     503#if defined key_lim2 
     504          IF(ln_bdy_ice_frs) THEN 
     505            frld_bdy (:) = frld_bdydta (:,2) 
     506            hicif_bdy(:) = hicif_bdydta(:,2) 
     507            hsnif_bdy(:) = hsnif_bdydta(:,2) 
     508          ENDIF 
     509#endif 
    443510 
    444511            IF(ln_bdy_tra_frs .or. ln_bdy_ice_frs) CALL iom_close( numbdyt ) 
     
    483550                vbdydta(:,:,1) =  vbdydta(:,:,2) 
    484551              ENDIF 
     552#if defined key_lim2 
     553              IF(ln_bdy_ice_frs) THEN 
     554                frld_bdydta (:,1) =  frld_bdydta (:,2) 
     555                hicif_bdydta(:,1) =  hicif_bdydta(:,2) 
     556                hsnif_bdydta(:,1) =  hsnif_bdydta(:,2) 
     557              ENDIF 
     558#endif 
    485559            END IF ! nbdy_a < ntimes_bdy 
    486560 
     
    497571             vbdydta(:,:,1) =  vbdydta(:,:,2) 
    498572           ENDIF 
    499   
     573#if defined key_lim2 
     574           IF(ln_bdy_ice_frs) THEN 
     575             frld_bdydta (:,1) =  frld_bdydta (:,2) 
     576             hicif_bdydta(:,1) =  hicif_bdydta(:,2) 
     577             hsnif_bdydta(:,1) =  hsnif_bdydta(:,2) 
     578           ENDIF 
     579#endif  
    500580           ! read another set 
    501581           ipj  = 1 
     
    543623              END DO 
    544624           ENDIF ! ln_bdy_dyn_frs 
    545  
     625           ! 
     626#if defined key_lim2 
     627           IF(ln_bdy_ice_frs) THEN 
     628             ! 
     629             igrd = 1                                    ! ice concentration 
     630             ipi=nblendta(igrd) 
     631             CALL iom_get ( numbdyt, jpdom_unknown,'ildsconc',zdta(1:ipi,:,1),nbdy_a ) 
     632             DO ib=1, nblen(igrd) 
     633               frld_bdydta(ib,2) =  zdta( nbmap(ib,igrd), 1, 1 ) 
     634             END DO 
     635             ! 
     636             igrd=1                                      ! ice thickness 
     637             ipi=nblendta(igrd) 
     638             CALL iom_get ( numbdyt, jpdom_unknown,'iicethic',zdta(1:ipi,:,1),nbdy_a ) 
     639             DO ib=1, nblen(igrd) 
     640               hicif_bdydta(ib,2) =  zdta( nbmap(ib,igrd), 1, 1 ) 
     641             END DO 
     642             ! 
     643             igrd=1                                      ! snow thickness 
     644             ipi=nblendta(igrd) 
     645             CALL iom_get ( numbdyt, jpdom_unknown,'isnowthi',zdta(1:ipi,:,1),nbdy_a ) 
     646             DO ib=1, nblen(igrd) 
     647               hsnif_bdydta(ib,2) =  zdta( nbmap(ib,igrd), 1, 1 ) 
     648             END DO 
     649           ENDIF ! ln_bdy_ice_frs 
     650#endif 
    546651           ! 
    547652           IF(lwp) WRITE(numout,*) 'bdy_dta : first record file used nbdy_b ',nbdy_b 
     
    559664       ! ******************** 
    560665       !  
    561        IF( ln_bdy_clim ) THEN   ;   zxy = REAL( nday                  , wp ) / REAL( nmonth_len(nbdy_b), wp ) + 0.5 - i15 
    562        ELSE                     ;   zxy = REAL( istep(nbdy_b) - itimer, wp ) / REAL( istep(nbdy_b) - istep(nbdy_a), wp ) 
     666       IF( ln_bdy_clim ) THEN   ;   zxy = REAL( nday                   ) / REAL( nmonth_len(nbdy_b) ) + 0.5 - i15 
     667       ELSEIF( istep(nbdy_b) == istep(nbdy_a) ) THEN  
     668                                    zxy = 0.0_wp 
     669       ELSE                     ;   zxy = REAL( istep(nbdy_b) - itimer ) / REAL( istep(nbdy_b) - istep(nbdy_a) ) 
    563670       END IF 
    564671 
     
    589696          ENDIF 
    590697 
     698#if defined key_lim2 
     699          IF(ln_bdy_ice_frs) THEN 
     700            igrd=1 
     701            DO ib=1, nblen(igrd) 
     702               frld_bdy(ib) = zxy *  frld_bdydta(ib,2) + (1.-zxy) *  frld_bdydta(ib,1) 
     703              hicif_bdy(ib) = zxy * hicif_bdydta(ib,2) + (1.-zxy) * hicif_bdydta(ib,1) 
     704              hsnif_bdy(ib) = zxy * hsnif_bdydta(ib,2) + (1.-zxy) * hsnif_bdydta(ib,1) 
     705            END DO 
     706          ENDIF ! just if ln_bdy_ice_frs is true 
     707#endif 
     708 
    591709      END IF                       !end if ((nbdy_dta==1).AND.(ntimes_bdy>1)) 
    592710     
     
    606724 
    607725 
    608    SUBROUTINE bdy_dta_bt( kt, jit ) 
     726   SUBROUTINE bdy_dta_bt( kt, jit, icycl ) 
    609727      !!--------------------------------------------------------------------------- 
    610728      !!                      ***  SUBROUTINE bdy_dta_bt  *** 
     
    620738      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index 
    621739      INTEGER, INTENT( in ) ::   jit         ! barotropic time step index 
     740      INTEGER, INTENT( in ) ::   icycl       ! number of cycles need for final file close 
    622741      !                                      ! (for timesplitting option, otherwise zero) 
    623742      !! 
     
    639758      REAL(wp), DIMENSION(jpbtime)      ::   zstepr             ! REAL time array from data files 
    640759      REAL(wp), DIMENSION(jpbdta,1)     ::   zdta               ! temporary array for data fields 
    641       CHARACTER(LEN=80), DIMENSION(3)   ::   clfile 
     760      CHARACTER(LEN=80), DIMENSION(6)   ::   clfile 
    642761      CHARACTER(LEN=70 )                ::   clunits            ! units attribute of time coordinate 
    643762      !!--------------------------------------------------------------------------- 
     
    688807 
    689808      !                                                !-------------------! 
    690       IF( kt == nit000 ) THEN                          !  First call only  ! 
     809      IF( kt == nit000 .and. jit ==2 ) THEN            !  First call only  ! 
    691810         !                                             !-------------------! 
    692811         istep_bt(:) = 0 
     
    712831                                                     ! necessary time dumps in file are included 
    713832 
    714           clfile(1) = filbdy_data_bt_T 
    715           clfile(2) = filbdy_data_bt_U 
    716           clfile(3) = filbdy_data_bt_V 
    717  
    718           DO igrd = 1,3 
     833          clfile(4) = filbdy_data_bt_T 
     834          clfile(5) = filbdy_data_bt_U 
     835          clfile(6) = filbdy_data_bt_V 
     836 
     837          DO igrd = 4,6 
    719838 
    720839            CALL iom_open( clfile(igrd), inum ) 
    721             CALL iom_gettime( inum, zstepr, kntime=ntimes_bdy, cdunits=clunits )  
     840            CALL iom_gettime( inum, zstepr, kntime=ntimes_bdy_bt, cdunits=clunits )  
    722841 
    723842            SELECT CASE( igrd ) 
    724                CASE (1)  
    725                   numbdyt = inum 
    726                CASE (2)  
    727                   numbdyu = inum 
    728                CASE (3)  
    729                   numbdyv = inum 
     843               CASE (4)  
     844                  numbdyt_bt = inum 
     845               CASE (5)  
     846                  numbdyu_bt = inum 
     847               CASE (6)  
     848                  numbdyv_bt = inum 
    730849            END SELECT 
    731850 
     
    757876 
    758877            ! Check that time array increases (or interp will fail): 
    759             DO it = 2, ntimes_bdy 
     878            DO it = 2, ntimes_bdy_bt 
    760879               IF ( zstepr(it-1) >= zstepr(it) ) THEN 
    761880                  CALL ctl_stop('Time array in unstructured boundary data file', & 
     
    778897               ! The same applies to the last time level: see setting of lect below. 
    779898 
    780                IF ( ntimes_bdy == 1 ) CALL ctl_stop( & 
     899               IF ( ntimes_bdy_bt == 1 ) CALL ctl_stop( & 
    781900                    'There is only one time dump in data files', & 
    782901                    'Set ln_bdy_clim=.true. in namelist for constant bdy forcing.' ) 
    783902 
    784903               zinterval_s = zstepr(2) - zstepr(1) 
    785                zinterval_e = zstepr(ntimes_bdy) - zstepr(ntimes_bdy-1) 
    786  
    787                IF ( zstepr(1) - zinterval_s / 2.0 > 0 ) THEN              
    788                   IF(lwp) WRITE(numout,*) 'First bdy time relative to nit000:', zstepr(1) 
    789                   IF(lwp) WRITE(numout,*) 'Interval between first two times: ', zinterval_s 
    790                   CALL ctl_stop( 'First data time is after start of run', &  
    791                        'by more than half a meaning period', & 
    792                        'Check file: ' // TRIM(clfile(igrd)) ) 
     904               zinterval_e = zstepr(ntimes_bdy_bt) - zstepr(ntimes_bdy_bt-1) 
     905 
     906               IF( zstepr(1) + zoffset > 0 ) THEN 
     907                     WRITE(ctmp1,*) 'Check file: ', clfile(igrd) 
     908                     CALL ctl_stop( 'First time dump in bdy file is after model initial time', ctmp1 ) 
    793909               END IF 
    794  
    795                IF ( zstepr(ntimes_bdy) + zinterval_e / 2.0 < totime ) THEN 
    796                   IF(lwp) WRITE(numout,*) 'Last bdy time relative to nit000:', zstepr(ntimes_bdy) 
    797                   IF(lwp) WRITE(numout,*) 'Interval between last two times: ', zinterval_e 
    798                   CALL ctl_stop( 'Last data time is before end of run', &  
    799                        'by more than half a meaning period', & 
    800                        'Check file: ' // TRIM(clfile(igrd))  ) 
     910               IF( zstepr(ntimes_bdy_bt) + zoffset < totime ) THEN 
     911                     WRITE(ctmp1,*) 'Check file: ', clfile(igrd) 
     912                     CALL ctl_stop( 'Last time dump in bdy file is before model final time', ctmp1 ) 
    801913               END IF 
    802  
    803914            END IF ! .NOT. ln_bdy_clim 
    804915 
    805             IF ( igrd .EQ. 1) THEN 
     916            IF ( igrd .EQ. 4) THEN 
    806917              ntimes_bdyt = ntimes_bdy_bt 
    807918              zoffsett = zoffset 
    808919              istept(:) = INT( zstepr(:) + zoffset ) 
    809             ELSE IF (igrd .EQ. 2) THEN 
     920            ELSE IF (igrd .EQ. 5) THEN 
    810921              ntimes_bdyu = ntimes_bdy_bt 
    811922              zoffsetu = zoffset 
    812923              istepu(:) = INT( zstepr(:) + zoffset ) 
    813             ELSE IF (igrd .EQ. 3) THEN 
     924            ELSE IF (igrd .EQ. 6) THEN 
    814925              ntimes_bdyv = ntimes_bdy_bt 
    815926              zoffsetv = zoffset 
     
    865976          nbdy_b_bt = it 
    866977 
    867           WRITE(numout,*) 'Time offset is ',zoffset 
    868           WRITE(numout,*) 'First record to read is ',nbdy_b_bt 
     978          IF(lwp) WRITE(numout,*) 'Time offset is ',zoffset 
     979          IF(lwp) WRITE(numout,*) 'First record to read is ',nbdy_b_bt 
    869980 
    870981        ENDIF ! endif (nbdy_dta == 1) 
     
    875986        IF ( nbdy_dta == 0) THEN 
    876987          ! boundary data arrays are filled with initial conditions 
    877           igrd = 2            ! U-points data  
     988          igrd = 5            ! U-points data  
    878989          DO ib = 1, nblen(igrd)               
    879990            ubtbdy(ib) = un(nbi(ib,igrd), nbj(ib,igrd), 1) 
    880991          END DO 
    881992 
    882           igrd = 3            ! V-points data  
     993          igrd = 6            ! V-points data  
    883994          DO ib = 1, nblen(igrd)               
    884995            vbtbdy(ib) = vn(nbi(ib,igrd), nbj(ib,igrd), 1) 
    885996          END DO 
    886997 
    887           igrd = 1            ! T-points data  
     998          igrd = 4            ! T-points data  
    888999          DO ib = 1, nblen(igrd)               
    8891000            sshbdy(ib) = sshn(nbi(ib,igrd), nbj(ib,igrd)) 
     
    9101021         ! Read first record: 
    9111022          ipj=1 
    912           igrd=1 
     1023          igrd=4 
    9131024          ipi=nblendta(igrd) 
    9141025 
    9151026          ! ssh 
    916           igrd=1 
     1027          igrd=4 
    9171028          IF ( nblendta(igrd) .le. 0 ) THEN  
    9181029            idvar = iom_varid( numbdyt_bt,'sossheig' ) 
     
    9291040  
    9301041          ! u-velocity 
    931           igrd=2 
     1042          igrd=5 
    9321043          IF ( nblendta(igrd) .le. 0 ) THEN  
    9331044            idvar = iom_varid( numbdyu_bt,'vobtcrtx' ) 
     
    9441055 
    9451056          ! v-velocity 
    946           igrd=3 
     1057          igrd=6 
    9471058          IF ( nblendta(igrd) .le. 0 ) THEN  
    9481059            idvar = iom_varid( numbdyv_bt,'vobtcrty' ) 
     
    10101121          ipj=1 
    10111122          ipk=jpk 
    1012           igrd=1 
     1123          igrd=4 
    10131124          ipi=nblendta(igrd) 
    10141125 
    10151126           
    10161127          ! ssh 
    1017           igrd=1 
     1128          igrd=4 
    10181129          ipi=nblendta(igrd) 
    10191130 
     
    10251136 
    10261137          ! u-velocity 
    1027           igrd=2 
     1138          igrd=5 
    10281139          ipi=nblendta(igrd) 
    10291140 
     
    10351146 
    10361147          ! v-velocity 
    1037           igrd=3 
     1148          igrd=6 
    10381149          ipi=nblendta(igrd) 
    10391150 
     
    10641175        END IF 
    10651176 
    1066           igrd=1 
     1177          igrd=4 
    10671178          DO ib=1, nblen(igrd) 
    10681179            sshbdy(ib) = zxy      * sshbdydta(ib,2) + & 
     
    10701181          END DO 
    10711182 
    1072           igrd=2 
     1183          igrd=5 
    10731184          DO ib=1, nblen(igrd) 
    10741185            ubtbdy(ib) = zxy      * ubtbdydta(ib,2) + & 
     
    10761187          END DO 
    10771188 
    1078           igrd=3 
     1189          igrd=6 
    10791190          DO ib=1, nblen(igrd) 
    10801191            vbtbdy(ib) = zxy      * vbtbdydta(ib,2) + & 
     
    10901201 
    10911202      ! Closing of the 3 files 
    1092       IF( kt == nitend ) THEN 
     1203      IF( kt == nitend   .and. jit == icycl ) THEN 
    10931204          CALL iom_close( numbdyt_bt ) 
    10941205          CALL iom_close( numbdyu_bt ) 
     
    11091220      WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt 
    11101221   END SUBROUTINE bdy_dta 
    1111    SUBROUTINE bdy_dta_bt( kt, kit )      ! Empty routine 
     1222   SUBROUTINE bdy_dta_bt( kt, kit, icycle )      ! Empty routine 
    11121223      WRITE(*,*) 'bdy_dta: You should not have seen this print! error?', kt, kit 
    11131224   END SUBROUTINE bdy_dta_bt 
Note: See TracChangeset for help on using the changeset viewer.