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

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90 @ 4409

Last change on this file since 4409 was 2715, checked in by rblod, 13 years ago

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 10.1 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 trdmod_oce
18   USE trdtra
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   !!----------------------------------------------------------------------
33   
34CONTAINS
35
36   SUBROUTINE trc_rad( kt )
37      !!----------------------------------------------------------------------
38      !!                  ***  ROUTINE trc_rad  ***
39      !!
40      !! ** Purpose :   "crappy" routine to correct artificial negative
41      !!              concentrations due to isopycnal scheme
42      !!
43      !! ** Method  : - PISCES or LOBSTER: Set negative concentrations to zero
44      !!                while computing the corresponding tracer content that
45      !!                is added to the tracers. Then, adjust the tracer
46      !!                concentration using a multiplicative factor so that
47      !!                the total tracer concentration is preserved.
48      !!              - CFC: simply set to zero the negative CFC concentration
49      !!                (the total CFC content is not strictly preserved)
50      !!----------------------------------------------------------------------
51      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index     
52      CHARACTER (len=22) :: charout
53      !!----------------------------------------------------------------------
54
55      IF( kt == nit000 ) THEN
56         IF(lwp) WRITE(numout,*)
57         IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
58         IF(lwp) WRITE(numout,*) '~~~~~~~ '
59      ENDIF
60
61      IF( lk_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0 , jp_cfc1               )  ! CFC model
62      IF( lk_c14b    )   CALL trc_rad_sms( kt, trb, trn, jp_c14b0, jp_c14b1              )  ! bomb C14
63      IF( lk_lobster )   CALL trc_rad_sms( kt, trb, trn, jp_lob0 , jp_lob1, cpreserv='Y' )  ! LOBSTER model
64      IF( lk_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0 , jp_pcs1, cpreserv='Y' )  ! PISCES model
65      IF( lk_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0 , jp_myt1               )  ! MY_TRC model
66
67
68      !
69      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
70         WRITE(charout, FMT="('rad')")
71         CALL prt_ctl_trc_info( charout )
72         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
73      ENDIF
74      !
75   END SUBROUTINE trc_rad
76
77   SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
78      !!-----------------------------------------------------------------------------
79      !!                  ***  ROUTINE trc_rad_sms  ***
80      !!
81      !! ** Purpose :   "crappy" routine to correct artificial negative
82      !!              concentrations due to isopycnal scheme
83      !!
84      !! ** Method  : 2 cases :
85      !!                - Set negative concentrations to zero while computing
86      !!                  the corresponding tracer content that is added to the
87      !!                  tracers. Then, adjust the tracer concentration using
88      !!                  a multiplicative factor so that the total tracer
89      !!                  concentration is preserved.
90      !!                - simply set to zero the negative CFC concentration
91      !!                  (the total content of concentration is not strictly preserved)
92      !!--------------------------------------------------------------------------------
93      !! Arguments
94      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
95      INTEGER  , INTENT( in ) ::  &
96         jp_sms0, &       !: First index of the passive tracer model
97         jp_sms1          !: Last  index of  the passive tracer model
98
99      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT( inout )  :: &
100         ptrb, ptrn       !: before and now traceur concentration
101
102      CHARACTER( len = 1) , INTENT(in), OPTIONAL  :: &
103         cpreserv          !: flag to preserve content or not
104     
105      ! Local declarations
106      INTEGER  ::  ji, jj, jk, jn     ! dummy loop indices
107      REAL(wp) :: zvolk, ztrcorb, ztrmasb   ! temporary scalars
108      REAL(wp) :: zcoef, ztrcorn, ztrmasn   !    "         "
109      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrtrdb  ! workspace arrays
110      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::   ztrtrdn  ! workspace arrays
111      REAL(wp) :: zs2rdt
112      LOGICAL ::   lldebug = .FALSE.
113
114      !!----------------------------------------------------------------------
115
116      IF( l_trdtrc ) THEN
117        !
118        ALLOCATE( ztrtrdb(jpi,jpj,jpk) )
119        ALLOCATE( ztrtrdn(jpi,jpj,jpk) )
120        !
121      ENDIF
122     
123      IF( PRESENT( cpreserv )  ) THEN   !  total tracer concentration is preserved
124     
125         DO jn = jp_sms0, jp_sms1
126         !                                                        ! ===========
127            ztrcorb = 0.e0   ;   ztrmasb = 0.e0
128            ztrcorn = 0.e0   ;   ztrmasn = 0.e0
129
130           IF( l_trdtrc ) THEN
131              ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
132              ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
133           ENDIF
134
135
136            DO jk = 1, jpkm1
137               DO jj = 1, jpj
138                  DO ji = 1, jpi
139                     zvolk  = cvol(ji,jj,jk)
140# if defined key_degrad
141                     zvolk  = zvolk * facvol(ji,jj,jk)
142# endif
143                     ztrcorb = ztrcorb + MIN( 0., ptrb(ji,jj,jk,jn) ) * zvolk
144                     ztrcorn = ztrcorn + MIN( 0., ptrn(ji,jj,jk,jn) ) * zvolk
145
146                     ptrb(ji,jj,jk,jn) = MAX( 0., ptrb(ji,jj,jk,jn) )
147                     ptrn(ji,jj,jk,jn) = MAX( 0., ptrn(ji,jj,jk,jn) )
148
149                     ztrmasb = ztrmasb + ptrb(ji,jj,jk,jn) * zvolk
150                     ztrmasn = ztrmasn + ptrn(ji,jj,jk,jn) * zvolk
151                  END DO
152               END DO
153            END DO
154
155            IF( lk_mpp ) THEN
156               CALL mpp_sum( ztrcorb )      ! sum over the global domain
157               CALL mpp_sum( ztrcorn )      ! sum over the global domain
158               CALL mpp_sum( ztrmasb )      ! sum over the global domain
159               CALL mpp_sum( ztrmasn )      ! sum over the global domain
160            ENDIF
161
162            IF( ztrcorb /= 0 ) THEN
163               zcoef = 1. + ztrcorb / ztrmasb
164               DO jk = 1, jpkm1
165                  ptrb(:,:,jk,jn) = ptrb(:,:,jk,jn) * zcoef * tmask(:,:,jk)
166               END DO
167            ENDIF
168
169            IF( ztrcorn /= 0 ) THEN
170               zcoef = 1. + ztrcorn / ztrmasn
171               DO jk = 1, jpkm1
172                  ptrn(:,:,jk,jn) = ptrn(:,:,jk,jn) * zcoef * tmask(:,:,jk)
173               END DO
174            ENDIF
175            !
176            IF( l_trdtrc ) THEN
177               !
178               zs2rdt = 1. / ( 2. * rdt )
179               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
180               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
181               CALL trd_tra( kt, 'TRC', jn, jptra_trd_radb, ztrtrdb )       ! Asselin-like trend handling
182               CALL trd_tra( kt, 'TRC', jn, jptra_trd_radn, ztrtrdn )       ! standard     trend handling
183              !
184            ENDIF
185
186         END DO
187         !
188         !
189      ELSE  ! total CFC content is not strictly preserved
190
191         DO jn = jp_sms0, jp_sms1 
192
193           IF( l_trdtrc ) THEN
194              ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
195              ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
196           ENDIF
197
198            DO jk = 1, jpkm1
199               DO jj = 1, jpj
200                  DO ji = 1, jpi
201                     ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
202                     ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
203                  END DO
204               END DO
205            END DO
206         
207            IF( l_trdtrc ) THEN
208               !
209               zs2rdt = 1. / ( 2. * rdt * FLOAT(nn_dttrc) )
210               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
211               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
212               CALL trd_tra( kt, 'TRC', jn, jptra_trd_radb, ztrtrdb )       ! Asselin-like trend handling
213               CALL trd_tra( kt, 'TRC', jn, jptra_trd_radn, ztrtrdn )       ! standard     trend handling
214              !
215            ENDIF
216            !
217         ENDDO
218
219      ENDIF
220
221      IF( l_trdtrc )   DEALLOCATE( ztrtrdb, ztrtrdn )
222
223   END SUBROUTINE trc_rad_sms
224#else
225   !!----------------------------------------------------------------------
226   !!   Dummy module :                                         NO TOP model
227   !!----------------------------------------------------------------------
228CONTAINS
229   SUBROUTINE trc_rad( kt )              ! Empty routine
230      INTEGER, INTENT(in) ::   kt
231      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
232   END SUBROUTINE trc_rad
233#endif
234   
235   !!======================================================================
236END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.