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 11822 for NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/SAS – NEMO

Ignore:
Timestamp:
2019-10-29T11:41:36+01:00 (5 years ago)
Author:
acc
Message:

Branch 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. Sette tested updates to branch to align with trunk changes between 10721 and 11740. Sette tests are passing but results differ from branch before these changes (except for GYRE_PISCES and VORTEX) and branch results already differed from trunk because of algorithmic fixes. Will need more checks to confirm correctness.

Location:
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/SAS
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/SAS/diawri.F90

    r11027 r11822  
    126126      !!      define all the NETCDF files and fields 
    127127      !!      At each time step call histdef to compute the mean if ncessary 
    128       !!      Each nwrite time step, output the instantaneous or mean fields 
     128      !!      Each nn_write time step, output the instantaneous or mean fields 
    129129      !!---------------------------------------------------------------------- 
    130130      !! 
     
    139139      REAL(wp) ::   zsto, zout, zmax, zjulian                ! local scalars 
    140140      !!---------------------------------------------------------------------- 
    141       !  
    142       IF( ln_timing )   CALL timing_start('dia_wri') 
    143141      ! 
    144142      ! Output the initial state and forcings 
     
    148146      ENDIF 
    149147      ! 
     148      IF( nn_write == -1 )   RETURN   ! we will never do any output 
     149      !  
     150      IF( ln_timing )   CALL timing_start('dia_wri') 
     151      ! 
    150152      ! 0. Initialisation 
    151153      ! ----------------- 
     
    160162      ENDIF 
    161163#if defined key_diainstant 
    162       zsto = nwrite * rdt 
     164      zsto = nn_write * rdt 
    163165      clop = "inst("//TRIM(clop)//")" 
    164166#else 
     
    166168      clop = "ave("//TRIM(clop)//")" 
    167169#endif 
    168       zout = nwrite * rdt 
     170      zout = nn_write * rdt 
    169171      zmax = ( nitend - nit000 + 1 ) * rdt 
    170172 
     
    197199         ! WRITE root name in date.file for use by postpro 
    198200         IF(lwp) THEN 
    199             CALL dia_nam( clhstnam, nwrite,' ' ) 
     201            CALL dia_nam( clhstnam, nn_write,' ' ) 
    200202            CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    201203            WRITE(inum,*) clhstnam 
     
    205207         ! Define the T grid FILE ( nid_T ) 
    206208 
    207          CALL dia_nam( clhstnam, nwrite, 'grid_T' ) 
     209         CALL dia_nam( clhstnam, nn_write, 'grid_T' ) 
    208210         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    209211         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     
    217219         ! Define the U grid FILE ( nid_U ) 
    218220 
    219          CALL dia_nam( clhstnam, nwrite, 'grid_U' ) 
     221         CALL dia_nam( clhstnam, nn_write, 'grid_U' ) 
    220222         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
    221223         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
     
    229231         ! Define the V grid FILE ( nid_V ) 
    230232 
    231          CALL dia_nam( clhstnam, nwrite, 'grid_V' )                   ! filename 
     233         CALL dia_nam( clhstnam, nn_write, 'grid_V' )                   ! filename 
    232234         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    233235         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
     
    292294      ! donne le nombre d'elements, et ndex la liste des indices a sortir 
    293295 
    294       IF( lwp .AND. MOD( itmod, nwrite ) == 0 ) THEN  
     296      IF( lwp .AND. MOD( itmod, nn_write ) == 0 ) THEN  
    295297         WRITE(numout,*) 'dia_wri : write model outputs in NetCDF files at ', kt, 'time-step' 
    296298         WRITE(numout,*) '~~~~~~ ' 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/SAS/nemogcm.F90

    r11421 r11822  
    164164      ! 
    165165      IF( nstop /= 0 .AND. lwp ) THEN        ! error print 
    166          WRITE(numout,cform_err) 
    167          WRITE(numout,*) '   ==>>>   nemo_gcm: a total of ', nstop, ' errors have been found' 
    168          WRITE(numout,*) 
     166         WRITE(ctmp1,*) '   ==>>>   nemo_gcm: a total of ', nstop, ' errors have been found' 
     167         CALL ctl_stop( ctmp1 ) 
    169168      ENDIF 
    170169      ! 
     
    184183      IF(lwm) THEN 
    185184         IF( nstop == 0 ) THEN   ;   STOP 0 
    186          ELSE                    ;   STOP 999 
     185         ELSE                    ;   STOP 123 
    187186         ENDIF 
    188187      ENDIF 
     
    197196      !! ** Purpose :   initialization of the NEMO GCM 
    198197      !!---------------------------------------------------------------------- 
    199       INTEGER  ::   ji                 ! dummy loop indices 
    200       INTEGER  ::   ios, ilocal_comm   ! local integers 
    201       CHARACTER(len=120), DIMENSION(60) ::   cltxt, cltxt2, clnam 
    202       CHARACTER(len=80)                 ::   clname 
     198      INTEGER ::   ios, ilocal_comm   ! local integers 
    203199      !! 
    204200      NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     
    208204      !!---------------------------------------------------------------------- 
    209205      ! 
    210       cltxt  = '' 
    211       cltxt2 = '' 
    212       clnam  = ''   
    213       cxios_context = 'nemo' 
    214       ! 
    215       !                             ! Open reference namelist and configuration namelist files 
    216       IF( lk_oasis ) THEN  
    217          CALL ctl_opn( numnam_ref, 'namelist_sas_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    218          CALL ctl_opn( numnam_cfg, 'namelist_sas_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    219          cxios_context = 'sas' 
    220          clname = 'output.namelist_sas.dyn' 
    221       ELSE 
    222          CALL ctl_opn( numnam_ref, 'namelist_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    223          CALL ctl_opn( numnam_cfg, 'namelist_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    224          cxios_context = 'nemo' 
    225          clname = 'output.namelist.dyn' 
    226    ENDIF 
    227       ! 
    228       REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
    229       READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    230 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist', .TRUE. ) 
    231       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    232       READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    233 902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist', .TRUE. ) 
    234       ! 
    235       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
    236       READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    237 903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist', .TRUE. ) 
    238       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
    239       READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    240 904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist', .TRUE. )    
    241  
    242       !                             !--------------------------! 
    243       !                             !  Set global domain size  !   (control print return in cltxt2) 
    244       !                             !--------------------------! 
    245       IF( ln_read_cfg ) THEN              ! Read sizes in domain configuration file 
    246          CALL domain_cfg ( cltxt2,        cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
    247          ! 
    248       ELSE                                ! user-defined namelist 
    249          CALL usr_def_nam( cltxt2, clnam, cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
    250       ENDIF 
    251       ! 
    252       ! 
    253       !                             !--------------------------------------------! 
    254       !                             !  set communicator & select the local node  ! 
    255       !                             !  NB: mynode also opens output.namelist.dyn ! 
    256       !                             !      on unit number numond on first proc   ! 
    257       !                             !--------------------------------------------! 
     206      IF( lk_oasis ) THEN   ;   cxios_context = 'sas' 
     207      ELSE                  ;   cxios_context = 'nemo' 
     208      ENDIF 
     209      ! 
     210      !                             !-------------------------------------------------! 
     211      !                             !     set communicator & select the local rank    ! 
     212      !                             !  must be done as soon as possible to get narea  ! 
     213      !                             !-------------------------------------------------! 
     214      ! 
    258215#if defined key_iomput 
    259216      IF( Agrif_Root() ) THEN 
    260217         IF( lk_oasis ) THEN 
    261             CALL cpl_init( "sas", ilocal_comm )                          ! nemo local communicator given by oasis  
    262             CALL xios_initialize( "not used",local_comm=ilocal_comm )    ! send nemo communicator to xios 
     218            CALL cpl_init( "sas", ilocal_comm )                                  ! nemo local communicator given by oasis  
     219            CALL xios_initialize( "not used",local_comm=ilocal_comm )            ! send nemo communicator to xios 
    263220         ELSE 
    264221            CALL xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
    265222         ENDIF 
    266223      ENDIF 
    267       narea = mynode ( cltxt, clname, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )  ! Nodes selection 
     224      CALL mpp_start( ilocal_comm ) 
    268225#else 
    269226      IF( lk_oasis ) THEN 
    270227         IF( Agrif_Root() ) THEN 
    271             CALL cpl_init( "sas", ilocal_comm )                          ! nemo local communicator given by oasis 
     228            CALL cpl_init( "sas", ilocal_comm )             ! nemo local communicator given by oasis 
    272229         ENDIF 
    273          narea = mynode( cltxt, clname, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
     230         CALL mpp_start( ilocal_comm ) 
    274231      ELSE 
    275          ilocal_comm = 0 
    276          narea = mynode( cltxt, clname, numnam_ref, numnam_cfg, numond , nstop )                ! Nodes selection (control print return in cltxt) 
    277       ENDIF 
    278 #endif 
    279  
    280       narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
    281  
    282       IF( sn_cfctl%l_config ) THEN 
    283          ! Activate finer control of report outputs 
    284          ! optionally switch off output from selected areas (note this only 
    285          ! applies to output which does not involve global communications) 
    286          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    287            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    288            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     232         CALL mpp_start( ) 
     233      ENDIF 
     234#endif 
     235      ! 
     236      narea = mpprank + 1                                   ! mpprank: the rank of proc (0 --> mppsize -1 ) 
     237      lwm = (narea == 1)                ! control of output namelists 
     238      ! 
     239      !                             !---------------------------------------------------------------! 
     240      !                             ! Open output files, reference and configuration namelist files ! 
     241      !                             !---------------------------------------------------------------! 
     242      ! 
     243      ! open ocean.output as soon as possible to get all output prints (including errors messages) 
     244      IF( lk_oasis ) THEN 
     245         IF( lwm )   CALL ctl_opn(     numout,              'sas.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     246         ! open reference and configuration namelist files 
     247                     CALL ctl_opn( numnam_ref,        'namelist_sas_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     248                     CALL ctl_opn( numnam_cfg,        'namelist_sas_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     249         IF( lwm )   CALL ctl_opn(     numond, 'output.namelist_sas.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    289250      ELSE 
    290          ! Use ln_ctl to turn on or off all options. 
    291          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    292       ENDIF 
    293  
    294       lwm = (narea == 1)                                    ! control of output namelists 
    295       lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print 
    296  
    297       IF(lwm) THEN               ! write merged namelists from earlier to output namelist  
    298          !                       ! now that the file has been opened in call to mynode.  
    299          !                       ! NB: nammpp has already been written in mynode (if lk_mpp_mpi) 
    300          WRITE( numond, namctl ) 
    301          WRITE( numond, namcfg ) 
    302          IF( .NOT.ln_read_cfg ) THEN 
    303             DO ji = 1, SIZE(clnam) 
    304                IF( TRIM(clnam(ji)) /= '' )   WRITE(numond, * ) clnam(ji)     ! namusr_def print 
    305             END DO 
     251         IF( lwm )   CALL ctl_opn(     numout,            'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     252         ! open reference and configuration namelist files 
     253                     CALL ctl_opn( numnam_ref,            'namelist_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     254                     CALL ctl_opn( numnam_cfg,            'namelist_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     255         IF( lwm )   CALL ctl_opn(     numond,     'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     256      ENDIF 
     257      ! open /dev/null file to be able to supress output write easily 
     258                     CALL ctl_opn(     numnul,               '/dev/null', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     259      ! 
     260      !                             !--------------------! 
     261      !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     262      !                             !--------------------! 
     263      ! 
     264      REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
     265      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
     266901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' ) 
     267      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
     268      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
     269902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
     270      ! 
     271      lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     272      ! 
     273      IF(lwp) THEN                      ! open listing units 
     274         ! 
     275         IF( .NOT. lwm ) THEN           ! alreay opened for narea == 1 
     276            IF(lk_oasis) THEN   ;   CALL ctl_opn( numout,   'sas.output','REPLACE','FORMATTED','SEQUENTIAL',-1,-1, .FALSE., narea ) 
     277            ELSE                ;   CALL ctl_opn( numout, 'ocean.output','REPLACE','FORMATTED','SEQUENTIAL',-1,-1, .FALSE., narea ) 
     278            ENDIF 
    306279         ENDIF 
    307       ENDIF 
    308  
    309       IF(lwp) THEN                            ! open listing units 
    310          ! 
    311          IF( lk_oasis ) THEN   ;   CALL ctl_opn( numout,   'sas.output', 'REPLACE','FORMATTED','SEQUENTIAL', -1, 6, .FALSE., narea ) 
    312          ELSE                  ;   CALL ctl_opn( numout, 'ocean.output', 'REPLACE','FORMATTED','SEQUENTIAL', -1, 6, .FALSE., narea ) 
    313          ENDIF 
    314280         ! 
    315281         WRITE(numout,*) 
    316          WRITE(numout,*) '   CNRS - NERC - Met OFFICE - MERCATOR-ocean - INGV - CMCC' 
     282         WRITE(numout,*) '   CNRS - NERC - Met OFFICE - MERCATOR-ocean - CMCC' 
    317283         WRITE(numout,*) '                       NEMO team' 
    318284         WRITE(numout,*) '            Ocean General Circulation Model' 
     
    330296         WRITE(numout,*) "       )  )       \) |`\ \)  '.   \      (   (   " 
    331297         WRITE(numout,*) "      (  (           \_/       '-._\      )   )  " 
    332          WRITE(numout,*) "       )  )                        `     (   (   " 
     298         WRITE(numout,*) "       )  ) jgs                    `     (   (   " 
    333299         WRITE(numout,*) "     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ " 
    334300         WRITE(numout,*) 
    335          DO ji = 1, SIZE(cltxt) 
    336             IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) cltxt(ji)    ! control print of mynode 
    337          END DO 
    338301         WRITE(numout,*) 
    339          WRITE(numout,*) 
    340          DO ji = 1, SIZE(cltxt2) 
    341             IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) cltxt2(ji)   ! control print of domain size 
    342          END DO 
    343302         ! 
    344303         WRITE(numout,cform_aaa)                                        ! Flag AAAAAAA 
    345304         ! 
    346305      ENDIF 
    347       ! open /dev/null file to be able to supress output write easily 
    348       CALL ctl_opn( numnul, '/dev/null', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    349       ! 
    350       !                                      ! Domain decomposition 
    351       CALL mpp_init                          ! MPP 
     306     ! 
     307      ! finalize the definition of namctl variables 
     308      IF( sn_cfctl%l_config ) THEN 
     309         ! Activate finer control of report outputs 
     310         ! optionally switch off output from selected areas (note this only 
     311         ! applies to output which does not involve global communications) 
     312         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     313           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     314           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     315      ELSE 
     316         ! Use ln_ctl to turn on or off all options. 
     317         CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
     318      ENDIF 
     319      ! 
     320      IF(lwm) WRITE( numond, namctl ) 
     321      ! 
     322      !                             !------------------------------------! 
     323      !                             !  Set global domain size parameters ! 
     324      !                             !------------------------------------! 
     325      ! 
     326      REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
     327      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
     328903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
     329      REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
     330      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
     331904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )    
     332      ! 
     333      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
     334         CALL domain_cfg ( cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
     335      ELSE                              ! user-defined namelist 
     336         CALL usr_def_nam( cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
     337      ENDIF 
     338      ! 
     339      IF(lwm)   WRITE( numond, namcfg ) 
     340      ! 
     341      !                             !-----------------------------------------! 
     342      !                             ! mpp parameters and domain decomposition ! 
     343      !                             !-----------------------------------------! 
     344      CALL mpp_init 
    352345 
    353346      ! Now we know the dimensions of the grid and numout has been set: we can allocate arrays 
     
    489482      ! 
    490483      IF( 1._wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows f2003 standard.',  & 
    491          &                                                'Compile with key_nosignedzero enabled' ) 
     484         &                                                'Compile with key_nosignedzero enabled:',   & 
     485         &                                                '--> add -Dkey_nosignedzero to the definition of %CPP in your arch file' ) 
    492486      ! 
    493487#if defined key_agrif 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/SAS/sbcssm.F90

    r11027 r11822  
    192192      REWIND( numnam_ref )              ! Namelist namsbc_sas in reference namelist : Input fields 
    193193      READ  ( numnam_ref, namsbc_sas, IOSTAT = ios, ERR = 901) 
    194 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_sas in reference namelist', lwp ) 
     194901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_sas in reference namelist' ) 
    195195      REWIND( numnam_cfg )              ! Namelist namsbc_sas in configuration namelist : Input fields 
    196196      READ  ( numnam_cfg, namsbc_sas, IOSTAT = ios, ERR = 902 ) 
    197 902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_sas in configuration namelist', lwp ) 
     197902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_sas in configuration namelist' ) 
    198198      IF(lwm) WRITE ( numond, namsbc_sas ) 
    199199      !            
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/SAS/step.F90

    r11421 r11822  
    101101      !           From SAS: ocean bdy data are wrong  (but we do not care) and ice bdy data are OK.   
    102102      !           This is not clean and should be changed in the future.  
    103       IF( ln_bdy     )       CALL bdy_dta ( kstp,     Nnn, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    104103      ! ==> 
     104      IF( ln_bdy     )       CALL bdy_dta( kstp,      Nnn, kt_offset=+1 )     ! update dynamic & tracer data at open boundaries 
    105105                             CALL sbc    ( kstp, Nbb, Nnn )                   ! Sea Boundary Condition (including sea-ice) 
    106106 
Note: See TracChangeset for help on using the changeset viewer.