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 14139 – NEMO

Changeset 14139


Ignore:
Timestamp:
2020-12-09T16:08:30+01:00 (3 years ago)
Author:
techene
Message:

#2385 SWE associated update in OCE

Location:
NEMO/trunk/src/OCE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/DOM/domain.F90

    r14125 r14139  
    2828   USE oce            ! ocean variables 
    2929   USE dom_oce        ! domain: ocean 
     30   USE domtile        ! tiling utilities 
    3031#if defined key_qco 
    31    USE domqco         ! quasi-eulerian 
     32   USE domqco         ! quasi-eulerian coord. 
     33#elif defined key_linssh 
     34   !                  ! fix in time coord. 
    3235#else 
    33    USE domvvl         ! variable volume 
    34 #endif 
    35    USE sshwzv  , ONLY : ssh_init_rst   ! set initial ssh 
     36   USE domvvl         ! variable volume coord. 
     37#endif 
    3638#if defined key_agrif 
    3739   USE agrif_oce_interp, ONLY : Agrif_istate_ssh ! ssh interpolated from parent 
     
    4244   USE domhgr         ! domain: set the horizontal mesh 
    4345   USE domzgr         ! domain: set the vertical mesh 
    44    USE domtile 
    4546   USE dommsk         ! domain: set the mask system 
    4647   USE domwri         ! domain: write the meshmask file 
     
    5455   USE lbclnk         ! ocean lateral boundary condition (or mpp link) 
    5556   USE lib_mpp        ! distributed memory computing library 
    56    USE restart        ! only for lrst_oce 
     57   USE restart        ! only for lrst_oce and rst_read_ssh 
    5758 
    5859   IMPLICIT NONE 
     
    172173         DO_2D( 1, 1, 1, 1 ) 
    173174            IF( ht_0(ji,jj) < 0._wp .AND. ssmask(ji,jj) == 1._wp ) THEN 
    174                CALL ctl_stop( 'ssh_init_rst : ht_0 must be positive at potentially wet points' ) 
     175               CALL ctl_stop( 'dom_init : ht_0 must be positive at potentially wet points' ) 
    175176            ENDIF 
    176177         END_2D 
     
    180181      ! 
    181182      !                                 != ssh initialization 
    182       IF( .NOT.l_offline .AND. .NOT.l_SAS ) THEN 
     183      ! 
     184      IF( l_offline .OR. l_SAS ) THEN        !* No ocean dynamics calculation : set to 0 
     185         ssh(:,:,:) = 0._wp 
    183186#if defined key_agrif 
    184          IF ( .NOT.Agrif_root().AND.(ln_init_chfrpar) ) THEN 
    185             ! Interpolate initial ssh from parent: 
    186             CALL Agrif_istate_ssh( Kbb, Kmm ) 
    187          ELSE 
    188 #endif 
    189             CALL ssh_init_rst( Kbb, Kmm, Kaa ) 
    190 #if defined key_agrif 
    191          ENDIF 
    192 #endif 
    193       ELSE 
    194          ssh(:,:,:) = 0._wp 
    195       ENDIF 
    196       ! 
     187      ELSEIF( .NOT.Agrif_root() .AND.    & 
     188         &     ln_init_chfrpar ) THEN        !* Interpolate initial ssh from parent 
     189         CALL Agrif_istate_ssh( Kbb, Kmm ) 
     190#endif 
     191      ELSE                                   !* Read in restart file or set by user 
     192         CALL rst_read_ssh( Kbb, Kmm, Kaa ) 
     193      ENDIF 
     194      !      
    197195#if defined key_qco 
    198196      !                                 != Quasi-Euerian coordinate case 
    199197      ! 
    200198      IF( .NOT.l_offline )   CALL dom_qco_init( Kbb, Kmm, Kaa ) 
     199#elif defined key_linssh 
     200      !                                 != Fix in time : key_linssh case, set through domzgr_substitute.h90 
    201201#else 
    202202      ! 
     
    357357      IF(lwm) WRITE( numond, namdom ) 
    358358      ! 
     359#if defined key_linssh 
     360      ln_linssh = lk_linssh      ! overwrite ln_linssh with the logical associated with key_linssh 
     361#endif 
     362      ! 
    359363#if defined key_agrif 
    360364      IF( .NOT. Agrif_Root() ) THEN    ! AGRIF child, subdivide the Parent timestep 
     
    383387      ! 
    384388#if defined key_qco 
    385       IF( ln_linssh )   CALL ctl_stop( 'STOP','domain: key_qco and ln_linssh = T are incompatible' ) 
     389      IF( ln_linssh )   CALL ctl_stop( 'STOP','domain: key_qco and ln_linssh=T or key_linssh are incompatible' ) 
    386390#endif 
    387391      ! 
  • NEMO/trunk/src/OCE/DOM/istate.F90

    r14086 r14139  
    9090 
    9191#if defined key_agrif 
    92       IF ( (.NOT.Agrif_root()).AND.ln_init_chfrpar ) THEN 
     92      IF ( .NOT.Agrif_root() .AND. ln_init_chfrpar ) THEN 
    9393         numror = 0                           ! define numror = 0 -> no restart file to read 
    9494         ln_1st_euler = .true.                ! Set time-step indicator at nit000 (euler forward) 
     
    9797         ! 
    9898         ts (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb) 
    99 !!st 
    100 !!st need for a recent agrif version to be displaced toward ssh_init_rst with agrif_istate_ssh 
    101          ssh(:,:,    Kmm) = ssh(:,:    ,Kbb) 
    102 !!st end 
    10399         uu (:,:,:  ,Kmm) = uu (:,:,:  ,Kbb) 
    104100         vv (:,:,:  ,Kmm) = vv (:,:,:  ,Kbb) 
     
    116112            CALL day_init                        ! model calendar (using both namelist and restart infos) 
    117113            !                                    ! Initialization of ocean to zero 
     114            ! 
    118115            IF( ln_tsd_init ) THEN                
    119116               CALL dta_tsd( nit000, ts(:,:,:,:,Kbb) )       ! read 3D T and S data at nit000 
    120117               ! 
    121                ssh(:,:,Kbb)   = 0._wp               ! set the ocean at rest 
    122                uu  (:,:,:,Kbb) = 0._wp 
     118               uu  (:,:,:,Kbb) = 0._wp               ! set the ocean at rest 
    123119               vv  (:,:,:,Kbb) = 0._wp   
    124                ! 
    125                IF( ll_wd ) THEN 
    126                   ssh(:,:,Kbb) =  -ssh_ref  ! Added in 30 here for bathy that adds 30 as Iterative test CEOD  
    127                   ! 
    128                   ! Apply minimum wetdepth criterion 
    129                   ! 
    130                   DO_2D( 1, 1, 1, 1 ) 
    131                      IF( ht_0(ji,jj) + ssh(ji,jj,Kbb)  < rn_wdmin1 ) THEN 
    132                         ssh(ji,jj,Kbb) = tmask(ji,jj,1)*( rn_wdmin1 - (ht_0(ji,jj)) ) 
    133                      ENDIF 
    134                   END_2D 
    135                ENDIF  
    136120               ! 
    137121            ELSE                                 ! user defined initial T and S 
     
    142126            ENDIF 
    143127            ts  (:,:,:,:,Kmm) = ts (:,:,:,:,Kbb)       ! set now values from to before ones 
    144             ssh (:,:,Kmm)     = ssh(:,:,Kbb)    
    145             uu   (:,:,:,Kmm)   = uu  (:,:,:,Kbb) 
    146             vv   (:,:,:,Kmm)   = vv  (:,:,:,Kbb) 
     128            uu    (:,:,:,Kmm) = uu   (:,:,:,Kbb) 
     129            vv    (:,:,:,Kmm) = vv   (:,:,:,Kbb) 
    147130 
    148131         ! 
  • NEMO/trunk/src/OCE/DYN/sshwzv.F90

    r14053 r14139  
    1818   !!   ssh_atf       : time filter the ssh arrays 
    1919   !!   wzv           : compute now vertical velocity 
    20    !!   ssh_init_rst  : ssh set from restart or domcfg.nc file or usr_def_istat_ssh 
    2120   !!---------------------------------------------------------------------- 
    2221   USE oce            ! ocean dynamics and tracers variables 
     
    2928   USE bdy_oce , ONLY : ln_bdy, bdytmask   ! Open BounDarY 
    3029   USE bdydyn2d       ! bdy_ssh routine 
     30   USE wet_dry        ! Wetting/Drying flux limiting 
    3131#if defined key_agrif 
    3232   USE agrif_oce 
     
    4141   USE lib_mpp        ! MPP library 
    4242   USE timing         ! Timing 
    43    USE wet_dry        ! Wetting/Drying flux limiting 
    44    USE usrdef_istate, ONLY : usr_def_istate_ssh   ! user defined ssh initial state  
    4543    
    4644   IMPLICIT NONE 
     
    5149   PUBLIC   wAimp          ! called by step.F90 
    5250   PUBLIC   ssh_atf        ! called by step.F90 
    53    PUBLIC   ssh_init_rst   ! called by domain.F90 
    5451 
    5552   !! * Substitutions 
     
    436433      ! 
    437434   END SUBROUTINE wAimp 
    438  
    439  
    440    SUBROUTINE ssh_init_rst( Kbb, Kmm, Kaa ) 
    441       !!--------------------------------------------------------------------- 
    442       !!                   ***  ROUTINE ssh_init_rst  *** 
    443       !! 
    444       !! ** Purpose :   ssh initialization of the sea surface height (ssh) 
    445       !! 
    446       !! ** Method  :   set ssh from restart or read configuration, or user_def 
    447       !!              * ln_rstart = T 
    448       !!                   USE of IOM library to read ssh in the restart file 
    449       !!                   Leap-Frog: Kbb and Kmm are read except for l_1st_euler=T 
    450       !! 
    451       !!              * otherwise  
    452       !!                   call user defined ssh or 
    453       !!                   set to -ssh_ref in wet and drying case with domcfg.nc 
    454       !! 
    455       !!              NB: ssh_b/n are written by restart.F90 
    456       !!---------------------------------------------------------------------- 
    457       INTEGER, INTENT(in) ::   Kbb, Kmm, Kaa   ! ocean time level indices 
    458       ! 
    459       INTEGER ::   ji, jj, jk 
    460       !!---------------------------------------------------------------------- 
    461       ! 
    462       IF(lwp) THEN 
    463          WRITE(numout,*) 
    464          WRITE(numout,*) 'ssh_init_rst : ssh initialization' 
    465          WRITE(numout,*) '~~~~~~~~~~~~ ' 
    466       ENDIF 
    467       ! 
    468       !                            !=============================! 
    469       IF( ln_rstart ) THEN         !==  Read the restart file  ==! 
    470          !                         !=============================! 
    471          ! 
    472          !                                     !*  Read ssh at Kmm 
    473          IF(lwp) WRITE(numout,*) 
    474          IF(lwp) WRITE(numout,*)    '      Kmm sea surface height read in the restart file' 
    475          CALL iom_get( numror, jpdom_auto, 'sshn'   , ssh(:,:,Kmm) ) 
    476          ! 
    477          IF( l_1st_euler ) THEN                !* Euler at first time-step 
    478             IF(lwp) WRITE(numout,*) 
    479             IF(lwp) WRITE(numout,*) '      Euler first time step : ssh(Kbb) = ssh(Kmm)' 
    480             ssh(:,:,Kbb) = ssh(:,:,Kmm) 
    481             ! 
    482          ELSE                                  !* read ssh at Kbb 
    483             IF(lwp) WRITE(numout,*) 
    484             IF(lwp) WRITE(numout,*) '      Kbb sea surface height read in the restart file' 
    485             CALL iom_get( numror, jpdom_auto, 'sshb', ssh(:,:,Kbb) ) 
    486          ENDIF 
    487          !                         !============================! 
    488       ELSE                         !==  Initialize at "rest"  ==! 
    489          !                         !============================! 
    490          ! 
    491          IF(lwp) WRITE(numout,*) 
    492          IF(lwp) WRITE(numout,*)    '      initialization at rest' 
    493          ! 
    494          IF( ll_wd ) THEN                      !* wet and dry  
    495             ! 
    496             IF( ln_read_cfg  ) THEN                 ! read configuration : ssh_ref is read in domain_cfg file 
    497 !!st  why ssh is not masked : i.e. ssh(:,:,Kmm) = -ssh_ref*ssmask(:,:), 
    498 !!st  since at the 1st time step lbclnk will be applied on ssh at Kaa but not initially at Kbb and Kmm 
    499                ssh(:,:,Kbb) = -ssh_ref 
    500                ! 
    501                DO_2D( 1, 1, 1, 1 ) 
    502                   IF( ht_0(ji,jj)-ssh_ref <  rn_wdmin1 ) THEN   ! if total depth is less than min depth 
    503                      ssh(ji,jj,Kbb) = rn_wdmin1 - ht_0(ji,jj) 
    504                   ENDIF 
    505                END_2D 
    506             ELSE                                    ! user define configuration case   
    507                CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) ) 
    508             ENDIF 
    509             ! 
    510          ELSE                                  !* user defined configuration 
    511             CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) ) 
    512             ! 
    513          ENDIF 
    514          ! 
    515          ssh(:,:,Kmm) = ssh(:,:,Kbb)           !* set now values from to before ones 
    516          ssh(:,:,Kaa) = 0._wp  
    517       ENDIF 
    518       ! 
    519    END SUBROUTINE ssh_init_rst 
    520435       
    521436   !!====================================================================== 
  • NEMO/trunk/src/OCE/IOM/restart.F90

    r14072 r14139  
    1111   !!            3.7  !  2014-01  (G. Madec) suppression of curl and hdiv from the restart 
    1212   !!             -   !  2014-12  (G. Madec) remove KPP scheme 
    13    !!            4.1  !  2020-11  (S. Techene, G. Madec)  move ssh initiatlisation in DYN/sshwzv:ssh_init_rst 
    14    !!---------------------------------------------------------------------- 
    15  
    16    !!---------------------------------------------------------------------- 
    17    !!   rst_opn    : open the ocean restart file 
    18    !!   rst_write  : write the ocean restart file 
    19    !!   rst_read   : read the ocean restart file 
    20    !!---------------------------------------------------------------------- 
    21    USE oce             ! ocean dynamics and tracers 
    22    USE dom_oce         ! ocean space and time domain 
    23    USE sbc_ice         ! only lk_si3 
    24    USE phycst          ! physical constants 
    25    USE eosbn2          ! equation of state            (eos bn2 routine) 
    26    USE trdmxl_oce      ! ocean active mixed layer tracers trends variables 
     13   !!            4.1  !  2020-11  (S. Techene, G. Madec)  move ssh initiatlisation in rst_read_ssh 
     14   !!             -   !                                   add restart in Shallow Water Eq. case 
     15   !!---------------------------------------------------------------------- 
     16 
     17   !!---------------------------------------------------------------------- 
     18   !!   rst_opn       : open the ocean restart file for writting 
     19   !!   rst_write     : write the ocean restart file 
     20   !!   rst_read_open : open the restart file for reading  
     21   !!   rst_read      : read the ocean restart file 
     22   !!   rst_read_ssh  : ssh set from restart or domcfg.nc file or usr_def_istat_ssh 
     23   !!---------------------------------------------------------------------- 
     24   USE oce            ! ocean dynamics and tracers 
     25   USE dom_oce        ! ocean space and time domain 
     26   USE sbc_ice        ! only lk_si3 
     27   USE phycst         ! physical constants 
     28   USE eosbn2         ! equation of state 
     29   USE wet_dry        ! Wetting/Drying flux limiting 
     30   USE usrdef_istate, ONLY : usr_def_istate_ssh   ! user defined ssh initial state  
     31   USE trdmxl_oce     ! ocean active mixed layer tracers trends variables 
     32   USE diu_bulk       ! ??? 
    2733   ! 
    28    USE in_out_manager  ! I/O manager 
    29    USE iom             ! I/O module 
    30    USE diu_bulk 
    31    USE lib_mpp         ! distribued memory computing library 
     34   USE in_out_manager ! I/O manager 
     35   USE iom            ! I/O module 
     36   USE lib_mpp        ! distribued memory computing library 
    3237 
    3338   IMPLICIT NONE 
    3439   PRIVATE 
    3540 
    36    PUBLIC   rst_opn         ! routine called by step module 
    37    PUBLIC   rst_write       ! routine called by step module 
    38    PUBLIC   rst_read        ! routine called by istate module 
    39    PUBLIC   rst_read_open   ! routine called in rst_read and (possibly) in dom_vvl_init 
    40  
     41   PUBLIC   rst_opn         ! called by step.F90 
     42   PUBLIC   rst_write       ! called by step.F90 
     43   PUBLIC   rst_read_open   ! called in rst_read_ssh 
     44   PUBLIC   rst_read        ! called by istate.F90 
     45   PUBLIC   rst_read_ssh    ! called by domain.F90 
     46    
     47   !! * Substitutions 
     48#  include "do_loop_substitute.h90" 
    4149   !!---------------------------------------------------------------------- 
    4250   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    142150      !! 
    143151      !!                NB: ssh is written here (rst_write) 
    144       !!                    but is read or set in DYN/sshwzv:shh_init_rst 
     152      !!                    but is read or set in rst_read_ssh 
    145153      !!---------------------------------------------------------------------- 
    146154      INTEGER, INTENT(in) ::   kt         ! ocean time-step 
    147155      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
    148156      !!---------------------------------------------------------------------- 
    149                      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rn_Dt       )   ! dynamics time step 
    150                      IF(.NOT.lwxios) CALL iom_delay_rst( 'WRITE', 'OCE', numrow )   ! save only ocean delayed global communication variables 
    151  
    152       IF ( .NOT. ln_diurnal_only ) THEN 
    153                      CALL iom_rstput( kt, nitrst, numrow, 'ub'     , uu(:,:,:       ,Kbb) )     ! before fields 
    154                      CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vv(:,:,:       ,Kbb) ) 
    155                      CALL iom_rstput( kt, nitrst, numrow, 'tb'     , ts(:,:,:,jp_tem,Kbb) ) 
    156                      CALL iom_rstput( kt, nitrst, numrow, 'sb'     , ts(:,:,:,jp_sal,Kbb) ) 
    157                      CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , ssh(:,:         ,Kbb)) 
    158                      ! 
    159                      CALL iom_rstput( kt, nitrst, numrow, 'un'     , uu(:,:,:       ,Kmm) )     ! now fields 
    160                      CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vv(:,:,:       ,Kmm) ) 
    161                      CALL iom_rstput( kt, nitrst, numrow, 'tn'     , ts(:,:,:,jp_tem,Kmm) ) 
    162                      CALL iom_rstput( kt, nitrst, numrow, 'sn'     , ts(:,:,:,jp_sal,Kmm) ) 
    163                      CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , ssh(:,:         ,Kmm)) 
    164                      CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      ) 
    165       ENDIF 
    166  
    167       IF (ln_diurnal) CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst ) 
     157      ! 
     158         CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rn_Dt       )   ! dynamics time step 
     159      ! 
     160      IF( .NOT.lwxios )   CALL iom_delay_rst( 'WRITE', 'OCE', numrow )   ! save only ocean delayed global communication variables 
     161      ! 
     162      IF( .NOT.ln_diurnal_only ) THEN 
     163         CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , ssh(:,:        ,Kbb) )     ! before fields 
     164         CALL iom_rstput( kt, nitrst, numrow, 'ub'     , uu(:,:,:       ,Kbb) ) 
     165         CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vv(:,:,:       ,Kbb) ) 
     166         IF( .NOT.lk_SWE ) THEN 
     167            CALL iom_rstput( kt, nitrst, numrow, 'tb'  , ts(:,:,:,jp_tem,Kbb) ) 
     168            CALL iom_rstput( kt, nitrst, numrow, 'sb'  , ts(:,:,:,jp_sal,Kbb) ) 
     169         ENDIF 
     170         ! 
     171         CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , ssh(:,:        ,Kmm) )     ! now fields 
     172         CALL iom_rstput( kt, nitrst, numrow, 'un'     , uu(:,:,:       ,Kmm) ) 
     173         CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vv(:,:,:       ,Kmm) ) 
     174         IF( .NOT.lk_SWE ) THEN 
     175            CALL iom_rstput( kt, nitrst, numrow, 'tn'  , ts(:,:,:,jp_tem,Kmm) ) 
     176            CALL iom_rstput( kt, nitrst, numrow, 'sn'  , ts(:,:,:,jp_sal,Kmm) ) 
     177            CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop                 ) 
     178         ENDIF 
     179      ENDIF 
     180 
     181      IF( ln_diurnal )   CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst ) 
    168182      IF( kt == nitrst ) THEN 
    169          IF(.NOT.lwxios) THEN 
     183         IF( .NOT.lwxios ) THEN 
    170184            CALL iom_close( numrow )     ! close the restart file (only at last time step) 
    171185         ELSE 
     
    177191!!gm  not sure what to do here   ===>>>  ask to Sebastian 
    178192         lrst_oce = .FALSE. 
    179             IF( ln_rst_list ) THEN 
    180                nrst_lst = MIN(nrst_lst + 1, SIZE(nn_stocklist,1)) 
    181                nitrst = nn_stocklist( nrst_lst ) 
    182             ENDIF 
     193         IF( ln_rst_list ) THEN 
     194            nrst_lst = MIN(nrst_lst + 1, SIZE(nn_stocklist,1)) 
     195            nitrst  = nn_stocklist( nrst_lst ) 
     196         ENDIF 
    183197      ENDIF 
    184198      ! 
     
    245259      !!                    (sshb) 
    246260      !! 
    247       !!                NB: ssh is read or set in DYN/sshwzv:shh_init_rst 
    248       !!                    but is written     in IOM/restart:rst_write 
    249       !!---------------------------------------------------------------------- 
    250       INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
     261      !!                NB: ssh is read or set in rst_read_ssh 
     262      !!---------------------------------------------------------------------- 
     263      INTEGER          , INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
    251264      INTEGER  ::   jk 
    252265      REAL(wp), DIMENSION(jpi, jpj, jpk) :: w3d 
    253266      !!---------------------------------------------------------------------- 
    254267      ! 
    255       IF(.NOT.lrxios ) CALL iom_delay_rst( 'READ', 'OCE', numror )   ! read only ocean delayed global communication variables 
     268      IF(.NOT.lrxios )   CALL iom_delay_rst( 'READ', 'OCE', numror )   ! read only ocean delayed global communication variables 
    256269      ! 
    257270      !                             !*  Diurnal DSST 
    258271      IF( ln_diurnal )   CALL iom_get( numror, jpdom_auto, 'Dsst' , x_dsst ) 
    259       IF ( ln_diurnal_only ) THEN 
     272      IF( ln_diurnal_only ) THEN 
    260273         IF(lwp) WRITE( numout, * ) & 
    261274         &   "rst_read:- ln_diurnal_only set, setting rhop=rho0" 
     
    268281      !                             !*  Read Kmm fields 
    269282      IF(lwp) WRITE(numout,*)    '           Kmm u, v and T-S fields read in the restart file' 
    270       CALL iom_get( numror, jpdom_auto, 'un'     , uu(:,:,:       ,Kmm), cd_type = 'U', psgn = -1._wp ) 
    271       CALL iom_get( numror, jpdom_auto, 'vn'     , vv(:,:,:       ,Kmm), cd_type = 'V', psgn = -1._wp ) 
    272       CALL iom_get( numror, jpdom_auto, 'tn'     , ts(:,:,:,jp_tem,Kmm) ) 
    273       CALL iom_get( numror, jpdom_auto, 'sn'     , ts(:,:,:,jp_sal,Kmm) ) 
     283      CALL iom_get( numror, jpdom_auto, 'un'   , uu(:,:,:       ,Kmm), cd_type = 'U', psgn = -1._wp ) 
     284      CALL iom_get( numror, jpdom_auto, 'vn'   , vv(:,:,:       ,Kmm), cd_type = 'V', psgn = -1._wp ) 
     285      IF( .NOT.lk_SWE ) THEN 
     286         CALL iom_get( numror, jpdom_auto, 'tn', ts(:,:,:,jp_tem,Kmm) ) 
     287         CALL iom_get( numror, jpdom_auto, 'sn', ts(:,:,:,jp_sal,Kmm) ) 
     288      ENDIF 
    274289      ! 
    275290      IF( l_1st_euler ) THEN        !*  Euler restart 
    276291         IF(lwp) WRITE(numout,*) '           Kbb u, v and T-S fields set to Kmm values' 
    277          ts(:,:,:,:,Kbb) = ts(:,:,:,:,Kmm)         ! all before fields set to now values 
    278          uu(:,:,:  ,Kbb) = uu(:,:,:  ,Kmm) 
     292         uu(:,:,:  ,Kbb) = uu(:,:,:  ,Kmm)         ! all before fields set to now values 
    279293         vv(:,:,:  ,Kbb) = vv(:,:,:  ,Kmm) 
     294         IF( .NOT.lk_SWE ) ts(:,:,:,:,Kbb) = ts(:,:,:,:,Kmm) 
     295         ! 
    280296      ELSE                          !* Leap frog restart 
    281297         IF(lwp) WRITE(numout,*) '           Kbb u, v and T-S fields read in the restart file' 
    282          CALL iom_get( numror, jpdom_auto, 'ub'     , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp ) 
    283          CALL iom_get( numror, jpdom_auto, 'vb'     , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp ) 
    284          CALL iom_get( numror, jpdom_auto, 'tb'     , ts(:,:,:,jp_tem,Kbb) ) 
    285          CALL iom_get( numror, jpdom_auto, 'sb'     , ts(:,:,:,jp_sal,Kbb) ) 
    286       ENDIF 
    287       ! 
    288       IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
    289          CALL iom_get( numror, jpdom_auto, 'rhop'   , rhop )   ! now    potential density 
    290       ELSE 
    291          CALL eos( ts(:,:,:,:,Kmm), rhd, rhop, gdept(:,:,:,Kmm) ) 
     298         CALL iom_get( numror, jpdom_auto, 'ub'   , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp ) 
     299         CALL iom_get( numror, jpdom_auto, 'vb'   , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp ) 
     300         IF( .NOT.lk_SWE ) THEN 
     301            CALL iom_get( numror, jpdom_auto, 'tb', ts(:,:,:,jp_tem,Kbb) ) 
     302            CALL iom_get( numror, jpdom_auto, 'sb', ts(:,:,:,jp_sal,Kbb) ) 
     303         ENDIF 
     304      ENDIF 
     305      ! 
     306      IF( .NOT.lk_SWE ) THEN 
     307         IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
     308            CALL iom_get( numror, jpdom_auto, 'rhop'   , rhop )   ! now    potential density 
     309         ELSE 
     310            CALL eos( ts(:,:,:,:,Kmm), rhd, rhop, gdept(:,:,:,Kmm) ) 
     311         ENDIF 
    292312      ENDIF 
    293313      ! 
    294314   END SUBROUTINE rst_read 
     315 
     316 
     317   SUBROUTINE rst_read_ssh( Kbb, Kmm, Kaa ) 
     318      !!--------------------------------------------------------------------- 
     319      !!                   ***  ROUTINE rst_read_ssh  *** 
     320      !! 
     321      !! ** Purpose :   ssh initialization of the sea surface height (ssh) 
     322      !! 
     323      !! ** Method  :   set ssh from restart or read configuration, or user_def 
     324      !!              * ln_rstart = T 
     325      !!                   USE of IOM library to read ssh in the restart file 
     326      !!                   Leap-Frog: Kbb and Kmm are read except for l_1st_euler=T 
     327      !! 
     328      !!              * otherwise  
     329      !!                   call user defined ssh or 
     330      !!                   set to -ssh_ref in wet and drying case with domcfg.nc 
     331      !! 
     332      !!              NB: ssh_b/n are written by restart.F90 
     333      !!---------------------------------------------------------------------- 
     334      INTEGER, INTENT(in) ::   Kbb, Kmm, Kaa   ! ocean time level indices 
     335      ! 
     336      INTEGER ::   ji, jj, jk 
     337      !!---------------------------------------------------------------------- 
     338      ! 
     339      IF(lwp) THEN 
     340         WRITE(numout,*) 
     341         WRITE(numout,*) 'rst_read_ssh : ssh initialization' 
     342         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     343      ENDIF 
     344      ! 
     345      !                            !=============================! 
     346      IF( ln_rstart ) THEN         !==  Read the restart file  ==! 
     347         !                         !=============================! 
     348         ! 
     349         !                                     !*  Read ssh at Kmm 
     350         IF(lwp) WRITE(numout,*) 
     351         IF(lwp) WRITE(numout,*)    '      Kmm sea surface height read in the restart file' 
     352         CALL iom_get( numror, jpdom_auto, 'sshn'   , ssh(:,:,Kmm) ) 
     353         ! 
     354         IF( l_1st_euler ) THEN                !* Euler at first time-step 
     355            IF(lwp) WRITE(numout,*) 
     356            IF(lwp) WRITE(numout,*) '      Euler first time step : ssh(Kbb) = ssh(Kmm)' 
     357            ssh(:,:,Kbb) = ssh(:,:,Kmm) 
     358            ! 
     359         ELSE                                  !* read ssh at Kbb 
     360            IF(lwp) WRITE(numout,*) 
     361            IF(lwp) WRITE(numout,*) '      Kbb sea surface height read in the restart file' 
     362            CALL iom_get( numror, jpdom_auto, 'sshb', ssh(:,:,Kbb) ) 
     363         ENDIF 
     364         !                         !============================! 
     365      ELSE                         !==  Initialize at "rest"  ==! 
     366         !                         !============================! 
     367         ! 
     368         IF(lwp) WRITE(numout,*) 
     369         IF(lwp) WRITE(numout,*)    '      initialization at rest' 
     370         ! 
     371         IF( ll_wd ) THEN                      !* wet and dry  
     372            ! 
     373            IF( ln_read_cfg  ) THEN                 ! read configuration : ssh_ref is read in domain_cfg file 
     374!!st  why ssh is not masked : i.e. ssh(:,:,Kmm) = -ssh_ref*ssmask(:,:), 
     375!!st  since at the 1st time step lbclnk will be applied on ssh at Kaa but not initially at Kbb and Kmm 
     376               ssh(:,:,Kbb) = -ssh_ref 
     377               ! 
     378               DO_2D( 1, 1, 1, 1 ) 
     379                  IF( ht_0(ji,jj)-ssh_ref <  rn_wdmin1 ) THEN   ! if total depth is less than min depth 
     380                     ssh(ji,jj,Kbb) = rn_wdmin1 - ht_0(ji,jj) 
     381                  ENDIF 
     382               END_2D 
     383            ELSE                                    ! user define configuration case   
     384               CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) ) 
     385            ENDIF 
     386            ! 
     387         ELSE                                  !* user defined configuration 
     388            CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) ) 
     389            ! 
     390         ENDIF 
     391         ! 
     392         ssh(:,:,Kmm) = ssh(:,:,Kbb)           !* set now values from to before ones 
     393         ssh(:,:,Kaa) = 0._wp  
     394      ENDIF 
     395      ! 
     396   END SUBROUTINE rst_read_ssh 
    295397 
    296398   !!===================================================================== 
Note: See TracChangeset for help on using the changeset viewer.