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.
trcdmp_sed.F90 in NEMO/branches/2020/dev_r12472_ASINTER-05_Masson_CurrentFeedback/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2020/dev_r12472_ASINTER-05_Masson_CurrentFeedback/src/TOP/PISCES/SED/trcdmp_sed.F90 @ 12495

Last change on this file since 12495 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.

File size: 7.1 KB
Line 
1MODULE trcdmp_sed
2   !!======================================================================
3   !!                       ***  MODULE  trcdmp  ***
4   !! Ocean physics: internal restoring trend on passive tracers
5   !!======================================================================
6   !! History :  OPA  !  1991-03  (O. Marti, G. Madec)  Original code
7   !!                 !  1996-01  (G. Madec) statement function for e3
8   !!                 !  1997-05  (H. Loukos)  adapted for passive tracers
9   !!    NEMO    9.0  !  2004-03  (C. Ethe)    free form + modules
10   !!            3.2  !  2007-02  (C. Deltel)  Diagnose ML trends for passive tracers
11   !!            3.3  !  2010-06  (C. Ethe, G. Madec) merge TRA-TRC
12   !!----------------------------------------------------------------------
13#if  defined key_top
14   !!----------------------------------------------------------------------
15   !!   trc_dmp      : update the tracer trend with the internal damping
16   !!   trc_dmp_init : initialization, namlist read, parameters control
17   !!----------------------------------------------------------------------
18   USE oce_trc         ! ocean dynamics and tracers variables
19   USE trc             ! ocean passive tracers variables
20   USE sed , ONLY : dtsed => dtsed      ! ocean dynamics and tracers variables
21   USE trc             ! ocean passive tracers variables
22   USE trcdta
23   USE prtctl_trc      ! Print control for debbuging
24   USE iom
25
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC trc_dmp_sed     
31   PUBLIC trc_dmp_sed_alloc 
32   PUBLIC trc_dmp_sed_ini   
33
34   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   restosed   ! restoring coeff. on tracers (s-1)
35
36   !! * Substitutions
37#  include "do_loop_substitute.h90"
38   !!----------------------------------------------------------------------
39   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
40   !! $Id: trcdmp.F90 7646 2017-02-06 09:25:03Z timgraham $
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44
45   INTEGER FUNCTION trc_dmp_sed_alloc()
46      !!----------------------------------------------------------------------
47      !!                   ***  ROUTINE trc_dmp_alloc  ***
48      !!----------------------------------------------------------------------
49      ALLOCATE( restosed(jpi,jpj,jpk) , STAT=trc_dmp_sed_alloc )
50      !
51      IF( trc_dmp_sed_alloc /= 0 )   CALL ctl_warn('trc_dmp_sed_alloc: failed to allocate array')
52      !
53   END FUNCTION trc_dmp_sed_alloc
54
55
56   SUBROUTINE trc_dmp_sed( kt, Kbb, Kmm, Krhs )
57      !!----------------------------------------------------------------------
58      !!                   ***  ROUTINE trc_dmp_sed  ***
59      !!                 
60      !! ** Purpose :   Compute the passive tracer trend due to a newtonian damping
61      !!      of the tracer field towards given data field and add it to the
62      !!      general tracer trends.
63      !!
64      !! ** Method  :   Newtonian damping towards trdta computed
65      !!      and add to the general tracer trends:
66      !!                     tr(Kmm) = tr(Krhs) + restotr * (trdta - tr(Kbb))
67      !!         The trend is computed either throughout the water column
68      !!      (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or
69      !!      below the well mixed layer (nlmdmptr=2)
70      !!
71      !! ** Action  : - update the tracer trends tr(Krhs) with the newtonian
72      !!                damping trends.
73      !!              - save the trends ('key_trdmxl_trc')
74      !!----------------------------------------------------------------------
75      INTEGER, INTENT(in) ::   kt              ! ocean time-step index
76      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! time level index
77      !
78      INTEGER ::   ji, jj, jk, jn, jl, ikt   ! dummy loop indices
79      CHARACTER (len=22) ::   charout
80      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrcdta   ! 3D  workspace
81      !!----------------------------------------------------------------------
82      !
83      IF( ln_timing )  CALL timing_start('trc_dmp_sed')
84      !
85      !
86      IF( nb_trcdta > 0 ) THEN  ! Initialisation of tracer from a file that may also be used for damping
87         !
88         DO jn = 1, jptra                                           ! tracer loop
89            !                                                       ! ===========
90            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file
91               !
92               jl = n_trc_index(jn) 
93               CALL trc_dta( kt, Kmm, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000
94               !
95               DO_2D_11_11
96                  ikt = mbkt(ji,jj)
97                  tr(ji,jj,ikt,jn,Kbb) = ztrcdta(ji,jj,ikt) + ( tr(ji,jj,ikt,jn,Kbb) -  ztrcdta(ji,jj,ikt) )     &
98                  &                  * exp( -restosed(ji,jj,ikt) * dtsed )
99               END_2D
100               !
101            ENDIF
102         END DO                                                     ! tracer loop
103         !                                                          ! ===========
104      ENDIF
105      !
106      !                                          ! print mean trends (used for debugging)
107      IF( sn_cfctl%l_prttrc ) THEN
108         WRITE(charout, FMT="('dmp ')")
109         CALL prt_ctl_trc_info(charout)
110         CALL prt_ctl_trc( tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
111      ENDIF
112      !
113      IF( ln_timing )  CALL timing_stop('trc_dmp_sed')
114      !
115   END SUBROUTINE trc_dmp_sed
116
117
118   SUBROUTINE trc_dmp_sed_ini
119      !!----------------------------------------------------------------------
120      !!                  ***  ROUTINE trc_dmp_ini  ***
121      !!
122      !! ** Purpose :   Initialization for the newtonian damping
123      !!
124      !! ** Method  :   read the nammbf namelist and check the parameters
125      !!              called by trc_dmp at the first timestep (nittrc000)
126      !!----------------------------------------------------------------------
127      !!----------------------------------------------------------------------
128      !
129      IF( ln_timing )  CALL timing_start('trc_dmp_sed_ini')
130
131      IF (lwp) WRITE(numout,*) '   tracer damping throughout the water column'
132      !
133      IF( trc_dmp_sed_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'trc_dmp_sed_ini: unable to allocate arrays' )
134      !
135      IF( .NOT.lk_c1d ) THEN
136         !Read in mask from file
137          restosed(:,:,:) = 0.5 / rday
138         !
139      ENDIF
140      IF( ln_timing )  CALL timing_stop('trc_dmp_sed_ini')
141     !
142   END SUBROUTINE trc_dmp_sed_ini
143
144#else
145   !!----------------------------------------------------------------------
146   !!  Dummy module :                                     No passive tracer
147   !!----------------------------------------------------------------------
148CONTAINS
149   SUBROUTINE trc_dmp_sed( kt, Kbb, Kmm, Krhs )   ! Empty routine
150      INTEGER, INTENT(in) :: kt
151      INTEGER, INTENT(in) :: Kbb, Kmm, Krhs
152      WRITE(*,*) 'trc_dmp_sed: You should not have seen this print! error?', kt
153   END SUBROUTINE trc_dmp_sed
154#endif
155
156   !!======================================================================
157END MODULE trcdmp_sed
Note: See TracBrowser for help on using the repository browser.