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 5208 for branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/OPA_SRC/step.F90 – NEMO

Ignore:
Timestamp:
2015-04-13T15:08:59+02:00 (9 years ago)
Author:
davestorkey
Message:

Merge in changes from trunk up to 5021.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4650_UKMO11_restart_functionality/NEMOGCM/NEMO/OPA_SRC/step.F90

    r4760 r5208  
    2424   !!             -   !  2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase + merge TRC-TRA 
    2525   !!            3.4  !  2011-04  (G. Madec, C. Ethe) Merge of dtatem and dtasal 
    26    !!                 !  2012-07  (J. Simeon, G. Madec. C. Ethe) Online coarsening of outputs 
     26   !!                 !  2012-07  (J. Simeon, G. Madec, C. Ethe) Online coarsening of outputs 
     27   !!            3.7  !  2014-04  (F. Roquet, G. Madec) New equations of state 
    2728   !!---------------------------------------------------------------------- 
    2829 
     
    3132   !!---------------------------------------------------------------------- 
    3233   USE step_oce         ! time stepping definition modules 
     34   USE iom 
    3335 
    3436   IMPLICIT NONE 
     
    3941   !! * Substitutions 
    4042#  include "domzgr_substitute.h90" 
    41 #  include "zdfddm_substitute.h90" 
    42    !!---------------------------------------------------------------------- 
    43    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     43!!gm   #  include "zdfddm_substitute.h90" 
     44   !!---------------------------------------------------------------------- 
     45   !! NEMO/OPA 3.7 , NEMO Consortium (2014) 
    4446   !! $Id$ 
    4547   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    106108      ! Ocean physics update                (ua, va, tsa used as workspace) 
    107109      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    108                          CALL bn2( tsb, rn2b )        ! before Brunt-Vaisala frequency 
    109                          CALL bn2( tsn, rn2  )        ! now    Brunt-Vaisala frequency 
     110      !  THERMODYNAMICS 
     111                         CALL eos_rab( tsb, rab_b )       ! before local thermal/haline expension ratio at T-points 
     112                         CALL eos_rab( tsn, rab_n )       ! now    local thermal/haline expension ratio at T-points 
     113                         CALL bn2    ( tsb, rab_b, rn2b ) ! before Brunt-Vaisala frequency 
     114                         CALL bn2    ( tsn, rab_n, rn2  ) ! now    Brunt-Vaisala frequency 
    110115      ! 
    111116      !  VERTICAL PHYSICS 
     
    141146      IF( lk_ldfslp ) THEN                            ! slope of lateral mixing 
    142147                         CALL eos( tsb, rhd, gdept_0(:,:,:) )             ! before in situ density 
    143          IF( ln_zps )    CALL zps_hde( kstp, jpts, tsb, gtsu, gtsv,  &    ! Partial steps: before horizontal gradient 
    144             &                                      rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
     148         IF( ln_zps )    CALL zps_hde( kstp, jpts, tsb, gtsu, gtsv,  &        ! Partial steps: before horizontal gradient 
     149            &                                      rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   &             ! 
     150            &                               gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi  )  ! of t, s, rd at the last ocean level 
    145151         IF( ln_traldf_grif ) THEN                           ! before slope for Griffies operator 
    146152                         CALL ldf_slp_grif( kstp ) 
     
    170176          ! Note that the computation of vertical velocity above, hence "after" sea level 
    171177          ! is necessary to compute momentum advection for the rhs of barotropic loop: 
    172                                   CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) ) ! now in situ density for hpg computation 
    173           IF( ln_zps      )       CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &   ! zps: now hor. derivative 
    174                 &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
     178                            CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) ) ! now in situ density for hpg computation 
     179            IF( ln_zps )    CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &        ! Partial steps: before horizontal gradient 
     180               &                                      rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   &             ! 
     181               &                               gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi  )  ! of t, s, rd at the last ocean level 
    175182 
    176183                                  ua(:,:,:) = 0.e0             ! set dynamics trends to zero 
     
    203210      IF( lk_floats  )   CALL flo_stp( kstp )         ! drifting Floats 
    204211      IF( lk_diahth  )   CALL dia_hth( kstp )         ! Thermocline depth (20 degres isotherm depth) 
    205       IF( lk_diafwb  )  CALL dia_fwb( kstp )         ! Fresh water budget diagnostics 
     212      IF( .NOT. lk_cpl ) CALL dia_fwb( kstp )         ! Fresh water budget diagnostics 
    206213      IF( ln_diaptr  )   CALL dia_ptr( kstp )         ! Poleward TRansports diagnostics 
    207214      IF( lk_diadct  )   CALL dia_dct( kstp )         ! Transports 
     
    219226                         CALL trc_stp( kstp )         ! time-stepping 
    220227#endif 
     228 
    221229 
    222230      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    245253                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
    246254                             CALL eos    ( tsa, rhd, rhop, fsdept_n(:,:,:) )  ! Time-filtered in situ density for hpg computation 
    247          IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsa, gtsu, gtsv,  &    ! zps: time filtered hor. derivative 
    248             &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
    249  
     255         IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsa, gtsu, gtsv,  &        ! Partial steps: before horizontal gradient 
     256            &                                      rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   &             ! 
     257            &                               gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi  )  ! of t, s, rd at the last ocean level 
    250258      ELSE                                                  ! centered hpg  (eos then time stepping) 
    251259         IF ( .NOT. lk_dynspg_ts ) THEN                     ! eos already called in time-split case 
    252                                 CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )  ! now in situ density for hpg computation 
    253             IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &    ! zps: now hor. derivative 
    254             &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
     260                             CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )  ! now in situ density for hpg computation 
     261         IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &        ! Partial steps: before horizontal gradient 
     262         &                                      rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   &             ! 
     263         &                               gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi  )  ! of t, s, rd at the last ocean level 
    255264         ENDIF 
    256265         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
     
    313322                 CALL iom_close( numror )     ! close input  ocean restart file 
    314323         IF(lwm) CALL FLUSH    ( numond )     ! flush output namelist oce 
    315          IF(lwm) CALL FLUSH    ( numoni )     ! flush output namelist ice     
     324         IF( lwm.AND.numoni /= -1 ) CALL FLUSH    ( numoni )     ! flush output namelist ice     
    316325      ENDIF 
    317326      IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file 
    318  
    319       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    320       ! Trends                              (ua, va, tsa used as workspace) 
    321       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    322       IF( nstop == 0 ) THEN 
    323          IF( lk_trddyn     )   CALL trd_dwr( kstp )         ! trends: dynamics 
    324          IF( lk_trdtra     )   CALL trd_twr( kstp )         ! trends: active tracers 
    325          IF( lk_trdmld     )   CALL trd_mld( kstp )         ! trends: Mixed-layer 
    326          IF( lk_trdvor     )   CALL trd_vor( kstp )         ! trends: vorticity budget 
    327       ENDIF 
    328327 
    329328      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
Note: See TracChangeset for help on using the changeset viewer.