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

Changeset 75


Ignore:
Timestamp:
2004-04-22T14:42:43+02:00 (20 years ago)
Author:
opalod
Message:

CT : UPDATE049 : # Use logical key lk_cpl instead of cpp key key_coupled and CALL cpl_stp instead of CALL cpl_cmo

# Now the vorticity scheme control is done in step.F90 in calling dyn_vor_ctl subroutine

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/step.F90

    r39 r75  
    1414   USE ldftra_oce 
    1515   USE ldfdyn_oce 
    16    USE cpl             ! coupled exchanges (???) 
     16   USE cpl_oce         ! ???  
    1717   USE in_out_manager  ! I/O manager 
    1818   USE lbclnk 
     
    4141   USE dynspg_rl       ! surface pressure gradient     (dyn_spg_rl routine) 
    4242   USE dynkeg          ! kinetic energy gradient          (dyn_keg routine) 
    43    USE dynvor          ! vorticity term                   (dyn_vor routine) 
     43   USE dynvor          ! vorticity term              (dyn_vor_... routines) 
    4444   USE dynzad          ! vertical advection               (dyn_adv routine) 
    4545   USE dynldf_bilapg   ! lateral mixing            (dyn_ldf_bilapg routine) 
     
    117117 
    118118   USE stpctl          ! time stepping control            (stp_ctl routine) 
    119    USE restart         ! ocean restart                  (rst_write routine) 
     119   USE restart         ! ocean restart                    (rst_wri routine) 
     120   USE cpl             ! exchanges in coupled mode        (cpl_stp routine) 
    120121 
    121122   IMPLICIT NONE 
     
    209210         ENDIF 
    210211         IF( lk_diaptr ) CALL dia_ptr_init            ! Poleward TRansport initialization 
    211       ENDIF 
    212  
    213       IF( l_ctl .AND. lwp ) THEN         ! print mean trends (used for debugging) 
     212 
     213      ENDIF 
     214 
     215      IF(l_ctl) THEN         ! print mean trends (used for debugging) 
    214216         WRITE(numout,*) ' emp  -   : ', SUM( emp       * tmask(:,:,1) ) 
    215217         WRITE(numout,*) ' emps -   : ', SUM( emps      * tmask(:,:,1) ) 
     
    262264      IF( lk_zdfddm )   CALL zdf_ddm( kstp )                 ! double diffusive mixing 
    263265 
    264                         CALL zdf_bfr( kstp )                 ! Bottom boudary condition 
     266                        CALL zdf_bfr( kstp )                 ! bottom friction 
    265267 
    266268                        CALL zdf_mxl( kstp )                 ! mixed layer depth 
     
    302304      !----------------------------------------------------------------------- 
    303305 
    304                                 ta(:,:,:) = 0.e0               ! set tracer trends to zero 
    305                                 sa(:,:,:) = 0.e0 
    306  
    307                                 CALL tra_sbc( kstp )           ! surface boundary condition 
     306                               ta(:,:,:) = 0.e0               ! set tracer trends to zero 
     307                               sa(:,:,:) = 0.e0 
     308 
     309                               CALL tra_sbc( kstp )           ! surface boundary condition 
    308310 
    309311      IF( ln_traqsr        )   CALL tra_qsr( kstp )           ! penetrative solar radiation qsr 
     
    314316      IF( lk_trabbl_adv    )   CALL tra_bbl_adv( kstp )           ! advective (and/or diffusive) bottom boundary layer scheme 
    315317 
    316       IF( lk_tradmp        )   CALL tra_dmp( kstp )            ! internal damping trends 
    317  
    318       !                                                        ! horizontal & vertical advection 
     318      IF( lk_tradmp        )   CALL tra_dmp( kstp )           ! internal damping trends 
     319 
     320      !                                                       ! horizontal & vertical advection 
    319321      IF( kstp == nit000   )   CALL tra_adv_ctl                    ! chose/control the scheme used 
    320322      IF( ln_traadv_cen2   )   CALL tra_adv_cen2  ( kstp )         ! 2nd order centered scheme 
     
    323325      IF( ln_traadv_muscl2 )   CALL tra_adv_muscl2( kstp )         ! MUSCL2 scheme 
    324326 
    325       IF( n_cla == 1       )   CALL tra_cla( kstp )            ! Cross Land Advection (Update Hor. advection) 
    326  
    327       !                                                        ! lateral mixing  
    328       IF( l_traldf_lap      )   CALL tra_ldf_lap    ( kstp )           ! iso-level laplacian 
    329       IF( l_traldf_bilap    )   CALL tra_ldf_bilap  ( kstp )           ! iso-level bilaplacian  
    330       IF( l_traldf_bilapg   )   CALL tra_ldf_bilapg ( kstp )           ! s-coord. horizontal bilaplacian 
    331       IF( l_traldf_iso      )   CALL tra_ldf_iso    ( kstp )           ! iso-neutral/geopot. laplacian  
    332       IF( l_traldf_iso_zps  )   CALL tra_ldf_iso_zps( kstp )           ! partial step iso-neutral/geopot. laplacian 
    333  
    334       !                                                        ! vertical diffusion 
    335       IF( l_trazdf_exp      )   CALL tra_zdf_exp     ( kstp )          ! explicit time stepping (time splitting scheme) 
    336       IF( l_trazdf_imp      )   CALL tra_zdf_imp     ( kstp )          ! implicit time stepping (euler backward) 
    337       IF( l_trazdf_iso      )   CALL tra_zdf_iso     ( kstp )          ! isopycnal 
    338       IF( l_trazdf_iso_vo   )   CALL tra_zdf_iso_vopt( kstp )          ! vector opt. isopycnal 
    339  
    340                                 CALL tra_nxt( kstp )           ! tracer fields at next time step 
    341  
    342       IF( ln_zdfnpc         )   CALL tra_npc( kstp )           ! update the new (t,s) fields by non 
    343       !                                                        ! penetrative convective adjustment 
    344  
    345       IF( ln_dynhpg_imp     ) THEN                             ! semi-implicit hpg  
    346                                    CALL eos( ta, sa, rhd, rhop )   ! Time-filtered in situ density used in dynhpg module 
    347          IF( lk_zps    )           CALL zps_hde( kstp, ta, sa, rhd,  & ! Partial steps: time filtered hor. gradient  
    348             &                                         gtu, gsu, gru, & ! of t, s, rd at the bottom ocean level 
    349             &                                         gtv, gsv, grv )   
    350       ELSE                                                     ! centered hpg (default case) 
     327      IF( n_cla == 1       )   CALL tra_cla( kstp )           ! Cross Land Advection (Update Hor. advection) 
     328 
     329      !                                                       ! lateral mixing  
     330      IF( l_traldf_lap     )   CALL tra_ldf_lap    ( kstp )           ! iso-level laplacian 
     331      IF( l_traldf_bilap   )   CALL tra_ldf_bilap  ( kstp )           ! iso-level bilaplacian  
     332      IF( l_traldf_bilapg  )   CALL tra_ldf_bilapg ( kstp )           ! s-coord. horizontal bilaplacian 
     333      IF( l_traldf_iso     )   CALL tra_ldf_iso    ( kstp )           ! iso-neutral/geopot. laplacian  
     334      IF( l_traldf_iso_zps )   CALL tra_ldf_iso_zps( kstp )           ! partial step iso-neutral/geopot. laplacian 
     335 
     336      !                                                       ! vertical diffusion 
     337      IF( l_trazdf_exp     )   CALL tra_zdf_exp     ( kstp )          ! explicit time stepping (time splitting scheme) 
     338      IF( l_trazdf_imp     )   CALL tra_zdf_imp     ( kstp )          ! implicit time stepping (euler backward) 
     339      IF( l_trazdf_iso     )   CALL tra_zdf_iso     ( kstp )          ! isopycnal 
     340      IF( l_trazdf_iso_vo  )   CALL tra_zdf_iso_vopt( kstp )          ! vector opt. isopycnal 
     341 
     342                               CALL tra_nxt( kstp )           ! tracer fields at next time step 
     343 
     344      IF( ln_zdfnpc        )   CALL tra_npc( kstp )           ! update the new (t,s) fields by non 
     345      !                                                       ! penetrative convective adjustment 
     346 
     347      IF( ln_dynhpg_imp    ) THEN                             ! semi-implicit hpg  
     348                                  CALL eos( ta, sa, rhd, rhop )   ! Time-filtered in situ density used in dynhpg module 
     349         IF( lk_zps    )          CALL zps_hde( kstp, ta, sa, rhd,  & ! Partial steps: time filtered hor. gradient  
     350            &                                        gtu, gsu, gru, & ! of t, s, rd at the bottom ocean level 
     351            &                                        gtv, gsv, grv )   
     352      ELSE                                                    ! centered hpg (default case) 
    351353                                  CALL eos( tb, sb, rhd, rhop )       ! now (swap=before) in situ density for dynhpg module 
    352354         IF( lk_zps    )          CALL zps_hde( kstp, tb, sb, rhd,  & ! Partial steps: now horizontal gradient 
     
    361363      !----------------------------------------------------------------------- 
    362364 
    363                             ua(:,:,:) = 0.e0                ! set dynamics trends to zero 
    364                             va(:,:,:) = 0.e0 
    365  
    366                             CALL dyn_keg( kstp )            ! horizontal gradient of kinetic energy 
    367  
    368       !                                                     ! vorticity term including Coriolis 
     365                               ua(:,:,:) = 0.e0               ! set dynamics trends to zero 
     366                               va(:,:,:) = 0.e0 
     367 
     368                               CALL dyn_keg( kstp )           ! horizontal gradient of kinetic energy 
     369 
     370      !                                                       ! vorticity term including Coriolis 
     371      IF( kstp == nit000   )   CALL dyn_vor_ctl                      ! chose/control the scheme used 
    369372      IF( ln_dynvor_ens    )   CALL dyn_vor_enstrophy( kstp )        ! enstrophy conserving scheme 
    370373      IF( ln_dynvor_ene    )   CALL dyn_vor_energy   ( kstp )        ! energy conserving scheme 
    371374      IF( ln_dynvor_mix    )   CALL dyn_vor_mixed    ( kstp )        ! mixed energy/enstrophy conserving scheme 
    372375 
    373       !                                                     ! lateral mixing  
     376      !                                                       ! lateral mixing  
    374377      IF( l_dynldf_lap     )   CALL dyn_ldf_lap    ( kstp )          ! iso-level laplacian 
    375378      IF( l_dynldf_bilap   )   CALL dyn_ldf_bilap  ( kstp )          ! iso-level bilaplacian  
     
    377380      IF( l_dynldf_iso     )   CALL dyn_ldf_iso    ( kstp )          ! iso-neutral laplacian  
    378381 
    379       !                                                     ! horizontal gradient of Hydrostatic pressure  
     382      !                                                       ! horizontal gradient of Hydrostatic pressure  
    380383      IF( lk_dynhpg        )   CALL dyn_hpg     ( kstp )             ! default case  (k-j-i loop) 
    381384      IF( lk_dynhpg_tsk    )   CALL dyn_hpg_atsk( kstp )             ! autatask case (j-k-i loop) 
    382385 
    383                                CALL dyn_zad    ( kstp )     ! vertical advection        
    384  
    385       !                                                     ! vertical diffusion 
     386                               CALL dyn_zad    ( kstp )       ! vertical advection        
     387 
     388      !                                                       ! vertical diffusion 
    386389      IF( l_dynzdf_exp     )   CALL dyn_zdf_exp    ( kstp )         ! explicit time stepping (time splitting scheme) 
    387390      IF( l_dynzdf_imp     )   CALL dyn_zdf_imp    ( kstp )         ! implicit time stepping (euler backward) 
     
    390393 
    391394      IF( lk_dynspg_rl ) THEN  
    392          IF( lk_obc    )       CALL obc_spg( kstp )                 ! surface pressure gradient at open boundaries 
     395         IF( lk_obc    )       CALL obc_spg( kstp )           ! surface pressure gradient at open boundaries 
    393396      ENDIF 
    394397                       indic=0 
    395       !                                                     ! surface pressure gradient 
    396398!i bug lbc sur emp 
    397399      CALL lbc_lnk( emp, 'T', 1. ) 
    398400!i 
     401      !                                                       ! surface pressure gradient 
    399402      IF( lk_dynspg_fsc     )   CALL dyn_spg_fsc     ( kstp, indic )  ! free surface constant volume case 
    400403      IF( lk_dynspg_fsc_tsk )   CALL dyn_spg_fsc_atsk( kstp, indic )  ! autotask free surface constant volume case 
    401404      IF( lk_dynspg_rl      )   CALL dyn_spg_rl      ( kstp, indic )  ! rigid-lid case 
    402405 
    403                        CALL dyn_nxt( kstp )                 ! lateral velocity at next time step  
     406                                CALL dyn_nxt( kstp )          ! lateral velocity at next time step  
    404407 
    405408 
     
    426429      !----------------------------------------------------------------------- 
    427430 
    428       ! Time loop: control and print 
    429       ! ---------------------------- 
    430  
     431      !                                            ! Time loop: control and print 
    431432                       CALL stp_ctl( kstp, indic ) 
    432  
    433       IF ( indic < 0 ) nstop = nstop + 1 
    434  
    435       IF ( nstop /= 0 ) RETURN 
    436  
    437       ! Diagnostics: 
    438       ! ------------ 
    439  
    440       IF( lk_floats  )   CALL flo_stp( kstp )                 ! drifting Floats 
    441  
    442       IF( lk_trddyn  )   CALL trd_dyn( kstp )                 ! trends: dynamics  
    443  
    444       IF( lk_trdtra  )   CALL trd_tra( kstp )                 ! trends: active tracers 
    445  
    446       IF( lk_trdmld  )   CALL trd_mld( kstp )                 ! trends: Mixed-layer  
    447  
    448       IF( lk_diaspr  )   CALL dia_spr( kstp )                 ! Surface pressure diagnostics 
    449  
    450       IF( lk_diahth  )   CALL dia_hth( kstp )                 ! Thermocline depth (20 degres isotherm depth) 
    451  
    452       IF( lk_diaptr  )   CALL dia_ptr( kstp )                 ! Poleward TRansport diagnostics 
    453  
    454       IF( lk_diagap )   CALL dia_gap( kstp )                 ! basin averaged diagnostics 
    455  
    456       IF( lk_diahdy  )   CALL dia_hdy( kstp )                 ! dynamical heigh diagnostics 
    457  
    458       IF( lk_diafwb  )   CALL dia_fwb( kstp )                 ! Fresh water budget diagnostics 
     433                       IF ( indic < 0 )   nstop = nstop + 1 
     434 
     435      IF ( nstop == 0 ) THEN 
     436         !                                         ! Diagnostics: 
     437         IF( lk_floats  )   CALL flo_stp( kstp )                 ! drifting Floats 
     438         IF( lk_trddyn  )   CALL trd_dyn( kstp )                 ! trends: dynamics  
     439         IF( lk_trdtra  )   CALL trd_tra( kstp )                 ! trends: active tracers 
     440         IF( lk_trdmld  )   CALL trd_mld( kstp )                 ! trends: Mixed-layer  
     441         IF( lk_diaspr  )   CALL dia_spr( kstp )                 ! Surface pressure diagnostics 
     442         IF( lk_diahth  )   CALL dia_hth( kstp )                 ! Thermocline depth (20 degres isotherm depth) 
     443         IF( lk_diagap  )   CALL dia_gap( kstp )                 ! basin averaged diagnostics 
     444         IF( lk_diahdy  )   CALL dia_hdy( kstp )                 ! dynamical heigh diagnostics 
     445         IF( lk_diafwb  )   CALL dia_fwb( kstp )                 ! Fresh water budget diagnostics 
    459446#if defined key_diaptr 
    460       IF( MOD( kstp, nf_ptr ) == 0 )   CALL dia_ptr( kstp ) ! Poleward TRansports 
     447         IF( kstp == nit000 .OR. MOD( kstp, nf_ptr ) == 0 )   & 
     448                            CALL dia_ptr( kstp )                 ! Poleward TRansports diagnostics 
    461449#endif 
    462450 
    463    ! save and outputs 
    464    ! ---------------- 
    465                         CALL rst_write( kstp )               ! ocean model: restart file output 
    466  
    467       IF( lk_obc     )   CALL obc_rst_wri(kstp)               ! ocean model: open boundary restart file output 
    468  
    469                         CALL dia_wri( kstp, indic )          ! ocean model: outputs 
    470 #if defined key_coupled 
    471                         CALL stp_cmo( kstp )                 ! coupling fields 
    472 #endif 
     451         !                                         ! save and outputs 
     452                           CALL rst_write  ( kstp )              ! ocean model: restart file output 
     453         IF( lk_obc    )   CALL obc_rst_wri( kstp )              ! ocean model: open boundary restart file output 
     454                           CALL dia_wri    ( kstp, indic )       ! ocean model: outputs 
     455 
     456      ENDIF 
     457 
     458      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     459      ! Coupled mode 
     460      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     461 
     462      IF( lk_cpl    )   CALL cpl_stp( kstp )                 ! coupled mode : field exchanges 
    473463 
    474464   END SUBROUTINE stp 
Note: See TracChangeset for help on using the changeset viewer.