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.
traldf.F90 in NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRA – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/OCE/TRA/traldf.F90 @ 10946

Last change on this file since 10946 was 10946, checked in by acc, 5 years ago

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Convert STO, TRD and USR modules and all knock on effects of these conversions. Note change to USR module may have implications for the TEST CASES (not tested yet). Standard SETTE tested only

  • Property svn:keywords set to Id
File size: 7.0 KB
RevLine 
[458]1MODULE traldf
2   !!======================================================================
3   !!                       ***  MODULE  traldf  ***
4   !! Ocean Active tracers : lateral diffusive trends
5   !!=====================================================================
[5836]6   !! History :  9.0  ! 2005-11  (G. Madec)  Original code
7   !!  NEMO      3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            3.7  ! 2013-12  (G. Madec) remove the optional computation from T & S anomaly profiles and traldf_bilapg
9   !!             -   ! 2013-12  (F. Lemarie, G. Madec)  triad operator (Griffies) + Method of Stabilizing Correction
10   !!             -   ! 2014-01  (G. Madec, S. Masson)  restructuration/simplification of lateral diffusive operators
[458]11   !!----------------------------------------------------------------------
[503]12
13   !!----------------------------------------------------------------------
[6140]14   !!   tra_ldf       : update the tracer trend with the lateral diffusion trend
15   !!   tra_ldf_init  : initialization, namelist read, and parameters control
[458]16   !!----------------------------------------------------------------------
[6140]17   USE oce            ! ocean dynamics and tracers
18   USE dom_oce        ! ocean space and time domain
19   USE phycst         ! physical constants
20   USE ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff.
21   USE ldfslp         ! lateral diffusion: iso-neutral slope
22   USE traldf_lap_blp ! lateral diffusion: laplacian iso-level            operator  (tra_ldf_lap/_blp   routines)
23   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine )
24   USE traldf_triad   ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_triad      routine )
25   USE trd_oce        ! trends: ocean variables
26   USE trdtra         ! ocean active tracers trends
[4990]27   !
[5836]28   USE prtctl         ! Print control
29   USE in_out_manager ! I/O manager
30   USE lib_mpp        ! distribued memory computing library
31   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
32   USE timing         ! Timing
[458]33
34   IMPLICIT NONE
35   PRIVATE
36
[4990]37   PUBLIC   tra_ldf        ! called by step.F90
[5836]38   PUBLIC   tra_ldf_init   ! called by nemogcm.F90
39   
[458]40   !! * Substitutions
41#  include "vectopt_loop_substitute.h90"
[503]42   !!----------------------------------------------------------------------
[9570]43   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1152]44   !! $Id$
[10068]45   !! Software governed by the CeCILL license (see ./LICENSE)
[503]46   !!----------------------------------------------------------------------
[458]47CONTAINS
48
[10946]49   SUBROUTINE tra_ldf( kt, Kmm, Krhs )
[458]50      !!----------------------------------------------------------------------
51      !!                  ***  ROUTINE tra_ldf  ***
52      !!
53      !! ** Purpose :   compute the lateral ocean tracer physics.
54      !!----------------------------------------------------------------------
[10874]55      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
[10946]56      INTEGER, INTENT( in ) ::   Kmm, Krhs  ! ocean time level indices
[503]57      !!
[9019]58      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds
[458]59      !!----------------------------------------------------------------------
[3294]60      !
[9019]61      IF( ln_timing )   CALL timing_start('tra_ldf')
[3294]62      !
[2528]63      IF( l_trdtra )   THEN                    !* Save ta and sa trends
[9019]64         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
[10874]65         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
66         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
[458]67      ENDIF
[5836]68      !
[9490]69      SELECT CASE ( nldf_tra )                 !* compute lateral mixing trend and add it to the general trend
[5836]70      CASE ( np_lap   )                                  ! laplacian: iso-level operator
[10874]71         CALL tra_ldf_lap  ( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb,      tsa, jpts,  1   )
[5836]72      CASE ( np_lap_i )                                  ! laplacian: standard iso-neutral operator (Madec)
[10874]73         CALL tra_ldf_iso  ( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb, tsb, tsa, jpts,  1   )
[5836]74      CASE ( np_lap_it )                                 ! laplacian: triad iso-neutral operator (griffies)
[10922]75         CALL tra_ldf_triad( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb, tsb, tsa, jpts,  1, Kmm   )
[5836]76      CASE ( np_blp , np_blp_i , np_blp_it )             ! bilaplacian: iso-level & iso-neutral operators
[10922]77         CALL tra_ldf_blp  ( kt, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, tsb      , tsa, jpts, nldf_tra, Kmm )
[458]78      END SELECT
[6140]79      !
[5836]80      IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics
[10874]81         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
82         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
[10946]83         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt )
84         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds )
[9019]85         DEALLOCATE( ztrdt, ztrds ) 
[458]86      ENDIF
[5836]87      !                                        !* print mean trends (used for debugging)
[2528]88      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf  - Ta: ', mask1=tmask,               &
89         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
[503]90      !
[9019]91      IF( ln_timing )   CALL timing_stop('tra_ldf')
[3294]92      !
[458]93   END SUBROUTINE tra_ldf
94
95
[2528]96   SUBROUTINE tra_ldf_init
[458]97      !!----------------------------------------------------------------------
[2528]98      !!                  ***  ROUTINE tra_ldf_init  ***
[458]99      !!
100      !! ** Purpose :   Choice of the operator for the lateral tracer diffusion
101      !!
[9490]102      !! ** Method  :   set nldf_tra from the namtra_ldf logicals
[458]103      !!----------------------------------------------------------------------
[5836]104      INTEGER ::   ioptio, ierr   ! temporary integers
[458]105      !!----------------------------------------------------------------------
[5836]106      !
[9019]107      IF(lwp) THEN                     !==  Namelist print  ==!
[458]108         WRITE(numout,*)
[2528]109         WRITE(numout,*) 'tra_ldf_init : lateral tracer diffusive operator'
[7646]110         WRITE(numout,*) '~~~~~~~~~~~~'
[6140]111         WRITE(numout,*) '   Namelist namtra_ldf: already read in ldftra module'
112         WRITE(numout,*) '      see ldf_tra_init report for lateral mixing parameters'
[9490]113         WRITE(numout,*)
[5836]114         !
[9490]115         SELECT CASE( nldf_tra )             ! print the choice of operator
[9190]116         CASE( np_no_ldf )   ;   WRITE(numout,*) '   ==>>>   NO lateral diffusion'
117         CASE( np_lap    )   ;   WRITE(numout,*) '   ==>>>   laplacian iso-level operator'
118         CASE( np_lap_i  )   ;   WRITE(numout,*) '   ==>>>   Rotated laplacian operator (standard)'
119         CASE( np_lap_it )   ;   WRITE(numout,*) '   ==>>>   Rotated laplacian operator (triad)'
120         CASE( np_blp    )   ;   WRITE(numout,*) '   ==>>>   bilaplacian iso-level operator'
121         CASE( np_blp_i  )   ;   WRITE(numout,*) '   ==>>>   Rotated bilaplacian operator (standard)'
122         CASE( np_blp_it )   ;   WRITE(numout,*) '   ==>>>   Rotated bilaplacian operator (triad)'
[6140]123         END SELECT
[458]124      ENDIF
[503]125      !
[2528]126   END SUBROUTINE tra_ldf_init
[458]127
128   !!======================================================================
[620]129END MODULE traldf
Note: See TracBrowser for help on using the repository browser.