trcrad.F90 9.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214
  1. MODULE 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. IMPLICIT NONE
  21. PRIVATE
  22. PUBLIC trc_rad, trc_rad_sms ! routine called by trcstp.F90
  23. !! * Substitutions
  24. # include "top_substitute.h90"
  25. !!----------------------------------------------------------------------
  26. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  27. !! $Id$
  28. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  29. !!----------------------------------------------------------------------
  30. CONTAINS
  31. SUBROUTINE trc_rad( kt )
  32. !!----------------------------------------------------------------------
  33. !! *** ROUTINE trc_rad ***
  34. !!
  35. !! ** Purpose : "crappy" routine to correct artificial negative
  36. !! concentrations due to isopycnal scheme
  37. !!
  38. !! ** Method : - PISCES or LOBSTER: Set negative concentrations to zero
  39. !! while computing the corresponding tracer content that
  40. !! is added to the tracers. Then, adjust the tracer
  41. !! concentration using a multiplicative factor so that
  42. !! the total tracer concentration is preserved.
  43. !! - CFC: simply set to zero the negative CFC concentration
  44. !! (the total CFC content is not strictly preserved)
  45. !!----------------------------------------------------------------------
  46. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  47. CHARACTER (len=22) :: charout
  48. !!----------------------------------------------------------------------
  49. !
  50. IF( nn_timing == 1 ) CALL timing_start('trc_rad')
  51. !
  52. IF( kt == nittrc000 ) THEN
  53. IF(lwp) WRITE(numout,*)
  54. IF(lwp) WRITE(numout,*) 'trc_rad : Correct artificial negative concentrations '
  55. IF(lwp) WRITE(numout,*) '~~~~~~~ '
  56. ENDIF
  57. IF( lk_age ) CALL trc_rad_sms( kt, trb, trn, jp_age0 , jp_age1 ) ! AGE tracer
  58. IF( lk_cfc ) CALL trc_rad_sms( kt, trb, trn, jp_cfc0 , jp_cfc1 ) ! CFC model
  59. IF( lk_c14b ) CALL trc_rad_sms( kt, trb, trn, jp_c14b0, jp_c14b1 ) ! bomb C14
  60. IF( lk_pisces ) CALL trc_rad_sms( kt, trb, trn, jp_pcs0 , jp_pcs1, cpreserv='Y' ) ! PISCES model
  61. IF( lk_my_trc ) CALL trc_rad_sms( kt, trb, trn, jp_myt0 , jp_myt1, cpreserv='Y' ) ! MY_TRC model
  62. !
  63. IF(ln_ctl) THEN ! print mean trends (used for debugging)
  64. WRITE(charout, FMT="('rad')")
  65. CALL prt_ctl_trc_info( charout )
  66. CALL prt_ctl_trc( tab4d=trn, mask=tmask, clinfo=ctrcnm )
  67. ENDIF
  68. !
  69. IF( nn_timing == 1 ) CALL timing_stop('trc_rad')
  70. !
  71. END SUBROUTINE trc_rad
  72. SUBROUTINE trc_rad_sms( kt, ptrb, ptrn, jp_sms0, jp_sms1, cpreserv )
  73. !!-----------------------------------------------------------------------------
  74. !! *** ROUTINE trc_rad_sms ***
  75. !!
  76. !! ** Purpose : "crappy" routine to correct artificial negative
  77. !! concentrations due to isopycnal scheme
  78. !!
  79. !! ** Method : 2 cases :
  80. !! - Set negative concentrations to zero while computing
  81. !! the corresponding tracer content that is added to the
  82. !! tracers. Then, adjust the tracer concentration using
  83. !! a multiplicative factor so that the total tracer
  84. !! concentration is preserved.
  85. !! - simply set to zero the negative CFC concentration
  86. !! (the total content of concentration is not strictly preserved)
  87. !!--------------------------------------------------------------------------------
  88. !! Arguments
  89. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  90. INTEGER , INTENT( in ) :: &
  91. jp_sms0, & !: First index of the passive tracer model
  92. jp_sms1 !: Last index of the passive tracer model
  93. REAL(wp), DIMENSION (jpi,jpj,jpk,jptra), INTENT( inout ) :: &
  94. ptrb, ptrn !: before and now traceur concentration
  95. CHARACTER( len = 1) , INTENT(in), OPTIONAL :: &
  96. cpreserv !: flag to preserve content or not
  97. ! Local declarations
  98. INTEGER :: ji, jj, jk, jn ! dummy loop indices
  99. REAL(wp) :: ztrcorb, ztrmasb ! temporary scalars
  100. REAL(wp) :: zcoef, ztrcorn, ztrmasn ! " "
  101. REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrtrdb, ztrtrdn ! workspace arrays
  102. REAL(wp) :: zs2rdt
  103. LOGICAL :: lldebug = .FALSE.
  104. !!----------------------------------------------------------------------
  105. IF( l_trdtrc ) CALL wrk_alloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
  106. IF( PRESENT( cpreserv ) ) THEN ! total tracer concentration is preserved
  107. DO jn = jp_sms0, jp_sms1
  108. ! ! ===========
  109. ztrcorb = 0.e0 ; ztrmasb = 0.e0
  110. ztrcorn = 0.e0 ; ztrmasn = 0.e0
  111. IF( l_trdtrc ) THEN
  112. ztrtrdb(:,:,:) = ptrb(:,:,:,jn) ! save input trb for trend computation
  113. ztrtrdn(:,:,:) = ptrn(:,:,:,jn) ! save input trn for trend computation
  114. ENDIF
  115. ! ! sum over the global domain
  116. ztrcorb = glob_sum( MIN( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
  117. ztrcorn = glob_sum( MIN( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
  118. ztrmasb = glob_sum( MAX( 0., ptrb(:,:,:,jn) ) * cvol(:,:,:) )
  119. ztrmasn = glob_sum( MAX( 0., ptrn(:,:,:,jn) ) * cvol(:,:,:) )
  120. IF( ztrcorb /= 0 ) THEN
  121. zcoef = 1. + ztrcorb / ztrmasb
  122. DO jk = 1, jpkm1
  123. ptrb(:,:,jk,jn) = MAX( 0., ptrb(:,:,jk,jn) )
  124. ptrb(:,:,jk,jn) = ptrb(:,:,jk,jn) * zcoef * tmask(:,:,jk)
  125. END DO
  126. ENDIF
  127. IF( ztrcorn /= 0 ) THEN
  128. zcoef = 1. + ztrcorn / ztrmasn
  129. DO jk = 1, jpkm1
  130. ptrn(:,:,jk,jn) = MAX( 0., ptrn(:,:,jk,jn) )
  131. ptrn(:,:,jk,jn) = ptrn(:,:,jk,jn) * zcoef * tmask(:,:,jk)
  132. END DO
  133. ENDIF
  134. !
  135. IF( l_trdtrc ) THEN
  136. !
  137. zs2rdt = 1. / ( 2. * rdt )
  138. ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
  139. ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt
  140. CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb ) ! Asselin-like trend handling
  141. CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn ) ! standard trend handling
  142. !
  143. ENDIF
  144. END DO
  145. !
  146. !
  147. ELSE ! total CFC content is not strictly preserved
  148. DO jn = jp_sms0, jp_sms1
  149. IF( l_trdtrc ) THEN
  150. ztrtrdb(:,:,:) = ptrb(:,:,:,jn) ! save input trb for trend computation
  151. ztrtrdn(:,:,:) = ptrn(:,:,:,jn) ! save input trn for trend computation
  152. ENDIF
  153. DO jk = 1, jpkm1
  154. DO jj = 1, jpj
  155. DO ji = 1, jpi
  156. ptrn(ji,jj,jk,jn) = MAX( 0. , ptrn(ji,jj,jk,jn) )
  157. ptrb(ji,jj,jk,jn) = MAX( 0. , ptrb(ji,jj,jk,jn) )
  158. END DO
  159. END DO
  160. END DO
  161. IF( l_trdtrc ) THEN
  162. !
  163. zs2rdt = 1. / ( 2. * rdt * FLOAT( nn_dttrc ) )
  164. ztrtrdb(:,:,:) = ( ptrb(:,:,:,jn) - ztrtrdb(:,:,:) ) * zs2rdt
  165. ztrtrdn(:,:,:) = ( ptrn(:,:,:,jn) - ztrtrdn(:,:,:) ) * zs2rdt
  166. CALL trd_tra( kt, 'TRC', jn, jptra_radb, ztrtrdb ) ! Asselin-like trend handling
  167. CALL trd_tra( kt, 'TRC', jn, jptra_radn, ztrtrdn ) ! standard trend handling
  168. !
  169. ENDIF
  170. !
  171. ENDDO
  172. ENDIF
  173. IF( l_trdtrc ) CALL wrk_dealloc( jpi, jpj, jpk, ztrtrdb, ztrtrdn )
  174. END SUBROUTINE trc_rad_sms
  175. #else
  176. !!----------------------------------------------------------------------
  177. !! Dummy module : NO TOP model
  178. !!----------------------------------------------------------------------
  179. CONTAINS
  180. SUBROUTINE trc_rad( kt ) ! Empty routine
  181. INTEGER, INTENT(in) :: kt
  182. WRITE(*,*) 'trc_rad: You should not have seen this print! error?', kt
  183. END SUBROUTINE trc_rad
  184. #endif
  185. !!======================================================================
  186. END MODULE trcrad