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

Changeset 11427


Ignore:
Timestamp:
2019-08-09T15:44:20+02:00 (5 years ago)
Author:
davestorkey
Message:

dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap :
Restore independent time level indices for TOP in order to enable the option for
TOP to have a different timestep to OCE (nn_dttrc > 1). But note that this version of
the code only works for nn_dttrc=1. Also sort out the time-level swapping for OFF.
This commit passes the GYRE_PISCES and ORCA2_OFF_PISCES tests but fails restartability
and bit-comparison with the control for ORCA2_ICE_PISCES.

Location:
NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/OCE/nemogcm.F90

    r11426 r11427  
    473473#if defined key_top 
    474474      !                                      ! Passive tracers 
    475                            CALL     trc_init( Nbb, Nnn, Naa ) 
     475                           CALL     trc_init 
    476476#endif 
    477477      IF( l_ldfslp     )   CALL ldf_slp_init    ! slope of lateral mixing 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/OFF/dtadyn.F90

    r11053 r11427  
    4646   PRIVATE 
    4747 
    48    PUBLIC   dta_dyn_init       ! called by opa.F90 
    49    PUBLIC   dta_dyn            ! called by step.F90 
    50    PUBLIC   dta_dyn_sed_init   ! called by opa.F90 
    51    PUBLIC   dta_dyn_sed        ! called by step.F90 
    52    PUBLIC   dta_dyn_swp        ! called by step.F90 
     48   PUBLIC   dta_dyn_init       ! called by nemo_init 
     49   PUBLIC   dta_dyn            ! called by nemo_gcm 
     50   PUBLIC   dta_dyn_sed_init   ! called by nemo_init 
     51   PUBLIC   dta_dyn_sed        ! called by nemo_gcm 
     52   PUBLIC   dta_dyn_atf        ! called by nemo_gcm 
     53   PUBLIC   dta_dyn_sf_interp  ! called by nemo_gcm 
    5354 
    5455   CHARACTER(len=100) ::   cn_dir          !: Root directory for location of ssr files 
     
    535536   END SUBROUTINE dta_dyn_sed_init 
    536537 
    537    SUBROUTINE dta_dyn_swp( kt, Kbb, Kmm, Kaa ) 
     538   SUBROUTINE dta_dyn_atf( kt, Kbb, Kmm, Kaa ) 
    538539     !!--------------------------------------------------------------------- 
    539540      !!                    ***  ROUTINE dta_dyn_swp  *** 
    540541      !! 
    541       !! ** Purpose :   Swap and the data and compute the vertical scale factor  
    542       !!              at U/V/W pointand the depht 
     542      !! ** Purpose :   Asselin time filter of now SSH 
    543543      !!--------------------------------------------------------------------- 
    544544      INTEGER, INTENT(in) :: kt             ! time step 
    545545      INTEGER, INTENT(in) :: Kbb, Kmm, Kaa  ! ocean time level indices 
    546546      ! 
     547      !!--------------------------------------------------------------------- 
     548 
     549      IF( kt == nit000 ) THEN 
     550         IF(lwp) WRITE(numout,*) 
     551         IF(lwp) WRITE(numout,*) 'dta_dyn_atf : Asselin time filter of sea surface height' 
     552         IF(lwp) WRITE(numout,*) '~~~~~~~~~~~ ' 
     553      ENDIF 
     554 
     555      ssh(:,:,Kmm) = ssh(:,:,Kmm) + atfp * ( ssh(:,:,Kbb) - 2 * ssh(:,:,Kmm) + ssh(:,:,Kaa))   
     556 
     557      !! Do we also need to time filter e3t?? 
     558      ! 
     559   END SUBROUTINE dta_dyn_atf 
     560    
     561   SUBROUTINE dta_dyn_sf_interp( kt, Kmm ) 
     562      !!--------------------------------------------------------------------- 
     563      !!                    ***  ROUTINE dta_dyn_sf_interp  *** 
     564      !! 
     565      !! ** Purpose :   Calculate scale factors at U/V/W points and depths 
     566      !!                given the after e3t field 
     567      !!--------------------------------------------------------------------- 
     568      INTEGER, INTENT(in) :: kt   ! time step 
     569      INTEGER, INTENT(in) :: Kmm  ! ocean time level indices 
     570      ! 
    547571      INTEGER             :: ji, jj, jk 
    548572      REAL(wp)            :: zcoef 
    549573      !!--------------------------------------------------------------------- 
    550  
    551       IF( kt == nit000 ) THEN 
    552          IF(lwp) WRITE(numout,*) 
    553          IF(lwp) WRITE(numout,*) 'ssh_swp : Asselin time filter and swap of sea surface height' 
    554          IF(lwp) WRITE(numout,*) '~~~~~~~ ' 
    555       ENDIF 
    556  
    557       ssh(:,:,Kbb) = ssh(:,:,Kmm) + atfp * ( ssh(:,:,Kbb) - 2 * ssh(:,:,Kmm) + ssh(:,:,Kaa))  ! before <-- now filtered 
    558       ssh(:,:,Kmm) = ssh(:,:,Kaa) 
    559  
    560       e3t(:,:,:,Kmm) = e3t(:,:,:,Kaa) 
    561  
    562       ! Reconstruction of all vertical scale factors at now and before time steps 
    563       ! ============================================================================= 
    564574 
    565575      ! Horizontal scale factor interpolations 
     
    571581      ! ------------------------------------ 
    572582      CALL dom_vvl_interpol( e3t(:,:,:,Kmm), e3w (:,:,:,Kmm), 'W' ) 
    573  
    574       e3t(:,:,:,Kbb)  = e3t(:,:,:,Kmm) 
    575       e3u(:,:,:,Kbb)  = e3u(:,:,:,Kmm) 
    576       e3v(:,:,:,Kbb)  = e3v(:,:,:,Kmm) 
    577583 
    578584      ! t- and w- points depth 
     
    592598      END DO 
    593599      ! 
    594       gdept(:,:,:,Kbb) = gdept(:,:,:,Kmm) 
    595       gdepw(:,:,:,Kbb) = gdepw(:,:,:,Kmm) 
    596       ! 
    597    END SUBROUTINE dta_dyn_swp 
    598     
     600   END SUBROUTINE dta_dyn_sf_interp 
    599601 
    600602   SUBROUTINE dta_dyn_ssh( kt, phdivtr, psshb,  pemp, pssha, pe3ta ) 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/OFF/nemogcm.F90

    r11053 r11427  
    119119#else 
    120120                                CALL dta_dyn    ( istp, Nbb, Nnn, Naa )       ! Interpolation of the dynamical fields 
    121          IF( .NOT.ln_linssh )   CALL dta_dyn_swp( istp, Nbb, Nnn, Naa )       ! swap of sea  surface height and vertical scale factors 
    122121#endif 
    123122                                CALL trc_stp    ( istp, Nbb, Nnn, Nrhs, Naa ) ! time-stepping 
     123#if ! defined key_sed_off 
     124         IF( .NOT.ln_linssh )   CALL dta_dyn_atf( istp, Nbb, Nnn, Naa )       ! time filter of sea  surface height and vertical scale factors 
     125#endif 
     126         ! Swap time levels 
     127         Nrhs = Nbb 
     128         Nbb = Nnn 
     129         Nnn = Naa 
     130         Naa = Nrhs 
     131         ! 
     132#if ! defined key_sed_off 
     133         IF( .NOT.ln_linssh )   CALL dta_dyn_sf_interp( istp, Nnn )  ! calculate now grid parameters 
     134#endif 
    124135                                CALL stp_ctl    ( istp, indic )  ! Time loop: control and print 
    125136         istp = istp + 1 
     
    333344#endif 
    334345 
    335                            CALL     trc_init( Nbb, Nnn, Naa )   ! Passive tracers initialization 
     346                           CALL     trc_init                         ! Passive tracers initialization 
    336347                           CALL dia_ptr_init   ! Poleward TRansports initialization 
    337348                            
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP/TRP/trcatf.F90

    r11099 r11427  
    162162         ENDIF 
    163163         ! 
    164          CALL lbc_lnk_multi( 'trcatf', ptr(:,:,:,:,Kbb), 'T', 1._wp, ptr(:,:,:,:,Kmm), 'T', 1._wp, ptr(:,:,:,:,Kaa), 'T', 1._wp ) 
     164         CALL lbc_lnk_multi( 'trcatf', ptr(:,:,:,:,Kmm), 'T', 1._wp, ptr(:,:,:,:,Kaa), 'T', 1._wp, ptr(:,:,:,:,Kaa), 'T', 1._wp ) 
    165165      ENDIF 
    166166      ! 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP/TRP/trctrp.F90

    r11057 r11427  
    3636   PUBLIC   trc_trp    ! called by trc_stp 
    3737 
     38   INTEGER, SAVE :: N_save  !  Save value of time index for time swapping for ln_top_euler=.true. 
     39 
    3840   !!---------------------------------------------------------------------- 
    3941   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    5355      !!              - Update the passive tracers 
    5456      !!---------------------------------------------------------------------- 
    55       INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
    56       INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices 
     57      INTEGER, INTENT( in    ) :: kt                  ! ocean time-step index 
     58      INTEGER, INTENT( inout ) :: Kbb, Kmm, Krhs, Kaa ! TOP time level indices (swapped in this routine) 
    5759      !! --------------------------------------------------------------------- 
    5860      ! 
    5961      IF( ln_timing )   CALL timing_start('trc_trp') 
     62      ! 
     63      IF ( kt == nit000 ) N_save = Kbb 
    6064      ! 
    6165      IF( .NOT. lk_c1d ) THEN 
     
    7983                                CALL trc_zdf    ( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer   ==> after 
    8084                                CALL trc_atf    ( kt, Kbb, Kmm, Kaa , tr )        ! time filtering of "now" tracer fields     
    81          IF( ln_trcrad )        CALL trc_rad    ( kt, Kbb, Kmm, Krhs, tr       )  ! Correct artificial negative concentrations 
    82          IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt, Kbb, Kmm )                  ! internal damping trends on closed seas only 
     85         ! 
     86         ! Swap TOP time levels (= Nrhs_trc, Nbb_trc etc) 
     87         IF( ln_top_euler ) THEN 
     88            ! For Euler timestepping we need the "before" and "now" fields to be the same. 
     89            ! Use N_save to ensure that the indices stay in sync with the (leapfrogging) OCE time indices for nn_dttrc=1. 
     90            Krhs = N_save 
     91            N_save = Kmm 
     92            Kbb = Kaa 
     93         ELSE 
     94            Krhs = Kbb 
     95            Kbb = Kmm 
     96         ENDIF 
     97         Kmm = Kaa 
     98         Kaa = Krhs 
     99         ! 
     100         IF( ln_trcrad )        CALL trc_rad    ( kt, Kbb, Kmm, Krhs, tr   )    ! Correct artificial negative concentrations 
     101         IF( ln_trcdmp_clo )    CALL trc_dmp_clo( kt, Kbb, Kmm )                ! internal damping trends on closed seas only 
    83102 
    84103         ! 
     
    88107                                CALL trc_zdf( kt, Kbb, Kmm, Krhs, tr, Kaa  )  ! vert. mixing & after tracer ==> after 
    89108                                CALL trc_atf( kt, Kbb, Kmm, Kaa , tr )        ! time filtering of "now" tracer fields 
    90           IF( ln_trcrad )       CALL trc_rad( kt, Kbb, Kmm, Krhs, tr       )  ! Correct artificial negative concentrations 
     109         ! 
     110         ! Swap TOP time levels (= Nrhs_trc, Nbb_trc etc) 
     111         Krhs = Kbb 
     112         Kbb = Kmm 
     113         Kmm = Kaa 
     114         Kaa = Krhs 
     115         ! 
     116         IF( ln_trcrad )       CALL trc_rad( kt, Kbb, Kmm, Krhs, tr       )  ! Correct artificial negative concentrations 
    91117         ! 
    92118      END IF 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP/trcini.F90

    r11053 r11427  
    4040CONTAINS 
    4141    
    42    SUBROUTINE trc_init( Kbb, Kmm, Kaa ) 
     42   SUBROUTINE trc_init 
    4343      !!--------------------------------------------------------------------- 
    4444      !!                     ***  ROUTINE trc_init  *** 
     
    5252      !!                or read data or analytical formulation 
    5353      !!--------------------------------------------------------------------- 
    54       INTEGER, INTENT( in ) :: Kbb, Kmm, Kaa ! time level indices 
    5554      ! 
    5655      IF( ln_timing )   CALL timing_start('trc_init') 
     
    5958      IF(lwp) WRITE(numout,*) 'trc_init : initial set up of the passive tracers' 
    6059      IF(lwp) WRITE(numout,*) '~~~~~~~~' 
     60      ! 
     61      ! Initialise time level indices 
     62      Nbb_trc = 1; Nnn_trc = 2; Naa_trc = 3; Nrhs_trc = Naa_trc 
    6163      ! 
    6264      CALL trc_ini_ctl   ! control  
     
    7173      IF(lwp) WRITE(numout,*) 
    7274      ! 
    73       CALL trc_ini_sms( Kmm )   ! SMS 
     75      CALL trc_ini_sms( Nnn_trc )   ! SMS 
    7476      CALL trc_ini_trp          ! passive tracers transport 
    7577      CALL trc_ice_ini          ! Tracers in sea ice 
     
    7981      ENDIF 
    8082      ! 
    81       CALL trc_ini_state( Kbb, Kmm, Kaa )  !  passive tracers initialisation : from a restart or from clim 
     83      CALL trc_ini_state( Nbb_trc, Nnn_trc, Naa_trc )  !  passive tracers initialisation : from a restart or from clim 
    8284      IF( nn_dttrc /= 1 ) & 
    83       CALL trc_sub_ini( Kmm )    ! Initialize variables for substepping passive tracers 
    84       ! 
    85       CALL trc_ini_inv( Kmm )    ! Inventories 
     85      CALL trc_sub_ini( Nnn_trc )    ! Initialize variables for substepping passive tracers 
     86      ! 
     87      CALL trc_ini_inv( Nnn_trc )    ! Inventories 
    8688      ! 
    8789      IF( ln_timing )   CALL timing_stop('trc_init') 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP/trcstp.F90

    r11053 r11427  
    3838 
    3939   !!---------------------------------------------------------------------- 
     40   !! time level indices 
     41   !!---------------------------------------------------------------------- 
     42   INTEGER, PUBLIC :: Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc      !! used by trc_init 
     43 
     44   !!---------------------------------------------------------------------- 
    4045   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
    4146   !! $Id$  
     
    4449CONTAINS 
    4550 
    46    SUBROUTINE trc_stp( kt, Kbb, Kmm, Krhs, Kaa ) 
     51   SUBROUTINE trc_stp( kt, Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ) 
    4752      !!------------------------------------------------------------------- 
    4853      !!                     ***  ROUTINE trc_stp  *** 
     
    5459      !!------------------------------------------------------------------- 
    5560      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
    56       INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices 
     61      INTEGER, INTENT( in ) :: Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ! time level indices 
    5762      ! 
    5863      INTEGER ::   jk, jn   ! dummy loop indices 
     
    7681      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution 
    7782         DO jk = 1, jpk 
    78             cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
     83            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm_oce) * tmask(:,:,jk) 
    7984         END DO 
    8085         IF ( ln_ctl .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )              & 
     
    8691      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    8792      !     
    88       IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt, Kbb, Kmm, Krhs )  ! averaging physical variables for sub-stepping 
     93      IF( nn_dttrc == 1 )  THEN 
     94         IF(lwp) WRITE(numout,*) "Kbb_oce, Kmm_oce, Kaa_oce, Krhs_oce : ",Kbb_oce, Kmm_oce, Kaa_oce, Krhs_oce 
     95         IF(lwp) WRITE(numout,*) "Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc : ",Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc 
     96         IF(lwp) CALL FLUSH(numout) 
     97         CALL mppsync()       
     98         IF( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN 
     99            ! The nn_dttrc == 1 case depends on the OCE and TRC time indices being the same always.  
     100            ! If this is not the case then something has gone wrong. 
     101            CALL ctl_stop( 'trc_stp : nn_dttrc = 1 but OCE and TRC time indices are different! Something has gone wrong.' ) 
     102         ENDIF 
     103      ELSE 
     104         CALL trc_sub_stp( kt, Nbb_trc, Nnn_trc, Nrhs_trc )  ! averaging physical variables for sub-stepping 
     105      ENDIF 
    89106      !     
    90107      IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
     
    95112         ENDIF 
    96113         ! 
    97          tr(:,:,:,:,Krhs) = 0.e0 
     114         tr(:,:,:,:,Nrhs_trc) = 0.e0 
    98115         ! 
    99116                                   CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
    100117         IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
    101                                    CALL trc_wri      ( kt,      Kmm       )       ! output of passive tracers with iom I/O manager 
    102                                    CALL trc_sms      ( kt, Kbb, Kmm, Krhs )       ! tracers: sinks and sources 
    103                                    CALL trc_trp      ( kt, Kbb, Kmm, Krhs, Kaa )  ! transport of passive tracers 
     118                                   CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager 
     119                                   CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources 
     120                                   CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers 
    104121         IF( kt == nittrc000 ) THEN 
    105122            CALL iom_close( numrtr )       ! close input tracer restart file 
    106123            IF(lwm) CALL FLUSH( numont )   ! flush namelist output 
    107124         ENDIF 
    108          IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Krhs )       ! write tracer restart file 
    109          IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,      Kmm       )       ! trends: Mixed-layer 
    110          ! 
    111          IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt, Kbb, Kmm, Krhs )       ! resetting physical variables when sub-stepping 
     125         IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file 
     126         IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer 
     127         ! 
     128         IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! resetting physical variables when sub-stepping 
    112129         ! 
    113130      ENDIF 
     
    116133         ztrai = 0._wp                                                   !  content of all tracers 
    117134         DO jn = 1, jptra 
    118             ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Kmm) * cvol(:,:,:)   ) 
     135            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Nnn_trc) * cvol(:,:,:)   ) 
    119136         END DO 
    120137         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot 
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP/trcsub.F90

    r10969 r11427  
    9292      !!------------------------------------------------------------------- 
    9393      INTEGER, INTENT( in ) ::   kt              ! ocean time-step index 
    94       INTEGER, INTENT( in ) ::   Kbb, Kmm, Krhs  ! ocean time-level index 
     94      INTEGER, INTENT( in ) ::   Kbb, Kmm, Krhs  !       time-level index 
    9595      ! 
    9696      INTEGER ::   ji, jj, jk   ! dummy loop indices 
Note: See TracChangeset for help on using the changeset viewer.