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 7351 for branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90 – NEMO

Ignore:
Timestamp:
2016-11-28T17:04:10+01:00 (7 years ago)
Author:
emanuelaclementi
Message:

ticket #1805 step 3: /2016/dev_INGV_UKMO_2016 aligned to the trunk at revision 7161

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_INGV_UKMO_2016/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r5836 r7351  
    2727   USE in_out_manager  ! I/O manager 
    2828   USE iom             ! I/O module 
    29  
     29   USE diurnal_bulk 
     30    
    3031   IMPLICIT NONE 
    3132   PRIVATE 
     
    3738 
    3839   !! * Substitutions 
    39 #  include "domzgr_substitute.h90" 
    4040#  include "vectopt_loop_substitute.h90" 
    4141   !!---------------------------------------------------------------------- 
     
    9595               WRITE(numout,*) 
    9696               SELECT CASE ( jprstlib ) 
    97                CASE ( jprstdimg )   ;   WRITE(numout,*)                            & 
    98                    '             open ocean restart binary file: ',TRIM(clpath)//clname 
    9997               CASE DEFAULT         ;   WRITE(numout,*)                            & 
    10098                   '             open ocean restart NetCDF file: ',TRIM(clpath)//clname 
     
    126124      !!---------------------------------------------------------------------- 
    127125 
    128                      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics time step 
    129                      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1) )   ! surface tracer time step 
    130  
     126                     CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt       )   ! dynamics and tracer time step 
     127 
     128      IF ( .NOT. ln_diurnal_only ) THEN 
    131129                     CALL iom_rstput( kt, nitrst, numrow, 'ub'     , ub        )     ! before fields 
    132130                     CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vb        ) 
     
    141139                     CALL iom_rstput( kt, nitrst, numrow, 'sshn'   , sshn      ) 
    142140                     CALL iom_rstput( kt, nitrst, numrow, 'rhop'   , rhop      ) 
     141 
     142                  ! extra variable needed for the ice sheet coupling 
     143                  IF ( ln_iscpl ) THEN  
     144                     CALL iom_rstput( kt, nitrst, numrow, 'tmask'  , tmask     ) ! need to extrapolate T/S 
     145                     CALL iom_rstput( kt, nitrst, numrow, 'umask'  , umask     ) ! need to correct barotropic velocity 
     146                     CALL iom_rstput( kt, nitrst, numrow, 'vmask'  , vmask     ) ! need to correct barotropic velocity 
     147                     CALL iom_rstput( kt, nitrst, numrow, 'smask'  , ssmask    ) ! need to correct barotropic velocity 
     148                     CALL iom_rstput( kt, nitrst, numrow, 'e3t_n', e3t_n(:,:,:) )   ! need to compute temperature correction 
     149                     CALL iom_rstput( kt, nitrst, numrow, 'e3u_n', e3u_n(:,:,:) )   ! need to compute bt conservation 
     150                     CALL iom_rstput( kt, nitrst, numrow, 'e3v_n', e3v_n(:,:,:) )   ! need to compute bt conservation 
     151                     CALL iom_rstput( kt, nitrst, numrow, 'gdepw_n', gdepw_n(:,:,:) ) ! need to compute extrapolation if vvl 
     152                  END IF 
     153      ENDIF 
     154       
     155      IF (ln_diurnal) CALL iom_rstput( kt, nitrst, numrow, 'Dsst', x_dsst    )   
     156 
    143157      IF( kt == nitrst ) THEN 
    144158         CALL iom_close( numrow )     ! close the restart file (only at last time step) 
     
    175189            SELECT CASE ( jprstlib ) 
    176190            CASE ( jpnf90    )   ;   WRITE(numout,*) 'rst_read : read oce NetCDF restart file' 
    177             CASE ( jprstdimg )   ;   WRITE(numout,*) 'rst_read : read oce binary restart file' 
    178191            END SELECT 
    179192            IF ( snc4set%luse )      WRITE(numout,*) 'rst_read : configured with NetCDF4 support' 
     
    183196         clpath = TRIM(cn_ocerst_indir) 
    184197         IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/' 
    185          IF ( jprstlib == jprstdimg ) THEN 
    186            ! eventually read netcdf file (monobloc)  for restarting on different number of processors 
    187            ! if {cn_ocerst_in}.nc exists, then set jlibalt to jpnf90 
    188            INQUIRE( FILE = TRIM(cn_ocerst_indir)//'/'//TRIM(cn_ocerst_in)//'.nc', EXIST = llok ) 
    189            IF ( llok ) THEN ; jlibalt = jpnf90  ; ELSE ; jlibalt = jprstlib ; ENDIF 
    190          ENDIF 
    191198         CALL iom_open( TRIM(clpath)//cn_ocerst_in, numror, kiolib = jlibalt ) 
    192199      ENDIF 
     
    202209      !! ** Method  :   Read in restart.nc file fields which are necessary for restart 
    203210      !!---------------------------------------------------------------------- 
    204       REAL(wp) ::   zrdt, zrdttra1 
     211      REAL(wp) ::   zrdt 
    205212      INTEGER  ::   jk 
    206       LOGICAL  ::   llok 
    207213      !!---------------------------------------------------------------------- 
    208214 
     
    214220         IF( zrdt /= rdt )   neuler = 0 
    215221      ENDIF 
    216       IF( iom_varid( numror, 'rdttra1', ldstop = .FALSE. ) > 0 )   THEN 
    217          CALL iom_get( numror, 'rdttra1', zrdttra1 ) 
    218          IF( zrdttra1 /= rdttra(1) )   neuler = 0 
    219       ENDIF 
    220       !  
     222 
     223      ! Diurnal DSST  
     224      IF( ln_diurnal ) CALL iom_get( numror, jpdom_autoglo, 'Dsst' , x_dsst  )  
     225      IF ( ln_diurnal_only ) THEN  
     226         IF(lwp) WRITE( numout, * ) & 
     227         &   "rst_read:- ln_diurnal_only set, setting rhop=rau0"  
     228         rhop = rau0 
     229         CALL iom_get( numror, jpdom_autoglo, 'tn'     , tsn(:,:,1,jp_tem) )  
     230         RETURN  
     231      ENDIF   
     232       
    221233      IF( iom_varid( numror, 'ub', ldstop = .FALSE. ) > 0 ) THEN 
    222234         CALL iom_get( numror, jpdom_autoglo, 'ub'     , ub      )   ! before fields 
     
    237249         CALL iom_get( numror, jpdom_autoglo, 'rhop'   , rhop    )   ! now    potential density 
    238250      ELSE 
    239          CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )    
     251         CALL eos( tsn, rhd, rhop, gdept_n(:,:,:) )    
    240252      ENDIF 
    241253      ! 
     
    246258         sshb (:,:)     = sshn (:,:) 
    247259         ! 
    248          IF( lk_vvl ) THEN 
     260         IF( .NOT.ln_linssh ) THEN 
    249261            DO jk = 1, jpk 
    250                fse3t_b(:,:,jk) = fse3t_n(:,:,jk) 
     262               e3t_b(:,:,jk) = e3t_n(:,:,jk) 
    251263            END DO 
    252264         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.