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.
trcrad.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trcrad.F90 @ 1119

Last change on this file since 1119 was 1119, checked in by cetlod, 16 years ago

style of all top namelist has been modified ; update modules to take it into account, see ticket:196

  • Property svn:executable set to *
File size: 8.0 KB
Line 
1MODULE trcrad
2   !!======================================================================
3   !!                       ***  MODULE  trcrad  ***
4   !! Ocean passive tracers:  correction of negative concentrations
5   !!======================================================================
6   !! History :   -   !  01-01  (O. Aumont & E. Kestenare)  Original code
7   !!            1.0  !  04-03  (C. Ethe)  free form F90
8   !!----------------------------------------------------------------------
9#if defined key_top
10   !!----------------------------------------------------------------------
11   !!   'key_top'                                                TOP models
12   !!----------------------------------------------------------------------
13   !!   trc_rad    : correction of negative concentrations
14   !!----------------------------------------------------------------------
15   USE oce_trc             ! ocean dynamics and tracers variables
16   USE trp_trc                 ! ocean passive tracers variables
17   USE lib_mpp
18   USE prtctl_trc          ! Print control for debbuging
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC trc_rad        ! routine called by trcstp.F90
24
25   !! * Substitutions
26#  include "top_substitute.h90"
27   !!----------------------------------------------------------------------
28   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)
29   !! $Id: trcrad.F90 776 2007-12-19 14:10:14Z gm $
30   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32   
33CONTAINS
34
35   SUBROUTINE trc_rad( kt )
36      !!----------------------------------------------------------------------
37      !!                  ***  ROUTINE trc_rad  ***
38      !!
39      !! ** Purpose :   "crappy" routine to correct artificial negative
40      !!              concentrations due to isopycnal scheme
41      !!
42      !! ** Method  : - PISCES or LOBSTER: Set negative concentrations to zero
43      !!                while computing the corresponding tracer content that
44      !!                is added to the tracers. Then, adjust the tracer
45      !!                concentration using a multiplicative factor so that
46      !!                the total tracer concentration is preserved.
47      !!              - CFC: simply set to zero the negative CFC concentration
48      !!                (the total CFC content is not strictly preserved)
49      !!----------------------------------------------------------------------
50      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index     
51      CHARACTER (len=22) :: charout
52      !!----------------------------------------------------------------------
53
54      IF( kt == nittrc000 ) THEN
55         IF(lwp) WRITE(numout,*)
56         IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
57         IF(lwp) WRITE(numout,*) '~~~~~~~ '
58      ENDIF
59
60      IF( lk_cfc     )   CALL trc_rad_sms( trb, trn, jp_cfc0, jp_cfc1               ) ! CFC model
61      IF( lk_lobster )   CALL trc_rad_sms( trb, trn, jp_lob0, jp_lob1, cpreserv='Y' )  ! LOBSTER model
62      IF( lk_pisces  )   CALL trc_rad_sms( trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  ! PISCES model
63      IF( lk_my_trc  )   CALL trc_rad_sms( trb, trn, jp_myt0, jp_myt1               ) ! MY_TRC model
64
65
66      !
67      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
68         WRITE(charout, FMT="('rad')")
69         CALL prt_ctl_trc_info( charout )
70         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
71      ENDIF
72      !
73   END SUBROUTINE trc_rad
74
75   SUBROUTINE trc_rad_sms( ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
76      !!-----------------------------------------------------------------------------
77      !!                  ***  ROUTINE trc_rad_sms  ***
78      !!
79      !! ** Purpose :   "crappy" routine to correct artificial negative
80      !!              concentrations due to isopycnal scheme
81      !!
82      !! ** Method  : 2 cases :
83      !!                - Set negative concentrations to zero while computing
84      !!                  the corresponding tracer content that is added to the
85      !!                  tracers. Then, adjust the tracer concentration using
86      !!                  a multiplicative factor so that the total tracer
87      !!                  concentration is preserved.
88      !!                - simply set to zero the negative CFC concentration
89      !!                  (the total content of concentration is not strictly preserved)
90      !!--------------------------------------------------------------------------------
91      !! Arguments
92      INTEGER  , INTENT( in ) ::  &
93         jp_sms0, &       !: First index of the passive tracer model
94         jp_sms1          !: Last  index of  the passive tracer model
95
96      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT( inout )  :: &
97         ptrb, ptrn       !: before and now traceur concentration
98
99      CHARACTER( len = 1) , INTENT(in), OPTIONAL  :: &
100         cpreserv          !: flag to preserve content or not
101     
102      ! Local declarations
103      INTEGER  ::  ji, jj, jk, jn     ! dummy loop indices
104      REAL(wp) :: zvolk, ztrcorb, ztrmasb   ! temporary scalars
105      REAL(wp) :: zcoef, ztrcorn, ztrmasn   !    "         "
106
107      !!----------------------------------------------------------------------
108
109     
110      IF( PRESENT( cpreserv )  ) THEN   !  total tracer concentration is preserved
111     
112         DO jn = jp_sms0, jp_sms1
113           
114            ztrcorb = 0.e0
115            ztrmasb = 0.e0
116            ztrcorn = 0.e0
117            ztrmasn = 0.e0
118
119            DO jk = 1, jpkm1
120               DO jj = 1, jpj
121                  DO ji = 1, jpi
122                     zvolk  = e1t(ji,jj) * e2t(ji,jj) * fse3t(ji,jj,jk)   &
123# if defined key_off_degrad
124                        &   * facvol(ji,jj,jk)   &
125# endif
126                        &   * tmask(ji,jj,jk) * tmask_i(ji,jj)
127
128                     ztrcorb = ztrcorb + MIN( 0., ptrb(ji,jj,jk,jn) )  * zvolk
129                     ztrcorn = ztrcorn + MIN( 0., ptrn(ji,jj,jk,jn) )  * zvolk
130
131                     ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
132                     ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
133
134                     ztrmasb = ztrmasb + ptrb(ji,jj,jk,jn) * zvolk
135                     ztrmasn = ztrmasn + ptrn(ji,jj,jk,jn) * zvolk
136                  END DO
137               END DO
138            END DO
139
140            IF( lk_mpp ) THEN
141               CALL mpp_sum( ztrcorb )      ! sum over the global domain
142               CALL mpp_sum( ztrcorn )      ! sum over the global domain
143               CALL mpp_sum( ztrmasb )      ! sum over the global domain
144               CALL mpp_sum( ztrmasn )      ! sum over the global domain
145            ENDIF
146
147            IF( ztrcorb /= 0 ) THEN
148               zcoef = 1. + ztrcorb / ztrmasb
149               DO jk = 1, jpkm1
150                  ptrb(:,:,jk,jn) = ptrb(:,:,jk,jn) * zcoef * tmask(:,:,jk)
151               END DO
152            ENDIF
153
154            IF( ztrcorn /= 0 ) THEN
155               zcoef = 1. + ztrcorn / ztrmasn
156               DO jk = 1, jpkm1
157                  ptrn(:,:,jk,jn) = ptrn(:,:,jk,jn) * zcoef * tmask(:,:,jk)
158               END DO
159            ENDIF
160            !
161         END DO
162         !
163         !
164      ELSE  ! total CFC content is not strictly preserved
165
166         DO jn = jp_sms0, jp_sms1 
167            DO jk = 1, jpkm1
168               DO jj = 1, jpj
169                  DO ji = 1, jpi
170                     ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
171                     ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
172                  END DO
173               END DO
174            END DO
175         END DO
176
177      ENDIF
178
179   END SUBROUTINE trc_rad_sms
180#else
181   !!----------------------------------------------------------------------
182   !!   Dummy module :                                         NO TOP model
183   !!----------------------------------------------------------------------
184CONTAINS
185   SUBROUTINE trc_rad( kt )              ! Empty routine
186      INTEGER, INTENT(in) ::   kt
187      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
188   END SUBROUTINE trc_rad
189#endif
190   
191   !!======================================================================
192END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.