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/trunk/src/OCE/TRA – NEMO

source: NEMO/trunk/src/OCE/TRA/traldf.F90 @ 12808

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

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 7.4 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   
[503]40   !!----------------------------------------------------------------------
[9570]41   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1152]42   !! $Id$
[10068]43   !! Software governed by the CeCILL license (see ./LICENSE)
[503]44   !!----------------------------------------------------------------------
[458]45CONTAINS
46
[12377]47   SUBROUTINE tra_ldf( kt, Kbb, Kmm, pts, Krhs )
[458]48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE tra_ldf  ***
50      !!
51      !! ** Purpose :   compute the lateral ocean tracer physics.
52      !!----------------------------------------------------------------------
[12377]53      INTEGER,                                   INTENT(in   ) :: kt              ! ocean time-step index
54      INTEGER,                                   INTENT(in   ) :: Kbb, Kmm, Krhs  ! ocean time level indices
55      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts             ! active tracers and RHS of tracer equation
[503]56      !!
[9019]57      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdt, ztrds
[458]58      !!----------------------------------------------------------------------
[3294]59      !
[9019]60      IF( ln_timing )   CALL timing_start('tra_ldf')
[3294]61      !
[2528]62      IF( l_trdtra )   THEN                    !* Save ta and sa trends
[9019]63         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
[12377]64         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) 
65         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs)
[458]66      ENDIF
[5836]67      !
[9490]68      SELECT CASE ( nldf_tra )                 !* compute lateral mixing trend and add it to the general trend
[5836]69      CASE ( np_lap   )                                  ! laplacian: iso-level operator
[12377]70         CALL tra_ldf_lap  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs),                   jpts,  1 )
[5836]71      CASE ( np_lap_i )                                  ! laplacian: standard iso-neutral operator (Madec)
[12377]72         CALL tra_ldf_iso  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts,  1 )
[5836]73      CASE ( np_lap_it )                                 ! laplacian: triad iso-neutral operator (griffies)
[12377]74         CALL tra_ldf_triad( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs), jpts,  1 )
[5836]75      CASE ( np_blp , np_blp_i , np_blp_it )             ! bilaplacian: iso-level & iso-neutral operators
[12377]76         CALL tra_ldf_blp  ( kt, Kmm, nit000,'TRA', ahtu, ahtv, gtsu, gtsv, gtui, gtvi, pts(:,:,:,:,Kbb), pts(:,:,:,:,Krhs),             jpts, nldf_tra )
[458]77      END SELECT
[6140]78      !
[5836]79      IF( l_trdtra )   THEN                    !* save the horizontal diffusive trends for further diagnostics
[12377]80         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:)
81         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:)
82         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_ldf, ztrdt )
83         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_ldf, ztrds )
[9019]84         DEALLOCATE( ztrdt, ztrds ) 
[458]85      ENDIF
[5836]86      !                                        !* print mean trends (used for debugging)
[12377]87      IF(sn_cfctl%l_prtctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' ldf  - Ta: ', mask1=tmask,               &
88         &                                  tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
[503]89      !
[9019]90      IF( ln_timing )   CALL timing_stop('tra_ldf')
[3294]91      !
[458]92   END SUBROUTINE tra_ldf
93
94
[2528]95   SUBROUTINE tra_ldf_init
[458]96      !!----------------------------------------------------------------------
[2528]97      !!                  ***  ROUTINE tra_ldf_init  ***
[458]98      !!
99      !! ** Purpose :   Choice of the operator for the lateral tracer diffusion
100      !!
[9490]101      !! ** Method  :   set nldf_tra from the namtra_ldf logicals
[458]102      !!----------------------------------------------------------------------
[5836]103      INTEGER ::   ioptio, ierr   ! temporary integers
[458]104      !!----------------------------------------------------------------------
[5836]105      !
[9019]106      IF(lwp) THEN                     !==  Namelist print  ==!
[458]107         WRITE(numout,*)
[2528]108         WRITE(numout,*) 'tra_ldf_init : lateral tracer diffusive operator'
[7646]109         WRITE(numout,*) '~~~~~~~~~~~~'
[6140]110         WRITE(numout,*) '   Namelist namtra_ldf: already read in ldftra module'
111         WRITE(numout,*) '      see ldf_tra_init report for lateral mixing parameters'
[9490]112         WRITE(numout,*)
[5836]113         !
[9490]114         SELECT CASE( nldf_tra )             ! print the choice of operator
[9190]115         CASE( np_no_ldf )   ;   WRITE(numout,*) '   ==>>>   NO lateral diffusion'
116         CASE( np_lap    )   ;   WRITE(numout,*) '   ==>>>   laplacian iso-level operator'
117         CASE( np_lap_i  )   ;   WRITE(numout,*) '   ==>>>   Rotated laplacian operator (standard)'
118         CASE( np_lap_it )   ;   WRITE(numout,*) '   ==>>>   Rotated laplacian operator (triad)'
119         CASE( np_blp    )   ;   WRITE(numout,*) '   ==>>>   bilaplacian iso-level operator'
120         CASE( np_blp_i  )   ;   WRITE(numout,*) '   ==>>>   Rotated bilaplacian operator (standard)'
121         CASE( np_blp_it )   ;   WRITE(numout,*) '   ==>>>   Rotated bilaplacian operator (triad)'
[6140]122         END SELECT
[458]123      ENDIF
[503]124      !
[2528]125   END SUBROUTINE tra_ldf_init
[458]126
127   !!======================================================================
[620]128END MODULE traldf
Note: See TracBrowser for help on using the repository browser.