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 14200 for NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/IOM/restart.F90 – NEMO

Ignore:
Timestamp:
2020-12-17T15:36:44+01:00 (4 years ago)
Author:
mcastril
Message:

Merging r14117 through r14199 into dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/OCE/IOM/restart.F90

    r14072 r14200  
    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 
     13   !!            4.1  !  2020-11  (S. Techene, G. Madec)  move ssh initiatlisation in rst_read_ssh 
     14   !!             -   !                                   add restart in Shallow Water Eq. case 
    1415   !!---------------------------------------------------------------------- 
    1516 
    1617   !!---------------------------------------------------------------------- 
    17    !!   rst_opn    : open the ocean restart file 
    18    !!   rst_write  : write the ocean restart file 
    19    !!   rst_read   : read the ocean restart file 
     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 
    2023   !!---------------------------------------------------------------------- 
    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 
     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" 
     49#  include "domzgr_substitute.h90" 
    4150   !!---------------------------------------------------------------------- 
    4251   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    142151      !! 
    143152      !!                NB: ssh is written here (rst_write) 
    144       !!                    but is read or set in DYN/sshwzv:shh_init_rst 
     153      !!                    but is read or set in rst_read_ssh 
    145154      !!---------------------------------------------------------------------- 
    146155      INTEGER, INTENT(in) ::   kt         ! ocean time-step 
    147156      INTEGER, INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
    148157      !!---------------------------------------------------------------------- 
    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 ) 
     158      ! 
     159         CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rn_Dt       )   ! dynamics time step 
     160      ! 
     161      IF( .NOT.lwxios )   CALL iom_delay_rst( 'WRITE', 'OCE', numrow )   ! save only ocean delayed global communication variables 
     162      ! 
     163      IF( .NOT.ln_diurnal_only ) THEN 
     164         CALL iom_rstput( kt, nitrst, numrow, 'sshb'   , ssh(:,:        ,Kbb) )     ! before fields 
     165         CALL iom_rstput( kt, nitrst, numrow, 'ub'     , uu(:,:,:       ,Kbb) ) 
     166         CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vv(:,:,:       ,Kbb) ) 
     167         IF( .NOT.lk_SWE ) THEN 
     168            CALL iom_rstput( kt, nitrst, numrow, 'tb'  , ts(:,:,:,jp_tem,Kbb) ) 
     169            CALL iom_rstput( kt, nitrst, numrow, 'sb'  , ts(:,:,:,jp_sal,Kbb) ) 
     170         ENDIF 
     171         ! 
     172#if ! defined key_RK3 
     173         CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , ssh(:,:        ,Kmm) )     ! now fields 
     174         CALL iom_rstput( kt, nitrst, numrow, 'un'     , uu(:,:,:       ,Kmm) ) 
     175         CALL iom_rstput( kt, nitrst, numrow, 'vn'     , vv(:,:,:       ,Kmm) ) 
     176         IF( .NOT.lk_SWE ) THEN 
     177            CALL iom_rstput( kt, nitrst, numrow, 'tn'  , ts(:,:,:,jp_tem,Kmm) ) 
     178            CALL iom_rstput( kt, nitrst, numrow, 'sn'  , ts(:,:,:,jp_sal,Kmm) ) 
     179            CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop                 ) 
     180         ENDIF 
     181#endif 
     182      ENDIF 
     183 
     184      IF( ln_diurnal )   CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst ) 
    168185      IF( kt == nitrst ) THEN 
    169          IF(.NOT.lwxios) THEN 
     186         IF( .NOT.lwxios ) THEN 
    170187            CALL iom_close( numrow )     ! close the restart file (only at last time step) 
    171188         ELSE 
     
    177194!!gm  not sure what to do here   ===>>>  ask to Sebastian 
    178195         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 
     196         IF( ln_rst_list ) THEN 
     197            nrst_lst = MIN(nrst_lst + 1, SIZE(nn_stocklist,1)) 
     198            nitrst  = nn_stocklist( nrst_lst ) 
     199         ENDIF 
    183200      ENDIF 
    184201      ! 
     
    245262      !!                    (sshb) 
    246263      !! 
    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 
     264      !!                NB: ssh is read or set in rst_read_ssh 
     265      !!---------------------------------------------------------------------- 
     266      INTEGER          , INTENT(in) ::   Kbb, Kmm   ! ocean time level indices 
    251267      INTEGER  ::   jk 
    252268      REAL(wp), DIMENSION(jpi, jpj, jpk) :: w3d 
    253       !!---------------------------------------------------------------------- 
    254       ! 
    255       IF(.NOT.lrxios ) CALL iom_delay_rst( 'READ', 'OCE', numror )   ! read only ocean delayed global communication variables 
     269      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zgdept       ! 3D workspace for QCO 
     270      !!---------------------------------------------------------------------- 
     271      ! 
     272      IF(.NOT.lrxios )   CALL iom_delay_rst( 'READ', 'OCE', numror )   ! read only ocean delayed global communication variables 
    256273      ! 
    257274      !                             !*  Diurnal DSST 
    258275      IF( ln_diurnal )   CALL iom_get( numror, jpdom_auto, 'Dsst' , x_dsst ) 
    259       IF ( ln_diurnal_only ) THEN 
     276      IF( ln_diurnal_only ) THEN 
    260277         IF(lwp) WRITE( numout, * ) & 
    261278         &   "rst_read:- ln_diurnal_only set, setting rhop=rho0" 
     
    266283      ENDIF 
    267284      ! 
    268       !                             !*  Read Kmm fields 
     285#if defined key_RK3 
     286      !                             !*  Read Kbb fields   (NB: in RK3 Kmm = Kbb = Nbb) 
     287      IF(lwp) WRITE(numout,*) '           Kbb u, v and T-S fields read in the restart file' 
     288      CALL iom_get( numror, jpdom_auto, 'ub'   , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp ) 
     289      CALL iom_get( numror, jpdom_auto, 'vb'   , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp ) 
     290      IF( .NOT.lk_SWE ) THEN 
     291         CALL iom_get( numror, jpdom_auto, 'tb', ts(:,:,:,jp_tem,Kbb) ) 
     292         CALL iom_get( numror, jpdom_auto, 'sb', ts(:,:,:,jp_sal,Kbb) ) 
     293      ENDIF 
     294#else 
     295      !                             !*  Read Kmm fields   (MLF only) 
    269296      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) ) 
    274       ! 
    275       IF( l_1st_euler ) THEN        !*  Euler restart 
     297      CALL iom_get( numror, jpdom_auto, 'un'   , uu(:,:,:       ,Kmm), cd_type = 'U', psgn = -1._wp ) 
     298      CALL iom_get( numror, jpdom_auto, 'vn'   , vv(:,:,:       ,Kmm), cd_type = 'V', psgn = -1._wp ) 
     299      IF( .NOT.lk_SWE ) THEN 
     300         CALL iom_get( numror, jpdom_auto, 'tn', ts(:,:,:,jp_tem,Kmm) ) 
     301         CALL iom_get( numror, jpdom_auto, 'sn', ts(:,:,:,jp_sal,Kmm) ) 
     302      ENDIF 
     303      ! 
     304      IF( l_1st_euler ) THEN        !*  Euler restart   (MLF only) 
    276305         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) 
     306         uu(:,:,:  ,Kbb) = uu(:,:,:  ,Kmm)         ! all before fields set to now values 
    279307         vv(:,:,:  ,Kbb) = vv(:,:,:  ,Kmm) 
    280       ELSE                          !* Leap frog restart 
     308         IF( .NOT.lk_SWE ) ts(:,:,:,:,Kbb) = ts(:,:,:,:,Kmm) 
     309         ! 
     310      ELSE                          !* Leap frog restart   (MLF only) 
    281311         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) ) 
     312         CALL iom_get( numror, jpdom_auto, 'ub'   , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp ) 
     313         CALL iom_get( numror, jpdom_auto, 'vb'   , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp ) 
     314         IF( .NOT.lk_SWE ) THEN 
     315            CALL iom_get( numror, jpdom_auto, 'tb', ts(:,:,:,jp_tem,Kbb) ) 
     316            CALL iom_get( numror, jpdom_auto, 'sb', ts(:,:,:,jp_sal,Kbb) ) 
     317         ENDIF 
     318      ENDIF 
     319#endif 
     320      ! 
     321      IF( .NOT.lk_SWE ) THEN 
     322         IF( iom_varid( numror, 'rhop', ldstop = .FALSE. ) > 0 ) THEN 
     323            CALL iom_get( numror, jpdom_auto, 'rhop'   , rhop )   ! now    potential density 
     324         ELSE 
     325#if defined key_qco 
     326            ALLOCATE( zgdept(jpi,jpj,jpk) ) 
     327            DO jk = 1, jpk 
     328               zgdept(:,:,jk) = gdept(:,:,jk,Kmm) 
     329            END DO 
     330            CALL eos( ts(:,:,:,:,Kmm), rhd, rhop, zgdept ) 
     331            DEALLOCATE( zgdept ) 
     332#else 
     333            CALL eos( ts(:,:,:,:,Kmm), rhd, rhop, gdept(:,:,:,Kmm) ) 
     334#endif 
     335         ENDIF 
    292336      ENDIF 
    293337      ! 
    294338   END SUBROUTINE rst_read 
     339 
     340 
     341   SUBROUTINE rst_read_ssh( Kbb, Kmm, Kaa ) 
     342      !!--------------------------------------------------------------------- 
     343      !!                   ***  ROUTINE rst_read_ssh  *** 
     344      !! 
     345      !! ** Purpose :   ssh initialization of the sea surface height (ssh) 
     346      !! 
     347      !! ** Method  :   set ssh from restart or read configuration, or user_def 
     348      !!              * ln_rstart = T 
     349      !!                   USE of IOM library to read ssh in the restart file 
     350      !!                   Leap-Frog: Kbb and Kmm are read except for l_1st_euler=T 
     351      !! 
     352      !!              * otherwise  
     353      !!                   call user defined ssh or 
     354      !!                   set to -ssh_ref in wet and drying case with domcfg.nc 
     355      !! 
     356      !!              NB: ssh_b/n are written by restart.F90 
     357      !!---------------------------------------------------------------------- 
     358      INTEGER, INTENT(in) ::   Kbb, Kmm, Kaa   ! ocean time level indices 
     359      ! 
     360      INTEGER ::   ji, jj, jk 
     361      !!---------------------------------------------------------------------- 
     362      ! 
     363      IF(lwp) THEN 
     364         WRITE(numout,*) 
     365         WRITE(numout,*) 'rst_read_ssh : ssh initialization' 
     366         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     367      ENDIF 
     368      ! 
     369      !                            !=============================! 
     370      IF( ln_rstart ) THEN         !==  Read the restart file  ==! 
     371         !                         !=============================! 
     372         ! 
     373#if defined key_RK3 
     374         !                                     !*  RK3: Read ssh at Kbb 
     375         IF(lwp) WRITE(numout,*) 
     376         IF(lwp) WRITE(numout,*)    '      Kbb sea surface height read in the restart file' 
     377         CALL iom_get( numror, jpdom_auto, 'sshb'   , ssh(:,:,Kbb) ) 
     378         ! 
     379         !                                     !*  RK3: Set ssh at Kmm for AGRIF 
     380         ssh(:,:,Kmm) = 0._wp 
     381#else 
     382         !                                     !*  MLF: Read ssh at Kmm 
     383         IF(lwp) WRITE(numout,*) 
     384         IF(lwp) WRITE(numout,*)    '      Kmm sea surface height read in the restart file' 
     385         CALL iom_get( numror, jpdom_auto, 'sshn'   , ssh(:,:,Kmm) ) 
     386         ! 
     387         IF( l_1st_euler ) THEN                !*  MLF: Euler at first time-step 
     388            IF(lwp) WRITE(numout,*) 
     389            IF(lwp) WRITE(numout,*) '      Euler first time step : ssh(Kbb) = ssh(Kmm)' 
     390            ssh(:,:,Kbb) = ssh(:,:,Kmm) 
     391            ! 
     392         ELSE                                  !*  MLF: read ssh at Kbb 
     393            IF(lwp) WRITE(numout,*) 
     394            IF(lwp) WRITE(numout,*) '      Kbb sea surface height read in the restart file' 
     395            CALL iom_get( numror, jpdom_auto, 'sshb', ssh(:,:,Kbb) ) 
     396         ENDIF 
     397#endif 
     398         !                         !============================! 
     399      ELSE                         !==  Initialize at "rest"  ==! 
     400         !                         !============================! 
     401         ! 
     402         IF(lwp) WRITE(numout,*) 
     403         IF(lwp) WRITE(numout,*)    '      initialization at rest' 
     404         ! 
     405         IF( ll_wd ) THEN                      !* wet and dry  
     406            ! 
     407            IF( ln_read_cfg  ) THEN                 ! read configuration : ssh_ref is read in domain_cfg file 
     408!!st  why ssh is not masked : i.e. ssh(:,:,Kmm) = -ssh_ref*ssmask(:,:), 
     409!!st  since at the 1st time step lbclnk will be applied on ssh at Kaa but not initially at Kbb and Kmm 
     410               ssh(:,:,Kbb) = -ssh_ref 
     411               ! 
     412               DO_2D( 1, 1, 1, 1 ) 
     413                  IF( ht_0(ji,jj)-ssh_ref <  rn_wdmin1 ) THEN   ! if total depth is less than min depth 
     414                     ssh(ji,jj,Kbb) = rn_wdmin1 - ht_0(ji,jj) 
     415                  ENDIF 
     416               END_2D 
     417            ELSE                                    ! user define configuration case   
     418               CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) ) 
     419            ENDIF 
     420            ! 
     421         ELSE                                  !* user defined configuration 
     422            CALL usr_def_istate_ssh( tmask, ssh(:,:,Kbb) ) 
     423            ! 
     424         ENDIF 
     425         ! 
     426#if defined key_RK3 
     427         ssh(:,:,Kmm) = 0._wp                  !* RK3: set Kmm to 0 for AGRIF 
     428#else 
     429         ssh(:,:,Kmm) = ssh(:,:,Kbb)           !* MLF: set now values from to before ones  
     430#endif 
     431      ENDIF 
     432      ! 
     433      !                            !==========================! 
     434      ssh(:,:,Kaa) = 0._wp         !==  Set to 0 for AGRIF  ==! 
     435      !                            !==========================! 
     436      ! 
     437   END SUBROUTINE rst_read_ssh 
    295438 
    296439   !!===================================================================== 
Note: See TracChangeset for help on using the changeset viewer.