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.
dynldf.F90 in NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/OCE/DYN – NEMO

source: NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/OCE/DYN/dynldf.F90 @ 11872

Last change on this file since 11872 was 11872, checked in by acc, 4 years ago

Branch 2019/fix_sn_cfctl_ticket2328. See #2328. Replacement of ln_ctl and activation of full functionality with
sn_cfctl structure. These changes rename structure components l_mppout and l_mpptop as l_prtctl and l_prttrc
and introduce l_glochk to activate former ln_ctl code in stpctl.F90 to perform global location of min and max
checks. Also added is l_allon which can be used to activate all output (much like the former ln_ctl). If l_allon
is .false. then l_config decides whether or not the suboptions are used.

   sn_cfctl%l_glochk = .FALSE.    ! Range sanity checks are local (F) or global (T). Set T for debugging only
   sn_cfctl%l_allon  = .FALSE.    ! IF T activate all options. If F deactivate all unless l_config is T
   sn_cfctl%l_config = .TRUE.     ! IF .true. then control which reports are written with the remaining options

Note, these changes pass SETTE tests but all references to ln_ctl need to be removed from the sette scripts.

  • Property svn:keywords set to Id
File size: 5.4 KB
RevLine 
[456]1MODULE dynldf
2   !!======================================================================
3   !!                       ***  MODULE  dynldf  ***
4   !! Ocean physics:  lateral diffusivity trends
5   !!=====================================================================
[5836]6   !! History :  2.0  ! 2005-11  (G. Madec)  Original code (new step architecture)
7   !!            3.7  ! 2014-01  (F. Lemarie, G. Madec)  restructuration/simplification of ahm specification,
8   !!                 !                                  add velocity dependent coefficient and optional read in file
[503]9   !!----------------------------------------------------------------------
[456]10
11   !!----------------------------------------------------------------------
[2528]12   !!   dyn_ldf      : update the dynamics trend with the lateral diffusion
13   !!   dyn_ldf_init : initialization, namelist read, and parameters control
[456]14   !!----------------------------------------------------------------------
[503]15   USE oce            ! ocean dynamics and tracers
16   USE dom_oce        ! ocean space and time domain
17   USE phycst         ! physical constants
[5836]18   USE ldfdyn         ! lateral diffusion: eddy viscosity coef.
19   USE dynldf_lap_blp ! lateral mixing   (dyn_ldf_lap & dyn_ldf_blp routines)
20   USE dynldf_iso     ! lateral mixing                 (dyn_ldf_iso routine )
[4990]21   USE trd_oce        ! trends: ocean variables
[5836]22   USE trddyn         ! trend manager: dynamics   (trd_dyn      routine)
[4990]23   !
[503]24   USE prtctl         ! Print control
25   USE in_out_manager ! I/O manager
26   USE lib_mpp        ! distribued memory computing library
27   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
[5836]28   USE timing         ! Timing
[456]29
30   IMPLICIT NONE
31   PRIVATE
32
[2528]33   PUBLIC   dyn_ldf       ! called by step module
34   PUBLIC   dyn_ldf_init  ! called by opa  module
[456]35
36   !! * Substitutions
37#  include "vectopt_loop_substitute.h90"
[2528]38   !!----------------------------------------------------------------------
[9598]39   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1152]40   !! $Id$
[10068]41   !! Software governed by the CeCILL license (see ./LICENSE)
[503]42   !!----------------------------------------------------------------------
[456]43CONTAINS
44
45   SUBROUTINE dyn_ldf( kt )
46      !!----------------------------------------------------------------------
47      !!                  ***  ROUTINE dyn_ldf  ***
48      !!
49      !! ** Purpose :   compute the lateral ocean dynamics physics.
[503]50      !!----------------------------------------------------------------------
51      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
[3294]52      !
[9019]53      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdu, ztrdv
[456]54      !!----------------------------------------------------------------------
[2715]55      !
[9019]56      IF( ln_timing )   CALL timing_start('dyn_ldf')
[3294]57      !
[5836]58      IF( l_trddyn )   THEN                      ! temporary save of momentum trends
[9019]59         ALLOCATE( ztrdu(jpi,jpj,jpk) , ztrdv(jpi,jpj,jpk) )
[7753]60         ztrdu(:,:,:) = ua(:,:,:) 
61         ztrdv(:,:,:) = va(:,:,:) 
[456]62      ENDIF
63
[9490]64      SELECT CASE ( nldf_dyn )                   ! compute lateral mixing trend and add it to the general trend
[503]65      !
[9490]66      CASE ( np_lap   )    ;   CALL dyn_ldf_lap( kt, ub, vb, ua, va, 1 )      ! iso-level    laplacian
67      CASE ( np_lap_i )    ;   CALL dyn_ldf_iso( kt )                         ! rotated      laplacian
68      CASE ( np_blp   )    ;   CALL dyn_ldf_blp( kt, ub, vb, ua, va    )      ! iso-level bi-laplacian
[503]69      !
[456]70      END SELECT
71
[503]72      IF( l_trddyn ) THEN                        ! save the horizontal diffusive trends for further diagnostics
[7753]73         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:)
74         ztrdv(:,:,:) = va(:,:,:) - ztrdv(:,:,:)
[4990]75         CALL trd_dyn( ztrdu, ztrdv, jpdyn_ldf, kt )
[9019]76         DEALLOCATE ( ztrdu , ztrdv )
[456]77      ENDIF
[503]78      !                                          ! print sum trends (used for debugging)
[11872]79      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' ldf  - Ua: ', mask1=umask,   &
80         &                                  tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' )
[503]81      !
[9019]82      IF( ln_timing )   CALL timing_stop('dyn_ldf')
[2715]83      !
[456]84   END SUBROUTINE dyn_ldf
85
86
[2528]87   SUBROUTINE dyn_ldf_init
[456]88      !!----------------------------------------------------------------------
[2528]89      !!                  ***  ROUTINE dyn_ldf_init  ***
[456]90      !!
91      !! ** Purpose :   initializations of the horizontal ocean dynamics physics
92      !!----------------------------------------------------------------------
[5836]93      !
[9490]94      IF(lwp) THEN                     !==  Namelist print  ==!
[456]95         WRITE(numout,*)
[2528]96         WRITE(numout,*) 'dyn_ldf_init : Choice of the lateral diffusive operator on dynamics'
[7646]97         WRITE(numout,*) '~~~~~~~~~~~~'
[9490]98         WRITE(numout,*) '   Namelist namdyn_ldf: already read in ldfdyn module'
99         WRITE(numout,*) '      see ldf_dyn_init report for lateral mixing parameters'
100         WRITE(numout,*)
[5836]101         !
[9490]102         SELECT CASE( nldf_dyn )             ! print the choice of operator
103         CASE( np_no_ldf )   ;   WRITE(numout,*) '   ==>>>   NO lateral viscosity'
104         CASE( np_lap    )   ;   WRITE(numout,*) '   ==>>>   iso-level laplacian operator'
105         CASE( np_lap_i  )   ;   WRITE(numout,*) '   ==>>>   rotated laplacian operator with iso-level background'
106         CASE( np_blp    )   ;   WRITE(numout,*) '   ==>>>   iso-level bi-laplacian operator'
107         END SELECT
[456]108      ENDIF
[503]109      !
[2528]110   END SUBROUTINE dyn_ldf_init
[456]111
112   !!======================================================================
113END MODULE dynldf
Note: See TracBrowser for help on using the repository browser.