trcstp.F90 16 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339
  1. MODULE trcstp
  2. !!======================================================================
  3. !! *** MODULE trcstp ***
  4. !! Time-stepping : time loop of opa for passive tracer
  5. !!======================================================================
  6. !! History : 1.0 ! 2004-03 (C. Ethe) Original
  7. !!----------------------------------------------------------------------
  8. #if defined key_top
  9. !!----------------------------------------------------------------------
  10. !! trc_stp : passive tracer system time-stepping
  11. !!----------------------------------------------------------------------
  12. USE oce_trc ! ocean dynamics and active tracers variables
  13. USE sbc_oce
  14. USE trc
  15. USE trctrp ! passive tracers transport
  16. USE trcsms ! passive tracers sources and sinks
  17. USE prtctl_trc ! Print control for debbuging
  18. USE trcdia
  19. USE trcwri
  20. USE trcrst
  21. USE trdtrc_oce
  22. USE trdmxl_trc
  23. USE iom
  24. USE in_out_manager
  25. USE trcsub
  26. ! EC-Earth C mass conservation correction - Raffaele Bernardello Jan 2019
  27. USE p4zsms
  28. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  29. IMPLICIT NONE
  30. PRIVATE
  31. PUBLIC trc_stp ! called by step
  32. REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE :: qsr_arr ! save qsr during TOP time-step
  33. REAL(wp) :: rdt_sampl
  34. INTEGER :: nb_rec_per_day, ktdcy
  35. REAL(wp) :: rsecfst, rseclast
  36. LOGICAL :: llnew
  37. !! * Substitutions
  38. # include "domzgr_substitute.h90"
  39. !!----------------------------------------------------------------------
  40. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  41. !! $Id: trcstp.F90 7654 2017-02-07 16:16:04Z cetlod $
  42. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  43. !!----------------------------------------------------------------------
  44. CONTAINS
  45. SUBROUTINE trc_stp( kt, kindic )
  46. !!-------------------------------------------------------------------
  47. !! *** ROUTINE trc_stp ***
  48. !!
  49. !! ** Purpose : Time loop of opa for passive tracer
  50. !!
  51. !! ** Method :
  52. !! Compute the passive tracers trends
  53. !! Update the passive tracers
  54. !!-------------------------------------------------------------------
  55. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  56. INTEGER, INTENT( inout ) :: kindic ! indicator
  57. INTEGER :: jk, jn ! dummy loop indices
  58. REAL(wp) :: ztrai
  59. CHARACTER (len=25) :: charout
  60. !!-------------------------------------------------------------------
  61. !
  62. IF( nn_timing == 1 ) CALL timing_start('trc_stp')
  63. !
  64. IF( kt == nittrc000 .AND. lk_trdmxl_trc ) CALL trd_mxl_trc_init ! trends: Mixed-layer
  65. !
  66. IF( lk_vvl ) THEN ! update ocean volume due to ssh temporal evolution
  67. DO jk = 1, jpk
  68. cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk)
  69. END DO
  70. IF( lk_degrad ) cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:) ! degrad option: reduction by facvol
  71. areatot = glob_sum( cvol(:,:,:) )
  72. ENDIF
  73. !
  74. IF( l_trcdm2dc ) CALL trc_mean_qsr( kt )
  75. !
  76. IF( nn_dttrc /= 1 ) CALL trc_sub_stp( kt ) ! averaging physical variables for sub-stepping
  77. !
  78. IF( MOD( kt , nn_dttrc ) == 0 ) THEN ! only every nn_dttrc time step
  79. !
  80. IF(ln_ctl) THEN
  81. WRITE(charout,FMT="('kt =', I4,' d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
  82. CALL prt_ctl_trc_info(charout)
  83. ENDIF
  84. !
  85. tra(:,:,:,:) = 0.e0
  86. !
  87. IF( .NOT.lk_offline ) CALL trc_rst_opn ( kt ) ! Open tracer restart file
  88. !!!!Begin EC-Earth modification for mass conservation of carbon. Author Raffaele Bernardello, January 2019
  89. IF( kt == nittrc000 ) THEN
  90. CALL trc_sms_cfix ( kt ) ! EC-Earth carbon mass conservation fix - Raffaele Bernardello Jan 2019
  91. ENDIF
  92. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  93. IF( lrst_trc ) CALL trc_rst_cal ( kt, 'WRITE' ) ! calendar
  94. IF( lk_iomput ) THEN ; CALL trc_wri ( kt ) ! output of passive tracers with iom I/O manager
  95. ELSE ; CALL trc_dia ( kt ) ! output of passive tracers with old I/O manager
  96. ENDIF
  97. CALL trc_sms ( kt ) ! tracers: sinks and sources
  98. CALL trc_trp ( kt ) ! transport of passive tracers
  99. IF( kt == nittrc000 ) THEN
  100. CALL iom_close( numrtr ) ! close input tracer restart file
  101. IF(lwm) CALL FLUSH( numont ) ! flush namelist output
  102. ENDIF
  103. !!!!Begin EC-Earth modification for mass conservation of carbon. Author Raffaele Bernardello, January 2019
  104. !
  105. ! We don't get satisfying mass conservation for passive tracers in NEMO. Drift in total mass is of
  106. ! the order of a few thousandths/year. Over a long spinup (thousands of years) this results in a drift of
  107. ! several points %. After much researching and asking around it seems we are not the only ones with this problem
  108. ! however, we haven't been able to find the reason. We need a workaround in order to run the ocean spinup needed for
  109. ! CMIP6. Unlike other tracers, DIC does not have a total mass correction available in PISCES
  110. ! code. So we are creating one here. Other tracers (NO3, Alk, PO4) are periodically adjusted in total mass to conserve
  111. ! the initial amount. This can't be done with DIC because the spun-up state will be used to run transient simulations
  112. ! with increase of atmospheric CO2 and consequent ocean uptake. So, the ocean DIC needs to be trully equilibrated.
  113. !
  114. ! Here, we compute the total amount of C in the ocean at the beginning of the leg. Then we do the same at the end
  115. ! of the leg. Plus, we consider the accumulated air-sea co2 flux, sedimentation of C and Cal, and river input during the leg.
  116. ! The change in internal mass has to equal the sum of sink and sources. The residual is used to compute a homogeneous
  117. ! global correction to be applied uniformly everywhere to DIC.
  118. !
  119. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  120. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  121. IF( kt == nitend ) THEN
  122. CALL trc_sms_cfix ( kt ) ! EC-Earth carbon mass conservation fix - Raffaele Bernardello Jan 2019
  123. ENDIF
  124. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  125. IF( lrst_trc ) CALL trc_rst_wri ( kt ) ! write tracer restart file
  126. IF( lk_trdmxl_trc ) CALL trd_mxl_trc ( kt ) ! trends: Mixed-layer
  127. !
  128. IF( nn_dttrc /= 1 ) CALL trc_sub_reset( kt ) ! resetting physical variables when sub-stepping
  129. !
  130. ENDIF
  131. !
  132. CALL trc_stp_ctl( kt, kindic )
  133. IF( lk_iomput .AND. kindic < 0 ) THEN
  134. CALL trc_wri_state( 'output.trc.abort', kt )
  135. nstop = nstop + 1
  136. ENDIF
  137. !
  138. ztrai = 0._wp ! content of all tracers
  139. DO jn = 1, jptra
  140. ztrai = ztrai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:) )
  141. END DO
  142. IF( lwp ) WRITE(numstr,9300) kt, ztrai / areatot
  143. 9300 FORMAT(i10,D23.16)
  144. !
  145. IF( nn_timing == 1 ) CALL timing_stop('trc_stp')
  146. !
  147. END SUBROUTINE trc_stp
  148. SUBROUTINE trc_mean_qsr( kt )
  149. !!----------------------------------------------------------------------
  150. !! *** ROUTINE trc_mean_qsr ***
  151. !!
  152. !! ** Purpose : Compute daily mean qsr for biogeochemical model in case
  153. !! of diurnal cycle
  154. !!
  155. !! ** Method : store in TOP the qsr every hour ( or every time-step if the latter
  156. !! is greater than 1 hour ) and then, compute the mean with
  157. !! a moving average over 24 hours.
  158. !! In coupled mode, the sampling is done at every coupling frequency
  159. !!----------------------------------------------------------------------
  160. INTEGER, INTENT(in) :: kt
  161. INTEGER :: jn
  162. REAL(wp) :: zkt, zrec
  163. CHARACTER(len=1) :: cl1 ! 1 character
  164. CHARACTER(len=2) :: cl2 ! 2 characters
  165. IF( kt == nittrc000 ) THEN
  166. IF( ln_cpl ) THEN
  167. rdt_sampl = rday / ncpl_qsr_freq
  168. nb_rec_per_day = ncpl_qsr_freq
  169. ELSE
  170. rdt_sampl = MAX( 3600., rdttrc(1) )
  171. nb_rec_per_day = INT( rday / rdt_sampl )
  172. ENDIF
  173. !
  174. IF( lwp ) THEN
  175. WRITE(numout,*)
  176. WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's',' Number of sampling per day nrec = ', nb_rec_per_day
  177. WRITE(numout,*)
  178. ENDIF
  179. !
  180. ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_day ) )
  181. !
  182. ! !* Restart: read in restart file
  183. IF( ln_rsttr .AND. nn_rsttr /= 0 .AND. iom_varid( numrtr, 'qsr_mean' , ldstop = .FALSE. ) > 0 &
  184. & .AND. iom_varid( numrtr, 'qsr_arr_1', ldstop = .FALSE. ) > 0 &
  185. & .AND. iom_varid( numrtr, 'ktdcy' , ldstop = .FALSE. ) > 0 &
  186. & .AND. iom_varid( numrtr, 'nrdcy' , ldstop = .FALSE. ) > 0 ) THEN
  187. CALL iom_get( numrtr, 'ktdcy', zkt )
  188. rsecfst = INT( zkt ) * rdttrc(1)
  189. IF(lwp) WRITE(numout,*) 'trc_qsr_mean: qsr_mean read in the restart file at time-step rsecfst =', rsecfst, ' s '
  190. CALL iom_get( numrtr, jpdom_autoglo, 'qsr_mean', qsr_mean ) ! A mean of qsr
  191. CALL iom_get( numrtr, 'nrdcy', zrec ) ! Number of record per days
  192. IF( INT( zrec ) == nb_rec_per_day ) THEN
  193. DO jn = 1, nb_rec_per_day
  194. IF( jn <= 9 ) THEN
  195. WRITE(cl1,'(i1)') jn
  196. CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) ) ! A mean of qsr
  197. ELSE
  198. WRITE(cl2,'(i2.2)') jn
  199. CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) ) ! A mean of qsr
  200. ENDIF
  201. ENDDO
  202. ELSE
  203. DO jn = 1, nb_rec_per_day
  204. qsr_arr(:,:,jn) = qsr_mean(:,:)
  205. ENDDO
  206. ENDIF
  207. ELSE !* no restart: set from nit000 values
  208. IF(lwp) WRITE(numout,*) 'trc_qsr_mean: qsr_mean set to nit000 values'
  209. rsecfst = kt * rdttrc(1)
  210. !
  211. qsr_mean(:,:) = qsr(:,:)
  212. DO jn = 1, nb_rec_per_day
  213. qsr_arr(:,:,jn) = qsr_mean(:,:)
  214. ENDDO
  215. ENDIF
  216. !
  217. ENDIF
  218. !
  219. rseclast = kt * rdttrc(1)
  220. !
  221. llnew = ( rseclast - rsecfst ) .ge. rdt_sampl ! new shortwave to store
  222. IF( llnew ) THEN
  223. ktdcy = kt
  224. IF( lwp .AND. kt < nittrc000 + 100 ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', ktdcy, &
  225. & ' time = ', rseclast/3600.,'hours '
  226. rsecfst = rseclast
  227. DO jn = 1, nb_rec_per_day - 1
  228. qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1)
  229. ENDDO
  230. qsr_arr (:,:,nb_rec_per_day) = qsr(:,:)
  231. qsr_mean(:,: ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_day
  232. ENDIF
  233. !
  234. IF( lrst_trc ) THEN !* Write the mean of qsr in restart file
  235. IF(lwp) WRITE(numout,*)
  236. IF(lwp) WRITE(numout,*) 'trc_mean_qsr : write qsr_mean in restart file kt =', kt
  237. IF(lwp) WRITE(numout,*) '~~~~~~~'
  238. zkt = REAL( ktdcy, wp )
  239. zrec = REAL( nb_rec_per_day, wp )
  240. CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt )
  241. CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec )
  242. DO jn = 1, nb_rec_per_day
  243. IF( jn <= 9 ) THEN
  244. WRITE(cl1,'(i1)') jn
  245. CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )
  246. ELSE
  247. WRITE(cl2,'(i2.2)') jn
  248. CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )
  249. ENDIF
  250. ENDDO
  251. CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) )
  252. ENDIF
  253. !
  254. END SUBROUTINE trc_mean_qsr
  255. SUBROUTINE trc_stp_ctl( kt, kindic )
  256. !!----------------------------------------------------------------------
  257. !! *** ROUTINE stp_ctl ***
  258. !!
  259. !! ** Purpose : Control the run
  260. !!
  261. !! ** Method : - Save the time step in numstp
  262. !! - Print it each 50 time steps
  263. !! - Print solver statistics in numsol
  264. !! - Stop the run IF problem for the solver ( indec < 0 )
  265. !!
  266. !! ** Actions : 'time.step' file containing the last ocean time-step
  267. !!
  268. !!----------------------------------------------------------------------
  269. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  270. INTEGER, INTENT( inout ) :: kindic ! indicator of solver convergence
  271. !!
  272. INTEGER :: ji, jj, jk, jn ! dummy loop indices
  273. INTEGER :: ii, ij, ik, itrc ! temporary integers
  274. INTEGER, DIMENSION(3) :: iloc !
  275. REAL(wp) :: zmax, zhuge ! temporary scalars
  276. REAL(wp), DIMENSION(jptra) :: ztrc ! temporary scalars
  277. !!----------------------------------------------------------------------
  278. DO jn = 1, jptra
  279. ztrc(jn) = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
  280. IF( lk_mpp ) CALL mpp_max( ztrc(jn) ) ! max over the global domain
  281. END DO
  282. zmax = ztrc(1)
  283. itrc = 1
  284. DO jn = 2, jptra
  285. IF( ztrc(jn) > zmax ) THEN
  286. zmax = ztrc(jn)
  287. itrc = jn
  288. ENDIF
  289. END DO
  290. zhuge = 1.e+10
  291. IF( ( zmax > zhuge ) .OR. isnan( zmax ) ) THEN
  292. IF( lk_mpp ) THEN
  293. CALL mpp_maxloc( trn(:,:,:,itrc),tmask, zmax,ii,ij,ik)
  294. ELSE
  295. iloc = MAXLOC( trn(:,:,:,itrc) )
  296. ii = iloc(1) + nimpp - 1
  297. ij = iloc(2) + njmpp - 1
  298. ik = iloc(3)
  299. ENDIF
  300. IF(lwp) THEN
  301. WRITE(numout,cform_err)
  302. WRITE(numout,*) " trc_stp_ctl : passive tracer ", TRIM( ctrcnm(itrc) ), " is too big. "
  303. WRITE(numout,*) ' ============ '
  304. WRITE(numout,9400) kt, zmax, ii, ij, ik
  305. WRITE(numout,*)
  306. WRITE(numout,*) ' output of last fields in numwso'
  307. ENDIF
  308. kindic = -3
  309. ENDIF
  310. 9400 FORMAT (' kt=',i6,' trcmax= ',D20.8,', i j k: ',3i5)
  311. END SUBROUTINE trc_stp_ctl
  312. #else
  313. !!----------------------------------------------------------------------
  314. !! Default key NO passive tracers
  315. !!----------------------------------------------------------------------
  316. CONTAINS
  317. SUBROUTINE trc_stp( kt ) ! Empty routine
  318. WRITE(*,*) 'trc_stp: You should not have seen this print! error?', kt
  319. END SUBROUTINE trc_stp
  320. #endif
  321. !!======================================================================
  322. END MODULE trcstp