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 NEMO/trunk/src/TOP/TRP – NEMO

source: NEMO/trunk/src/TOP/TRP/trcrad.F90 @ 10425

Last change on this file since 10425 was 10425, checked in by smasson, 5 years ago

trunk: merge back dev_r10164_HPC09_ESIWACE_PREP_MERGE@10424 into the trunk

  • Property svn:keywords set to Id
File size: 14.5 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 par_trc             ! need jptra, number of passive tracers
16   USE oce_trc             ! ocean dynamics and tracers variables
17   USE trc                 ! ocean passive tracers variables
18   USE trd_oce
19   USE trdtra
20   USE prtctl_trc          ! Print control for debbuging
21   USE lib_fortran
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC trc_rad     
27   PUBLIC trc_rad_ini 
28
29   LOGICAL , PUBLIC ::   ln_trcrad           !: flag to artificially correct negative concentrations
30   REAL(wp), DIMENSION(:,:), ALLOCATABLE::   gainmass
31
32   !!----------------------------------------------------------------------
33   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
34   !! $Id$
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE trc_rad( kt )
40      !!----------------------------------------------------------------------
41      !!                  ***  ROUTINE trc_rad  ***
42      !!
43      !! ** Purpose :   "crappy" routine to correct artificial negative
44      !!              concentrations due to isopycnal scheme
45      !!
46      !! ** Method  : - PISCES or LOBSTER: Set negative concentrations to zero
47      !!                while computing the corresponding tracer content that
48      !!                is added to the tracers. Then, adjust the tracer
49      !!                concentration using a multiplicative factor so that
50      !!                the total tracer concentration is preserved.
51      !!              - CFC: simply set to zero the negative CFC concentration
52      !!                (the total CFC content is not strictly preserved)
53      !!----------------------------------------------------------------------
54      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
55      !
56      CHARACTER (len=22) :: charout
57      !!----------------------------------------------------------------------
58      !
59      IF( ln_timing )   CALL timing_start('trc_rad')
60      !
61      IF( ln_age     )   CALL trc_rad_sms( kt, trb, trn, jp_age , jp_age                )  !  AGE
62      IF( ll_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0, jp_cfc1               )  !  CFC model
63      IF( ln_c14     )   CALL trc_rad_sms( kt, trb, trn, jp_c14 , jp_c14                )  !  C14
64      IF( ln_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model
65      IF( ln_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0, jp_myt1               )  !  MY_TRC model
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      IF( ln_timing )   CALL timing_stop('trc_rad')
74      !
75   END SUBROUTINE trc_rad
76
77
78   SUBROUTINE trc_rad_ini
79      !!---------------------------------------------------------------------
80      !!                  ***  ROUTINE trc _rad_ini ***
81      !!
82      !! ** Purpose :   read  namelist options
83      !!----------------------------------------------------------------------
84      INTEGER ::   ios   ! Local integer output status for namelist read
85      !!
86      NAMELIST/namtrc_rad/ ln_trcrad
87      !!----------------------------------------------------------------------
88      !
89      REWIND( numnat_ref )              ! namtrc_rad in reference namelist
90      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
91907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
92      REWIND( numnat_cfg )              ! namtrc_rad in configuration namelist
93      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
94908   IF( ios > 0 )   CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
95      IF(lwm) WRITE( numont, namtrc_rad )
96
97      IF(lwp) THEN                     !   ! Control print
98         WRITE(numout,*)
99         WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
100         WRITE(numout,*) '~~~~~~~ '
101         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
102         WRITE(numout,*) '      correct artificially negative concen. or not   ln_trcrad = ', ln_trcrad
103         WRITE(numout,*)
104         IF( ln_trcrad ) THEN   ;   WRITE(numout,*) '      ===>>   ensure the global tracer conservation'
105         ELSE                   ;   WRITE(numout,*) '      ===>>   NO strict global tracer conservation'     
106         ENDIF
107      ENDIF
108      !
109      ALLOCATE( gainmass(jptra,2) )
110      gainmass(:,:) = 0.
111      !
112   END SUBROUTINE trc_rad_ini
113
114
115   SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
116      !!-----------------------------------------------------------------------------
117      !!                  ***  ROUTINE trc_rad_sms  ***
118      !!
119      !! ** Purpose :   "crappy" routine to correct artificial negative
120      !!              concentrations due to isopycnal scheme
121      !!
122      !! ** Method  : 2 cases :
123      !!                - Set negative concentrations to zero while computing
124      !!                  the corresponding tracer content that is added to the
125      !!                  tracers. Then, adjust the tracer concentration using
126      !!                  a multiplicative factor so that the total tracer
127      !!                  concentration is preserved.
128      !!                - simply set to zero the negative CFC concentration
129      !!                  (the total content of concentration is not strictly preserved)
130      !!--------------------------------------------------------------------------------
131      INTEGER                                , INTENT(in   ) ::   kt                 ! ocean time-step index
132      INTEGER                                , INTENT(in   ) ::   jp_sms0, jp_sms1   ! First & last index of the passive tracer model
133      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT(inout) ::   ptrb    , ptrn     ! before and now traceur concentration
134      CHARACTER( len = 1), OPTIONAL          , INTENT(in   ) ::   cpreserv           ! flag to preserve content or not
135      !
136      INTEGER ::   ji, ji2, jj, jj2, jk, jn     ! dummy loop indices
137      INTEGER ::   icnt
138      LOGICAL ::   lldebug = .FALSE.            ! local logical
139      REAL(wp)::   zcoef, zs2rdt, ztotmass
140      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrneg, ztrpos
141      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrtrd   ! workspace arrays
142      !!----------------------------------------------------------------------
143      !
144      IF( l_trdtrc )   ALLOCATE( ztrtrd(jpi,jpj,jpk) )
145      zs2rdt = 1. / ( 2. * rdt * REAL( nn_dttrc, wp ) )
146      !
147      IF( PRESENT( cpreserv )  ) THEN     !==  total tracer concentration is preserved  ==!
148         !
149         ALLOCATE( ztrneg(1:jpi,1:jpj,jp_sms0:jp_sms1), ztrpos(1:jpi,1:jpj,jp_sms0:jp_sms1) )
150
151         DO jn = jp_sms0, jp_sms1
152            ztrneg(:,:,jn) = SUM( MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:), dim = 3 )   ! sum of the negative values
153            ztrpos(:,:,jn) = SUM( MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:), dim = 3 )   ! sum of the positive values
154         END DO
155         CALL sum3x3( ztrneg )
156         CALL sum3x3( ztrpos )
157         
158         DO jn = jp_sms0, jp_sms1
159            !
160            IF( l_trdtrc )   ztrtrd(:,:,:) = ptrb(:,:,:,jn)                            ! save input trb for trend computation           
161            !
162            DO jk = 1, jpkm1
163               DO jj = 1, jpj
164                  DO ji = 1, jpi
165                     IF( ztrneg(ji,jj,jn) /= 0. ) THEN                                 ! if negative values over the 3x3 box
166                        !
167                        ptrb(ji,jj,jk,jn) = ptrb(ji,jj,jk,jn) * tmask(ji,jj,jk)   ! really needed?
168                        IF( ptrb(ji,jj,jk,jn) < 0. ) ptrb(ji,jj,jk,jn) = 0.       ! supress negative values
169                        IF( ptrb(ji,jj,jk,jn) > 0. ) THEN                         ! use positive values to compensate mass gain
170                           zcoef = 1. + ztrneg(ji,jj,jn) / ztrpos(ji,jj,jn)       ! ztrpos > 0 as ptrb > 0
171                           ptrb(ji,jj,jk,jn) = ptrb(ji,jj,jk,jn) * zcoef
172                           IF( zcoef < 0. ) THEN                                  ! if the compensation exceed the positive value
173                              gainmass(jn,1) = gainmass(jn,1) - ptrb(ji,jj,jk,jn) * cvol(ji,jj,jk)   ! we are adding mass...
174                              ptrb(ji,jj,jk,jn) = 0.                              ! limit the compensation to keep positive value
175                           ENDIF
176                        ENDIF
177                        !
178                     ENDIF
179                  END DO
180               END DO
181            END DO
182            !
183            IF( l_trdtrc ) THEN
184               ztrtrd(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt
185               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrd )       ! Asselin-like trend handling
186            ENDIF
187            !
188         END DO
189 
190         IF( kt == nitend ) THEN
191            CALL mpp_sum( 'trcrad', gainmass(:,1) )
192            DO jn = jp_sms0, jp_sms1
193               IF( gainmass(jn,1) > 0. ) THEN
194                  ztotmass = glob_sum( 'trcrad', ptrb(:,:,:,jn) * cvol(:,:,:) )
195                  IF(lwp) WRITE(numout, '(a, i2, a, D23.16, a, D23.16)') 'trcrad ptrb, traceur ', jn  &
196                     &        , ' total mass : ', ztotmass, ', mass gain : ',  gainmass(jn,1)
197               END IF
198            END DO
199         ENDIF
200
201         DO jn = jp_sms0, jp_sms1
202            ztrneg(:,:,jn) = SUM( MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:), dim = 3 )   ! sum of the negative values
203            ztrpos(:,:,jn) = SUM( MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:), dim = 3 )   ! sum of the positive values
204         END DO
205         CALL sum3x3( ztrneg )
206         CALL sum3x3( ztrpos )
207         
208         DO jn = jp_sms0, jp_sms1
209            !
210            IF( l_trdtrc )   ztrtrd(:,:,:) = ptrn(:,:,:,jn)                            ! save input trb for trend computation
211            !
212            DO jk = 1, jpkm1
213               DO jj = 1, jpj
214                  DO ji = 1, jpi
215                     IF( ztrneg(ji,jj,jn) /= 0. ) THEN                                 ! if negative values over the 3x3 box
216                        !
217                        ptrn(ji,jj,jk,jn) = ptrn(ji,jj,jk,jn) * tmask(ji,jj,jk)   ! really needed?
218                        IF( ptrn(ji,jj,jk,jn) < 0. ) ptrn(ji,jj,jk,jn) = 0.       ! supress negative values
219                        IF( ptrn(ji,jj,jk,jn) > 0. ) THEN                         ! use positive values to compensate mass gain
220                           zcoef = 1. + ztrneg(ji,jj,jn) / ztrpos(ji,jj,jn)       ! ztrpos > 0 as ptrb > 0
221                           ptrn(ji,jj,jk,jn) = ptrn(ji,jj,jk,jn) * zcoef
222                           IF( zcoef < 0. ) THEN                                  ! if the compensation exceed the positive value
223                              gainmass(jn,2) = gainmass(jn,2) - ptrn(ji,jj,jk,jn) * cvol(ji,jj,jk)   ! we are adding mass...
224                              ptrn(ji,jj,jk,jn) = 0.                              ! limit the compensation to keep positive value
225                           ENDIF
226                        ENDIF
227                        !
228                     ENDIF
229                  END DO
230               END DO
231            END DO
232            !
233            IF( l_trdtrc ) THEN
234               ztrtrd(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt
235               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrd )       ! standard     trend handling
236            ENDIF
237            !
238         END DO
239 
240         IF( kt == nitend ) THEN
241            CALL mpp_sum( 'trcrad', gainmass(:,2) )
242            DO jn = jp_sms0, jp_sms1
243               IF( gainmass(jn,2) > 0. ) THEN
244                  ztotmass = glob_sum( 'trcrad', ptrn(:,:,:,jn) * cvol(:,:,:) )
245                  WRITE(numout, '(a, i2, a, D23.16, a, D23.16)') 'trcrad ptrn, traceur ', jn  &
246                     &        , ' total mass : ', ztotmass, ', mass gain : ',  gainmass(jn,1)
247               END IF
248            END DO
249         ENDIF
250
251         DEALLOCATE( ztrneg, ztrpos )
252         !
253      ELSE                                !==  total CFC content is NOT strictly preserved  ==!
254         !
255         DO jn = jp_sms0, jp_sms1 
256            !
257            IF( l_trdtrc )   ztrtrd(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
258            !
259            WHERE( ptrb(:,:,:,jn) < 0. )   ptrb(:,:,:,jn) = 0.
260            !
261            IF( l_trdtrc ) THEN
262               ztrtrd(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt
263               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrd )       ! Asselin-like trend handling
264            ENDIF
265            !
266            IF( l_trdtrc )   ztrtrd(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
267            !
268            WHERE( ptrn(:,:,:,jn) < 0. )   ptrn(:,:,:,jn) = 0.
269            !
270            IF( l_trdtrc ) THEN
271               ztrtrd(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrd(:,:,:) ) * zs2rdt
272               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrd )       ! standard     trend handling
273            ENDIF
274            !
275         END DO
276         !
277      ENDIF
278      !
279      IF( l_trdtrc )  DEALLOCATE( ztrtrd )
280      !
281   END SUBROUTINE trc_rad_sms
282
283#else
284   !!----------------------------------------------------------------------
285   !!   Dummy module :                                         NO TOP model
286   !!----------------------------------------------------------------------
287CONTAINS
288   SUBROUTINE trc_rad( kt )              ! Empty routine
289      INTEGER, INTENT(in) ::   kt
290      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
291   END SUBROUTINE trc_rad
292#endif
293   
294   !!======================================================================
295END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.