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/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/TRP/trcrad.F90 @ 11960

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

Branch 2019/dev_r11943_MERGE_2019. Merge in changes from 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. (svn merge -r 11614:11954). Resolved tree conflicts and one actual conflict. Sette tested(these changes alter the ext/AGRIF reference; remember to update). See ticket #2341

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