trcrst.F90 15 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330
  1. MODULE trcrst
  2. !!======================================================================
  3. !! *** MODULE trcrst ***
  4. !! TOP : Manage the passive tracer restart
  5. !!======================================================================
  6. !! History : - ! 1991-03 () original code
  7. !! 1.0 ! 2005-03 (O. Aumont, A. El Moussaoui) F90
  8. !! - ! 2005-10 (C. Ethe) print control
  9. !! 2.0 ! 2005-10 (C. Ethe, G. Madec) revised architecture
  10. !!----------------------------------------------------------------------
  11. #if defined key_top
  12. !!----------------------------------------------------------------------
  13. !! 'key_top' TOP models
  14. !!----------------------------------------------------------------------
  15. !!----------------------------------------------------------------------
  16. !! trc_rst : Restart for passive tracer
  17. !!----------------------------------------------------------------------
  18. !!----------------------------------------------------------------------
  19. !! 'key_top' TOP models
  20. !!----------------------------------------------------------------------
  21. !! trc_rst_opn : open restart file
  22. !! trc_rst_read : read restart file
  23. !! trc_rst_wri : write restart file
  24. !!----------------------------------------------------------------------
  25. USE oce_trc
  26. USE trc
  27. USE trcnam_trp
  28. USE iom
  29. USE daymod
  30. IMPLICIT NONE
  31. PRIVATE
  32. PUBLIC trc_rst_opn ! called by ???
  33. PUBLIC trc_rst_read ! called by ???
  34. PUBLIC trc_rst_wri ! called by ???
  35. PUBLIC trc_rst_cal
  36. !! * Substitutions
  37. # include "top_substitute.h90"
  38. CONTAINS
  39. SUBROUTINE trc_rst_opn( kt )
  40. !!----------------------------------------------------------------------
  41. !! *** trc_rst_opn ***
  42. !!
  43. !! ** purpose : output of sea-trc variable in a netcdf file
  44. !!----------------------------------------------------------------------
  45. INTEGER, INTENT(in) :: kt ! number of iteration
  46. !
  47. CHARACTER(LEN=20) :: clkt ! ocean time-step define as a character
  48. CHARACTER(LEN=50) :: clname ! trc output restart file name
  49. CHARACTER(LEN=256) :: clpath ! full path to ocean output restart file
  50. !!----------------------------------------------------------------------
  51. !
  52. IF( lk_offline ) THEN
  53. IF( kt == nittrc000 ) THEN
  54. lrst_trc = .FALSE.
  55. IF( ln_rst_list ) THEN
  56. nrst_lst = 1
  57. nitrst = nstocklist( nrst_lst )
  58. ELSE
  59. nitrst = nitend
  60. ENDIF
  61. ENDIF
  62. IF( .NOT. ln_rst_list .AND. MOD( kt - 1, nstock ) == 0 ) THEN
  63. ! we use kt - 1 and not kt - nittrc000 to keep the same periodicity from the beginning of the experiment
  64. nitrst = kt + nstock - 1 ! define the next value of nitrst for restart writing
  65. IF( nitrst > nitend ) nitrst = nitend ! make sure we write a restart at the end of the run
  66. ENDIF
  67. ELSE
  68. IF( kt == nittrc000 ) lrst_trc = .FALSE.
  69. ENDIF
  70. ! to get better performances with NetCDF format:
  71. ! we open and define the tracer restart file one tracer time step before writing the data (-> at nitrst - 2*nn_dttrc + 1)
  72. ! except if we write tracer restart files every tracer time step or if a tracer restart file was writen at nitend - 2*nn_dttrc + 1
  73. IF( kt == nitrst - 2*nn_dttrc .OR. nstock == nn_dttrc .OR. ( kt == nitend - nn_dttrc .AND. .NOT. lrst_trc ) ) THEN
  74. ! beware of the format used to write kt (default is i8.8, that should be large enough)
  75. IF( nitrst > 1.0e9 ) THEN ; WRITE(clkt,* ) nitrst
  76. ELSE ; WRITE(clkt,'(i8.8)') nitrst
  77. ENDIF
  78. ! create the file
  79. IF(lwp) WRITE(numout,*)
  80. clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_"//TRIM(cn_trcrst_out)
  81. clpath = TRIM(cn_trcrst_outdir)
  82. IF( clpath(LEN_TRIM(clpath):) /= '/' ) clpath = TRIM(clpath) // '/'
  83. IF(lwp) WRITE(numout,*) &
  84. ' open trc restart.output NetCDF file: ',TRIM(clpath)//clname
  85. CALL iom_open( TRIM(clpath)//TRIM(clname), numrtw, ldwrt = .TRUE., kiolib = jprstlib )
  86. lrst_trc = .TRUE.
  87. ENDIF
  88. !
  89. END SUBROUTINE trc_rst_opn
  90. SUBROUTINE trc_rst_read
  91. !!----------------------------------------------------------------------
  92. !! *** trc_rst_opn ***
  93. !!
  94. !! ** purpose : read passive tracer fields in restart files
  95. !!----------------------------------------------------------------------
  96. INTEGER :: jn
  97. !!----------------------------------------------------------------------
  98. !
  99. IF(lwp) WRITE(numout,*)
  100. IF(lwp) WRITE(numout,*) 'trc_rst_read : read data in the TOP restart file'
  101. IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
  102. ! READ prognostic variables and computes diagnostic variable
  103. DO jn = 1, jptra
  104. CALL iom_get( numrtr, jpdom_autoglo, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
  105. END DO
  106. DO jn = 1, jptra
  107. CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
  108. END DO
  109. !
  110. END SUBROUTINE trc_rst_read
  111. SUBROUTINE trc_rst_wri( kt )
  112. !!----------------------------------------------------------------------
  113. !! *** trc_rst_wri ***
  114. !!
  115. !! ** purpose : write passive tracer fields in restart files
  116. !!----------------------------------------------------------------------
  117. INTEGER, INTENT( in ) :: kt ! ocean time-step index
  118. !!
  119. INTEGER :: jn
  120. REAL(wp) :: zarak0
  121. !!----------------------------------------------------------------------
  122. !
  123. CALL iom_rstput( kt, nitrst, numrtw, 'rdttrc1', rdttrc(1) ) ! surface passive tracer time step
  124. ! prognostic variables
  125. ! --------------------
  126. DO jn = 1, jptra
  127. CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) )
  128. END DO
  129. DO jn = 1, jptra
  130. CALL iom_rstput( kt, nitrst, numrtw, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )
  131. END DO
  132. !
  133. IF( kt == nitrst ) THEN
  134. CALL trc_rst_stat ! statistics
  135. CALL iom_close( numrtw ) ! close the restart file (only at last time step)
  136. #if ! defined key_trdmxl_trc
  137. lrst_trc = .FALSE.
  138. #endif
  139. IF( lk_offline .AND. ln_rst_list ) THEN
  140. nrst_lst = nrst_lst + 1
  141. nitrst = nstocklist( nrst_lst )
  142. ENDIF
  143. ENDIF
  144. !
  145. END SUBROUTINE trc_rst_wri
  146. SUBROUTINE trc_rst_cal( kt, cdrw )
  147. !!---------------------------------------------------------------------
  148. !! *** ROUTINE trc_rst_cal ***
  149. !!
  150. !! ** Purpose : Read or write calendar in restart file:
  151. !!
  152. !! WRITE(READ) mode:
  153. !! kt : number of time step since the begining of the experiment at the
  154. !! end of the current(previous) run
  155. !! adatrj(0) : number of elapsed days since the begining of the experiment at the
  156. !! end of the current(previous) run (REAL -> keep fractions of day)
  157. !! ndastp : date at the end of the current(previous) run (coded as yyyymmdd integer)
  158. !!
  159. !! According to namelist parameter nrstdt,
  160. !! nn_rsttr = 0 no control on the date (nittrc000 is arbitrary).
  161. !! nn_rsttr = 1 we verify that nittrc000 is equal to the last
  162. !! time step of previous run + 1.
  163. !! In both those options, the exact duration of the experiment
  164. !! since the beginning (cumulated duration of all previous restart runs)
  165. !! is not stored in the restart and is assumed to be (nittrc000-1)*rdt.
  166. !! This is valid is the time step has remained constant.
  167. !!
  168. !! nn_rsttr = 2 the duration of the experiment in days (adatrj)
  169. !! has been stored in the restart file.
  170. !!----------------------------------------------------------------------
  171. INTEGER , INTENT(in) :: kt ! ocean time-step
  172. CHARACTER(len=*), INTENT(in) :: cdrw ! "READ"/"WRITE" flag
  173. !
  174. INTEGER :: jlibalt = jprstlib
  175. LOGICAL :: llok
  176. REAL(wp) :: zkt, zrdttrc1
  177. REAL(wp) :: zndastp
  178. ! Time domain : restart
  179. ! ---------------------
  180. IF( TRIM(cdrw) == 'READ' ) THEN
  181. IF(lwp) WRITE(numout,*)
  182. IF(lwp) WRITE(numout,*) 'trc_rst_cal : read the TOP restart file for calendar'
  183. IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
  184. IF ( jprstlib == jprstdimg ) THEN
  185. ! eventually read netcdf file (monobloc) for restarting on different number of processors
  186. ! if {cn_trcrst_in}.nc exists, then set jlibalt to jpnf90
  187. INQUIRE( FILE = TRIM(cn_trcrst_indir)//'/'//TRIM(cn_trcrst_in)//'.nc', EXIST = llok )
  188. IF ( llok ) THEN ; jlibalt = jpnf90 ; ELSE ; jlibalt = jprstlib ; ENDIF
  189. ENDIF
  190. IF( ln_rsttr ) THEN
  191. CALL iom_open( TRIM(cn_trcrst_indir)//'/'//cn_trcrst_in, numrtr, kiolib = jlibalt )
  192. CALL iom_get ( numrtr, 'kt', zkt ) ! last time-step of previous run
  193. IF(lwp) THEN
  194. WRITE(numout,*) ' *** Info read in restart : '
  195. WRITE(numout,*) ' previous time-step : ', NINT( zkt )
  196. WRITE(numout,*) ' *** restart option'
  197. SELECT CASE ( nn_rsttr )
  198. CASE ( 0 ) ; WRITE(numout,*) ' nn_rsttr = 0 : no control of nittrc000'
  199. CASE ( 1 ) ; WRITE(numout,*) ' nn_rsttr = 1 : no control the date at nittrc000 (use ndate0 read in the namelist)'
  200. CASE ( 2 ) ; WRITE(numout,*) ' nn_rsttr = 2 : calendar parameters read in restart'
  201. END SELECT
  202. WRITE(numout,*)
  203. ENDIF
  204. ! Control of date
  205. IF( nittrc000 - NINT( zkt ) /= nn_dttrc .AND. nn_rsttr /= 0 ) &
  206. & CALL ctl_stop( ' ===>>>> : problem with nittrc000 for the restart', &
  207. & ' verify the restart file or rerun with nn_rsttr = 0 (namelist)' )
  208. ENDIF
  209. !
  210. IF( lk_offline ) THEN
  211. ! ! set the date in offline mode
  212. IF( ln_rsttr .AND. nn_rsttr == 2 ) THEN
  213. CALL iom_get( numrtr, 'ndastp', zndastp )
  214. ndastp = NINT( zndastp )
  215. CALL iom_get( numrtr, 'adatrj', adatrj )
  216. ELSE
  217. ndastp = ndate0 - 1 ! ndate0 read in the namelist in dom_nam
  218. adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday
  219. ! note this is wrong if time step has changed during run
  220. ENDIF
  221. !
  222. IF(lwp) THEN
  223. WRITE(numout,*) ' *** Info used values : '
  224. WRITE(numout,*) ' date ndastp : ', ndastp
  225. WRITE(numout,*) ' number of elapsed days since the begining of run : ', adatrj
  226. WRITE(numout,*)
  227. ENDIF
  228. !
  229. IF( ln_rsttr ) THEN ; neuler = 1
  230. ELSE ; neuler = 0
  231. ENDIF
  232. !
  233. CALL day_init ! compute calendar
  234. !
  235. ENDIF
  236. !
  237. ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
  238. !
  239. IF( kt == nitrst ) THEN
  240. IF(lwp) WRITE(numout,*)
  241. IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp
  242. IF(lwp) WRITE(numout,*) '~~~~~~~'
  243. ENDIF
  244. CALL iom_rstput( kt, nitrst, numrtw, 'kt' , REAL( kt , wp) ) ! time-step
  245. CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) ) ! date
  246. CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj ) ! number of elapsed days since
  247. ! ! the begining of the run [s]
  248. ENDIF
  249. END SUBROUTINE trc_rst_cal
  250. SUBROUTINE trc_rst_stat
  251. !!----------------------------------------------------------------------
  252. !! *** trc_rst_stat ***
  253. !!
  254. !! ** purpose : Compute tracers statistics
  255. !!----------------------------------------------------------------------
  256. INTEGER :: jk, jn
  257. REAL(wp) :: ztraf, zmin, zmax, zmean, zdrift
  258. REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
  259. !!----------------------------------------------------------------------
  260. IF( lwp ) THEN
  261. WRITE(numout,*)
  262. WRITE(numout,*) ' ----TRACER STAT---- '
  263. WRITE(numout,*)
  264. ENDIF
  265. !
  266. DO jk = 1, jpk
  267. zvol(:,:,jk) = e1e2t(:,:) * fse3t_a(:,:,jk) * tmask(:,:,jk)
  268. END DO
  269. !
  270. DO jn = 1, jptra
  271. ztraf = glob_sum( trn(:,:,:,jn) * zvol(:,:,:) )
  272. zmin = MINVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
  273. zmax = MAXVAL( trn(:,:,:,jn), mask= ((tmask*SPREAD(tmask_i,DIM=3,NCOPIES=jpk).NE.0.)) )
  274. IF( lk_mpp ) THEN
  275. CALL mpp_min( zmin ) ! min over the global domain
  276. CALL mpp_max( zmax ) ! max over the global domain
  277. END IF
  278. zmean = ztraf / areatot
  279. zdrift = ( ( ztraf - trai(jn) ) / ( trai(jn) + 1.e-12 ) ) * 100._wp
  280. IF(lwp) WRITE(numout,9000) jn, TRIM( ctrcnm(jn) ), zmean, zmin, zmax, zdrift
  281. END DO
  282. IF(lwp) WRITE(numout,*)
  283. 9000 FORMAT(' tracer nb :',i2,' name :',a10,' mean :',e18.10,' min :',e18.10, &
  284. & ' max :',e18.10,' drift :',e18.10, ' %')
  285. !
  286. END SUBROUTINE trc_rst_stat
  287. #else
  288. !!----------------------------------------------------------------------
  289. !! Dummy module : No passive tracer
  290. !!----------------------------------------------------------------------
  291. CONTAINS
  292. SUBROUTINE trc_rst_read ! Empty routines
  293. END SUBROUTINE trc_rst_read
  294. SUBROUTINE trc_rst_wri( kt )
  295. INTEGER, INTENT ( in ) :: kt
  296. WRITE(*,*) 'trc_rst_wri: You should not have seen this print! error?', kt
  297. END SUBROUTINE trc_rst_wri
  298. #endif
  299. !!----------------------------------------------------------------------
  300. !! NEMO/TOP 3.3 , NEMO Consortium (2010)
  301. !! $Id: trcrst.F90 5513 2015-06-30 09:59:46Z cetlod $
  302. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  303. !!======================================================================
  304. END MODULE trcrst