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

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 10.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 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   USE yomhook, ONLY: lhook, dr_hook
22   USE parkind1, ONLY: jprb, jpim
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC trc_rad         ! routine called by trcstp.F90
28
29   !! * Substitutions
30#  include "top_substitute.h90"
31   !!----------------------------------------------------------------------
32   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
33   !! $Id$
34   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
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      CHARACTER (len=22) :: charout
56      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
57      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
58      REAL(KIND=jprb)               :: zhook_handle
59
60      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_RAD'
61
62      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
63
64      !!----------------------------------------------------------------------
65      !
66      IF( nn_timing == 1 )  CALL timing_start('trc_rad')
67      !
68      IF( kt == nittrc000 ) THEN
69         IF(lwp) WRITE(numout,*)
70         IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
71         IF(lwp) WRITE(numout,*) '~~~~~~~ '
72      ENDIF
73
74      IF( lk_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0 , jp_cfc1               )  ! CFC model
75      IF( lk_c14b    )   CALL trc_rad_sms( kt, trb, trn, jp_c14b0, jp_c14b1              )  ! bomb C14
76      IF( lk_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0 , jp_pcs1, cpreserv='Y' )  ! PISCES model
77      IF( lk_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0 , jp_myt1               )  ! MY_TRC model
78
79      !
80      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
81         WRITE(charout, FMT="('rad')")
82         CALL prt_ctl_trc_info( charout )
83         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
84      ENDIF
85      !
86      IF( nn_timing == 1 )  CALL timing_stop('trc_rad')
87      !
88      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
89   END SUBROUTINE trc_rad
90
91   SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
92      !!-----------------------------------------------------------------------------
93      !!                  ***  ROUTINE trc_rad_sms  ***
94      !!
95      !! ** Purpose :   "crappy" routine to correct artificial negative
96      !!              concentrations due to isopycnal scheme
97      !!
98      !! ** Method  : 2 cases :
99      !!                - Set negative concentrations to zero while computing
100      !!                  the corresponding tracer content that is added to the
101      !!                  tracers. Then, adjust the tracer concentration using
102      !!                  a multiplicative factor so that the total tracer
103      !!                  concentration is preserved.
104      !!                - simply set to zero the negative CFC concentration
105      !!                  (the total content of concentration is not strictly preserved)
106      !!--------------------------------------------------------------------------------
107      !! Arguments
108      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
109      INTEGER  , INTENT( in ) ::  &
110         jp_sms0, &       !: First index of the passive tracer model
111         jp_sms1          !: Last  index of  the passive tracer model
112
113      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT( inout )  :: &
114         ptrb, ptrn       !: before and now traceur concentration
115
116      CHARACTER( len = 1) , INTENT(in), OPTIONAL  :: &
117         cpreserv          !: flag to preserve content or not
118     
119      ! Local declarations
120      INTEGER  :: ji, jj, jk, jn     ! dummy loop indices
121      REAL(wp) :: ztrcorb, ztrmasb   ! temporary scalars
122      REAL(wp) :: zcoef, ztrcorn, ztrmasn   !    "         "
123      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrdb, ztrtrdn   ! workspace arrays
124      REAL(wp) :: zs2rdt
125      LOGICAL ::   lldebug = .FALSE.
126      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
127      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
128      REAL(KIND=jprb)               :: zhook_handle
129
130      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_RAD_SMS'
131
132      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
133
134      !!----------------------------------------------------------------------
135
136 
137      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
138     
139      IF( PRESENT( cpreserv )  ) THEN   !  total tracer concentration is preserved
140     
141         DO jn = jp_sms0, jp_sms1
142            !                                                        ! ===========
143            ztrcorb = 0.e0   ;   ztrmasb = 0.e0
144            ztrcorn = 0.e0   ;   ztrmasn = 0.e0
145
146            IF( l_trdtrc ) THEN
147               ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
148               ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
149            ENDIF
150            !                                                         ! sum over the global domain
151            ztrcorb = glob_sum( MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
152            ztrcorn = glob_sum( MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
153
154            ztrmasb = glob_sum( MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
155            ztrmasn = glob_sum( MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
156
157            IF( ztrcorb /= 0 ) THEN
158               zcoef = 1. + ztrcorb / ztrmasb
159               DO jk = 1, jpkm1
160                  ptrb(:,:,jk,jn) = MAX( 0., ptrb(:,:,jk,jn) )
161                  ptrb(:,:,jk,jn) = ptrb(:,:,jk,jn) * zcoef * tmask(:,:,jk)
162               END DO
163            ENDIF
164
165            IF( ztrcorn /= 0 ) THEN
166               zcoef = 1. + ztrcorn / ztrmasn
167               DO jk = 1, jpkm1
168                  ptrn(:,:,jk,jn) = MAX( 0., ptrn(:,:,jk,jn) )
169                  ptrn(:,:,jk,jn) = ptrn(:,:,jk,jn) * zcoef * tmask(:,:,jk)
170               END DO
171            ENDIF
172            !
173            IF( l_trdtrc ) THEN
174               !
175               zs2rdt = 1. / ( 2. * rdt )
176               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
177               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
178               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
179               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
180              !
181            ENDIF
182
183         END DO
184         !
185         !
186      ELSE  ! total CFC content is not strictly preserved
187
188         DO jn = jp_sms0, jp_sms1 
189
190           IF( l_trdtrc ) THEN
191              ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
192              ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
193           ENDIF
194
195            DO jk = 1, jpkm1
196               DO jj = 1, jpj
197                  DO ji = 1, jpi
198                     ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
199                     ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
200                  END DO
201               END DO
202            END DO
203         
204            IF( l_trdtrc ) THEN
205               !
206               zs2rdt = 1. / ( 2. * rdt * FLOAT( nn_dttrc ) )
207               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
208               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
209               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
210               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
211              !
212            ENDIF
213            !
214         ENDDO
215
216      ENDIF
217
218      IF( l_trdtrc )  CALL wrk_dealloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
219
220      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
221   END SUBROUTINE trc_rad_sms
222#else
223   !!----------------------------------------------------------------------
224   !!   Dummy module :                                         NO TOP model
225   !!----------------------------------------------------------------------
226CONTAINS
227   SUBROUTINE trc_rad( kt )              ! Empty routine
228      INTEGER, INTENT(in) ::   kt
229      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
230      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
231      REAL(KIND=jprb)               :: zhook_handle
232
233      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_RAD'
234
235      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
236
237      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
238      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
239   END SUBROUTINE trc_rad
240#endif
241   
242   !!======================================================================
243END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.