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/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/TOP/TRP – NEMO

source: NEMO/branches/2020/dev_r14116_HPC-04_mcastril_Mixed_Precision_implementation_final/src/TOP/TRP/trcrad.F90 @ 14219

Last change on this file since 14219 was 14219, checked in by mcastril, 4 years ago

Add Mixed Precision support by Oriol Tintó

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