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

source: branches/UKMO/dev_merge_2017_GC_couple_pkg/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90 @ 9677

Last change on this file since 9677 was 9677, checked in by dancopsey, 6 years ago

Strip out SVN keywords.

File size: 11.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 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   !!----------------------------------------------------------------------
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      !
53      CHARACTER (len=22) :: charout
54      !!----------------------------------------------------------------------
55      !
56      IF( ln_timing )   CALL timing_start('trc_rad')
57      !
58      IF( ln_age     )   CALL trc_rad_sms( kt, trb, trn, jp_age , jp_age                )  !  AGE
59      IF( ll_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0, jp_cfc1               )  !  CFC model
60      IF( ln_c14     )   CALL trc_rad_sms( kt, trb, trn, jp_c14 , jp_c14                )  !  C14
61      IF( ln_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model
62      IF( ln_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0, jp_myt1               )  !  MY_TRC model
63      !
64      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
65         WRITE(charout, FMT="('rad')")
66         CALL prt_ctl_trc_info( charout )
67         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
68      ENDIF
69      !
70      IF( ln_timing )   CALL timing_stop('trc_rad')
71      !
72   END SUBROUTINE trc_rad
73
74
75   SUBROUTINE trc_rad_ini
76      !!---------------------------------------------------------------------
77      !!                  ***  ROUTINE trc _rad_ini ***
78      !!
79      !! ** Purpose :   read  namelist options
80      !!----------------------------------------------------------------------
81      INTEGER ::   ios   ! Local integer output status for namelist read
82      !!
83      NAMELIST/namtrc_rad/ ln_trcrad
84      !!----------------------------------------------------------------------
85      !
86      REWIND( numnat_ref )              ! namtrc_rad in reference namelist
87      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
88907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
89      REWIND( numnat_cfg )              ! namtrc_rad in configuration namelist
90      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
91908   IF( ios > 0 )   CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
92      IF(lwm) WRITE( numont, namtrc_rad )
93
94      IF(lwp) THEN                     !   ! Control print
95         WRITE(numout,*)
96         WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
97         WRITE(numout,*) '~~~~~~~ '
98         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
99         WRITE(numout,*) '      correct artificially negative concen. or not   ln_trcrad = ', ln_trcrad
100         WRITE(numout,*)
101         IF( ln_trcrad ) THEN   ;   WRITE(numout,*) '      ===>>   ensure the global tracer conservation'
102         ELSE                   ;   WRITE(numout,*) '      ===>>   NO strict global tracer conservation'     
103         ENDIF
104      ENDIF
105      !
106   END SUBROUTINE trc_rad_ini
107
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      INTEGER                                , INTENT(in   ) ::   kt                 ! ocean time-step index
126      INTEGER                                , INTENT(in   ) ::   jp_sms0, jp_sms1   ! First & last index of the passive tracer model
127      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT(inout) ::   ptrb    , ptrn     ! before and now traceur concentration
128      CHARACTER( len = 1), OPTIONAL          , INTENT(in   ) ::   cpreserv           ! flag to preserve content or not
129      !
130      INTEGER ::   ji, jj, jk, jn     ! dummy loop indices
131      LOGICAL ::   lldebug = .FALSE.           ! local logical
132      REAL(wp)::   ztrcorb, ztrmasb, zs2rdt    ! temporary scalars
133      REAL(wp)::   zcoef  , ztrcorn, ztrmasn   !    -         -
134      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrtrdb, ztrtrdn   ! workspace arrays
135      !!----------------------------------------------------------------------
136      !
137      IF( l_trdtrc )   ALLOCATE( ztrtrdb(jpi,jpj,jpk), ztrtrdn(jpi,jpj,jpk) )
138      !
139      IF( PRESENT( cpreserv )  ) THEN     !==  total tracer concentration is preserved  ==!
140         !
141         DO jn = jp_sms0, jp_sms1
142            !
143            ztrcorb = 0._wp   ;   ztrmasb = 0._wp
144            ztrcorn = 0._wp   ;   ztrmasn = 0._wp
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      ELSE                                !==  total CFC content is NOT strictly preserved  ==!
186         !
187         DO jn = jp_sms0, jp_sms1 
188            !
189            IF( l_trdtrc ) THEN
190               ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
191               ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
192            ENDIF
193            !
194            DO jk = 1, jpkm1
195               DO jj = 1, jpj
196                  DO ji = 1, jpi
197                     ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
198                     ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
199                  END DO
200               END DO
201            END DO
202            !
203            IF( l_trdtrc ) THEN
204               !
205               zs2rdt = 1. / ( 2. * rdt * REAL( nn_dttrc, wp ) )
206               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
207               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
208               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
209               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
210              !
211            ENDIF
212            !
213         END DO
214         !
215      ENDIF
216      !
217      IF( l_trdtrc )  DEALLOCATE( ztrtrdb, ztrtrdn )
218      !
219   END SUBROUTINE trc_rad_sms
220
221#else
222   !!----------------------------------------------------------------------
223   !!   Dummy module :                                         NO TOP model
224   !!----------------------------------------------------------------------
225CONTAINS
226   SUBROUTINE trc_rad( kt )              ! Empty routine
227      INTEGER, INTENT(in) ::   kt
228      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
229   END SUBROUTINE trc_rad
230#endif
231   
232   !!======================================================================
233END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.