user_output_mmix.F90 22 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685
  1. !### macro's #####################################################
  2. !
  3. #define TRACEBACK write (gol,'("in ",a," (",a,", line",i5,")")') rname, __FILE__, __LINE__; call goErr
  4. #define IF_NOTOK_RETURN(action) if (rcode/=0) then; TRACEBACK; action; return; end if
  5. #define IF_ERROR_RETURN(action) if (rcode> 0) then; TRACEBACK; action; return; end if
  6. !
  7. #include "tm5.inc"
  8. !
  9. !----------------------------------------------------------------------------
  10. ! TM5 !
  11. !----------------------------------------------------------------------------
  12. !BOP
  13. !
  14. ! !MODULE: USER_OUTPUT_MMIX
  15. !
  16. ! !DESCRIPTION: Handles initialisation, accumulation and output of monthly
  17. ! mean tracers mixing ratio, temperature, and pressure.
  18. ! For run shorter than a month, average is done over the
  19. ! duration of the run.
  20. !\\
  21. !\\
  22. ! !INTERFACE:
  23. !
  24. MODULE USER_OUTPUT_MMIX
  25. !
  26. ! !USES:
  27. !
  28. use GO, only : gol, goPr, goErr, goBug, goLabel
  29. use dims !, mname_dims=>mname
  30. use chem_param, only: ntrace, nstd
  31. IMPLICIT NONE
  32. PRIVATE
  33. !
  34. ! !PUBLIC MEMBER FUNCTIONS:
  35. !
  36. public :: mmix_Init, mmix_Done ! object life cycle
  37. public :: accumulate_mmix ! accumulate data
  38. public :: reset_mmix ! reset data
  39. public :: write_mmix ! write data
  40. public :: mmix_dat, w_mmix
  41. !
  42. ! !PUBLIC TYPES:
  43. !
  44. type, public :: mmix_data
  45. real,dimension(:,:,:,:),pointer :: rmmix
  46. real,dimension(:,:,:,:),pointer :: std_mmix
  47. real,dimension(:,:,:),pointer :: tempm
  48. real,dimension(:,:),pointer :: presm
  49. end type mmix_data
  50. type(mmix_data), dimension(nregions), target :: mmix_dat ! accumulated data
  51. real, dimension(nregions) :: w_mmix ! accumulated weight
  52. integer, dimension(6) :: startdate
  53. character(len=*), parameter :: mname = 'user_output_mmix'
  54. !
  55. ! !REVISION HISTORY:
  56. ! 16 Nov 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  57. !
  58. ! !REMARKS:
  59. !
  60. !EOP
  61. !------------------------------------------------------------------------
  62. CONTAINS
  63. !--------------------------------------------------------------------------
  64. ! TM5 !
  65. !--------------------------------------------------------------------------
  66. !BOP
  67. !
  68. ! !IROUTINE: MMIX_INIT
  69. !
  70. ! !DESCRIPTION: Allocate and set to 0 fields to accumulate.
  71. !\\
  72. !\\
  73. ! !INTERFACE:
  74. !
  75. SUBROUTINE MMIX_INIT(rcode)
  76. !
  77. ! !USES:
  78. !
  79. use tm5_distgrid, only : dgrid, Get_DistGrid
  80. !
  81. ! !OUTPUT PARAMETERS:
  82. !
  83. integer, intent(out) :: rcode
  84. !
  85. ! !REVISION HISTORY:
  86. ! 16 Nov 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  87. !
  88. !EOP
  89. !------------------------------------------------------------------------
  90. !BOC
  91. character(len=*), parameter :: rname = mname//'/Init_mmix'
  92. integer :: region, i1, i2, j1, j2
  93. call goLabel(rname)
  94. do region=1,nregions
  95. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  96. allocate(mmix_dat(region)%rmmix (i1:i2, j1:j2, lm(region), ntrace) )
  97. allocate(mmix_dat(region)%std_mmix(i1:i2, j1:j2, lm(region), nstd) )
  98. allocate(mmix_dat(region)%tempm (i1:i2, j1:j2, lm(region)) )
  99. allocate(mmix_dat(region)%presm (i1:i2, j1:j2) )
  100. w_mmix(region) = 0.0
  101. mmix_dat(region)%rmmix = 0.0
  102. mmix_dat(region)%std_mmix = 0.0
  103. mmix_dat(region)%presm = 0.0
  104. mmix_dat(region)%tempm = 0.0
  105. end do
  106. startdate = idatei ! start of model run
  107. call goLabel(); rcode=0
  108. end subroutine mmix_Init
  109. !EOC
  110. !--------------------------------------------------------------------------
  111. ! TM5 !
  112. !--------------------------------------------------------------------------
  113. !BOP
  114. !
  115. ! !IROUTINE: MMIX_DONE
  116. !
  117. ! !DESCRIPTION: deallocate data
  118. !\\
  119. !\\
  120. ! !INTERFACE:
  121. !
  122. SUBROUTINE MMIX_DONE(rcode)
  123. !
  124. ! !OUTPUT PARAMETERS:
  125. !
  126. integer, intent(out) :: rcode
  127. !
  128. ! !REVISION HISTORY:
  129. !
  130. !EOP
  131. !------------------------------------------------------------------------
  132. !BOC
  133. character(len=*), parameter :: rname = mname//'/mmix_Done'
  134. integer :: region
  135. call goLabel( rname )
  136. do region = 1,nregions
  137. deallocate ( mmix_dat(region)%rmmix )
  138. deallocate ( mmix_dat(region)%std_mmix)
  139. deallocate ( mmix_dat(region)%tempm )
  140. deallocate ( mmix_dat(region)%presm )
  141. end do
  142. call goLabel(); rcode=0
  143. END SUBROUTINE MMIX_DONE
  144. !EOC
  145. !--------------------------------------------------------------------------
  146. ! TM5 !
  147. !--------------------------------------------------------------------------
  148. !BOP
  149. !
  150. ! !IROUTINE: RESET_MMIX
  151. !
  152. ! !DESCRIPTION: reset to zero all accumulated fields
  153. !\\
  154. !\\
  155. ! !INTERFACE:
  156. !
  157. SUBROUTINE RESET_MMIX( rcode )
  158. !
  159. ! !OUTPUT PARAMETERS:
  160. !
  161. integer, intent(out) :: rcode
  162. !
  163. ! !REVISION HISTORY:
  164. !
  165. !EOP
  166. !------------------------------------------------------------------------
  167. !BOC
  168. character(len=*), parameter :: rname = mname//'/reset_mmix'
  169. integer :: region
  170. call goLabel( rname )
  171. do region=1,nregions
  172. w_mmix(region) = 0.0
  173. mmix_dat(region)%rmmix = 0.0
  174. mmix_dat(region)%std_mmix = 0.0
  175. mmix_dat(region)%presm = 0.0
  176. mmix_dat(region)%tempm = 0.0
  177. enddo
  178. startdate = idate
  179. ! ok
  180. call goLabel(); rcode=0
  181. END SUBROUTINE RESET_MMIX
  182. !EOC
  183. !--------------------------------------------------------------------------
  184. ! TM5 !
  185. !--------------------------------------------------------------------------
  186. !BOP
  187. !
  188. ! !IROUTINE: ACCUMULATE_MMIX
  189. !
  190. ! !DESCRIPTION: accumulates fields
  191. !\\
  192. !\\
  193. ! !INTERFACE:
  194. !
  195. SUBROUTINE ACCUMULATE_MMIX( region, rcode)
  196. !
  197. ! !USES:
  198. !
  199. !use dims, only : lm, okdebug, ndyn, ndyn_max
  200. use chem_param, only : istd , nstd, ntrace, ntracet, ntrace_chem
  201. use global_data, only : region_dat, mass_dat, chem_dat
  202. use meteodata , only : sp_dat, temper_dat, m_dat
  203. use partools, only : isRoot
  204. use tm5_distgrid, only : dgrid, Get_DistGrid
  205. !
  206. ! !INPUT PARAMETERS:
  207. !
  208. integer, intent(in) :: region
  209. !
  210. ! !OUTPUT PARAMETERS:
  211. !
  212. integer, intent(out) :: rcode
  213. !
  214. ! !REVISION HISTORY:
  215. ! 16 Nov 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  216. !
  217. !EOP
  218. !------------------------------------------------------------------------
  219. !BOC
  220. character(len=*), parameter :: rname = mname//'/accumulate_mmix'
  221. real,dimension(:,:,:,:),pointer :: rm, rmmix, std_mmix, rmc
  222. real,dimension(:,:,:), pointer :: t, tempm, m
  223. real,dimension(:,:,:), pointer :: p
  224. real,dimension(:,:), pointer :: presm
  225. integer,dimension(:,:), pointer :: zoomed
  226. integer :: n, i1, i2, j1, j2, itrace, i,j,l
  227. real :: weight
  228. ! start
  229. call goLabel( rname )
  230. if (newmonth.and.(.not.newsrun)) then
  231. call write_mmix(rcode)
  232. IF_NOTOK_RETURN(rcode=1)
  233. call reset_mmix(rcode)
  234. IF_NOTOK_RETURN(rcode=1)
  235. endif
  236. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  237. ! debug
  238. if (region /= 1) then
  239. print*, rname//" - unexpected region - FIXME ZOOM"; rcode=1
  240. IF_NOTOK_RETURN(rcode=1)
  241. end if
  242. ! input
  243. rm => mass_dat(region)%rm(i1:i2,j1:j2,:,:)
  244. if ( ntrace_chem > 0 ) rmc => chem_dat(region)%rm(i1:i2,j1:j2,:,:)
  245. m => m_dat(region)%data(i1:i2,j1:j2,:)
  246. t => temper_dat(region)%data(i1:i2,j1:j2,:)
  247. p => sp_dat(region)%data(i1:i2,j1:j2,:)
  248. ! output
  249. rmmix => mmix_dat(region)%rmmix
  250. std_mmix => mmix_dat(region)%std_mmix
  251. tempm => mmix_dat(region)%tempm
  252. presm => mmix_dat(region)%presm
  253. weight = float(ndyn)/float(ndyn_max)
  254. ! mmix....
  255. do n=1, ntracet
  256. rmmix(:,:,:,n) = rmmix(:,:,:,n) + weight*rm(:,:,:,n)/m(:,:,:)
  257. end do
  258. ! non-transported tracers, if any
  259. if ( ntrace_chem > 0 ) then
  260. do n= ntracet+1, ntracet+ntrace_chem
  261. rmmix(:,:,:,n) = rmmix(:,:,:,n) + weight*rmc(:,:,:,n-ntracet)/m(:,:,:)
  262. end do
  263. end if
  264. ! stdt deviations
  265. do n=1,nstd
  266. itrace = istd(n)
  267. std_mmix(:,:,:,n) = std_mmix(:,:,:,n) + weight*(rm(:,:,:,itrace)/m(:,:,:))**2
  268. end do
  269. ! met fields
  270. tempm = tempm + weight*t
  271. presm = presm + weight*p(:,:,1)
  272. w_mmix(region) = w_mmix(region) + weight
  273. if ( okdebug ) print*, 'accumulate_mmix: region ',region, &
  274. '; w_mmix',w_mmix(region)
  275. nullify(m)
  276. nullify(rm)
  277. nullify(t)
  278. nullify(p)
  279. nullify(rmmix)
  280. nullify(std_mmix)
  281. nullify(presm)
  282. nullify(tempm)
  283. ! ok
  284. call goLabel(); rcode=0
  285. END SUBROUTINE ACCUMULATE_MMIX
  286. !EOC
  287. !--------------------------------------------------------------------------
  288. ! TM5 !
  289. !--------------------------------------------------------------------------
  290. !BOP
  291. !
  292. ! !IROUTINE: WRITE_MMIX
  293. !
  294. ! !DESCRIPTION: Write to file mean fields defined in this module, plus all
  295. ! essential model parameters
  296. !\\
  297. !\\
  298. ! !INTERFACE:
  299. !
  300. SUBROUTINE WRITE_MMIX( rcode )
  301. !
  302. ! !USES:
  303. !
  304. use chem_param
  305. use io_hdf
  306. use datetime, only : tstamp
  307. use global_data, only : outdir
  308. use ParTools, only : Par_Barrier, isRoot
  309. use User_Output_Common, only : User_Output_Check_Overwrite
  310. !
  311. ! !INPUT/OUTPUT PARAMETERS:
  312. !
  313. integer, intent(inout) :: rcode
  314. !
  315. ! !REVISION HISTORY:
  316. ! 16 Nov 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  317. !
  318. !EOP
  319. !------------------------------------------------------------------------
  320. !BOC
  321. character(len=*), parameter :: rname = mname//'/write_mmix'
  322. integer :: istat, sfsnatt, sfscatt, io, sfstart
  323. integer :: sfend, region
  324. integer :: i,j,l,n,k,ind
  325. !integer,dimension(6) ::
  326. character(len=12) :: name
  327. character(len=200):: FFilename
  328. ! start
  329. call goLabel( rname )
  330. REG : do region=nregions,1,-1
  331. IOroot : if ( isRoot ) then
  332. write (FFilename,'(a,"/mmix_",i4.4,3i2.2,"_",i4.4,3i2.2,"_",a,".hdf")') &
  333. ! trim(outdir), idatei(1:4), idatee(1:4),trim(region_name(region))
  334. trim(outdir), startdate(1:4), idate(1:4),trim(region_name(region))
  335. ! check existence ...
  336. call User_Output_Check_Overwrite( trim(FFilename), rcode )
  337. IF_NOTOK_RETURN(rcode=1)
  338. ! open
  339. io = sfstart(FFilename,DFACC_CREATE)
  340. if ( io < 0 ) then
  341. write (gol,'("While starting mmix file")'); call goErr
  342. write (gol,'("Filename:",a)') trim(Ffilename); call goErr
  343. write (gol,'("IIO unit:",i10)') io; call goErr
  344. write (gol,'("in program")'); call goErr; rcode=1; return
  345. end if
  346. !write (gol,'("write_mmix: io unit",i10)') io; call goPr
  347. istat = sfsnatt(io,'itau', DFNT_INT32, 1, itau)
  348. istat = sfsnatt(io,'nregions', DFNT_INT32, 1, nregions)
  349. istat = sfscatt(io,'region_name', DFNT_CHAR, &
  350. len_trim(region_name(region)), trim(region_name(region)) )
  351. istat = sfsnatt(io,'im', DFNT_INT32, 1, im(region))
  352. istat = sfsnatt(io,'jm', DFNT_INT32, 1, jm(region))
  353. istat = sfsnatt(io,'lm', DFNT_INT32, 1, lm(region))
  354. istat = sfsnatt(io,'dx', DFNT_FLOAT64, 1, dx/xref(region))
  355. istat = sfsnatt(io,'dy', DFNT_FLOAT64, 1, dy/yref(region))
  356. istat = sfsnatt(io,'dz', DFNT_FLOAT64, 1, dz/zref(region))
  357. istat = sfsnatt(io,'xbeg', DFNT_INT32, 1, xbeg(region))
  358. istat = sfsnatt(io,'xend', DFNT_INT32, 1, xend(region))
  359. istat = sfsnatt(io,'ybeg', DFNT_INT32, 1, ybeg(region))
  360. istat = sfsnatt(io,'yend', DFNT_INT32, 1, yend(region))
  361. istat = sfsnatt(io,'zbeg', DFNT_INT32, 1, zbeg(region))
  362. istat = sfsnatt(io,'zend', DFNT_INT32, 1, zend(region))
  363. if(region/=1) then
  364. istat = sfsnatt(io,'ibeg', DFNT_INT32, 1, ibeg(region))
  365. istat = sfsnatt(io,'iend', DFNT_INT32, 1, iend(region))
  366. istat = sfsnatt(io,'jbeg', DFNT_INT32, 1, jbeg(region))
  367. istat = sfsnatt(io,'jend', DFNT_INT32, 1, jend(region))
  368. istat = sfsnatt(io,'lbeg', DFNT_INT32, 1, lbeg(region))
  369. istat = sfsnatt(io,'lend', DFNT_INT32, 1, lend(region))
  370. end if
  371. istat = sfsnatt(io,'xref', DFNT_INT32, 1, xref(region))
  372. istat = sfsnatt(io,'yref', DFNT_INT32, 1, yref(region))
  373. istat = sfsnatt(io,'zref', DFNT_INT32, 1, zref(region))
  374. istat = sfsnatt(io,'tref', DFNT_INT32, 1, tref(region))
  375. istat = sfsnatt(io,'ntrace',DFNT_INT32, 1, ntrace)
  376. istat = sfsnatt(io,'ntracet',DFNT_INT32, 1, ntracet)
  377. istat = sfsnatt(io,'nstd',DFNT_INT32, 1, nstd)
  378. istat = sfsnatt(io,'idate' ,DFNT_INT32, 6, idate)
  379. istat = sfsnatt(io,'istart', DFNT_INT32, 1, istart)
  380. istat = sfsnatt(io,'ndyn_max', DFNT_INT32, 1, ndyn_max)
  381. istat = sfsnatt(io,'nconv', DFNT_INT32, 1, nconv)
  382. istat = sfsnatt(io,'ndiag', DFNT_INT32, 1, ndiag)
  383. istat = sfsnatt(io,'nchem', DFNT_INT32, 1, nchem)
  384. istat = sfsnatt(io,'nsrce', DFNT_INT32, 1, nsrce)
  385. istat = sfsnatt(io,'nread', DFNT_INT32, 1, nread)
  386. istat = sfsnatt(io,'nwrite',DFNT_INT32, 1, nwrite)
  387. istat = sfsnatt(io,'ninst', DFNT_INT32, 1, ninst)
  388. istat = sfsnatt(io,'ncheck',DFNT_INT32, 1, ncheck)
  389. istat = sfsnatt(io,'ndiff', DFNT_INT32, 1, ndiff)
  390. istat = sfsnatt(io,'itaui', DFNT_INT32, 1, itaui)
  391. istat = sfsnatt(io,'itaue', DFNT_INT32, 1, itaue)
  392. istat = sfsnatt(io,'itaut', DFNT_INT32, 1, itaut)
  393. istat = sfsnatt(io,'itau0', DFNT_INT32, 1, itau0)
  394. istat = sfsnatt(io,'idatei' , DFNT_INT32, 6, idatei)
  395. istat = sfsnatt(io,'idatee' , DFNT_INT32, 6, idatee)
  396. istat = sfsnatt(io,'idatet' , DFNT_INT32, 6, idatet)
  397. istat = sfsnatt(io,'idate0' , DFNT_INT32, 6, idate0)
  398. istat = sfsnatt(io,'icalendo' ,DFNT_INT32, 1, icalendo)
  399. istat = sfsnatt(io,'iyear0' , DFNT_INT32, 1, iyear0)
  400. istat = sfsnatt(io,'julday0' , DFNT_INT32, 1, julday0)
  401. istat = sfsnatt(io,'ndiagp1' , DFNT_INT32, 1, ndiagp1)
  402. istat = sfsnatt(io,'ndiagp2' , DFNT_INT32, 1, ndiagp2)
  403. istat = sfsnatt(io,'nstep' , DFNT_INT32, 1, nstep)
  404. istat = sfsnatt(io,'cpu0' , DFNT_FLOAT64, 1, cpu0)
  405. istat = sfsnatt(io,'cpu1' , DFNT_FLOAT64, 1, cpu1)
  406. istat = sfsnatt(io,'ra' , DFNT_FLOAT64, ntracet, ra)
  407. istat = sfsnatt(io,'fscale' , DFNT_FLOAT64, ntrace, fscale)
  408. istat = sfscatt(io,'names' , DFNT_CHAR, ntrace*tracer_name_len, names)
  409. istat = sfsnatt(io,'areag' , DFNT_FLOAT64, 1, areag)
  410. istat = sfsnatt(io,'czeta' , DFNT_FLOAT64, 1, czeta)
  411. istat = sfsnatt(io,'czetak' , DFNT_FLOAT64, 1, czetak)
  412. istat = sfscatt(io,'xlabel' , DFNT_CHAR, 160, xlabel)
  413. istat = sfsnatt(io,'istd' , DFNT_INT32, nstd, istd)
  414. istat = sfsnatt(io,'newyr' , DFNT_INT32, 1, newyr)
  415. istat = sfsnatt(io,'newmonth', DFNT_INT32, 1, newmonth)
  416. istat = sfsnatt(io,'newday' , DFNT_INT32, 1, newday)
  417. istat = sfsnatt(io,'newsrun' , DFNT_INT32, 1, newsrun)
  418. ! istat = sfsnatt(io,'cdebug' , DFNT_INT32, 1, cdebug)
  419. istat = sfsnatt(io,'limits' , DFNT_INT32, 1, limits)
  420. istat = sfsnatt(io,'nregions' , DFNT_INT32, 1, nregions)
  421. istat = sfsnatt(io,'w_mmix' , DFNT_FLOAT64, 1, w_mmix(region))
  422. istat = sfsnatt(io,'at' , DFNT_FLOAT64,lm(1)+1, at)
  423. istat = sfsnatt(io,'bt' , DFNT_FLOAT64,lm(1)+1, bt)
  424. #ifdef slopes
  425. #ifndef secmom
  426. istat = sfscatt(io,'adv_scheme' , DFNT_CHAR, 5, 'slope')
  427. #else
  428. istat = sfscatt(io,'adv_scheme' , DFNT_CHAR, 5, '2nd_m')
  429. #endif
  430. #endif
  431. istat = sfsnatt(io,'nsplitsteps' , DFNT_INT32, 1, nsplitsteps)
  432. istat = sfscatt(io,'splitorder' , DFNT_CHAR, nsplitsteps, splitorder)
  433. end if IOroot
  434. CALL WRITEMMIX_REGION( region, rcode )
  435. IF_NOTOK_RETURN(rcode=1)
  436. call par_barrier
  437. if ( isRoot ) then
  438. write(gol,'("write mmix: sfend returns",i4)') sfend(io) ; call goPr
  439. endif
  440. END DO REG
  441. ! ok
  442. call goLabel(); rcode=0
  443. CONTAINS
  444. !------------------------------------------------------------------------
  445. ! TM5 !
  446. !------------------------------------------------------------------------
  447. !BOP
  448. !
  449. ! !IROUTINE: WRITEMMIX_REGION
  450. !
  451. ! !DESCRIPTION: Write to file mean fields defined in this module
  452. !\\
  453. !\\
  454. ! !INTERFACE:
  455. !
  456. SUBROUTINE WRITEMMIX_REGION( region, rcode )
  457. !
  458. ! !USES:
  459. !
  460. use global_data, only : region_dat
  461. use tm5_distgrid, only : dgrid, Get_DistGrid, gather
  462. use ParTools, only : isRoot
  463. !
  464. ! !INPUT PARAMETERS:
  465. !
  466. integer,intent(in) :: region
  467. !
  468. ! !INPUT/OUTPUT PARAMETERS:
  469. !
  470. integer, intent(inout) :: rcode
  471. !
  472. ! !REVISION HISTORY:
  473. ! 17 Nov 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  474. !
  475. ! !REMARKS:
  476. !
  477. !EOP
  478. !---------------------------------------------------------------------
  479. !BOC
  480. character(len=*), parameter :: rname = mname//'/write_mmix_region'
  481. real,dimension(:,:,:,:),pointer :: rmmix, std_mmix
  482. real,dimension(:,:,:) ,pointer :: tempm
  483. real,dimension(:,:) ,pointer :: presm
  484. real,dimension(:,:,:,:),allocatable :: rmmix_glb
  485. real,dimension(:,:,:,:),allocatable :: std_mmix_glb
  486. integer :: imr, jmr, lmr, nsend, i1, i2, j1, j2, n
  487. real :: ahelp,ahelp1
  488. ! start
  489. call goLabel( rname )
  490. ! global and local indices
  491. imr = im(region)
  492. jmr = jm(region)
  493. lmr = lm(region)
  494. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  495. ! array to gather data
  496. if (isRoot) then
  497. allocate( rmmix_glb(imr,jmr,lmr,ntrace) )
  498. allocate(std_mmix_glb(imr,jmr,lmr,nstd) )
  499. else
  500. allocate( rmmix_glb(1,1,1,1) )
  501. allocate(std_mmix_glb(1,1,1,1) )
  502. end if
  503. ! shortcut
  504. rmmix => mmix_dat(region)%rmmix
  505. std_mmix => mmix_dat(region)%std_mmix
  506. tempm => mmix_dat(region)%tempm
  507. presm => mmix_dat(region)%presm
  508. !
  509. !write(gol,'("writemmix_region: w_mmix",f12.2)') w_mmix(region); call goPr
  510. if ( w_mmix(region) > 2 ) then
  511. ! scale stdt deviation tracers
  512. do k= 1,nstd
  513. do l= 1,lmr
  514. do j=j1,j2
  515. do i=i1,i2
  516. n = istd(k)
  517. ahelp = rmmix(i,j,l,n)
  518. ahelp1= fscale(n) * &
  519. (std_mmix(i,j,l,k) - ahelp*ahelp/w_mmix(region) ) / &
  520. (w_mmix(region)-1)
  521. std_mmix(i,j,l,k)=max(1e-35,ahelp1)
  522. end do
  523. end do
  524. end do
  525. end do
  526. ! scale tracers
  527. do n=1,ntrace
  528. rmmix(:,:,:,n) = fscale(n) * rmmix(:,:,:,n)/w_mmix(region)
  529. end do
  530. ! scale temperature and pressure
  531. tempm = tempm/w_mmix(region)
  532. presm = presm/w_mmix(region)
  533. ! GATHER AND WRITE METEO
  534. call gather(dgrid(region), tempm, rmmix_glb(:,:,:,1), 0, rcode)
  535. IF_NOTOK_RETURN(rcode=1)
  536. if (isRoot) then
  537. call io_write3d_32d(io,imr,'LON'//trim(region_name(region)), &
  538. jmr,'LAT'//trim(region_name(region)),lmr, &
  539. 'HYBRID',rmmix_glb(1:imr,1:jmr,1:lmr,1),'tempm',idate)
  540. end if
  541. call gather(dgrid(region), presm, rmmix_glb(:,:,1,1), 0, rcode)
  542. IF_NOTOK_RETURN(rcode=1)
  543. if (isRoot) then
  544. call io_write2d_32d(io,imr,'LON'//trim(region_name(region)), &
  545. jmr,'LAT'//trim(region_name(region)), &
  546. rmmix_glb(1:imr,1:jmr,1,1),'presm',idate)
  547. end if
  548. ! gather & write mmix
  549. call gather(dgrid(region), rmmix, rmmix_glb, 0, rcode)
  550. IF_NOTOK_RETURN(rcode=1)
  551. if (isRoot) then
  552. do n=1,ntrace
  553. name=names(n)
  554. call io_write3d_32d(io,imr,'LON'//trim(region_name(region)), &
  555. jmr,'LAT'//trim(region_name(region)),lmr,'HYBRID', &
  556. rmmix_glb(1:imr,1:jmr,1:lmr,n),name,idate)
  557. end do
  558. end if
  559. ! gather and write stdt dev
  560. call gather(dgrid(region), std_mmix, std_mmix_glb, 0, rcode)
  561. IF_NOTOK_RETURN(rcode=1)
  562. if (isRoot) then
  563. do k=1,nstd
  564. n = istd(k)
  565. name = 'std_'//names(n)
  566. call io_write3d_32d(io,imr,'LON'//trim(region_name(region)), &
  567. jmr,'LAT'//trim(region_name(region)),lmr,'HYBRID', &
  568. std_mmix_glb(1:imr,1:jmr,1:lmr,k),name,idate)
  569. end do
  570. end if
  571. else
  572. write(gol,'("writemmix_region: NO WRITING! just avoided division by zero!")') ; call goPr
  573. end if
  574. deallocate(rmmix_glb)
  575. deallocate(std_mmix_glb)
  576. nullify(rmmix)
  577. nullify(std_mmix)
  578. nullify(tempm)
  579. nullify(presm)
  580. ! ok
  581. call goLabel(); rcode=0
  582. END SUBROUTINE WRITEMMIX_REGION
  583. !EOC
  584. END SUBROUTINE WRITE_MMIX
  585. !EOC
  586. END MODULE USER_OUTPUT_MMIX