diawri_dimg.h90 14 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372
  1. !!----------------------------------------------------------------------
  2. !! *** diawri_dimg.h90 ***
  3. !!----------------------------------------------------------------------
  4. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  5. !! $Id $
  6. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  7. !!----------------------------------------------------------------------
  8. SUBROUTINE dia_wri( kt )
  9. !!----------------------------------------------------------------------
  10. !! *** routine dia_wri ***
  11. !!
  12. !! ** Purpose : output dynamics and tracer fields on direct access file
  13. !! suitable for MPP computing
  14. !!
  15. !! ** define key : 'key_dimgout'
  16. !!
  17. !! ** Method : Default is to cumulate the values over the interval between
  18. !! 2 output, and each nwrite time-steps the mean value is computed
  19. !! and written to the direct access file.
  20. !! If 'key_diainstant' is defined, no mean values are computed and the
  21. !! instantaneous fields are dump.
  22. !! Each processor creates its own file with its local data
  23. !! Merging all the files is performed off line by a dedicated program
  24. !!
  25. !! ** Arguments :
  26. !! kt : time-step number
  27. !! kindinc : error condition indicator : >=0 : OK, < 0 : error.
  28. !!
  29. !! ** Naming convention for files
  30. !!
  31. !! {cexper}_{var}_y----m--d--.dimg
  32. !! cexper is the name of the experience, given in the namelist
  33. !! var can be either U, V, T, S, KZ, SSH, ...
  34. !! var can also be 2D, which means that each level of the file is a 2D field as described below
  35. !! y----m--d-- is the date at the time of the dump
  36. !! For mpp output, each processor dumps its own memory, on appropriate record range
  37. !! (direct access : for level jk of a klev field on proc narea irec = 1+ klev*(narea -1) + jk )
  38. !! To be tested with a lot of procs !!!!
  39. !!
  40. !! level 1: utau(:,:) * umask(:,:,1) zonal stress in N.m-2
  41. !! level 2: vtau(:,:) * vmask(:,:,1) meridional stress in N. m-2
  42. !! level 3: qsr + qns total heat flux (W/m2)
  43. !! level 4: ( emp (:,:)-rnf(:,:) ) E-P flux (mm/day)
  44. !! level 5: tb (:,:,1)-sst model SST -forcing sst (degree C) ! deprecated
  45. !! level 6: bsfb(:,:) streamfunction (m**3/s)
  46. !! level 7: qsr (:,:) solar flux (W/m2)
  47. !! level 8: qrp (:,:) relax component of T flux.
  48. !! level 9: erp (:,:) relax component of S flux
  49. !! level 10: hmld(:,:) turbocline depth
  50. !! level 11: hmlp(:,:) mixed layer depth
  51. !! level 12: fr_i(:,:) ice fraction (between 0 and 1)
  52. !! level 13: sst(:,:) the observed SST we relax to. ! deprecated
  53. !! level 14: qct(:,:) equivalent flux due to treshold SST
  54. !! level 15: fbt(:,:) feedback term .
  55. !! level 16: ( emp * sss ) concentration/dilution term on salinity
  56. !! level 17: ( emp * sst ) concentration/dilution term on temperature
  57. !! level 17: fsalt(:,:) Ice=>ocean net freshwater
  58. !! level 18: gps(:,:) the surface pressure (m).
  59. !! level 19: spgu(:,:) the surface pressure gradient in X direction.
  60. !! level 20: spgv(:,:) the surface pressure gradient in Y direction.
  61. !!
  62. !! History: OPA ! 1997-02 ( Clipper Group ) dimg files
  63. !! - ! 2003-12 ( J.M. Molines) f90, mpp output for OPA9.0
  64. !! NEMO 1.0 ! 2005-05 (S. Theetten) add emps fsalt move gps spgu spgv 2 lines below
  65. !! - ! 2005-11 (V. Garnier) Surface pressure gradient organization
  66. !!----------------------------------------------------------------------
  67. USE lib_mpp
  68. !!
  69. INTEGER ,INTENT(in) :: kt
  70. !!
  71. #if defined key_diainstant
  72. LOGICAL, PARAMETER :: ll_dia_inst=.TRUE. !: for instantaneous output
  73. #else
  74. LOGICAL, PARAMETER :: ll_dia_inst=.FALSE. !: for average output
  75. #endif
  76. INTEGER , SAVE :: nmoyct
  77. REAL(wp), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: um , vm, wm ! mean u, v, w fields
  78. REAL(wp), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: avtm ! mean kz fields
  79. REAL(wp), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: tm , sm ! mean t, s fields
  80. REAL(wp), ALLOCATABLE, SAVE, DIMENSION (:,:,:) :: fsel ! mean 2d fields
  81. INTEGER :: inbsel, jk
  82. INTEGER :: iyear,imon,iday
  83. INTEGER :: ialloc
  84. REAL(wp) :: zdtj
  85. CHARACTER(LEN=80) :: clname
  86. CHARACTER(LEN=80) :: cltext
  87. CHARACTER(LEN=80) :: clmode
  88. CHARACTER(LEN= 4) :: clver
  89. !!----------------------------------------------------------------------
  90. IF( nn_timing == 1 ) CALL timing_start('dia_wri')
  91. !
  92. ! Initialization
  93. ! ---------------
  94. !
  95. IF( .NOT. ALLOCATED(um) )THEN
  96. ALLOCATE(um(jpi,jpj,jpk), vm(jpi,jpj,jpk), &
  97. wm(jpi,jpj,jpk), &
  98. avtm(jpi,jpj,jpk), &
  99. tm(jpi,jpj,jpk), sm(jpi,jpj,jpk), &
  100. fsel(jpi,jpj,jpk), &
  101. STAT=ialloc )
  102. !
  103. IF( lk_mpp ) CALL mpp_sum ( ialloc )
  104. IF( ialloc /= 0 ) CALL ctl_warn('dia_wri( diawri_dimg.h90) : failed to allocate arrays')
  105. ENDIF
  106. inbsel = 18
  107. IF( inbsel > jpk ) THEN
  108. IF(lwp) WRITE(numout,*) ' STOP inbsel =',inbsel,' is larger than jpk=',jpk
  109. STOP
  110. ENDIF
  111. iyear = ndastp/10000
  112. imon = (ndastp-iyear*10000)/100
  113. iday = ndastp - imon*100 - iyear*10000
  114. !
  115. !! dimg format V1.0 should start with the 4 char. string '@!01'
  116. !!
  117. clver='@!01'
  118. !
  119. IF( .NOT. ll_dia_inst ) THEN
  120. !
  121. !! * Mean output section
  122. !! ----------------------
  123. !
  124. IF( kt == nit000 .AND. lwp ) WRITE(numout,*) &
  125. 'THE OUTPUT FILES CONTAINS THE AVERAGE OF EACH FIELD'
  126. !
  127. IF( kt == nit000 ) THEN
  128. ! reset arrays for average computation
  129. nmoyct = 0
  130. !
  131. um(:,:,:) = 0._wp
  132. vm(:,:,:) = 0._wp
  133. wm(:,:,:) = 0._wp
  134. avtm(:,:,:) = 0._wp
  135. tm(:,:,:) = 0._wp
  136. sm(:,:,:) = 0._wp
  137. fsel(:,:,:) = 0._wp
  138. !
  139. ENDIF
  140. ! cumulate values
  141. ! ---------------
  142. nmoyct = nmoyct+1
  143. !
  144. um(:,:,:)=um(:,:,:) + un (:,:,:)
  145. vm(:,:,:)=vm(:,:,:) + vn (:,:,:)
  146. wm(:,:,:)=wm(:,:,:) + wn (:,:,:)
  147. avtm(:,:,:)=avtm(:,:,:) + avt (:,:,:)
  148. tm(:,:,:)=tm(:,:,:) + tsn(:,:,:,jp_tem)
  149. sm(:,:,:)=sm(:,:,:) + tsn(:,:,:,jp_sal)
  150. !
  151. fsel(:,:,1 ) = fsel(:,:,1 ) + utau(:,:) * umask(:,:,1)
  152. fsel(:,:,2 ) = fsel(:,:,2 ) + vtau(:,:) * vmask(:,:,1)
  153. fsel(:,:,3 ) = fsel(:,:,3 ) + qsr (:,:) + qns (:,:)
  154. fsel(:,:,4 ) = fsel(:,:,4 ) + ( emp(:,:)-rnf(:,:) )
  155. ! fsel(:,:,5 ) = fsel(:,:,5 ) + tsb(:,:,1,jp_tem) !RB not used
  156. fsel(:,:,6 ) = fsel(:,:,6 ) + sshn(:,:)
  157. fsel(:,:,7 ) = fsel(:,:,7 ) + qsr(:,:)
  158. IF( ln_ssr ) THEN
  159. IF( nn_sstr /= 0 ) fsel(:,:,8 ) = fsel(:,:,8 ) + qrp (:,:)
  160. IF( nn_sssr /= 0 ) fsel(:,:,9 ) = fsel(:,:,9 ) + erp (:,:)
  161. ENDIF
  162. fsel(:,:,10) = fsel(:,:,10) + hmld(:,:)
  163. fsel(:,:,11) = fsel(:,:,11) + hmlp(:,:)
  164. fsel(:,:,12) = fsel(:,:,12) + fr_i(:,:)
  165. ! fsel(:,:,13) = fsel(:,:,13) !RB not used
  166. ! fsel(:,:,14) = fsel(:,:,14) + qct(:,:)
  167. ! fsel(:,:,15) = fsel(:,:,15) + fbt(:,:)
  168. fsel(:,:,16) = fsel(:,:,16) + ( emp(:,:)*tsn(:,:,1,jp_sal) )
  169. fsel(:,:,17) = fsel(:,:,17) + ( emp(:,:)*tsn(:,:,1,jp_tem) )
  170. !
  171. ! Output of dynamics and tracer fields and selected fields
  172. ! --------------------------------------------------------
  173. !
  174. !
  175. zdtj=rdt/86400. ! time step in days
  176. WRITE(clmode,'(f5.1,a)' ) nwrite*zdtj,' days average'
  177. ! iwrite=NINT(adatrj/rwrite)
  178. ! IF (abs(adatrj-iwrite*rwrite) < zdtj/2. &
  179. IF( ( MOD (kt-nit000+1,nwrite) == 0 ) &
  180. & .OR. ( kt == 1 .AND. ninist ==1 ) ) THEN
  181. ! it is time to make a dump on file
  182. ! compute average
  183. um(:,:,:) = um(:,:,:) / nmoyct
  184. vm(:,:,:) = vm(:,:,:) / nmoyct
  185. wm(:,:,:) = wm(:,:,:) / nmoyct
  186. avtm(:,:,:) = avtm(:,:,:) / nmoyct
  187. tm(:,:,:) = tm(:,:,:) / nmoyct
  188. sm(:,:,:) = sm(:,:,:) / nmoyct
  189. !
  190. fsel(:,:,:) = fsel(:,:,:) / nmoyct
  191. !
  192. ! note : the surface pressure is not averaged, but rather
  193. ! computed from the averaged gradients.
  194. !
  195. ! mask mean field with tmask except utau vtau (1,2)
  196. DO jk=3,inbsel
  197. fsel(:,:,jk)=fsel(:,:,jk)*tmask(:,:,1)
  198. END DO
  199. ENDIF
  200. !
  201. ELSE ! ll_dia_inst true
  202. !
  203. !! * Instantaneous output section
  204. !! ------------------------------
  205. !
  206. IF( kt == nit000 .AND. lwp ) WRITE(numout,*) &
  207. 'THE OUTPUT FILES CONTAINS INSTANTANEOUS VALUES OF EACH FIELD'
  208. !
  209. zdtj=rdt/86400. ! time step in days
  210. ! iwrite=NINT(adatrj/rwrite)
  211. clmode='instantaneous'
  212. ! IF (abs(adatrj-iwrite*rwrite) < zdtj/2. &
  213. IF ( ( MOD (kt-nit000+1,nwrite) == 0 ) &
  214. & .OR. ( kt == 1 .AND. ninist == 1 ) ) THEN
  215. !
  216. ! transfer wp arrays to sp arrays for dimg files
  217. fsel(:,:,:) = 0._wp
  218. !
  219. fsel(:,:,1 ) = utau(:,:) * umask(:,:,1)
  220. fsel(:,:,2 ) = vtau(:,:) * vmask(:,:,1)
  221. fsel(:,:,3 ) = (qsr (:,:) + qns (:,:)) * tmask(:,:,1)
  222. fsel(:,:,4 ) = ( emp(:,:)-rnf(:,:) ) * tmask(:,:,1)
  223. ! fsel(:,:,5 ) = (tsb(:,:,1,jp_tem) - sf_sst(1)%fnow(:,:) ) *tmask(:,:,1) !RB not used
  224. fsel(:,:,6 ) = sshn(:,:)
  225. fsel(:,:,7 ) = qsr (:,:) * tmask(:,:,1)
  226. IF( ln_ssr ) THEN
  227. IF( nn_sstr /= 0 ) fsel(:,:,8 ) = qrp (:,:) * tmask(:,:,1)
  228. IF( nn_sssr /= 0 ) fsel(:,:,9 ) = erp (:,:) * tmask(:,:,1)
  229. ENDIF
  230. fsel(:,:,10) = hmld(:,:) * tmask(:,:,1)
  231. fsel(:,:,11) = hmlp(:,:) * tmask(:,:,1)
  232. fsel(:,:,12) = fr_i(:,:) * tmask(:,:,1)
  233. ! fsel(:,:,13) = sf_sst(1)%fnow(:,:) !RB not used
  234. ! fsel(:,:,14) = qct(:,:)
  235. ! fsel(:,:,15) = fbt(:,:)
  236. fsel(:,:,16) = ( emp(:,:)-tsn(:,:,1,jp_sal) ) * tmask(:,:,1)
  237. fsel(:,:,17) = ( emp(:,:)-tsn(:,:,1,jp_tem) ) * tmask(:,:,1)
  238. !
  239. ! qct(:,:) = 0._wp
  240. ENDIF
  241. ENDIF
  242. !
  243. ! Opening of the datrj.out file with the absolute time in day of each dump
  244. ! this file gives a record of the dump date for post processing ( ASCII file )
  245. !
  246. IF( ( MOD (kt-nit000+1,nwrite) == 0 ) &
  247. & .OR. ( kt == 1 .AND. ninist == 1 ) ) THEN
  248. IF( lwp) WRITE(numout,*)'Days since the begining of the run :',adatrj
  249. !! * U section
  250. WRITE(clname,9000) TRIM(cexper),'U',iyear,imon,iday
  251. cltext=TRIM(cexper)//' U(m/s) '//TRIM(clmode)
  252. !
  253. IF( ll_dia_inst) THEN ; CALL dia_wri_dimg(clname, cltext, un, jpk, 'T')
  254. ELSE ; CALL dia_wri_dimg(clname, cltext, um, jpk, 'T')
  255. ENDIF
  256. !! * V section
  257. WRITE(clname,9000) TRIM(cexper),'V',iyear,imon,iday
  258. cltext=TRIM(cexper)//' V(m/s) '//TRIM(clmode)
  259. !
  260. IF( ll_dia_inst) THEN
  261. CALL dia_wri_dimg(clname, cltext, vn, jpk, 'T')
  262. ELSE
  263. CALL dia_wri_dimg(clname, cltext, vm, jpk, 'T')
  264. ENDIF
  265. !
  266. !! * KZ section
  267. WRITE(clname,9000) TRIM(cexper),'KZ',iyear,imon,iday
  268. cltext=TRIM(cexper)//' KZ(m2/s) '//TRIM(clmode)
  269. IF( ll_dia_inst) THEN
  270. CALL dia_wri_dimg(clname, cltext, avt, jpk, 'W')
  271. ELSE
  272. CALL dia_wri_dimg(clname, cltext, avtm, jpk, 'W')
  273. ENDIF
  274. !
  275. !! * W section
  276. WRITE(clname,9000) TRIM(cexper),'W',iyear,imon,iday
  277. cltext=TRIM(cexper)//' W(m/s) '//TRIM(clmode)
  278. IF( ll_dia_inst) THEN
  279. CALL dia_wri_dimg(clname, cltext, wn, jpk, 'W')
  280. ELSE
  281. CALL dia_wri_dimg(clname, cltext, wm, jpk, 'W')
  282. ENDIF
  283. !! * T section
  284. WRITE(clname,9000) TRIM(cexper),'T',iyear,imon,iday
  285. cltext=TRIM(cexper)//' T (DegC) '//TRIM(clmode)
  286. IF( ll_dia_inst) THEN
  287. CALL dia_wri_dimg(clname, cltext, tsn(:,:,:,jp_tem), jpk, 'T')
  288. ELSE
  289. CALL dia_wri_dimg(clname, cltext, tm , jpk, 'T')
  290. ENDIF
  291. !
  292. !! * S section
  293. WRITE(clname,9000) TRIM(cexper),'S',iyear,imon,iday
  294. cltext=TRIM(cexper)//' S (PSU) '//TRIM(clmode)
  295. IF( ll_dia_inst) THEN
  296. CALL dia_wri_dimg(clname, cltext, tsn(:,:,:,jp_sal), jpk, 'T')
  297. ELSE
  298. CALL dia_wri_dimg(clname, cltext, sm , jpk, 'T')
  299. ENDIF
  300. !
  301. !! * 2D section
  302. WRITE(clname,9000) TRIM(cexper),'2D',iyear,imon,iday
  303. cltext='2D fields '//TRIM(clmode)
  304. IF( ll_dia_inst) THEN
  305. CALL dia_wri_dimg(clname, cltext, fsel, inbsel, '2')
  306. ELSE
  307. CALL dia_wri_dimg(clname, cltext, fsel, inbsel, '2')
  308. ENDIF
  309. IF( lk_mpp ) CALL mppsync ! synchronization in mpp
  310. !! * Log message in numout
  311. IF( lwp)WRITE(numout,*) ' '
  312. IF( lwp)WRITE(numout,*) ' **** WRITE in dimg file ',kt
  313. IF( lwp .AND. ll_dia_inst) WRITE(numout,*) ' instantaneous fields'
  314. IF( lwp .AND. .NOT. ll_dia_inst) WRITE(numout,*) ' average fields with ',nmoyct,'pdt'
  315. !
  316. !
  317. !! * Reset cumulating arrays and counter to 0 after writing
  318. !
  319. IF( .NOT. ll_dia_inst ) THEN
  320. nmoyct = 0
  321. !
  322. um(:,:,:) = 0._wp
  323. vm(:,:,:) = 0._wp
  324. wm(:,:,:) = 0._wp
  325. tm(:,:,:) = 0._wp
  326. sm(:,:,:) = 0._wp
  327. fsel(:,:,:) = 0._wp
  328. avtm(:,:,:) = 0._wp
  329. ENDIF
  330. ENDIF
  331. !
  332. IF( nn_timing == 1 ) CALL timing_stop('dia_wri')
  333. !
  334. 9000 FORMAT(a,"_",a,"_y",i4.4,"m",i2.2,"d",i2.2,".dimgproc")
  335. !
  336. END SUBROUTINE dia_wri