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/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90 @ 7698

Last change on this file since 7698 was 7698, checked in by mocavero, 7 years ago

update trunk with OpenMP parallelization

  • Property svn:keywords set to Id
File size: 12.9 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 trc                 ! ocean passive tracers variables
17   USE trd_oce
18   USE trdtra
19   USE prtctl_trc          ! Print control for debbuging
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC trc_rad     
25   PUBLIC trc_rad_ini 
26
27   LOGICAL , PUBLIC ::   ln_trcrad           !: flag to artificially correct negative concentrations
28
29   !!----------------------------------------------------------------------
30   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
31   !! $Id$
32   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
33   !!----------------------------------------------------------------------
34   
35CONTAINS
36
37   SUBROUTINE trc_rad( kt )
38      !!----------------------------------------------------------------------
39      !!                  ***  ROUTINE trc_rad  ***
40      !!
41      !! ** Purpose :   "crappy" routine to correct artificial negative
42      !!              concentrations due to isopycnal scheme
43      !!
44      !! ** Method  : - PISCES or LOBSTER: Set negative concentrations to zero
45      !!                while computing the corresponding tracer content that
46      !!                is added to the tracers. Then, adjust the tracer
47      !!                concentration using a multiplicative factor so that
48      !!                the total tracer concentration is preserved.
49      !!              - CFC: simply set to zero the negative CFC concentration
50      !!                (the total CFC content is not strictly preserved)
51      !!----------------------------------------------------------------------
52      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index     
53      CHARACTER (len=22) :: charout
54      !!----------------------------------------------------------------------
55      !
56      IF( nn_timing == 1 )  CALL timing_start('trc_rad')
57      !
58      IF( kt == nittrc000 ) THEN
59         IF(lwp) WRITE(numout,*)
60         IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
61         IF(lwp) WRITE(numout,*) '~~~~~~~ '
62      ENDIF
63
64      IF( ln_age     )   CALL trc_rad_sms( kt, trb, trn, jp_age , jp_age               )  !  AGE
65      IF( ll_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0, jp_cfc1               )  !  CFC model
66      IF( ln_c14     )   CALL trc_rad_sms( kt, trb, trn, jp_c14 , jp_c14               )  !  C14
67      IF( ln_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model
68      IF( ln_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0, jp_myt1               )  !  MY_TRC model
69
70      !
71      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
72         WRITE(charout, FMT="('rad')")
73         CALL prt_ctl_trc_info( charout )
74         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
75      ENDIF
76      !
77      IF( nn_timing == 1 )  CALL timing_stop('trc_rad')
78      !
79   END SUBROUTINE trc_rad
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      NAMELIST/namtrc_rad/ ln_trcrad
89      !!----------------------------------------------------------------------
90
91      !
92      REWIND( numnat_ref )              ! namtrc_rad in reference namelist
93      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
94907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
95
96      REWIND( numnat_cfg )              ! namtrc_rad in configuration namelist
97      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
98908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
99      IF(lwm) WRITE ( numont, namtrc_rad )
100
101      IF(lwp) THEN                     !   ! Control print
102         WRITE(numout,*)
103         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
104         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
105      ENDIF
106      !
107   END SUBROUTINE trc_rad_ini
108
109   SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
110      !!-----------------------------------------------------------------------------
111      !!                  ***  ROUTINE trc_rad_sms  ***
112      !!
113      !! ** Purpose :   "crappy" routine to correct artificial negative
114      !!              concentrations due to isopycnal scheme
115      !!
116      !! ** Method  : 2 cases :
117      !!                - Set negative concentrations to zero while computing
118      !!                  the corresponding tracer content that is added to the
119      !!                  tracers. Then, adjust the tracer concentration using
120      !!                  a multiplicative factor so that the total tracer
121      !!                  concentration is preserved.
122      !!                - simply set to zero the negative CFC concentration
123      !!                  (the total content of concentration is not strictly preserved)
124      !!--------------------------------------------------------------------------------
125      !! Arguments
126      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
127      INTEGER  , INTENT( in ) ::  &
128         jp_sms0, &       !: First index of the passive tracer model
129         jp_sms1          !: Last  index of  the passive tracer model
130
131      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT( inout )  :: &
132         ptrb, ptrn       !: before and now traceur concentration
133
134      CHARACTER( len = 1) , INTENT(in), OPTIONAL  :: &
135         cpreserv          !: flag to preserve content or not
136     
137      ! Local declarations
138      INTEGER  :: ji, jj, jk, jn     ! dummy loop indices
139      REAL(wp) :: ztrcorb, ztrmasb   ! temporary scalars
140      REAL(wp) :: zcoef, ztrcorn, ztrmasn   !    "         "
141      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrdb, ztrtrdn   ! workspace arrays
142      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zcptrbmax, zcptrnmax, zcptrbmin, zcptrnmin   ! workspace arrays
143      REAL(wp) :: zs2rdt
144      LOGICAL ::   lldebug = .FALSE.
145      !!----------------------------------------------------------------------
146
147 
148      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
149     
150      CALL wrk_alloc( jpi, jpj, jpk, zcptrbmax, zcptrnmax, zcptrbmin, zcptrnmin )
151      IF( PRESENT( cpreserv )  ) THEN   !  total tracer concentration is preserved
152     
153         DO jn = jp_sms0, jp_sms1
154            !                                                        ! ===========
155            ztrcorb = 0.e0   ;   ztrmasb = 0.e0
156            ztrcorn = 0.e0   ;   ztrmasn = 0.e0
157
158            IF( l_trdtrc ) THEN
159!$OMP PARALLEL DO schedule(static) private(jk,jj,ji)
160               DO jk = 1, jpk
161                  DO jj = 1, jpj
162                     DO ji = 1, jpi
163                        ztrtrdb(ji,jj,jk) = ptrb(ji,jj,jk,jn)                        ! save input trb for trend computation
164                        ztrtrdn(ji,jj,jk) = ptrn(ji,jj,jk,jn)
165                     END DO
166                  END DO
167               END DO
168            ENDIF
169            !                                                         ! sum over the global domain
170!$OMP PARALLEL DO schedule(static) private(jk,jj,ji)
171            DO jk = 1, jpk
172               DO jj = 1, jpj
173                  DO ji = 1, jpi
174                     zcptrbmin(ji,jj,jk) = MIN( 0., ptrb(ji,jj,jk,jn) ) * cvol(ji,jj,jk)
175                     zcptrnmin(ji,jj,jk) = MIN( 0., ptrn(ji,jj,jk,jn) ) * cvol(ji,jj,jk)
176                     zcptrbmax(ji,jj,jk) = MAX( 0., ptrb(ji,jj,jk,jn) ) * cvol(ji,jj,jk)
177                     zcptrnmax(ji,jj,jk) = MAX( 0., ptrn(ji,jj,jk,jn) ) * cvol(ji,jj,jk)
178                  END DO
179               END DO
180            END DO
181            ztrcorb = glob_sum( zcptrbmin(:,:,:) )
182            ztrcorn = glob_sum( zcptrnmin(:,:,:) )
183            ztrmasb = glob_sum( zcptrbmax(:,:,:) )
184            ztrmasn = glob_sum( zcptrnmax(:,:,:) )
185
186            IF( ztrcorb /= 0 ) THEN
187               zcoef = 1. + ztrcorb / ztrmasb
188!$OMP PARALLEL DO schedule(static) private(jk)
189               DO jk = 1, jpkm1
190                  DO jj = 1, jpj
191                     DO ji = 1, jpi
192                        ptrb(ji,jj,jk,jn) = MAX( 0., ptrb(ji,jj,jk,jn) )
193                        ptrb(ji,jj,jk,jn) = ptrb(ji,jj,jk,jn) * zcoef * tmask(ji,jj,jk)
194                     END DO
195                  END DO
196               END DO
197            ENDIF
198
199            IF( ztrcorn /= 0 ) THEN
200               zcoef = 1. + ztrcorn / ztrmasn
201!$OMP PARALLEL DO schedule(static) private(jk)
202               DO jk = 1, jpkm1
203                  DO jj = 1, jpj
204                     DO ji = 1, jpi
205                        ptrn(ji,jj,jk,jn) = MAX( 0., ptrn(ji,jj,jk,jn) )
206                        ptrn(ji,jj,jk,jn) = ptrn(ji,jj,jk,jn) * zcoef * tmask(ji,jj,jk)
207                     END DO
208                  END DO
209               END DO
210            ENDIF
211            !
212            IF( l_trdtrc ) THEN
213               !
214               zs2rdt = 1. / ( 2. * rdt )
215!$OMP PARALLEL DO schedule(static) private(jk,jj,ji)
216               DO jk = 1, jpk
217                  DO jj = 1, jpj
218                     DO ji = 1, jpi
219                        ztrtrdb(ji,jj,jk) = ( ptrb(ji,jj,jk,jn) - ztrtrdb(ji,jj,jk) ) * zs2rdt
220                        ztrtrdn(ji,jj,jk) = ( ptrn(ji,jj,jk,jn) - ztrtrdn(ji,jj,jk) ) * zs2rdt
221                     END DO
222                  END DO
223               END DO
224
225               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
226               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
227              !
228            ENDIF
229
230         END DO
231         !
232         !
233      ELSE  ! total CFC content is not strictly preserved
234
235         DO jn = jp_sms0, jp_sms1 
236
237           IF( l_trdtrc ) THEN
238!$OMP PARALLEL DO schedule(static) private(jk,jj,ji)
239              DO jk = 1, jpk
240                 DO jj = 1, jpj
241                    DO ji = 1, jpi
242                       ztrtrdb(ji,jj,jk) = ptrb(ji,jj,jk,jn)                        ! save input trb for trend computation
243                       ztrtrdn(ji,jj,jk) = ptrn(ji,jj,jk,jn)
244                    END DO
245                 END DO
246              END DO
247           END IF
248
249!$OMP PARALLEL DO schedule(static) private(jk,jj,ji)
250           DO jk = 1, jpkm1
251              DO jj = 1, jpj
252                 DO ji = 1, jpi
253                    ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
254                    ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
255                 END DO
256              END DO
257           END DO
258
259           IF( l_trdtrc ) THEN
260               !
261               zs2rdt = 1. / ( 2. * rdt * REAL( nn_dttrc, wp ) )
262!$OMP PARALLEL DO schedule(static) private(jk,jj,ji)
263               DO jk = 1, jpk
264                  DO jj = 1, jpj
265                     DO ji = 1, jpi
266                        ztrtrdb(ji,jj,jk) = ( ptrb(ji,jj,jk,jn) - ztrtrdb(ji,jj,jk) ) * zs2rdt
267                        ztrtrdn(ji,jj,jk) = ( ptrn(ji,jj,jk,jn) - ztrtrdn(ji,jj,jk) ) * zs2rdt
268                     END DO
269                  END DO
270               END DO
271               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
272               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
273              !
274            ENDIF
275            !
276         ENDDO
277
278      ENDIF
279
280      IF( l_trdtrc )  CALL wrk_dealloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
281      CALL wrk_dealloc( jpi, jpj, jpk, zcptrbmax, zcptrnmax, zcptrbmin, zcptrnmin )
282
283   END SUBROUTINE trc_rad_sms
284#else
285   !!----------------------------------------------------------------------
286   !!   Dummy module :                                         NO TOP model
287   !!----------------------------------------------------------------------
288CONTAINS
289   SUBROUTINE trc_rad( kt )              ! Empty routine
290      INTEGER, INTENT(in) ::   kt
291      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
292   END SUBROUTINE trc_rad
293#endif
294   
295   !!======================================================================
296END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.