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 NEMO/trunk/src/TOP/TRP – NEMO

source: NEMO/trunk/src/TOP/TRP/trcrad.F90 @ 10067

Last change on this file since 10067 was 10067, checked in by nicolasmartin, 6 years ago

Finalize the standardisation of routines header to the new release number (NEMO 4.0)

  • Property svn:keywords set to Id
File size: 11.1 KB
RevLine 
[941]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   !!----------------------------------------------------------------------
[9788]15   USE par_trc             ! need jptra, number of passive tracers
[941]16   USE oce_trc             ! ocean dynamics and tracers variables
[2528]17   USE trc                 ! ocean passive tracers variables
[4990]18   USE trd_oce
[2528]19   USE trdtra
[941]20   USE prtctl_trc          ! Print control for debbuging
21
22   IMPLICIT NONE
23   PRIVATE
24
[5836]25   PUBLIC trc_rad     
26   PUBLIC trc_rad_ini 
[941]27
[5836]28   LOGICAL , PUBLIC ::   ln_trcrad           !: flag to artificially correct negative concentrations
29
[941]30   !!----------------------------------------------------------------------
[10067]31   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[7753]32   !! $Id$
[9598]33   !! Software governed by the CeCILL licence (./LICENSE)
[941]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      !!----------------------------------------------------------------------
[9169]52      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
53      !
[941]54      CHARACTER (len=22) :: charout
55      !!----------------------------------------------------------------------
[3294]56      !
[9124]57      IF( ln_timing )   CALL timing_start('trc_rad')
[3294]58      !
[9169]59      IF( ln_age     )   CALL trc_rad_sms( kt, trb, trn, jp_age , jp_age                )  !  AGE
[7646]60      IF( ll_cfc     )   CALL trc_rad_sms( kt, trb, trn, jp_cfc0, jp_cfc1               )  !  CFC model
[9169]61      IF( ln_c14     )   CALL trc_rad_sms( kt, trb, trn, jp_c14 , jp_c14                )  !  C14
[7646]62      IF( ln_pisces  )   CALL trc_rad_sms( kt, trb, trn, jp_pcs0, jp_pcs1, cpreserv='Y' )  !  PISCES model
63      IF( ln_my_trc  )   CALL trc_rad_sms( kt, trb, trn, jp_myt0, jp_myt1               )  !  MY_TRC model
[1003]64      !
65      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
66         WRITE(charout, FMT="('rad')")
67         CALL prt_ctl_trc_info( charout )
68         CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
69      ENDIF
70      !
[9124]71      IF( ln_timing )   CALL timing_stop('trc_rad')
[3294]72      !
[1003]73   END SUBROUTINE trc_rad
74
[9169]75
[5836]76   SUBROUTINE trc_rad_ini
77      !!---------------------------------------------------------------------
78      !!                  ***  ROUTINE trc _rad_ini ***
79      !!
[9169]80      !! ** Purpose :   read  namelist options
[5836]81      !!----------------------------------------------------------------------
[9169]82      INTEGER ::   ios   ! Local integer output status for namelist read
83      !!
[5836]84      NAMELIST/namtrc_rad/ ln_trcrad
85      !!----------------------------------------------------------------------
86      !
87      REWIND( numnat_ref )              ! namtrc_rad in reference namelist
88      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
[9169]89907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
[5836]90      REWIND( numnat_cfg )              ! namtrc_rad in configuration namelist
91      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
[9169]92908   IF( ios > 0 )   CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
93      IF(lwm) WRITE( numont, namtrc_rad )
[5836]94
95      IF(lwp) THEN                     !   ! Control print
96         WRITE(numout,*)
[9169]97         WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
98         WRITE(numout,*) '~~~~~~~ '
[5836]99         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
[9169]100         WRITE(numout,*) '      correct artificially negative concen. or not   ln_trcrad = ', ln_trcrad
101         WRITE(numout,*)
102         IF( ln_trcrad ) THEN   ;   WRITE(numout,*) '      ===>>   ensure the global tracer conservation'
103         ELSE                   ;   WRITE(numout,*) '      ===>>   NO strict global tracer conservation'     
104         ENDIF
[5836]105      ENDIF
106      !
107   END SUBROUTINE trc_rad_ini
108
[9169]109
[1175]110   SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
[1003]111      !!-----------------------------------------------------------------------------
112      !!                  ***  ROUTINE trc_rad_sms  ***
113      !!
114      !! ** Purpose :   "crappy" routine to correct artificial negative
115      !!              concentrations due to isopycnal scheme
116      !!
117      !! ** Method  : 2 cases :
118      !!                - Set negative concentrations to zero while computing
119      !!                  the corresponding tracer content that is added to the
120      !!                  tracers. Then, adjust the tracer concentration using
121      !!                  a multiplicative factor so that the total tracer
122      !!                  concentration is preserved.
123      !!                - simply set to zero the negative CFC concentration
124      !!                  (the total content of concentration is not strictly preserved)
125      !!--------------------------------------------------------------------------------
[9169]126      INTEGER                                , INTENT(in   ) ::   kt                 ! ocean time-step index
127      INTEGER                                , INTENT(in   ) ::   jp_sms0, jp_sms1   ! First & last index of the passive tracer model
128      REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT(inout) ::   ptrb    , ptrn     ! before and now traceur concentration
129      CHARACTER( len = 1), OPTIONAL          , INTENT(in   ) ::   cpreserv           ! flag to preserve content or not
130      !
131      INTEGER ::   ji, jj, jk, jn     ! dummy loop indices
132      LOGICAL ::   lldebug = .FALSE.           ! local logical
133      REAL(wp)::   ztrcorb, ztrmasb, zs2rdt    ! temporary scalars
134      REAL(wp)::   zcoef  , ztrcorn, ztrmasn   !    -         -
[9125]135      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrtrdb, ztrtrdn   ! workspace arrays
[1003]136      !!----------------------------------------------------------------------
[9169]137      !
138      IF( l_trdtrc )   ALLOCATE( ztrtrdb(jpi,jpj,jpk), ztrtrdn(jpi,jpj,jpk) )
139      !
140      IF( PRESENT( cpreserv )  ) THEN     !==  total tracer concentration is preserved  ==!
141         !
[1003]142         DO jn = jp_sms0, jp_sms1
[9169]143            !
144            ztrcorb = 0._wp   ;   ztrmasb = 0._wp
145            ztrcorn = 0._wp   ;   ztrmasn = 0._wp
146            !
[3294]147            IF( l_trdtrc ) THEN
[7753]148               ztrtrdb(:,:,:) = ptrb(:,:,:,jn)                        ! save input trb for trend computation
149               ztrtrdn(:,:,:) = ptrn(:,:,:,jn)                        ! save input trn for trend computation
[3294]150            ENDIF
151            !                                                         ! sum over the global domain
[7753]152            ztrcorb = glob_sum( MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
153            ztrcorn = glob_sum( MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
[9169]154            !
[7753]155            ztrmasb = glob_sum( MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
156            ztrmasn = glob_sum( MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
[9169]157            !
[941]158            IF( ztrcorb /= 0 ) THEN
159               zcoef = 1. + ztrcorb / ztrmasb
160               DO jk = 1, jpkm1
[7753]161                  ptrb(:,:,jk,jn) = MAX( 0., ptrb(:,:,jk,jn) )
162                  ptrb(:,:,jk,jn) = ptrb(:,:,jk,jn) * zcoef * tmask(:,:,jk)
[941]163               END DO
164            ENDIF
[9169]165            !
[941]166            IF( ztrcorn /= 0 ) THEN
167               zcoef = 1. + ztrcorn / ztrmasn
168               DO jk = 1, jpkm1
[7753]169                  ptrn(:,:,jk,jn) = MAX( 0., ptrn(:,:,jk,jn) )
170                  ptrn(:,:,jk,jn) = ptrn(:,:,jk,jn) * zcoef * tmask(:,:,jk)
[941]171               END DO
172            ENDIF
173            !
[1175]174            IF( l_trdtrc ) THEN
175               !
[1257]176               zs2rdt = 1. / ( 2. * rdt )
[7753]177               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
178               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
[4990]179               CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb )       ! Asselin-like trend handling
180               CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn )       ! standard     trend handling
[1175]181              !
182            ENDIF
[9169]183            !
[941]184         END DO
185         !
[9169]186      ELSE                                !==  total CFC content is NOT strictly preserved  ==!
[1003]187         !
188         DO jn = jp_sms0, jp_sms1 
[9169]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            !
[7753]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
[9169]203            !
[7753]204            IF( l_trdtrc ) THEN
[7698]205               !
206               zs2rdt = 1. / ( 2. * rdt * REAL( nn_dttrc, wp ) )
[7753]207               ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
208               ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt 
[4990]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
[1257]211              !
212            ENDIF
213            !
[9169]214         END DO
215         !
[941]216      ENDIF
[9169]217      !
[9125]218      IF( l_trdtrc )  DEALLOCATE( ztrtrdb, ztrtrdn )
[9169]219      !
220   END SUBROUTINE trc_rad_sms
[1175]221
[941]222#else
223   !!----------------------------------------------------------------------
224   !!   Dummy module :                                         NO TOP model
225   !!----------------------------------------------------------------------
226CONTAINS
227   SUBROUTINE trc_rad( kt )              ! Empty routine
228      INTEGER, INTENT(in) ::   kt
229      WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
230   END SUBROUTINE trc_rad
231#endif
232   
233   !!======================================================================
234END MODULE trcrad
Note: See TracBrowser for help on using the repository browser.