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

source: branches/2012/dev_r3309_LOCEAN12_Ediag/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90 @ 3318

Last change on this file since 3318 was 3318, checked in by gm, 12 years ago

Ediag branche: #927 split TRA/DYN trd computation

  • Property svn:keywords set to Id
File size: 9.6 KB
Line 
1MODULE trcrad
2   !!======================================================================
3   !!                       ***  MODULE  trcrad  ***
4   !! Ocean passive tracers:  correction of negative concentrations
5   !!======================================================================
6   !! History :  OPA  !  2001-01  (O. Aumont & E. Kestenare)  Original code
7   !!   NEMO     1.0  !  2004-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        ! trends: ocean variables
18   USE trdtra         ! trends: tracer manager
19   USE prtctl_trc     ! Print control for debbuging
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   trc_rad   ! routine called by trcstp.F90
25
26   !! * Substitutions
27#  include "top_substitute.h90"
28   !!----------------------------------------------------------------------
29   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
30   !! $Id$
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE trc_rad( kt )
36      !!----------------------------------------------------------------------
37      !!                  ***  ROUTINE trc_rad  ***
38      !!
39      !! ** Purpose :   "crappy" routine to correct artificial negative
40      !!              concentrations due to isopycnal scheme
41      !!
42      !! ** Method  : - PISCES or LOBSTER: Set negative concentrations to zero
43      !!                while computing the corresponding tracer content that
44      !!                is added to the tracers. Then, adjust the tracer
45      !!                concentration using a multiplicative factor so that
46      !!                the total tracer concentration is preserved.
47      !!              - CFC: simply set to zero the negative CFC concentration
48      !!                (the total CFC content is not strictly preserved)
49      !!----------------------------------------------------------------------
50      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
51      !
52      CHARACTER (len=22) :: charout
53      !!----------------------------------------------------------------------
54      !
55      IF( nn_timing == 1 )  CALL timing_start('trc_rad')
56      !
57      IF( kt == nittrc000 ) THEN
58         IF(lwp) WRITE(numout,*)
59         IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
60         IF(lwp) WRITE(numout,*) '~~~~~~~ '
61      ENDIF
62
63      IF( lk_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0 , jp_cfc1               )  ! CFC model
64      IF( lk_c14b    )   CALL trc_rad_sms( kt, trb, trn, jp_c14b0, jp_c14b1              )  ! bomb C14
65      IF( lk_lobster )   CALL trc_rad_sms( kt, trb, trn, jp_lob0 , jp_lob1, cpreserv='Y' )  ! LOBSTER model
66      IF( lk_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0 , jp_pcs1, cpreserv='Y' )  ! PISCES model
67      IF( lk_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0 , jp_myt1               )  ! MY_TRC model
68
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=trn, mask=tmask, clinfo=ctrcnm )
74      ENDIF
75      !
76      IF( nn_timing == 1 )  CALL timing_stop('trc_rad')
77      !
78   END SUBROUTINE trc_rad
79
80
81   SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
82      !!-----------------------------------------------------------------------------
83      !!                  ***  ROUTINE trc_rad_sms  ***
84      !!
85      !! ** Purpose :   "crappy" routine to correct artificial negative
86      !!              concentrations due to isopycnal scheme
87      !!
88      !! ** Method  : 2 cases :
89      !!                - Set negative concentrations to zero while computing
90      !!                  the corresponding tracer content that is added to the
91      !!                  tracers. Then, adjust the tracer concentration using
92      !!                  a multiplicative factor so that the total tracer
93      !!                  concentration is preserved.
94      !!                - simply set to zero the negative CFC concentration
95      !!                  (the total content of concentration is not strictly preserved)
96      !!--------------------------------------------------------------------------------
97      INTEGER                                , INTENT(in   ) ::   kt                 ! ocean time-step index
98      INTEGER                                , INTENT(in   ) ::   jp_sms0, jp_sms1   ! first/last index of the passive tracer model
99      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT(inout) ::   ptrb, ptrn         ! before/now traceur concentration
100      CHARACTER( len = 1),      OPTIONAL     , INTENT(in   ) ::   cpreserv           ! flag to preserve content or not
101      !
102      INTEGER  ::   ji, jj, jk, jn             ! dummy loop indices
103      REAL(wp) ::   ztrcorb, ztrmasb, zs2rdt   ! local scalars
104      REAL(wp) ::   zcoef, ztrcorn, ztrmasn    !   -      -
105      LOGICAL  ::   lldebug = .FALSE.
106      REAL(wp), POINTER, DIMENSION(:,:,:) ::   ztrtrdb, ztrtrdn   ! 3D workspace
107      !!----------------------------------------------------------------------
108 
109      IF( l_trdtrc )  CALL wrk_alloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
110     
111      IF( PRESENT( cpreserv )  ) THEN   !  total tracer concentration is preserved
112         !                                                           ! ===========
113
114         DO jn = jp_sms0, jp_sms1
115            !
116            ztrcorb = 0._wp   ;   ztrmasb = 0._wp
117            ztrcorn = 0._wp   ;   ztrmasn = 0._wp
118            !
119            IF( l_trdtrc ) THEN
120               ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
121               ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
122            ENDIF
123            !                                                         ! sum over the global domain
124            ztrcorb = glob_sum( MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
125            ztrcorn = glob_sum( MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
126            ztrmasb = glob_sum( MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
127            ztrmasn = glob_sum( MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
128            !
129            IF( ztrcorb /= 0 ) THEN
130               zcoef = 1. + ztrcorb / ztrmasb
131               DO jk = 1, jpkm1
132                  ptrb(:,:,jk,jn) = MAX( 0., ptrb(:,:,jk,jn) )
133                  ptrb(:,:,jk,jn) = ptrb(:,:,jk,jn) * zcoef * tmask(:,:,jk)
134               END DO
135            ENDIF
136            !
137            IF( ztrcorn /= 0 ) THEN
138               zcoef = 1. + ztrcorn / ztrmasn
139               DO jk = 1, jpkm1
140                  ptrn(:,:,jk,jn) = MAX( 0., ptrn(:,:,jk,jn) )
141                  ptrn(:,:,jk,jn) = ptrn(:,:,jk,jn) * zcoef * tmask(:,:,jk)
142               END DO
143            ENDIF
144            !
145            IF( l_trdtrc ) THEN
146               !
147               zs2rdt = 1. / ( 2. * rdt )
148               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
149               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
150               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
151               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
152              !
153            ENDIF
154            !
155         END DO
156         !
157         !
158      ELSE  ! total CFC content is not strictly preserved
159         !
160         DO jn = jp_sms0, jp_sms1 
161            !
162            IF( l_trdtrc ) THEN
163               ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
164               ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
165            ENDIF
166            !
167            DO jk = 1, jpkm1
168               DO jj = 1, jpj
169                  DO ji = 1, jpi
170                     ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
171                     ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
172                  END DO
173               END DO
174            END DO
175            !
176            IF( l_trdtrc ) THEN
177               zs2rdt = 1. / ( 2. * rdt * FLOAT( nn_dttrc ) )
178               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
179               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
180               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
181               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
182            ENDIF
183            !
184         END DO
185         !
186      ENDIF
187      !
188      IF( l_trdtrc )  CALL wrk_dealloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
189      !
190   END SUBROUTINE trc_rad_sms
191
192#else
193   !!----------------------------------------------------------------------
194   !!   Dummy module :                                         NO TOP model
195   !!----------------------------------------------------------------------
196CONTAINS
197   SUBROUTINE trc_rad( kt )              ! Empty routine
198      INTEGER, INTENT(in) ::   kt
199      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
200   END SUBROUTINE trc_rad
201#endif
202   
203   !!======================================================================
204END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.