io_save.F90 78 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217
  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 (status/=0) then; TRACEBACK; action; return; end if
  5. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  6. #define IF_NOTOK_MDF(action) if (status/=0) then; TRACEBACK; action; call MDF_CLose(fid,status); status=1; return; end if
  7. !
  8. #include "tm5.inc"
  9. #include "tmm.inc"
  10. !
  11. !-----------------------------------------------------------------------------
  12. ! TM5-MP !
  13. !-----------------------------------------------------------------------------
  14. !BOP
  15. !
  16. ! !MODULE: IO_SAVE
  17. !
  18. ! !DESCRIPTION: Contains routines to read HDF emissions files and
  19. ! the main model state (as replacement for restart file).
  20. !\\
  21. !\\
  22. ! !INTERFACE:
  23. !
  24. MODULE IO_SAVE
  25. !
  26. ! !USES:
  27. !
  28. use GO, only : gol, goErr, goPr, goBug
  29. use GO, only : TrcFile, InitRc => Init, DoneRc => Done, ReadRc
  30. use global_data, only : rcfile
  31. IMPLICIT NONE
  32. PRIVATE
  33. !
  34. ! !PUBLIC MEMBER FUNCTIONS:
  35. !
  36. PUBLIC :: READHDFMMR ! Read mmix from "old save file" (istart=4 )
  37. PUBLIC :: READ_MMIX ! Read mmix file (mean mixing ratio of transported tracers) (istart=5 )
  38. PUBLIC :: READ_SAVE_FILE_30 ! Read save-file (mixing ratio, opt. slopes, of transported tracers) (istart=30)
  39. PUBLIC :: READ_SAVE_FILE ! Read save file (mass of all tracers, grid info) (istart=31)
  40. PUBLIC :: WRITE_SAVE_FILE ! Write save-file (to be read with read_save_file)
  41. PUBLIC :: READ_HDF4 ! Read a record from hdf file (new way)
  42. PUBLIC :: READTM3HDF ! Read a record from hdf file (old way, a la TM3)
  43. PUBLIC :: READ_SCATTER_HDF ! Read a record from hdf file, and do the MPI scattering
  44. !
  45. ! !PRIVATE DATA MEMBERS:
  46. !
  47. character(len=*), parameter :: mname = 'io_save'
  48. type(TrcFile) :: rcF
  49. integer :: fid ! file id for IF_NOTOK_MDF macro
  50. !
  51. ! !INTERFACE:
  52. !
  53. INTERFACE READ_HDF4
  54. MODULE PROCEDURE READ_HDF4_2DR
  55. END INTERFACE
  56. !
  57. ! !REVISION HISTORY:
  58. ! 16 Nov 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  59. !
  60. ! !REMARKS:
  61. ! (1) The READTM3 routines are kept for quick fix when converting old code.
  62. ! All new code should use the MDF module to read any data.
  63. !
  64. !EOP
  65. !------------------------------------------------------------------------
  66. CONTAINS
  67. !--------------------------------------------------------------------------
  68. ! TM5 !
  69. !--------------------------------------------------------------------------
  70. !BOP
  71. !
  72. ! !IROUTINE: READ_HDF4_2DR
  73. !
  74. ! !DESCRIPTION: read one 2D record of real from an HDF4 file.
  75. !
  76. !\\
  77. !\\
  78. ! !INTERFACE:
  79. !
  80. SUBROUTINE READ_HDF4_2DR(fname, odata, status, dir, vname, vid)
  81. !
  82. ! !USES:
  83. !
  84. USE MDF, ONLY : MDF_Open, MDF_HDF4, MDF_READ, MDF_Inq_VarID, MDF_Get_Var, MDF_Close
  85. USE global_data, ONLY : inputdir
  86. !
  87. ! !INPUT PARAMETERS:
  88. !
  89. character(len=*), intent(in) :: fname ! name of HDF file to read
  90. character(len=*), intent(in), optional :: dir ! dir where file is. Default is "inputdir"
  91. character(len=*), intent(in), optional :: vname ! record name. Default is to use record #0.
  92. integer, intent(in), optional :: vid ! record id #. Default is to use record #0.
  93. !
  94. ! !OUTPUT PARAMETERS:
  95. !
  96. real, intent(out) :: odata(:,:)
  97. integer, intent(out) :: status
  98. !
  99. ! !REVISION HISTORY:
  100. ! 28 Mar 2012 - P. Le Sager - v0
  101. !
  102. ! !REMARKS:
  103. ! (1) This wrapper around MDF routines is only for convenience: a lot of
  104. ! calls for the chemistry emissions, and participate to the effort
  105. ! of getting rid of file_hdf.f90 routine, in favor of the MDF module.
  106. ! (2) By default **FIRST** record is read, unless another variable number
  107. ! (vid) and/or variable name (vname) is passed. If both vid and vname
  108. ! are passed, vname is ignored.
  109. !
  110. !EOP
  111. !------------------------------------------------------------------------
  112. !BOC
  113. character(len=*), parameter :: rname = mname//'/read_hdf4_2dr'
  114. character(len=512):: Lvname, Ldir
  115. integer :: Lvid
  116. !--- check input
  117. Ldir=inputdir
  118. if(present(dir)) Ldir=dir
  119. Lvname=''
  120. if(present(vname)) Lvname=vname
  121. Lvid=1
  122. if (present(vid)) then
  123. Lvid=vid
  124. Lvname=''
  125. end if
  126. !--- read
  127. CALL MDF_Open( trim(Ldir)//'/'//TRIM(fname), MDF_HDF4, MDF_READ, fid, status )
  128. IF_NOTOK_RETURN(status=1)
  129. if (len(trim(Lvname))/=0) then
  130. CALL MDF_Inq_VarID( fid, TRIM(Lvname), Lvid, status )
  131. IF_NOTOK_MDF(status=1)
  132. end if
  133. CALL MDF_Get_Var( fid, Lvid, odata, status )
  134. IF_NOTOK_MDF(status=1)
  135. CALL MDF_Close( fid, status )
  136. IF_NOTOK_RETURN(status=1)
  137. status=0
  138. END SUBROUTINE READ_HDF4_2DR
  139. !EOC
  140. ! ======================================================================
  141. !WP! this subroutine reads HDF emissions files on
  142. ! 1x1 degree resolution and returns the specified field.
  143. !WP! input for this subroutine are:
  144. !WP!
  145. !WP! filename --> name of hdf file to be opened or read
  146. !MK! rank --> rank of the dataset (1,2,3)
  147. !WP! im_emis --> x-DIMENSION of requested field
  148. !WP! jm_emis --> y-DIMENSION of requested field
  149. !WP! lm_emis --> z-DIMENSION of requested field
  150. !WP! month --> the month to read (0 for january or simply the first field)
  151. !WP! field --> the field (im_emis,jm_emis,lm_emis) to put the values in
  152. !WP! field_name --> the name of the field to match the one in the HDF file
  153. !WP!
  154. !WP! The routine checks the dimensions and reports the succes/failure.
  155. subroutine readtm3hdf( filename, rank, im_emis, jm_emis, lm_emis, &
  156. month, field, field_name, idt )
  157. #ifdef with_hdf4
  158. use file_hdf, only : THdfFile, Init, Done
  159. use io_hdf , only : FAIL
  160. use io_hdf , only : io_read2d_32g, io_read3d_32g
  161. #endif
  162. use toolbox , only : escape_tm
  163. ! --- in/out --------------------------------------
  164. character(len=*),intent(in) :: filename
  165. character(len=*),intent(in) :: field_name
  166. integer,intent(in) :: rank
  167. integer,intent(in) :: month
  168. integer,intent(in) :: im_emis, jm_emis, lm_emis
  169. real,dimension(im_emis,jm_emis,lm_emis),intent(out) :: field
  170. integer,dimension(6),optional :: idt
  171. ! --- local ----------------------------------------
  172. #ifdef with_hdf4
  173. type(THdfFile) :: hdf
  174. #endif
  175. integer :: status
  176. integer :: idx
  177. real, allocatable :: field1d(:) ! first dim will be 1
  178. real, allocatable :: field2d(:,:)
  179. real, allocatable :: field3d(:,:,:)
  180. ! --- begin -------------------------------------------
  181. #ifdef with_hdf4
  182. ! open hdf file:
  183. call Init( hdf, trim(filename), 'read', status )
  184. if (status/=0) call escape_tm('ERROR in readtm3hdf')
  185. #else
  186. call escape_tm('not compiled with hdf4')
  187. #endif
  188. !FD hdf files indices run from 0 ...n-1
  189. idx = month
  190. select case(rank)
  191. case(1) ! latitudional field
  192. allocate(field1d(jm_emis))
  193. #ifdef with_hdf4
  194. if(present(idt)) call io_read2d_32g(hdf%id,im_emis,jm_emis,field1d,field_name, status,idate=idt)
  195. if(.not.present(idt)) call io_read2d_32g(hdf%id,im_emis,jm_emis,field1d,field_name, status,index=idx)
  196. if ( status /= 0 ) then
  197. write(gol,*) 'readtm3hdf: io_read2d_32g failed:' ; call goPr
  198. write(gol,*) 'readtm3hdf: filename : ', trim(filename) ; call goPr
  199. write(gol,*) 'readtm3hdf: rank : ', rank ; call goPr
  200. write(gol,*) 'readtm3hdf: im_emis : ', im_emis ; call goPr
  201. write(gol,*) 'readtm3hdf: jm_emis : ', jm_emis ; call goPr
  202. write(gol,*) 'readtm3hdf: lm_emis : ', lm_emis ; call goPr
  203. write(gol,*) 'readtm3hdf: month : ', month ; call goPr
  204. write(gol,*) 'readtm3hdf: field_name : ', trim(field_name); call goPr
  205. if (present(idt)) write(gol,*) 'readtm3hdf: idt : ', idt; call goPr
  206. call escape_tm('readtm3hdf: Error reading HDF file 1D')
  207. end if
  208. #else
  209. call escape_tm('not compiled with hdf4')
  210. #endif
  211. field(1,:,1)=field1d
  212. deallocate(field1d)
  213. case(2) ! 2D surface field
  214. allocate(field2d(im_emis,jm_emis))
  215. #ifdef with_hdf4
  216. if(present(idt)) call io_read2d_32g(hdf%id,im_emis,jm_emis,field2d,field_name, status,idate=idt)
  217. if(.not.present(idt)) call io_read2d_32g(hdf%id,im_emis,jm_emis,field2d,field_name, status,index=idx)
  218. if ( status /= 0 ) then
  219. write(gol,*) 'readtm3hdf: io_read2d_32g failed:' ; call goPr
  220. write(gol,*) 'readtm3hdf: filename : ', trim(filename) ; call goPr
  221. write(gol,*) 'readtm3hdf: rank : ', rank ; call goPr
  222. write(gol,*) 'readtm3hdf: im_emis : ', im_emis ; call goPr
  223. write(gol,*) 'readtm3hdf: jm_emis : ', jm_emis ; call goPr
  224. write(gol,*) 'readtm3hdf: lm_emis : ', lm_emis ; call goPr
  225. write(gol,*) 'readtm3hdf: month : ', month ; call goPr
  226. write(gol,*) 'readtm3hdf: field_name : ', trim(field_name) ; call goPr
  227. if (present(idt)) write(gol,*) 'readtm3hdf: idt : ', idt ; call goPr
  228. call escape_tm('readtm3hdf: Error reading HDF file 2D')
  229. endif
  230. #else
  231. call escape_tm('not compiled with hdf4')
  232. #endif
  233. field(:,:,1)=field2d
  234. deallocate(field2d)
  235. case (3) ! 3D field
  236. allocate(field3d(im_emis,jm_emis,lm_emis))
  237. #ifdef with_hdf4
  238. if(present(idt)) call io_read3d_32g(hdf%id,im_emis,jm_emis,lm_emis,field3d,field_name, status,idate=idt)
  239. if(.not.present(idt)) call io_read3d_32g(hdf%id,im_emis,jm_emis,lm_emis,field3d,field_name, status,index=idx)
  240. if ( status /= 0 ) then
  241. write(gol,*) 'readtm3hdf: io_read2d_32g failed:' ; call goPr
  242. write(gol,*) 'readtm3hdf: filename : ', trim(filename) ; call goPr
  243. write(gol,*) 'readtm3hdf: rank : ', rank ; call goPr
  244. write(gol,*) 'readtm3hdf: im_emis : ', im_emis ; call goPr
  245. write(gol,*) 'readtm3hdf: jm_emis : ', jm_emis ; call goPr
  246. write(gol,*) 'readtm3hdf: lm_emis : ', lm_emis ; call goPr
  247. write(gol,*) 'readtm3hdf: month : ', month ; call goPr
  248. write(gol,*) 'readtm3hdf: field_name : ', trim(field_name) ; call goPr
  249. if (present(idt)) write(gol,*) 'readtm3hdf: idt : ', idt ; call goPr
  250. call escape_tm('readtm3hdf: Error reading HDF file 3D')
  251. endif
  252. #else
  253. call escape_tm('not compiled with hdf4')
  254. #endif
  255. field(:,:,:)=field3d
  256. deallocate(field3d)
  257. case (23) ! 2D field lat-pres
  258. allocate(field2d(jm_emis,lm_emis))
  259. #ifdef with_hdf4
  260. if(present(idt)) call io_read2d_32g(hdf%id,jm_emis,lm_emis,field2d,field_name, status,idate=idt)
  261. if(.not.present(idt)) call io_read2d_32g(hdf%id,jm_emis,lm_emis,field2d,field_name, status,index=idx)
  262. if ( status /= 0 ) then !might be due to (1,jm,lm) file!
  263. write(gol,*) 'readtm3hdf: try shape : ', 1, jm_emis, lm_emis
  264. allocate(field3d(1,jm_emis,lm_emis))
  265. if ( present(idt) ) then
  266. call io_read3d_32g(hdf%id,1,jm_emis,lm_emis,field3d,field_name, status,idate=idt)
  267. else
  268. call io_read3d_32g(hdf%id,1,jm_emis,lm_emis,field3d,field_name, status,index=idx)
  269. end if
  270. if ( status /= 0 ) then
  271. write(gol,*) 'readtm3hdf: io_read2d_32g failed:' ; call goPr
  272. write(gol,*) 'readtm3hdf: filename : ', trim(filename) ; call goPr
  273. write(gol,*) 'readtm3hdf: rank : ', rank ; call goPr
  274. write(gol,*) 'readtm3hdf: im_emis : ', im_emis ; call goPr
  275. write(gol,*) 'readtm3hdf: jm_emis : ', jm_emis ; call goPr
  276. write(gol,*) 'readtm3hdf: lm_emis : ', lm_emis ; call goPr
  277. write(gol,*) 'readtm3hdf: month : ', month ; call goPr
  278. write(gol,*) 'readtm3hdf: field_name : ', trim(field_name) ; call goPr
  279. if (present(idt)) write(gol,*) 'readtm3hdf: idt : ', idt ; call goPr
  280. call escape_tm('readtm3hdf: Error reading HDF file 23')
  281. end if
  282. field(:,:,:)=field3d
  283. deallocate(field3d)
  284. else
  285. field(1,:,:)=field2d
  286. end if
  287. #else
  288. call escape_tm('not compiled with hdf4')
  289. #endif
  290. deallocate(field2d)
  291. case default
  292. write (gol,*) 'readtm3hdf: Please check the rank of the required field,', &
  293. ' must be 1,2,3, or 23'; call goPr
  294. end select
  295. #ifdef with_hdf4
  296. ! close:
  297. call Done( hdf, status )
  298. if (status/=0) call escape_tm('ERROR in readtm3hdf')
  299. #else
  300. call escape_tm('not compiled with hdf4')
  301. #endif
  302. !if ( idx >= 0 ) then
  303. ! write (gol,*) 'readtm3hdf: ',trim(filename),' ; ds#= ',idx+1; call goPr
  304. ! write (gol,*) 'readtm3hdf: total month sum after reading the full field', &
  305. ! sum(field)/1e9 ,' (x1e9) '; call goPr
  306. !end if
  307. end subroutine readtm3hdf
  308. !--------------------------------------------------------------------------
  309. ! TM5 !
  310. !--------------------------------------------------------------------------
  311. !BOP
  312. !
  313. ! !IROUTINE: READ_SCATTER_HDF
  314. !
  315. ! !DESCRIPTION: simple adaptation of readtm3hdf to use MDF module, and
  316. ! scatter data.
  317. !\\
  318. !\\
  319. ! !INTERFACE:
  320. !
  321. SUBROUTINE READ_SCATTER_HDF( filename, rank, region, i1, j1, field, status, &
  322. idx, field_name, idt )
  323. !
  324. ! !USES:
  325. !
  326. use partools, only : isRoot
  327. use tm5_distgrid, only : dgrid, Get_DistGrid, scatter
  328. !
  329. ! !INPUT PARAMETERS:
  330. !
  331. character(len=*), intent(in) :: filename ! HDF4 file to read
  332. integer, intent(in) :: rank ! 1,2,.. [only 2 implemented for now]
  333. integer, intent(in) :: region, i1, j1 ! region and local array start index
  334. integer, intent(in), optional :: idx ! variable id in [1..nmax]
  335. character(len=*), intent(in), optional :: field_name ! variable name, ignored if idx set
  336. integer, intent(in), optional :: idt(6) ! date [not implemented]
  337. !
  338. ! !OUTPUT PARAMETERS:
  339. !
  340. real, intent(out) :: field(i1:,j1:) ! scattered read data
  341. integer, intent(out) :: status
  342. !
  343. ! !REVISION HISTORY:
  344. ! 23 Jan 2012 - P. Le Sager - for lat-lon mpi decomposition
  345. !
  346. ! !REMARKS:
  347. ! (1) tested only with rank=2 (see dry_deposition.F90)
  348. ! (2) not all features of readtm3hdf are available, but probably also
  349. ! not needed... will add as needed.
  350. !EOP
  351. !------------------------------------------------------------------------
  352. !BOC
  353. character(len=*), parameter :: rname = mname//'/read_scatter_hdf'
  354. integer :: im_emis, jm_emis
  355. real, allocatable :: field1d(:)
  356. real, allocatable :: field2d(:,:)
  357. ! --- begin -------------------------------------------
  358. CALL GET_DISTGRID( DGRID(region), I_WRLD=im_emis, J_WRLD=jm_emis )
  359. status=0
  360. READ: if (isRoot) then
  361. allocate(field2d(im_emis,jm_emis))
  362. field2D=0.
  363. select case(rank)
  364. ! case(1) ! latitudional field
  365. !
  366. ! allocate(field1d(jm_emis))
  367. ! if(present(idt)) call io_read2d_32g(hdf%id,im_emis,jm_emis,field1d,field_name, status,idate=idt)
  368. ! if(.not.present(idt)) call io_read2d_32g(hdf%id,im_emis,jm_emis,field1d,field_name, status,index=idx)
  369. ! if ( status /= 0 ) then
  370. ! write(gol,*) 'readtm3hdf: io_read2d_32g failed:'
  371. ! write(gol,*) 'readtm3hdf: filename : ', trim(filename)
  372. ! write(gol,*) 'readtm3hdf: rank : ', rank
  373. ! write(gol,*) 'readtm3hdf: im_emis : ', im_emis
  374. ! write(gol,*) 'readtm3hdf: jm_emis : ', jm_emis
  375. ! write(gol,*) 'readtm3hdf: month : ', month
  376. ! write(gol,*) 'readtm3hdf: field_name : ', trim(field_name)
  377. ! if (present(idt)) write(gol,*) 'readtm3hdf: idt : ', idt
  378. ! call escape_tm('readtm3hdf: Error reading HDF file 1D')
  379. ! end if
  380. ! field2D(1,:)=field1d
  381. ! deallocate(field1d)
  382. case(2) ! 2D surface field
  383. call READ_HDF4(filename, field2d, status, dir='', vname=field_name, vid=idx)
  384. IF_NOTOK_RETURN(status=1)
  385. case default
  386. write (gol,*) rname//' : Please check the rank of the required field,', &
  387. ' must be 1,2,3, or 23'; call goPr
  388. status=1
  389. end select
  390. else
  391. allocate(field2d(1,1))
  392. end if READ
  393. call SCATTER( dgrid(region), field, field2d, 0, status)
  394. IF_NOTOK_RETURN(status=1)
  395. deallocate(field2d)
  396. END SUBROUTINE READ_SCATTER_HDF
  397. !EOC
  398. !--------------------------------------------------------------------------
  399. ! TM5 !
  400. !--------------------------------------------------------------------------
  401. !BOP
  402. !
  403. ! !IROUTINE: READ_SAVE_FILE_30
  404. !
  405. ! !DESCRIPTION: reads initial MIXING RATIO (+ slopes, and second moments if
  406. ! they are switched on) of TRANSPORTED tracers from HDF-4
  407. ! "save files". The save file must be specified in rc file with key:
  408. !
  409. ! start.30.<region-name>
  410. !
  411. ! No regridding available.
  412. !
  413. ! Used for istart=30.
  414. !\\
  415. !\\
  416. ! !INTERFACE:
  417. !
  418. SUBROUTINE READ_SAVE_FILE_30( region, file_name, status )
  419. !
  420. ! !USES:
  421. !
  422. #ifdef with_hdf4
  423. use io_hdf
  424. #endif
  425. use dims, only : im, jm, lm
  426. use global_data, only : mass_dat
  427. use meteodata , only : m_dat
  428. use chem_param, only : ntracet
  429. use partools, only : isRoot
  430. use tm5_distgrid, only : dgrid, Get_DistGrid, scatter
  431. !
  432. ! !INPUT PARAMETERS:
  433. !
  434. integer, intent(in) :: region
  435. character(len=*), intent(in) :: file_name
  436. !
  437. ! !OUTPUT PARAMETERS:
  438. !
  439. integer, intent(out) :: status
  440. !
  441. ! !REVISION HISTORY:
  442. ! 4 Oct 2011 - P. Le Sager - TM5-MP version
  443. !
  444. ! !REMARKS:
  445. ! (1) no zoom (must put from_file stuff back in)
  446. ! (2) FIXME: not tested...
  447. !
  448. !EOP
  449. !------------------------------------------------------------------------
  450. !BOC
  451. character(len=*), parameter :: rname = mname//'/read_save_file_30'
  452. real,dimension(:,:,:,:),pointer :: rm
  453. real,dimension(:,:,:,:),pointer :: rxm,rym,rzm
  454. #ifdef secmom
  455. real,dimension(:,:,:,:),pointer :: rxxm,rxym,rxzm,ryym,ryzm,rzzm
  456. #endif
  457. real,dimension(:,:,:),pointer :: m
  458. #ifdef with_hdf4
  459. integer :: io, sfstart
  460. integer :: istat
  461. integer :: sfend
  462. #endif
  463. integer :: i,j,l,n
  464. integer :: imr,jmr,lmr, halo
  465. real,dimension(:,:,:,:), allocatable :: field
  466. real,dimension(:,:,:), allocatable :: msave, msave_local
  467. integer :: i1, i2, j1, j2
  468. ! --- begin --------------------------------
  469. m => m_dat(region)%data
  470. rm => mass_dat(region)%rm
  471. #ifdef slopes
  472. rxm => mass_dat(region)%rxm
  473. rym => mass_dat(region)%rym
  474. rzm => mass_dat(region)%rzm
  475. #ifdef secmom
  476. rxxm => mass_dat(region)%rxxm
  477. rxym => mass_dat(region)%rxym
  478. rxzm => mass_dat(region)%rxzm
  479. ryym => mass_dat(region)%ryym
  480. ryzm => mass_dat(region)%ryzm
  481. rzzm => mass_dat(region)%rzzm
  482. #endif
  483. #endif
  484. halo = mass_dat(region)%halo
  485. ! global array
  486. imr = im(region) ; jmr = jm(region) ; lmr = lm(region)
  487. if ( isRoot ) then
  488. allocate(field(imr, jmr, lmr, ntracet))
  489. field = 0.0
  490. allocate(msave(imr,jmr,lmr))
  491. else
  492. allocate(field(1,1,1,1))
  493. allocate(msave(1,1,1))
  494. end if
  495. ! local indices
  496. call Get_DistGrid( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  497. allocate(msave_local(i1:i2,j1:j2,lmr))
  498. #ifdef with_hdf4
  499. ! read on root
  500. if ( isRoot ) then
  501. io = sfstart( file_name, DFACC_READ )
  502. if ( io == FAIL ) then
  503. write(gol,*) 'Read_save_file_30 : Could not open file '// trim(file_name) ; call goPr
  504. call goErr
  505. TRACEBACK ; status=1 ; return
  506. end if
  507. write(gol,'("Read_save_file_30: opened for READ access: ",a)') trim(file_name); call goPr
  508. call io_read3d_32g(io,imr,jmr,lmr,msave,'m',status)
  509. IF_NOTOK_RETURN(status=1)
  510. call io_read4d_32g(io,imr,jmr,lmr,ntracet, field,'rm',status)
  511. ! try again
  512. if( status /= 0 .and. ntracet == 1 ) then
  513. call io_read3d_32g(io,imr,jmr,lmr,field,'rm',status)
  514. end if
  515. IF_NOTOK_RETURN(write (*,'("read_save_file_30: Read rm, status = ",i6)') status)
  516. end if !root
  517. ! get local chunk
  518. call SCATTER( dgrid(region), rm, field, halo, status)
  519. IF_NOTOK_RETURN(status=1)
  520. field = 0.0
  521. call SCATTER( dgrid(region), msave_local, msave, 0, status)
  522. IF_NOTOK_RETURN(status=1)
  523. #ifdef slopes
  524. if ( isRoot ) then
  525. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rxm',status)
  526. if ( status /= 0 .and. ntracet == 1 ) then
  527. call io_read3d_32g(io,imr,jmr,lmr,field,'rxm',status)
  528. end if
  529. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  530. end if
  531. ! get local chunk
  532. call SCATTER( dgrid(region), rxm, field, halo, status)
  533. IF_NOTOK_RETURN(status=1)
  534. field = 0.0
  535. if(isRoot) then
  536. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rym',status)
  537. if ( status /= 0 .and. ntracet == 1 ) then
  538. call io_read3d_32g(io,imr,jmr,lmr,field,'rym',status)
  539. end if
  540. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  541. end if !root
  542. ! get local chunk
  543. call SCATTER( dgrid(region), rym, field, halo, status)
  544. IF_NOTOK_RETURN(status=1)
  545. field = 0.0
  546. if ( isRoot ) then
  547. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rzm',status)
  548. if ( status /= 0 .and. ntracet == 1 ) then
  549. call io_read3d_32g(io,imr,jmr,lmr,field,'rzm',status)
  550. end if
  551. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  552. end if
  553. ! get local chunk
  554. call SCATTER( dgrid(region), rzm, field, halo, status)
  555. IF_NOTOK_RETURN(status=1)
  556. ! reset
  557. field = 0.0
  558. #endif
  559. ! >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  560. ! >>> second moments
  561. ! >>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
  562. #ifdef secmom
  563. if ( isRoot) then
  564. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rxxm',status)
  565. if ( status /= 0 .and. ntracet == 1 ) then
  566. call io_read3d_32g(io,imr,jmr,lmr,field,'rxxm',status)
  567. end if
  568. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  569. endif
  570. call SCATTER( dgrid(region), rxxm, field, halo, status)
  571. IF_NOTOK_RETURN(status=1)
  572. field = 0.0
  573. if(isRoot) then
  574. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rxym',status)
  575. if ( status /= 0 .and. ntracet == 1 ) then
  576. call io_read3d_32g(io,imr,jmr,lmr,field,'rxym',status)
  577. end if
  578. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  579. endif
  580. call SCATTER( dgrid(region), rxym, field, halo, status)
  581. IF_NOTOK_RETURN(status=1)
  582. field = 0.0
  583. if(isRoot) then
  584. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rxzm',status)
  585. if ( status /= 0 .and. ntracet == 1 ) then
  586. call io_read3d_32g(io,imr,jmr,lmr,field,'rxzm',status)
  587. end if
  588. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  589. endif
  590. call SCATTER( dgrid(region), rxzm, field, halo, status)
  591. IF_NOTOK_RETURN(status=1)
  592. field = 0.0
  593. if(isRoot) then
  594. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'ryym',status)
  595. if ( status /= 0 .and. ntracet == 1 ) then
  596. call io_read3d_32g(io,imr,jmr,lmr,field,'ryym',status)
  597. end if
  598. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  599. endif
  600. call SCATTER( dgrid(region), ryym, field, halo, status)
  601. IF_NOTOK_RETURN(status=1)
  602. field = 0.0
  603. if(isRoot) then
  604. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'ryzm',status)
  605. if ( status /= 0 .and. ntracet == 1 ) then
  606. call io_read3d_32g(io,imr,jmr,lmr,field,'ryzm',status)
  607. end if
  608. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  609. endif
  610. call SCATTER( dgrid(region), ryzm, field, halo, status)
  611. IF_NOTOK_RETURN(status=1)
  612. ! reset
  613. field = 0.0
  614. if(isRoot) then
  615. call io_read4d_32g(io,imr,jmr,lmr,ntracet,field,'rzzm',status)
  616. if ( status /= 0 .and. ntracet == 1 ) then
  617. call io_read3d_32g(io,imr,jmr,lmr,field,'rzzm',status)
  618. end if
  619. IF_NOTOK_RETURN(write (*,'("read_save_file_30: status = ",i6)') status)
  620. endif
  621. call SCATTER( dgrid(region), rzzm, field, halo, status)
  622. IF_NOTOK_RETURN(status=1)
  623. field = 0.0
  624. #endif
  625. ! <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  626. ! <<< end second moments
  627. ! <<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
  628. if ( isRoot ) then
  629. istat = sfend(io)
  630. if ( istat /= FAIL ) then
  631. write(gol,'("read_save_file_30: ... file closed")') ; call goPr
  632. write(gol,'("read_save_file_30: ")') ; call goPr
  633. else
  634. TRACEBACK ; status=1 ; return
  635. end if
  636. end if
  637. ! CONVERSION
  638. ! rm/msave ---> mixing ratio on file. mr*m --> something back in kilo's
  639. if ( isRoot ) then
  640. write(gol,*) 'read_save_file_30: Maximum ratio of the air masses:', &
  641. maxval(abs(msave/m(1:imr,1:jmr,1:lmr))) ; call goPr
  642. write(gol,*) 'read_save_file_30: Minimum ratio of the air masses:', &
  643. minval(abs(msave/m(1:imr,1:jmr,1:lmr))) ; call goPr
  644. end if
  645. do n = 1, ntracet
  646. do l = 1, lmr
  647. rm(i1:i2,j1:j2,l,n) = rm (i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  648. #ifdef slopes
  649. rxm(i1:i2,j1:j2,l,n) = rxm(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  650. rym(i1:i2,j1:j2,l,n) = rym(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  651. rzm(i1:i2,j1:j2,l,n) = rzm(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  652. #ifdef secmom
  653. rxxm(i1:i2,j1:j2,l,n) = rxxm(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  654. rxym(i1:i2,j1:j2,l,n) = rxym(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  655. rxzm(i1:i2,j1:j2,l,n) = rxzm(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  656. ryym(i1:i2,j1:j2,l,n) = ryym(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  657. ryzm(i1:i2,j1:j2,l,n) = ryzm(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  658. rzzm(i1:i2,j1:j2,l,n) = rzzm(i1:i2,j1:j2,l,n)*m(i1:i2,j1:j2,l)/msave_local(i1:i2,j1:j2,l)
  659. #endif
  660. #endif
  661. end do
  662. end do
  663. #else
  664. write (gol,'("not compiled with hdf4")'); call goErr
  665. TRACEBACK; status=1; return
  666. #endif // with_hdf4
  667. ! cleanup
  668. deallocate(msave, msave_local)
  669. deallocate(field)
  670. nullify(m)
  671. nullify(rm)
  672. #ifdef slopes
  673. nullify(rxm)
  674. nullify(rym)
  675. nullify(rzm)
  676. #ifdef secmom
  677. nullify(rxxm)
  678. nullify(rxym)
  679. nullify(rxzm)
  680. nullify(ryym)
  681. nullify(ryzm)
  682. nullify(rzzm)
  683. #endif
  684. #endif
  685. END SUBROUTINE READ_SAVE_FILE_30
  686. !EOC
  687. !--------------------------------------------------------------------------
  688. ! TM5 !
  689. !--------------------------------------------------------------------------
  690. !BOP
  691. !
  692. ! !IROUTINE: READHDFMMR
  693. !
  694. ! !DESCRIPTION: read tracer mixing ratio from so-called "old save" file and
  695. ! uses air mass to convert to mass, in order to initialize the
  696. ! model.
  697. !
  698. ! Used with option istart=4
  699. !\\
  700. !\\
  701. ! !INTERFACE:
  702. !
  703. SUBROUTINE READHDFMMR( region, file_name, status )
  704. !
  705. ! !USES:
  706. !
  707. use dims, only : im, jm, lm, nregions, datadir, region_name
  708. #ifdef with_hdf4
  709. use io_hdf
  710. #endif
  711. use global_data, only : mass_dat
  712. use meteodata , only : m_dat
  713. use chem_param, only : fscale, ntracet
  714. use tm5_distgrid, only : dgrid, Get_DistGrid, scatter
  715. use partools, only : isRoot
  716. !
  717. ! !INPUT PARAMETERS:
  718. !
  719. integer, intent(in) :: region
  720. character(len=*), intent(in) :: file_name
  721. !
  722. ! !OUTPUT PARAMETERS:
  723. !
  724. integer, intent(out) :: status
  725. !
  726. ! !REVISION HISTORY:
  727. ! 4 Jul 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition (FIXME: not tested)
  728. !
  729. ! !REMARKS:
  730. ! (1) similar to read_mmix, but all tranported tracers are read at once.
  731. ! That is: no check on tracers name, and order of tracer matters,
  732. ! which depends on the number of processors in TM5 v3.
  733. ! (2) All tracers must be in the file, and the 4D array should be the
  734. ! second dataset.
  735. !
  736. !EOP
  737. !------------------------------------------------------------------------
  738. !BOC
  739. character(len=*), parameter :: rname = mname//'/readhdfmmr'
  740. real, dimension(:,:,:,:), pointer :: rm
  741. real, dimension(:,:,:), pointer :: m
  742. #ifdef with_hdf4
  743. integer :: io, sfstart, ifail, sds_id
  744. integer :: n_datasets, n_file_attrs
  745. integer :: istat, attributes, num_type
  746. integer :: sffinfo, sfselect, sfginfo
  747. integer :: sfend, sfrnatt, sfrcatt, sffattr
  748. #endif
  749. integer, dimension(6) :: idate_save
  750. integer, dimension(nregions) :: im_file,jm_file,lm_file
  751. integer :: ntrace_file
  752. character(len=80) :: msg_file
  753. integer :: ind,n,i,j,l,offsetn
  754. real,dimension(:,:,:,:), allocatable :: field
  755. ! start
  756. m => m_dat(region)%data
  757. rm => mass_dat(region)%rm
  758. #ifdef slopes
  759. mass_dat(region)%rxm = 0.
  760. mass_dat(region)%rym = 0.
  761. mass_dat(region)%rzm = 0.
  762. #ifdef secmom
  763. mass_dat(region)%rxxm = 0.
  764. mass_dat(region)%rxym = 0.
  765. mass_dat(region)%rxzm = 0.
  766. mass_dat(region)%ryym = 0.
  767. mass_dat(region)%ryzm = 0.
  768. mass_dat(region)%rzzm = 0.
  769. #endif
  770. #endif
  771. if (isRoot) then
  772. allocate(field(im(region),jm(region),lm(region),ntracet))
  773. else
  774. allocate(field(1,1,1,1))
  775. end if
  776. #ifdef with_hdf4
  777. ! Read on root
  778. if ( isRoot ) then
  779. io = sfstart( file_name, DFACC_READ )
  780. if ( io == -1 ) then
  781. write(gol,*)'readhdfmmr: Could not open file:'//file_name ; call goErr
  782. TRACEBACK; status=1; return
  783. end if
  784. ind = 1 ! select 1st dataset....(0 = m)
  785. istat = sffinfo(io, n_datasets, n_file_attrs)
  786. write(gol,*) 'readhdfmmr: Number of datasets and attributes', &
  787. n_datasets, n_file_attrs ; call goPr
  788. call io_read4d_32g(io,im(region),jm(region),lm(region),ntracet, &
  789. field,'rm',ifail,index=ind)
  790. if ( ifail /= 0 .and. ntracet == 1 ) then
  791. call io_read3d_32g(io,im(region),jm(region),lm(region), &
  792. field,'rm',ifail,index=ind)
  793. end if
  794. if ( ifail /= 0 ) then
  795. write(gol,*) 'readhdfmmr: '//trim(file_name) ; call goErr
  796. write(gol,*)'readhdfmmr: Failed to read fields'; call goErr
  797. TRACEBACK; status=1; return
  798. end if
  799. write(gol,*) 'readhdfmmr: Read rm, ifail = ', ifail
  800. istat = sfend(io)
  801. if (istat /= FAIL) then
  802. write(gol,*)'readhdfmmr: ... file closed' ; call goErr
  803. write(gol,*)' ' ; call goPr
  804. else
  805. write(gol,*)'readhdfmmr: ERROR in restart from HDF file'; call goErr
  806. TRACEBACK; status=1; return
  807. end if
  808. end if ! root
  809. #else
  810. write (gol,'("not compiled with hdf4")'); call goErr
  811. TRACEBACK; status=1; return
  812. #endif // with_hdf4
  813. call SCATTER( dgrid(region), rm, field, mass_dat(region)%halo, status)
  814. do n=1,ntracet
  815. rm(:,:,:,n) = rm(:,:,:,n)*m(:,:,:)/fscale(n)
  816. end do
  817. deallocate(field)
  818. nullify(m)
  819. nullify(rm)
  820. END SUBROUTINE READHDFMMR
  821. !EOC
  822. !--------------------------------------------------------------------------
  823. ! TM5 !
  824. !--------------------------------------------------------------------------
  825. !BOP
  826. !
  827. ! !IROUTINE: READ_MMIX
  828. !
  829. ! !DESCRIPTION: read mean mixing ratio of TRANSPORTED tracers from an "mmix hdf
  830. ! file" and uses air mass to convert to mass. Missing tracers
  831. ! are set to 0.0
  832. !
  833. ! Used with option istart=5.
  834. !\\
  835. !\\
  836. ! !INTERFACE:
  837. !
  838. SUBROUTINE READ_MMIX( region, file_name, status )
  839. !
  840. ! !USES:
  841. !
  842. use dims, only : im, jm, lm, nregions, datadir, region_name, parent
  843. #ifdef with_hdf4
  844. use io_hdf
  845. #endif
  846. use global_data, only : mass_dat
  847. use meteodata , only : m_dat
  848. use chem_param, only : fscale, ntracet, names
  849. use tm5_distgrid, only : dgrid, Get_DistGrid, scatter
  850. use ParTools, only : isRoot
  851. !
  852. ! !INPUT PARAMETERS:
  853. !
  854. integer, intent(in) :: region
  855. character(len=*), intent(in) :: file_name
  856. !
  857. ! !OUTPUT PARAMETERS:
  858. !
  859. integer, intent(out) :: status
  860. !
  861. ! !REVISION HISTORY:
  862. ! 4 Jul 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition (FIXME: not tested)
  863. !
  864. ! !REMARKS:
  865. !
  866. ! (1) This is typically the choice for combining different versions
  867. ! or extending the number of tracers.
  868. ! (2) The compounds are searched by name. If not in the mmix file
  869. ! the field is initialized as zero.
  870. !
  871. !EOP
  872. !------------------------------------------------------------------------
  873. !BOC
  874. character(len=*), parameter :: rname = mname//'/read_mmix'
  875. real,dimension(:,:,:,:),pointer :: rm
  876. #ifdef slopes
  877. real,dimension(:,:,:,:),pointer :: rxm,rym,rzm
  878. #endif
  879. real,dimension(:,:,:),pointer :: m
  880. #ifdef with_hdf4
  881. integer :: io, sfstart, ifail, sds_id
  882. integer :: n_datasets, n_file_attrs
  883. integer :: istat, attributes, num_type
  884. integer :: sffinfo, sfselect, sfginfo
  885. integer :: sfend, sfrnatt, sfrcatt, sffattr
  886. #endif
  887. integer,dimension(6) :: idate_save
  888. integer,dimension(nregions) :: im_file,jm_file,lm_file
  889. integer :: ntrace_file
  890. character(len=80) :: msg_file
  891. integer :: ind,n,i,j,l,from_file, my_parent
  892. real,dimension(:,:,:,:), allocatable :: field
  893. real,dimension(:,:,:), allocatable :: field3d
  894. ! start
  895. m => m_dat(region)%data
  896. rm => mass_dat(region)%rm
  897. #ifdef slopes
  898. rxm => mass_dat(region)%rxm
  899. rym => mass_dat(region)%rym
  900. rzm => mass_dat(region)%rzm
  901. #endif
  902. rm = 0.0
  903. #ifdef slopes
  904. rxm = 0.0
  905. rym = 0.0
  906. rzm = 0.0
  907. #endif
  908. if (isRoot) then
  909. allocate(field(im(region),jm(region),lm(region),ntracet))
  910. else
  911. allocate(field(1,1,1,1))
  912. end if
  913. #ifdef with_hdf4
  914. ! Read on root
  915. if ( isRoot ) then
  916. from_file = 1
  917. allocate(field3d(im(region),jm(region),lm(region)))
  918. io = sfstart(file_name, DFACC_READ)
  919. if ( io == FAIL ) then
  920. my_parent = parent(region)
  921. if ( my_parent == 0 ) then
  922. write(gol,*)'read_mmix : Could not open file and no parent '// &
  923. 'available :'//file_name ; call goErr
  924. TRACEBACK; status=1; return
  925. else
  926. ! FIXME : this is not going anywhere
  927. from_file = 0
  928. write(gol,*) 'readhdf: Trying to initialise '//trim(region_name(region))// &
  929. ' from parent....'; call goPr
  930. endif
  931. endif
  932. if ( from_file == 1 ) then ! read from file:
  933. write(gol,*) 'read_mmix: ',file_name,'... opened for READ access.' ; call goPr
  934. istat = sffinfo(io, n_datasets, n_file_attrs)
  935. write(gol,*) 'read_mmix: Number of datasets and attributes', n_datasets, n_file_attrs
  936. call goPr
  937. do n = 1, ntracet
  938. call io_read3d_32(io, im(region), jm(region), lm(region), field3d, names(n), ifail)
  939. if (ifail == 0) then
  940. field(1:im(region), 1:jm(region), 1:lm(region), n) = field3d
  941. else
  942. write(gol,*) 'Read_mmix:', names(n), ' not found in dataset --> 0.0 ' ; call goPr
  943. field(1:im(region), 1:jm(region), 1:lm(region), n) = tiny(1.0)
  944. endif
  945. enddo
  946. istat = sfend(io)
  947. if (istat /= FAIL) then
  948. write(gol,*)'read_mmix: ... file closed' ; call goPr
  949. write(gol,*)' '; call goPr
  950. else
  951. write(gol,*)'read_mmix: ERROR in restart from HDF file'; call goErr
  952. TRACEBACK; status=1; return
  953. end if
  954. deallocate(field3d) ! no longer needed
  955. endif ! from file
  956. endif ! root
  957. #else
  958. write (gol,'("not compiled with hdf4")'); call goErr
  959. TRACEBACK; status=1; return
  960. #endif // with_hdf4
  961. call SCATTER( dgrid(region), rm, field, mass_dat(region)%halo, status)
  962. ! Convert from mmix to kg tracer
  963. do n = 1, ntracet
  964. rm(:,:,:,n) = rm(:,:,:,n)*m/fscale(n)
  965. end do
  966. #ifdef slopes
  967. rxm = 0.0 ; rym = 0.0 ; rzm = 0.0
  968. #endif
  969. ! Done
  970. deallocate(field)
  971. nullify(m, rm)
  972. #ifdef slopes
  973. nullify(rxm, rym, rzm)
  974. #endif
  975. END SUBROUTINE READ_MMIX
  976. !EOC
  977. !--------------------------------------------------------------------------
  978. ! TM5 !
  979. !--------------------------------------------------------------------------
  980. !BOP
  981. !
  982. ! !IROUTINE: READ_SAVE_FILE
  983. !
  984. ! !DESCRIPTION: Read mass of both transpoted AND short lived species from so
  985. ! -called "save file". No slopes, but regridding to model
  986. ! resolution is available, since grid information is also read.
  987. !
  988. ! Used with istart=31 option.
  989. !\\
  990. !\\
  991. ! !INTERFACE:
  992. !
  993. SUBROUTINE READ_SAVE_FILE( region, fname, status, tm4 )
  994. !
  995. ! !USES:
  996. !
  997. #ifdef with_hdf4
  998. use file_hdf , only : THdfFile, TSds, Init, Done, ReadAttribute, ReadData
  999. #endif
  1000. use grid , only : TllGridInfo, TLevelInfo, Init, Done, Fill3D
  1001. use dims , only : im, jm, lm
  1002. use chem_param , only : ntrace, ntracet, fscale, names, ntrace_chem
  1003. use partools , only : root, ierr, my_real, localComm, isRoot
  1004. use global_data , only : mass_dat, chem_dat
  1005. use meteodata , only : global_lli, levi, sp_dat, m_dat
  1006. use tm5_distgrid, only : dgrid, Get_DistGrid, gather, scatter
  1007. !
  1008. ! !INPUT PARAMETERS:
  1009. !
  1010. integer, intent(in) :: region
  1011. character(len=*), intent(in) :: fname
  1012. logical, intent(in), optional :: tm4
  1013. !
  1014. ! !OUTPUT PARAMETERS:
  1015. !
  1016. integer, intent(out) :: status
  1017. !
  1018. ! !REVISION HISTORY:
  1019. ! 4 Oct 2011 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  1020. !
  1021. ! !REMARKS:
  1022. ! (1) tracers not found in the file are left unchanged (ie to their initialized values)
  1023. !
  1024. !EOP
  1025. !------------------------------------------------------------------------
  1026. !BOC
  1027. character(len=*), parameter :: rname = mname//'/Read_save_file'
  1028. ! 31 (from 60) layer defintition for TM4 save files:
  1029. real, parameter :: at_tm4_60_31(0:31) = (/ &
  1030. 0., 7.367743, 467.333588, 1385.912598, 2887.696533, &
  1031. 4941.778320, 6144.314941, 8802.356445, 10209.500977, 11632.758789, &
  1032. 14411.124023, 15706.447266, 16899.468750, 17961.357422, 18864.750000, &
  1033. 19584.330078, 20097.402344, 20384.480469, 20222.205078, 19755.109375, &
  1034. 19027.695313, 18045.183594, 16819.474609, 15379.805664, 13775.325195, &
  1035. 12077.446289, 10376.126953, 8765.053711, 6018.019531, 3960.291504, &
  1036. 2082.273926, 0./)
  1037. real, parameter :: bt_tm4_60_31(0:31) = (/ &
  1038. 1.00000000, 0.99401945, 0.96764523, 0.93194032, 0.87965691, &
  1039. 0.81125343, 0.77159661, 0.68326861, 0.63554746, 0.58616841, &
  1040. 0.48477158, 0.43396294, 0.38389215, 0.33515489, 0.28832296, &
  1041. 0.24393314, 0.20247590, 0.16438432, 0.09967469, 0.07353383, &
  1042. 0.05169041, 0.03412116, 0.02067788, 0.01114291, 0.00508112, &
  1043. 0.00181516, 0.00046139, 0.00007582, 0.00000000, 0.00000000, &
  1044. 0.00000000, 0.00000000/)
  1045. ! 34 (from 91) layer defintition for TM4 save files:
  1046. real, parameter :: at_tm4_91_34(0:34) = (/ &
  1047. 0.000000, 6.575628, 336.772369, 1297.656128, 3010.146973, &
  1048. 5422.802734, 8356.252930, 11543.166992, 14665.645508, 17385.595703, &
  1049. 19348.775391, 20319.011719, 20348.916016, 19919.796875, 19184.544922, &
  1050. 18191.029297, 16990.623047, 15638.053711, 14192.009766, 12713.897461, &
  1051. 11262.484375, 9873.560547, 8564.624023, 7341.469727, 6199.839355, &
  1052. 4663.776367, 3358.425781, 2292.155518, 1463.163940, 857.945801, &
  1053. 450.685791, 204.637451, 76.167656, 21.413612, 0.000000/)
  1054. real, parameter :: bt_tm4_91_34(0:34) = (/ &
  1055. 1.000000, 0.994204, 0.973466, 0.935157, 0.875518, &
  1056. 0.795385, 0.698224, 0.589317, 0.475016, 0.362203, &
  1057. 0.259554, 0.176091, 0.112979, 0.080777, 0.055474, &
  1058. 0.036227, 0.022189, 0.012508, 0.006322, 0.002765, &
  1059. 0.001000, 0.000279, 0.000055, 0.000000, 0.000000, &
  1060. 0.000000, 0.000000, 0.000000, 0.000000, 0.000000, &
  1061. 0.000000, 0.000000, 0.000000, 0.000000, 0.000000/)
  1062. ! 34 (from standard) layer defintition for TM4 save files:
  1063. real, parameter :: at_tm4_std_34(0:34) = (/ &
  1064. 0., 7.367743, 210.393890, 855.361755, &
  1065. 2063.779785, 3850.913330, 6144.314941, 8802.356445, &
  1066. 11632.758789, 14411.124023, 16899.468750, 17961.357422, &
  1067. 18864.750000, 19584.330078, 20097.402344, 20384.480469, &
  1068. 20429.863281, 20222.205078, 19755.109375, 19027.695313, &
  1069. 18045.183594, 16819.474609, 15379.805664, 13775.325195, &
  1070. 12077.446289, 10376.126953, 8765.053711, 7306.631348, &
  1071. 6018.019531, 3960.291504, 1680.640259, 713.218079, &
  1072. 298.495789, 95.636963, 0./)
  1073. real, parameter :: bt_tm4_std_34(0:34) = (/ &
  1074. 1.00000000, 0.99401945, 0.97966272, 0.95182151, &
  1075. 0.90788388, 0.84737492, 0.77159661, 0.68326861, &
  1076. 0.58616841, 0.48477158, 0.38389215, 0.33515489, &
  1077. 0.28832296, 0.24393314, 0.20247590, 0.16438432, &
  1078. 0.13002251, 0.09967469, 0.07353383, 0.05169041, &
  1079. 0.03412116, 0.02067788, 0.01114291, 0.00508112, &
  1080. 0.00181516, 0.00046139, 0.00007582, 0.00000000, &
  1081. 0.00000000, 0.00000000, 0.00000000, 0.00000000, &
  1082. 0.00000000, 0.00000000, 0.00000000/)
  1083. ! --- local -------------------------------
  1084. integer :: imr, jmr, lmr
  1085. real, dimension(:,:,:), pointer :: sp
  1086. real, dimension(:,:,:), pointer :: m
  1087. #ifdef with_hdf4
  1088. type(THdfFile) :: hdf
  1089. type(TSds) :: sds_rm, sds_rmc
  1090. #endif
  1091. integer :: n, ns
  1092. integer :: ntrace_in, ntracet_in
  1093. integer :: n_in, nl
  1094. character(len=8), allocatable :: names_in(:)
  1095. integer :: xbeg_in, ybeg_in
  1096. real :: dx_in, dy_in
  1097. integer :: im_in, jm_in, lm_in
  1098. real, allocatable :: at_in(:), bt_in(:)
  1099. type(TllGridInfo) :: lli_in
  1100. type(TLevelInfo) :: levi_in
  1101. real, allocatable :: rm_in(:,:,:,:), sp_gbl(:,:,:)
  1102. real, allocatable :: rmt(:,:,:,:),rms(:,:,:,:)
  1103. integer :: l
  1104. logical :: with_tm4
  1105. ! --- begin -------------------------------
  1106. ! global grid sizes
  1107. imr = im(region)
  1108. jmr = jm(region)
  1109. lmr = lm(region)
  1110. ! set pointers
  1111. sp => sp_dat(region)%data ! surface pressure
  1112. m => m_dat(region)%data ! air mass
  1113. ! special input ?
  1114. with_tm4 = .false.
  1115. if ( present(tm4) ) with_tm4 = tm4
  1116. ! temporary global storage
  1117. if (isRoot) then
  1118. allocate( rmt(imr,jmr,lmr,ntracet ) )
  1119. allocate( rms(imr,jmr,lmr,ntrace_chem) )
  1120. allocate( sp_gbl(imr,jmr,1) )
  1121. else
  1122. allocate( rmt(1,1,1,1) )
  1123. allocate( rms(1,1,1,1) )
  1124. allocate(sp_gbl(1,1,1))
  1125. endif
  1126. ! init to 0 in case of not found in file
  1127. rmt=tiny(0.)
  1128. rms=tiny(0.)
  1129. call gather( dgrid(region), sp, sp_gbl, sp_dat(region)%halo, status) ! get global surf pressure
  1130. IF_NOTOK_RETURN(status=1)
  1131. #ifdef with_hdf4
  1132. ! read on root (until we implement the stride in reading)
  1133. if ( isRoot ) then
  1134. ! open hdf file
  1135. call Init( hdf, fname, 'read', status )
  1136. IF_NOTOK_RETURN(status=1)
  1137. ! read list with tracer names in file:
  1138. call ReadAttribute( hdf, 'ntrace', ntrace_in, status )
  1139. IF_NOTOK_RETURN(status=1)
  1140. call ReadAttribute( hdf, 'ntracet', ntracet_in, status )
  1141. IF_NOTOK_RETURN(status=1)
  1142. allocate( names_in(ntrace_in) )
  1143. call ReadAttribute( hdf, 'names', names_in, status )
  1144. IF_NOTOK_RETURN(status=1)
  1145. ! read level definition
  1146. call ReadAttribute( hdf, 'lm', lm_in, status )
  1147. IF_NOTOK_RETURN(status=1)
  1148. allocate( at_in(0:lm_in) )
  1149. allocate( bt_in(0:lm_in) )
  1150. if ( with_tm4 ) then
  1151. select case ( lm_in )
  1152. case ( 31 )
  1153. at_in = at_tm4_60_31
  1154. bt_in = bt_tm4_60_31
  1155. case ( 34 )
  1156. at_in = at_tm4_std_34
  1157. bt_in = bt_tm4_std_34
  1158. case default
  1159. write (gol,'("input from TM4 save file implemented for 60-31 and 91-34levels only ...")'); call goErr
  1160. TRACEBACK; status=1; return
  1161. end select
  1162. else
  1163. call ReadAttribute( hdf, 'at', at_in, status )
  1164. IF_NOTOK_RETURN(status=1)
  1165. call ReadAttribute( hdf, 'bt', bt_in, status )
  1166. IF_NOTOK_RETURN(status=1)
  1167. end if
  1168. call Init( levi_in, lm_in, at_in, bt_in, status )
  1169. IF_NOTOK_RETURN(status=1)
  1170. deallocate( at_in )
  1171. deallocate( bt_in )
  1172. ! read grid definition:
  1173. call ReadAttribute( hdf, 'im', im_in, status )
  1174. IF_NOTOK_RETURN(status=1)
  1175. call ReadAttribute( hdf, 'jm', jm_in, status )
  1176. IF_NOTOK_RETURN(status=1)
  1177. if ( with_tm4 ) then
  1178. xbeg_in = -180.0
  1179. dx_in = 360.0/im_in
  1180. ybeg_in = -90.0
  1181. dy_in = 180.0/jm_in
  1182. else
  1183. call ReadAttribute( hdf, 'xbeg', xbeg_in, status )
  1184. IF_NOTOK_RETURN(status=1)
  1185. call ReadAttribute( hdf, 'dx', dx_in, status )
  1186. IF_NOTOK_RETURN(status=1)
  1187. call ReadAttribute( hdf, 'ybeg', ybeg_in, status )
  1188. IF_NOTOK_RETURN(status=1)
  1189. call ReadAttribute( hdf, 'dy', dy_in, status )
  1190. IF_NOTOK_RETURN(status=1)
  1191. end if
  1192. call Init( lli_in, xbeg_in+0.5*dx_in, dx_in, im_in, &
  1193. ybeg_in+0.5*dy_in, dy_in, jm_in, status )
  1194. IF_NOTOK_RETURN(status=1)
  1195. ! temporary storage:
  1196. allocate( rm_in(im_in,jm_in,lm_in,1) )
  1197. ! open tracer masses:
  1198. call Init( sds_rm, hdf, 'rm', status )
  1199. IF_NOTOK_RETURN(status=1)
  1200. if ( .not. with_tm4 ) then
  1201. call Init( sds_rmc, hdf, 'rmc', status )
  1202. if(status /= 0) write (gol,'("WARNING - No short lived tracer array found in save file...continuing execution")')
  1203. call goPr
  1204. end if
  1205. ! loop over all tracers:
  1206. do n = 1, ntrace
  1207. ! search input record:
  1208. n_in = -1
  1209. do nl = 1, ntrace_in
  1210. if ( names(n) == names_in(nl) ) then
  1211. n_in = nl
  1212. exit
  1213. end if
  1214. end do
  1215. ! not found ?
  1216. if ( n_in < 0 ) then
  1217. if ( n <= ntracet ) then
  1218. write (gol,'("WARNING - transported tracer not found in save file:")')
  1219. else
  1220. write (gol,'("WARNING - short-lived tracer not found in save file:")')
  1221. end if
  1222. call goPr
  1223. write (gol,'("WARNING - file : ",a)') trim(fname) ; call goPr
  1224. write (gol,'("WARNING - tracer : ",i3," ",a)') n, trim(names(n)) ; call goPr
  1225. if ( n <= ntracet ) then
  1226. write (gol,'(" initialised tracer ",i2,x,a,"; max mass : ",e10.3)') n, names(n), maxval(rmt(:,:,:,n))
  1227. else
  1228. ns = n-ntracet
  1229. write (gol,'(" initialised tracer ",i2,x,a,"; max mass : ",e10.3)') n, names(n), maxval(rms(:,:,:,ns))
  1230. endif
  1231. call goPr
  1232. cycle
  1233. end if
  1234. ! transported or short lived ?
  1235. if ( n <= ntracet ) then
  1236. ! read 3D tracer field from rm or rmc:
  1237. if ( n_in <= ntracet_in ) then
  1238. call ReadData( sds_rm, rm_in, status, start=(/0,0,0,n_in-1/) ) ! kg
  1239. IF_NOTOK_RETURN(status=1)
  1240. else
  1241. call ReadData( sds_rmc, rm_in, status, start=(/0,0,0,n_in-ntracet_in-1/) ) ! kg
  1242. IF_NOTOK_RETURN(status=1)
  1243. end if
  1244. ! expand polar cell for TM4 files ...
  1245. if ( with_tm4 ) then
  1246. do l = 1, lm_in
  1247. rm_in(:, 1,l,1) = rm_in(1, 1,l,1) / im_in
  1248. rm_in(:,jm_in,l,1) = rm_in(1,jm_in,l,1) / im_in
  1249. end do
  1250. end if
  1251. ! regrid from saved grid to current model grid
  1252. call Fill3D( global_lli(region), levi, 'n', sp_gbl(1:imr,1:jmr,1), rmt(1:imr,1:jmr,1:lmr,n), &
  1253. lli_in, levi_in, rm_in(:,:,:,1), 'sum', status )
  1254. IF_NOTOK_RETURN(status=1)
  1255. ! info
  1256. write (gol,'(" initialised tracer ",i2,x,a,"; max mass : ",e10.3)') n, names(n), maxval(rmt(:,:,:,n))
  1257. call goPr
  1258. !Need to gather "m" globally to get VMR
  1259. ! maxval(rmt(1:imr,1:jmr,1:lmr,n)/m_gbl(1:imr,1:jmr,1:lmr)*fscale(n)); call goPr
  1260. else
  1261. ! short lived tracer
  1262. ! read 3D tracer field:
  1263. if ( with_tm4 ) then
  1264. ! tm4 save files have short lived tracers in rm
  1265. call ReadData( sds_rm, rm_in, status, start=(/0,0,0,n_in-1/) ) ! kg
  1266. IF_NOTOK_RETURN(status=1)
  1267. ! expand polar cell ...
  1268. do l = 1, lm_in
  1269. rm_in(:, 1,l,1) = rm_in(1, 1,l,1) / im_in
  1270. rm_in(:,jm_in,l,1) = rm_in(1,jm_in,l,1) / im_in
  1271. end do
  1272. else
  1273. ! read 3D tracer field from rm or rmc:
  1274. if ( n_in <= ntracet_in ) then
  1275. call ReadData( sds_rm, rm_in, status, start=(/0,0,0,n_in-1/) ) ! kg
  1276. IF_NOTOK_RETURN(status=1)
  1277. else
  1278. call ReadData( sds_rmc, rm_in, status, start=(/0,0,0,n_in-ntracet_in-1/) ) ! kg
  1279. IF_NOTOK_RETURN(status=1)
  1280. end if
  1281. end if
  1282. ! regrid from saved grid to current model grid
  1283. ns = n-ntracet
  1284. call Fill3D( global_lli(region), levi, 'n', sp_gbl(1:imr,1:jmr,1), rms(1:imr,1:jmr,1:lmr,ns), &
  1285. lli_in, levi_in, rm_in(:,:,:,1), 'sum', status )
  1286. IF_NOTOK_RETURN(status=1)
  1287. ! info
  1288. write (gol,'(" initialised tracer ",i2,x,a,"; max mass : ",e10.3)') n, names(n), maxval(rms(1:imr,1:jmr,1:lmr,ns))
  1289. call goPr
  1290. !Need to gather "m" globally to get VMR
  1291. ! maxval(rms(1:imr,1:jmr,1:lmr,ns)/m(1:imr,1:jmr,1:lmr)*fscale(n)); call goPr
  1292. end if
  1293. end do
  1294. ! cleanup
  1295. deallocate( names_in )
  1296. deallocate( rm_in )
  1297. ! done with grid
  1298. call Done( lli_in, status )
  1299. IF_NOTOK_RETURN(status=1)
  1300. call Done( levi_in, status )
  1301. IF_NOTOK_RETURN(status=1)
  1302. ! close data sets
  1303. call Done( sds_rm, status )
  1304. IF_NOTOK_RETURN(status=1)
  1305. if ( .not. with_tm4 ) then
  1306. call Done( sds_rmc, status )
  1307. end if
  1308. ! close hdf file (all pe)
  1309. call Done( hdf, status )
  1310. IF_NOTOK_RETURN(status=1)
  1311. end if
  1312. #else
  1313. write (gol,'("not compiled with hdf4")'); call goErr
  1314. TRACEBACK; status=1; return
  1315. #endif
  1316. ! distribute
  1317. call scatter( dgrid(region), mass_dat(region)%rm, rmt, mass_dat(region)%halo, status)
  1318. IF_NOTOK_RETURN(status=1)
  1319. call scatter( dgrid(region), chem_dat(region)%rm, rms, chem_dat(region)%halo, status)
  1320. IF_NOTOK_RETURN(status=1)
  1321. ! done
  1322. deallocate( rmt, rms, sp_gbl )
  1323. status = 0
  1324. END SUBROUTINE READ_SAVE_FILE
  1325. !EOC
  1326. !--------------------------------------------------------------------------
  1327. ! TM5 !
  1328. !--------------------------------------------------------------------------
  1329. !BOP
  1330. !
  1331. ! !IROUTINE: WRITE_SAVE_FILE
  1332. !
  1333. ! !DESCRIPTION: save all essential model parameters and fields in a HDF
  1334. ! file. This so-called "save file" is created only if no
  1335. ! restart is written at the end of the run. It can be read
  1336. ! (with READ_SAVE_FILE) to initialize a run, by using
  1337. ! istart=31 option.
  1338. !\\
  1339. !\\
  1340. ! !INTERFACE:
  1341. !
  1342. SUBROUTINE WRITE_SAVE_FILE( msg, file_name, status )
  1343. !
  1344. ! !USES:
  1345. !
  1346. #ifdef with_hdf4
  1347. use file_hdf , only : THdfFile, Init, Done, WriteAttribute, TSds, SetDim, WriteData
  1348. #endif
  1349. use dims , only : nregions, region_name
  1350. use dims , only : im, jm, lm
  1351. use dims , only : dx, xref, xbeg, xend, ibeg, iend
  1352. use dims , only : dy, yref, ybeg, yend, jbeg, jend
  1353. use dims , only : dz, zref, zbeg, zend, lbeg, lend
  1354. use dims , only : areag
  1355. use dims , only : czeta, czetak
  1356. use dims , only : itau, itaui, itaue, itau0, itaut
  1357. use dims , only : idate, idatei, idatee, idate0, idatet
  1358. use dims , only : icalendo, iyear0, julday0
  1359. use dims , only : newyr, newmonth, newday, newsrun
  1360. use dims , only : tref
  1361. use dims , only : ndyn, nconv, ndiag, nchem, nsrce
  1362. use dims , only : nread, ninst, ncheck, ndiff, ndiagp1, ndiagp2, nstep
  1363. use dims , only : nwrite
  1364. use dims , only : istart
  1365. use dims , only : cpu0, cpu1
  1366. use dims , only : xlabel
  1367. use dims , only : limits
  1368. use dims , only : at, bt
  1369. use dims , only : nsplitsteps, splitorder
  1370. use global_data, only : mass_dat, chem_dat
  1371. use meteodata , only : m_dat
  1372. use chem_param , only : ntrace, ntrace_chem, ntracet, ra, names, fscale
  1373. use chem_param , only : nstd, istd
  1374. #ifdef with_hdf4
  1375. use io_hdf, only : io_write
  1376. #endif
  1377. use datetime, only : tstamp
  1378. use global_data, only : outdir
  1379. use tm5_distgrid, only : dgrid, Get_DistGrid, GATHER
  1380. use ParTools, only : isRoot
  1381. !
  1382. ! !INPUT PARAMETERS:
  1383. !
  1384. character(len=*), intent(in) :: file_name ! base filename if not found in rc file
  1385. character(len=*), intent(in) :: msg ! message attribute
  1386. !
  1387. ! !OUTPUT PARAMETERS:
  1388. !
  1389. integer, intent(out) :: status ! return code
  1390. !
  1391. ! !REVISION HISTORY:
  1392. !
  1393. ! 11 Nov 2011 - P. Le Sager - adapted for adapted for lon-lat MPI domain decomposition
  1394. !
  1395. ! !REMARKS:
  1396. !
  1397. !EOP
  1398. !------------------------------------------------------------------------
  1399. !BOC
  1400. character(len=*), parameter :: rname = mname//'/Write_save_file'
  1401. ! --- local ----------------------------------
  1402. real, dimension(:,:,:,:), pointer :: rm
  1403. #ifdef slopes
  1404. real, dimension(:,:,:,:), pointer :: rxm,rym,rzm
  1405. #ifdef secmom
  1406. real, dimension(:,:,:,:), pointer :: rxxm,rxym,rxzm,ryym,ryzm,rzzm
  1407. #endif
  1408. #endif
  1409. real, dimension(:,:,:,:), pointer :: rmc
  1410. real, dimension(:,:,:,:), allocatable :: glbfield
  1411. #ifdef with_hdf4
  1412. type(THdfFile) :: hdf
  1413. type(TSds) :: sds
  1414. #endif
  1415. integer :: region, imr, jmr, lmr, i, n, I1, J1, IH1, halo
  1416. character(len=64) :: msg_file
  1417. character(len=256) :: fname
  1418. character(len=32 ) :: key
  1419. ! --- begin -----------------------------------
  1420. call InitRc( rcF, rcfile, status )
  1421. IF_NOTOK_RETURN(status=1)
  1422. do region = 1,nregions
  1423. #ifdef with_hdf4
  1424. if ( isRoot ) then
  1425. ! try if filename for istart.3 was specified in rcfile:
  1426. write (key,'("start.3.",a)') trim(region_name(region))
  1427. call ReadRc( rcF, key, fname, status, default='file_name_empty' )
  1428. if(status == -1) then ! no specific istart.3 file name found, use default name
  1429. write (fname,'(a,"_",i4.4,3i2.2,"_",a,".hdf")') trim(file_name), idate(1:4), trim(region_name(region))
  1430. else
  1431. write (gol,*) 'Using save file names from rc-file start.3.* values'; call goPr
  1432. endif
  1433. call Init( hdf, trim(fname), 'create', status )
  1434. IF_NOTOK_RETURN(status=1)
  1435. ! lib cannot handle kind=8:
  1436. ! call WriteAttribute( hdf, 'itau' , itau , status )
  1437. ! IF_NOTOK_RETURN(status=1)
  1438. call WriteAttribute( hdf, 'nregions' , nregions , status )
  1439. IF_NOTOK_RETURN(status=1)
  1440. call WriteAttribute( hdf, 'region_name', trim(region_name(region)), status )
  1441. IF_NOTOK_RETURN(status=1)
  1442. call WriteAttribute( hdf, 'im' , im(region) , status )
  1443. IF_NOTOK_RETURN(status=1)
  1444. call WriteAttribute( hdf, 'jm' , jm(region) , status )
  1445. IF_NOTOK_RETURN(status=1)
  1446. call WriteAttribute( hdf, 'lm' , lm(region) , status )
  1447. IF_NOTOK_RETURN(status=1)
  1448. call WriteAttribute( hdf, 'dx' , dx/xref(region) , status )
  1449. IF_NOTOK_RETURN(status=1)
  1450. call WriteAttribute( hdf, 'dy' , dy/yref(region) , status )
  1451. IF_NOTOK_RETURN(status=1)
  1452. call WriteAttribute( hdf, 'dz' , dz/zref(region) , status )
  1453. IF_NOTOK_RETURN(status=1)
  1454. call WriteAttribute( hdf, 'xbeg' , xbeg(region) , status )
  1455. IF_NOTOK_RETURN(status=1)
  1456. call WriteAttribute( hdf, 'xend' , xend(region) , status )
  1457. IF_NOTOK_RETURN(status=1)
  1458. call WriteAttribute( hdf, 'ybeg' , ybeg(region) , status )
  1459. IF_NOTOK_RETURN(status=1)
  1460. call WriteAttribute( hdf, 'yend' , yend(region) , status )
  1461. IF_NOTOK_RETURN(status=1)
  1462. call WriteAttribute( hdf, 'zbeg' , zbeg(region) , status )
  1463. IF_NOTOK_RETURN(status=1)
  1464. call WriteAttribute( hdf, 'zend' , zend(region) , status )
  1465. IF_NOTOK_RETURN(status=1)
  1466. if ( region /= 1 ) then
  1467. call WriteAttribute( hdf, 'ibeg', ibeg(region), status )
  1468. IF_NOTOK_RETURN(status=1)
  1469. call WriteAttribute( hdf, 'iend', iend(region), status )
  1470. IF_NOTOK_RETURN(status=1)
  1471. call WriteAttribute( hdf, 'jbeg', jbeg(region), status )
  1472. IF_NOTOK_RETURN(status=1)
  1473. call WriteAttribute( hdf, 'jend', jend(region), status )
  1474. IF_NOTOK_RETURN(status=1)
  1475. call WriteAttribute( hdf, 'lbeg', lbeg(region), status )
  1476. IF_NOTOK_RETURN(status=1)
  1477. call WriteAttribute( hdf, 'lend', lend(region), status )
  1478. IF_NOTOK_RETURN(status=1)
  1479. end if
  1480. call WriteAttribute( hdf, 'xref' , xref(region), status )
  1481. IF_NOTOK_RETURN(status=1)
  1482. call WriteAttribute( hdf, 'yref' , yref(region), status )
  1483. IF_NOTOK_RETURN(status=1)
  1484. call WriteAttribute( hdf, 'zref' , zref(region), status )
  1485. IF_NOTOK_RETURN(status=1)
  1486. call WriteAttribute( hdf, 'tref' , tref(region), status )
  1487. IF_NOTOK_RETURN(status=1)
  1488. call WriteAttribute( hdf, 'ntracet' , ntracet , status )
  1489. IF_NOTOK_RETURN(status=1)
  1490. call WriteAttribute( hdf, 'ntrace ' , ntrace , status )
  1491. IF_NOTOK_RETURN(status=1)
  1492. call WriteAttribute( hdf, 'nstd' , nstd , status )
  1493. IF_NOTOK_RETURN(status=1)
  1494. call WriteAttribute( hdf, 'idate' , idate , status )
  1495. IF_NOTOK_RETURN(status=1)
  1496. call WriteAttribute( hdf, 'istart' , istart , status )
  1497. IF_NOTOK_RETURN(status=1)
  1498. call WriteAttribute( hdf, 'ndyn' , ndyn , status )
  1499. IF_NOTOK_RETURN(status=1)
  1500. call WriteAttribute( hdf, 'nconv' , nconv , status )
  1501. IF_NOTOK_RETURN(status=1)
  1502. call WriteAttribute( hdf, 'ndiag' , ndiag , status )
  1503. IF_NOTOK_RETURN(status=1)
  1504. call WriteAttribute( hdf, 'nchem' , nchem , status )
  1505. IF_NOTOK_RETURN(status=1)
  1506. call WriteAttribute( hdf, 'nsrce' , nsrce , status )
  1507. IF_NOTOK_RETURN(status=1)
  1508. call WriteAttribute( hdf, 'nread' , nread , status )
  1509. IF_NOTOK_RETURN(status=1)
  1510. call WriteAttribute( hdf, 'nwrite' , nwrite , status )
  1511. IF_NOTOK_RETURN(status=1)
  1512. call WriteAttribute( hdf, 'ninst' , ninst , status )
  1513. IF_NOTOK_RETURN(status=1)
  1514. call WriteAttribute( hdf, 'ncheck' , ncheck , status )
  1515. IF_NOTOK_RETURN(status=1)
  1516. call WriteAttribute( hdf, 'ndiff' , ndiff , status )
  1517. IF_NOTOK_RETURN(status=1)
  1518. ! lib cannot handle kind=8:
  1519. ! call WriteAttribute( hdf, 'itaui' , itaui , status )
  1520. ! IF_NOTOK_RETURN(status=1)
  1521. ! call WriteAttribute( hdf, 'itaue' , itaue , status )
  1522. ! IF_NOTOK_RETURN(status=1)
  1523. ! call WriteAttribute( hdf, 'itaut' , itaut , status )
  1524. ! IF_NOTOK_RETURN(status=1)
  1525. ! call WriteAttribute( hdf, 'itau0' , itau0 , status )
  1526. IF_NOTOK_RETURN(status=1)
  1527. call WriteAttribute( hdf, 'idatei' , idatei , status )
  1528. IF_NOTOK_RETURN(status=1)
  1529. call WriteAttribute( hdf, 'idatee' , idatee , status )
  1530. IF_NOTOK_RETURN(status=1)
  1531. call WriteAttribute( hdf, 'idatet' , idatet , status )
  1532. IF_NOTOK_RETURN(status=1)
  1533. call WriteAttribute( hdf, 'idate0' , idate0 , status )
  1534. IF_NOTOK_RETURN(status=1)
  1535. call WriteAttribute( hdf, 'icalendo' , icalendo , status )
  1536. IF_NOTOK_RETURN(status=1)
  1537. call WriteAttribute( hdf, 'iyear0' , iyear0 , status )
  1538. IF_NOTOK_RETURN(status=1)
  1539. call WriteAttribute( hdf, 'julday0' , julday0 , status )
  1540. IF_NOTOK_RETURN(status=1)
  1541. call WriteAttribute( hdf, 'ndiagp1' , ndiagp1 , status )
  1542. IF_NOTOK_RETURN(status=1)
  1543. call WriteAttribute( hdf, 'ndiagp2' , ndiagp2 , status )
  1544. IF_NOTOK_RETURN(status=1)
  1545. call WriteAttribute( hdf, 'nstep' , nstep , status )
  1546. IF_NOTOK_RETURN(status=1)
  1547. call WriteAttribute( hdf, 'cpu0' , cpu0 , status )
  1548. IF_NOTOK_RETURN(status=1)
  1549. call WriteAttribute( hdf, 'cpu1' , cpu1 , status )
  1550. IF_NOTOK_RETURN(status=1)
  1551. call WriteAttribute( hdf, 'ra' , ra , status )
  1552. IF_NOTOK_RETURN(status=1)
  1553. call WriteAttribute( hdf, 'fscale' , fscale , status )
  1554. IF_NOTOK_RETURN(status=1)
  1555. call WriteAttribute( hdf, 'names' , names , status )
  1556. IF_NOTOK_RETURN(status=1)
  1557. call WriteAttribute( hdf, 'areag' , areag , status )
  1558. IF_NOTOK_RETURN(status=1)
  1559. call WriteAttribute( hdf, 'czeta' , czeta , status )
  1560. IF_NOTOK_RETURN(status=1)
  1561. call WriteAttribute( hdf, 'czetak' , czetak , status )
  1562. IF_NOTOK_RETURN(status=1)
  1563. call WriteAttribute( hdf, 'xlabel' , xlabel , status )
  1564. IF_NOTOK_RETURN(status=1)
  1565. call WriteAttribute( hdf, 'istd' , istd , status )
  1566. IF_NOTOK_RETURN(status=1)
  1567. call WriteAttribute( hdf, 'newyr' , newyr , status )
  1568. IF_NOTOK_RETURN(status=1)
  1569. call WriteAttribute( hdf, 'newmonth' , newmonth , status )
  1570. IF_NOTOK_RETURN(status=1)
  1571. call WriteAttribute( hdf, 'newday' , newday , status )
  1572. IF_NOTOK_RETURN(status=1)
  1573. call WriteAttribute( hdf, 'newsrun' , newsrun , status )
  1574. IF_NOTOK_RETURN(status=1)
  1575. ! call WriteAttribute( hdf, 'cdebug' , cdebug , status )
  1576. ! IF_NOTOK_RETURN(status=1)
  1577. call WriteAttribute( hdf, 'limits' , limits , status )
  1578. IF_NOTOK_RETURN(status=1)
  1579. call WriteAttribute( hdf, 'at' , at , status )
  1580. IF_NOTOK_RETURN(status=1)
  1581. call WriteAttribute( hdf, 'bt' , bt , status )
  1582. IF_NOTOK_RETURN(status=1)
  1583. call WriteAttribute( hdf, 'nsplitsteps', nsplitsteps , status )
  1584. IF_NOTOK_RETURN(status=1)
  1585. call WriteAttribute( hdf, 'splitorder' , splitorder , status )
  1586. IF_NOTOK_RETURN(status=1)
  1587. msg_file = msg
  1588. call WriteAttribute( hdf, 'msg', msg_file, status )
  1589. IF_NOTOK_RETURN(status=1)
  1590. end if ! root all PEs from here
  1591. ! Short cuts
  1592. !----------------------
  1593. rm => mass_dat(region)%rm
  1594. #ifdef slopes
  1595. rxm => mass_dat(region)%rxm
  1596. rym => mass_dat(region)%rym
  1597. rzm => mass_dat(region)%rzm
  1598. #ifdef secmom
  1599. rxxm => mass_dat(region)%rxxm
  1600. rxym => mass_dat(region)%rxym
  1601. rxzm => mass_dat(region)%rxzm
  1602. ryym => mass_dat(region)%ryym
  1603. ryzm => mass_dat(region)%ryzm
  1604. rzzm => mass_dat(region)%rzzm
  1605. #endif
  1606. #endif
  1607. ! Local & global bounds
  1608. !-----------------------
  1609. call Get_DistGrid( dgrid(region), I_STRT=i1, J_STRT=j1, I_STRT_HALO=ih1 )
  1610. halo = i1-ih1
  1611. imr = im(region) ; jmr = jm(region) ; lmr = lm(region)
  1612. ! Allocate global array
  1613. !----------------------
  1614. if (isRoot) then
  1615. allocate( glbfield( imr, jmr, lmr, ntracet) )
  1616. glbfield = 0.0
  1617. else
  1618. allocate( glbfield(1,1,1,1) )
  1619. end if
  1620. ! M (Air mass)
  1621. !----------------------
  1622. CALL GATHER( dgrid(region), m_dat(region)%data, glbfield(:,:,:,1), m_dat(region)%halo, status )
  1623. IF_ERROR_RETURN(status=1)
  1624. if ( isRoot ) then
  1625. call Init( sds, hdf, 'm', (/imr,jmr,lmr/), 'real(4)', status )
  1626. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1627. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1628. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1629. call WriteData(sds, glbfield(:,:,:,1), status)
  1630. call Done(sds,status)
  1631. IF_ERROR_RETURN(status=1)
  1632. end if
  1633. ! RM (transported tracer masses)
  1634. !-----------------------------
  1635. CALL GATHER( dgrid(region), rm, glbfield, halo, status )
  1636. IF_ERROR_RETURN(status=1)
  1637. if ( isRoot ) then
  1638. call Init( sds, hdf, 'rm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1639. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1640. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1641. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1642. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1643. call WriteData(sds,glbfield,status)
  1644. call Done(sds,status)
  1645. IF_ERROR_RETURN(status=1)
  1646. end if
  1647. #ifdef slopes
  1648. ! RXM
  1649. !-----------------------------
  1650. CALL GATHER( dgrid(region), rxm, glbfield, halo, status )
  1651. IF_ERROR_RETURN(status=1)
  1652. if ( isRoot ) then
  1653. call Init( sds, hdf, 'rxm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1654. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1655. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1656. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1657. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1658. call WriteData(sds,glbfield,status)
  1659. call Done(sds,status)
  1660. IF_ERROR_RETURN(status=1)
  1661. end if
  1662. ! RYM
  1663. !-----------------------------
  1664. CALL GATHER( dgrid(region), rym, glbfield, halo, status )
  1665. IF_ERROR_RETURN(status=1)
  1666. if ( isRoot ) then
  1667. call Init( sds, hdf, 'rym', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1668. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1669. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1670. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1671. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1672. call WriteData(sds,glbfield,status)
  1673. call Done(sds,status)
  1674. IF_ERROR_RETURN(status=1)
  1675. end if
  1676. ! RZM
  1677. !-----------------------------
  1678. CALL GATHER( dgrid(region), rzm, glbfield, halo, status )
  1679. IF_ERROR_RETURN(status=1)
  1680. if ( isRoot ) then
  1681. call Init( sds, hdf, 'rzm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1682. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1683. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1684. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1685. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1686. call WriteData(sds,glbfield,status)
  1687. call Done(sds,status)
  1688. IF_ERROR_RETURN(status=1)
  1689. end if
  1690. #ifdef secmom
  1691. ! second moments
  1692. ! RXXM
  1693. !-----------------------------
  1694. CALL GATHER( dgrid(region), rxxm, glbfield, halo, status )
  1695. IF_ERROR_RETURN(status=1)
  1696. if ( isRoot ) then
  1697. call Init( sds, hdf, 'rxxm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1698. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1699. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1700. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1701. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1702. call WriteData(sds,glbfield,status)
  1703. call Done(sds,status)
  1704. IF_ERROR_RETURN(status=1)
  1705. end if
  1706. ! RXYM
  1707. !-----------------------------
  1708. CALL GATHER( dgrid(region), rxym, glbfield, halo, status )
  1709. IF_ERROR_RETURN(status=1)
  1710. if ( isRoot ) then
  1711. call Init( sds, hdf, 'rxym', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1712. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1713. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1714. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1715. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1716. call WriteData(sds,glbfield,status)
  1717. call Done(sds,status)
  1718. IF_ERROR_RETURN(status=1)
  1719. end if
  1720. ! RXZM
  1721. !-----------------------------
  1722. CALL GATHER( dgrid(region), rxzm, glbfield, halo, status )
  1723. IF_ERROR_RETURN(status=1)
  1724. if ( isRoot ) then
  1725. call Init( sds, hdf, 'rxzm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1726. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1727. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1728. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1729. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1730. call WriteData(sds,glbfield,status)
  1731. call Done(sds,status)
  1732. IF_ERROR_RETURN(status=1)
  1733. end if
  1734. ! RYYM
  1735. !-----------------------------
  1736. CALL GATHER( dgrid(region), ryym, glbfield, halo, status )
  1737. IF_ERROR_RETURN(status=1)
  1738. if ( isRoot) then
  1739. call Init( sds, hdf, 'ryym', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1740. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1741. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1742. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1743. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1744. call WriteData(sds,glbfield,status)
  1745. call Done(sds,status)
  1746. IF_ERROR_RETURN(status=1)
  1747. end if
  1748. ! RYZM
  1749. !-----------------------------
  1750. CALL GATHER( dgrid(region), ryzm, glbfield, halo, status )
  1751. IF_ERROR_RETURN(status=1)
  1752. if ( isRoot) then
  1753. call Init( sds, hdf, 'ryzm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1754. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1755. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1756. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1757. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1758. call WriteData(sds,glbfield,status)
  1759. call Done(sds,status)
  1760. IF_ERROR_RETURN(status=1)
  1761. endif
  1762. ! RZZM
  1763. !-----------------------------
  1764. CALL GATHER( dgrid(region), rzzm, glbfield, halo, status )
  1765. IF_ERROR_RETURN(status=1)
  1766. if ( isRoot) then
  1767. call Init( sds, hdf, 'rzzm', (/imr,jmr,lmr,ntracet/), 'real(4)', status )
  1768. call SetDim(sds,0,'LON'//region_name(region),'deg',(/(xbeg(region)+(i+0.5)*dx/xref(region),i=0,imr-1)/),status)
  1769. call SetDim(sds,1,'LAT'//region_name(region),'deg',(/(ybeg(region)+(i+0.5)*dy/yref(region),i=0,jmr-1)/),status)
  1770. call SetDim(sds,2,'HYBRID','number',(/(i,i=1,lmr)/),status)
  1771. call SetDim(sds,3,'ntracet','None',(/(i,i=1,ntracet)/),status)
  1772. call WriteData(sds,glbfield,status)
  1773. call Done(sds,status)
  1774. IF_ERROR_RETURN(status=1)
  1775. endif
  1776. #endif
  1777. #endif
  1778. ! clear
  1779. deallocate(glbfield)
  1780. nullify(rm)
  1781. #ifdef slopes
  1782. nullify(rxm)
  1783. nullify(rym)
  1784. nullify(rzm)
  1785. #ifdef secmom
  1786. nullify(rxxm)
  1787. nullify(rxym)
  1788. nullify(rxzm)
  1789. nullify(ryym)
  1790. nullify(ryzm)
  1791. nullify(rzzm)
  1792. #endif
  1793. #endif
  1794. ! SHORT LIVED TRACERS if any
  1795. ! ----------------------------
  1796. if ( ntrace_chem > 0 ) then
  1797. ! allocate global array
  1798. if (isRoot) then
  1799. allocate(glbfield(imr,jmr,lmr,ntrace_chem))
  1800. else
  1801. allocate(glbfield(1,1,1,1))
  1802. end if
  1803. ! tracer mass
  1804. rmc => chem_dat(region)%rm
  1805. CALL GATHER( dgrid(region), rmc, glbfield, 0, status )
  1806. IF_NOTOK_RETURN(status=1)
  1807. if ( isRoot ) then
  1808. ! write tracers
  1809. call io_write( hdf%id, imr,'LON'//region_name(region),&
  1810. jmr,'LAT'//region_name(region), &
  1811. lmr,'HYBRID',ntrace_chem,'NTRACE_CHEM',glbfield,'rmc')
  1812. end if
  1813. ! clear
  1814. nullify(rmc)
  1815. deallocate(glbfield)
  1816. end if ! ntrace_chem > 0
  1817. ! Close
  1818. !-------
  1819. if ( isRoot ) then
  1820. call Done( hdf, status )
  1821. IF_NOTOK_RETURN(status=1)
  1822. end if
  1823. #else
  1824. write (gol,'("not compiled with hdf4")'); call goErr
  1825. TRACEBACK; status=1; return
  1826. #endif
  1827. end do !regions...
  1828. ! -------
  1829. ! Done
  1830. ! -------
  1831. call DoneRc( rcF, status )
  1832. IF_NOTOK_RETURN(status=1)
  1833. ! ok
  1834. status = 0
  1835. END SUBROUTINE WRITE_SAVE_FILE
  1836. !EOC
  1837. END MODULE IO_SAVE