user_output_flask.F90 63 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593
  1. #define TRACEBACK write (gol,'("in ",a," (",a,", line",i5,")")') rname, __FILE__, __LINE__; call goErr
  2. #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if
  3. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  4. #include "tm5.inc"
  5. !#################################################################
  6. module user_output_flask ! *************** DUMMY TM5-MP VERSION *******************
  7. !BOP
  8. !
  9. ! !MODULE: user_output_flask
  10. !
  11. ! !PUBLIC TYPES: none
  12. !
  13. ! !PUBLIC MEMBER FUNCTIONS:
  14. ! user_output_flask_init
  15. ! user_output_flask_sample
  16. ! user_output_flask_done
  17. !
  18. ! !PUBLIC DATA MEMBERS:
  19. !
  20. ! !DESCRIPTION:
  21. !
  22. ! Routine for simulating flask samples in TM5.
  23. !
  24. ! "Flask" is shorthand for any x,y,z,t sampling of the model. This
  25. ! routine is intended for producing model output of low-frequency,
  26. ! intermittent, or sporadic sampling (like NOAA Cooperative Sampling
  27. ! Network flasks), but is also useful for other observations like
  28. ! aircraft profiles or daily averages from continuous station data.
  29. !
  30. ! I/O is via netCDF files, using the MDF interface. Observation
  31. ! list from input file is truncated to begin/end times of the current run.
  32. !
  33. ! Input file format:
  34. ! Routine expects to read a netCDF (v3) file with:
  35. !
  36. ! "obspack_id" : record dimension, unique 100-character string across obspacks
  37. ! "latitude" : 1-d real array, length id, of latitudes (degrees N)
  38. ! "longitude" : 1-d real array, length id, of longitudes (degrees E)
  39. ! "altitude" : 1-d real array, length id, of altitudes (m ASL)
  40. !
  41. ! "calendar_components": 2-D variable with dims (id,6),
  42. ! with time of observations in 6-integer 'idate' format
  43. ! (year, month, day, hour, minute, second in UTC time.
  44. !
  45. ! "sampling_strategy" 1-D integer array designed to represent
  46. ! distinct schemes for sampling TM5 to represent the
  47. ! observations in this file. Add to the following list if
  48. ! you define a new scheme:
  49. !
  50. ! VALUE MEANING
  51. !
  52. ! 1 Four-hour averages, centered on observation time.
  53. ! 2 One-hour averages, centered on observation time.
  54. ! 3 90-minute averages, centered on observation time.
  55. !
  56. ! Controlling rc-file keys:
  57. !
  58. ! output.flask (logical, default F)
  59. ! Whether or not this routine is active. Note that
  60. ! unlike other rc-file keys, this one is read in
  61. ! user_output.F90. Sets flask_data (a public logical
  62. ! in that module).
  63. !
  64. ! output.flask.infile (string, required, no default value)
  65. ! Path to input netCDF file, e.g. "/path/to/input/flask_obs.nc"
  66. !
  67. ! output.flask.verbose (logical, optional, default F)
  68. ! If true, some extra information is printed to stdout.
  69. !
  70. ! output.flask.replicate.forecast (logical, optional, default F)
  71. ! If true, mimic the sampling scheme of user_output_forecast.F90:
  72. !
  73. ! (1) obs are in-window for this simulation if itaui <= obs < itaue,
  74. ! where itaui and itaue are the initial and ending simulation
  75. ! time values, and obs is the observation center time. The
  76. ! default behavior of this routine is instead to sample all
  77. ! obs meeting the criterion itaui-window/2 <= obs <= itaue+window/2.
  78. ! This will result in obs being sampled in multiple simulations
  79. ! when their sampling windows cross itaui or itaue. This
  80. ! must be dealt with in post-processing.
  81. !
  82. !
  83. ! !REVISION HISTORY:
  84. !
  85. ! Andy Jacobson, Aug 2010
  86. !
  87. ! Adapted from code in user_output_forecast, user_output_station,
  88. ! and user_output_noaa, mostly if not all originally written by
  89. ! Wouter Peters. Also used Arjo Segers' file_MDF example code
  90. ! for netCDF I/O.
  91. !
  92. ! Andy Jacobson, Aug 2011
  93. !
  94. ! Changed variable names to be consistent with Ken Masarie's new
  95. ! ObsPack data distribution system.
  96. !
  97. ! Andy Jacobson, April 2013
  98. !
  99. ! Change to ndyn weighting.
  100. !
  101. ! Mike Trudeau, Apr 2013
  102. !
  103. ! Removed 'obspack_num' references and added netcdf writes of 'obspack_id'.
  104. !
  105. !EOP
  106. !-------------------------------------------------------------------------
  107. ! #ifdef MPI
  108. ! use mpi_const, only : my_real,mpi_comm_world,ierr,mpi_integer,mpi_character
  109. ! use mpi_const, only : MPI_SUCCESS, MPI_INFO_NULL
  110. ! use mpi_comm, only : barrier
  111. ! #endif
  112. ! use ParTools, only : ntracetloc, myid, root, npes, ntracet_ar, par_barrier
  113. ! use chem_param, only : ntracet
  114. ! use MDF , only : MDF_Open
  115. ! use MDF , only : MDF_Create, MDF_Close, MDF_EndDef
  116. ! use MDF , only : MDF_NETCDF, MDF_REPLACE, MDF_GLOBAL, MDF_CHAR, MDF_INT, MDF_FLOAT, MDF_UNLIMITED, MDF_READ
  117. ! use MDF , only : MDF_Put_Att
  118. ! use MDF , only : MDF_Def_Dim
  119. ! use MDF , only : MDF_Inq_Dimid, MDF_Inquire_Dimension
  120. ! use MDF , only : MDF_Inq_VarID
  121. ! use MDF , only : MDF_Def_Var, MDF_Put_Var, MDF_Get_Var
  122. implicit none
  123. private
  124. public :: user_output_flask_init
  125. public :: user_output_flask_done
  126. public :: user_output_flask_sample
  127. ! character(len=1024) :: inFile = ''
  128. ! character(len=1024) :: outFile = ''
  129. ! logical :: flask_replicate_forecast=.false.
  130. ! logical :: flask_sample_meteo=.false.
  131. ! logical :: flask_verbose=.false.
  132. ! integer :: nflasks
  133. ! real*4, parameter :: flask_missing_value=-1.0e34
  134. ! character(len=*), parameter :: mname = 'user_output_flask'
  135. ! ! "obspack_id" is meant to be a flask identifier guaranteed to be unique, for the
  136. ! ! purpose of matching input file records with output file records.
  137. ! type flask_sample
  138. ! real :: lat ! sample latitude
  139. ! real :: lon ! sample longitude
  140. ! real :: alt ! sample altitude (meters above sea level)
  141. ! integer :: itau_start ! sampling start time
  142. ! integer :: itau_center ! sampling center time
  143. ! integer :: itau_end ! sampling end time
  144. ! character(len=100) :: obspack_id ! unique sample identifier
  145. ! real, dimension(:), allocatable :: mix ! mixing ratio of interest sampled using x-y-z slopes
  146. ! real, dimension(:), allocatable :: mix_grd ! mixing ratio of interest sampled using grid-box values
  147. ! integer :: nsamples ! number of samples accumulated
  148. ! real :: accum_weight ! accumulated weight
  149. ! integer :: region ! zoom region index from which this flask is sampled
  150. ! integer :: ifr, jfr ! i,j region indices for flask's grid cell
  151. ! integer :: ifn, jfn ! i,j region indices for flask's "next" grid cell
  152. ! real :: rif, rjf ! fractions from center of ifr,jfr box
  153. ! real :: surface_height ! surface height in meters
  154. ! integer :: lfr ! vertical level number of the sample
  155. ! real :: wcx, wcy ! x and y weighting factors for slopes interpolation
  156. ! logical :: evaluated ! whether or not the average has been computed from mix/nsamples
  157. ! real :: u,v,blh,q,pressure,temperature ! meteorological variables
  158. ! logical :: below_surface_warning = .False.
  159. ! end type flask_sample
  160. ! type(flask_sample), dimension(:), allocatable :: flasks
  161. contains
  162. !BOP
  163. !
  164. ! !IROUTINE: user_output_flask_init
  165. !
  166. ! !INPUT PARAMETERS:
  167. ! rcF - handle to open rc file
  168. ! status - integer status indicator
  169. !
  170. ! !OUTPUT PARAMETERS: none
  171. !
  172. ! !DESCRIPTION:
  173. ! Initialization tasks for user_output_flask:
  174. ! - reads rc file for flask keys
  175. ! - allocates flasks array
  176. ! - reads input netCDF file
  177. ! - computes x,y grid indices and weights for slopes interpolation
  178. ! - transmits flasks array to all PEs
  179. !
  180. !
  181. !EOP
  182. subroutine user_output_flask_init(rcF, status)
  183. use GO, only : TrcFile, ReadRc
  184. ! use GO, only : pathsep
  185. ! use GO, only : gol, goErr, goPr, goBug, goTranslate
  186. ! use global_data, only : outdir
  187. ! use Meteo, only : Set
  188. ! use Meteo, only : gph_dat
  189. ! use binas, only : ae, twopi, grav
  190. ! use dims, only : im, jm, lm, dx, dy, xref, yref, xbeg, ybeg, xend, yend
  191. ! use dims, only : nregions, region_name, itaui, itaue, xcyc, idate
  192. ! use chem_param, only : ntrace, ntracet, names, fscale
  193. ! use toolbox, only : escape_tm
  194. ! use datetime, only : date2tau, tau2date
  195. ! use ParTools
  196. ! implicit none
  197. ! ! --- in/out ---------------------------------
  198. type(TrcFile), intent(in) :: rcF
  199. integer, intent(out) :: status
  200. ! ! local
  201. ! integer :: hid,dimid
  202. ! character(len=256) :: name
  203. ! logical,dimension(:), allocatable :: mask
  204. ! integer,dimension(:,:), allocatable :: idate_f
  205. ! real, dimension(:), allocatable :: lat
  206. ! real, dimension(:), allocatable :: lon
  207. ! real, dimension(:), allocatable :: alt
  208. ! integer, dimension(:), allocatable :: sampling_strategy
  209. ! integer, dimension(:), allocatable :: itau_center
  210. ! integer, dimension(:), allocatable :: itau_start
  211. ! integer, dimension(:), allocatable :: itau_end
  212. ! character*100, dimension(:), allocatable :: obspack_id
  213. ! integer, dimension(6) :: idatei,idatee,idatef
  214. ! logical :: new_region
  215. ! integer :: region
  216. ! integer :: iflask
  217. ! integer :: varid
  218. ! logical :: input_file_exists
  219. ! ! x,y resolution (in degrees) for current region
  220. ! real :: dxr, dyr
  221. ! ! --- const ------------------------------
  222. ! character(len=*), parameter :: rname = mname//'/user_output_flask_init'
  223. ! do region=1,nregions
  224. ! call Set( gph_dat(region), status, used=.true. )
  225. ! IF_NOTOK_RETURN(status=1)
  226. ! enddo
  227. ! if(myid==root) then
  228. ! call ReadRc(rcF, 'output.flask.verbose', flask_verbose, status, default = .false.)
  229. ! IF_NOTOK_RETURN(status=1)
  230. ! call ReadRc(rcF, 'output.flask.meteo', flask_sample_meteo, status, default = .false.)
  231. ! IF_NOTOK_RETURN(status=1)
  232. ! call ReadRc(rcF, 'output.flask.replicate.forecast', flask_replicate_forecast, status, default = .false.)
  233. ! IF_NOTOK_RETURN(status=1)
  234. ! call tau2date(itaui,idatei)
  235. ! call tau2date(itaue,idatee)
  236. ! write (inFile,'(a,"/flask_input.",i4.4,3i2.2,"_",i4.4,3i2.2,".nc")') trim(outdir), idatei(1:4), idatee(1:4)
  237. ! write (gol,'("[user_output_flask_init] input from ",a)') trim(inFile); call goPr
  238. ! write (outFile,'(a,"/flask_output.",i4.4,3i2.2,"_",i4.4,3i2.2,".nc")') trim(outdir), idatei(1:4), idatee(1:4)
  239. ! write (gol,'("[user_output_flask_init] output to ",a)') trim(outFile); call goPr
  240. ! if(flask_verbose) then
  241. ! write (gol,'("[user_output_flask_init] verbose output requested.")'); call goPr
  242. ! endif
  243. ! if(flask_sample_meteo) then
  244. ! write (gol,'("[user_output_flask_init] meteo variables will also be sampled.")'); call goPr
  245. ! endif
  246. ! if(flask_replicate_forecast) then
  247. ! write (gol,'("[user_output_flask_init] sampling will replicate user_output_forecast scheme.")'); call goPr
  248. ! endif
  249. ! endif
  250. ! ! read input file
  251. ! ! get from nc input file:
  252. ! ! lat, lon, alt, date_components, sampling_strategy, obspack_id
  253. ! ! restrict to flasks between itaui and itaue
  254. ! ! for each flask, determine region, ifr, jfr, ...things that don't change.
  255. ! if(myid==root) then
  256. ! inquire(file=inFile,exist=input_file_exists)
  257. ! if (input_file_exists) then
  258. ! call MDF_Open(filename=inFile, ftype=MDF_NETCDF, mode=MDF_READ, hid=hid, status=status)
  259. ! IF_NOTOK_RETURN(status=1)
  260. ! call MDF_Inq_DimID(hid, "obs", dimid, status)
  261. ! IF_NOTOK_RETURN(status=1)
  262. ! call MDF_Inquire_Dimension(hid, dimid, status, length=nflasks)
  263. ! IF_NOTOK_RETURN(status=1)
  264. ! write (gol,'("[user_output_flask_init] ",i," obs in input file.")') nflasks; call goPr
  265. ! allocate(idate_f(6,nflasks))
  266. ! allocate(mask(nflasks))
  267. ! allocate(itau_start(nflasks))
  268. ! allocate(itau_center(nflasks))
  269. ! allocate(itau_end(nflasks))
  270. ! allocate(lat(nflasks))
  271. ! allocate(lon(nflasks))
  272. ! allocate(alt(nflasks))
  273. ! allocate(sampling_strategy(nflasks))
  274. ! allocate(obspack_id(nflasks))
  275. ! call MDF_Inq_VarID(hid, "time_components", varid, status)
  276. ! IF_NOTOK_RETURN(status=1)
  277. ! call MDF_Get_Var(hid,varid,idate_f,status)
  278. ! IF_NOTOK_RETURN(status=1)
  279. ! call MDF_Inq_VarID(hid, "latitude", varid, status)
  280. ! IF_NOTOK_RETURN(status=1)
  281. ! call MDF_Get_Var(hid,varid,lat,status)
  282. ! IF_NOTOK_RETURN(status=1)
  283. ! call MDF_Inq_VarID(hid, "longitude", varid, status)
  284. ! IF_NOTOK_RETURN(status=1)
  285. ! call MDF_Get_Var(hid,varid,lon,status)
  286. ! IF_NOTOK_RETURN(status=1)
  287. ! call MDF_Inq_VarID(hid, "altitude", varid, status)
  288. ! IF_NOTOK_RETURN(status=1)
  289. ! call MDF_Get_Var(hid,varid,alt,status)
  290. ! IF_NOTOK_RETURN(status=1)
  291. ! call MDF_Inq_VarID(hid, "sampling_strategy", varid, status)
  292. ! IF_NOTOK_RETURN(status=1)
  293. ! call MDF_Get_Var(hid,varid,sampling_strategy,status)
  294. ! IF_NOTOK_RETURN(status=1)
  295. ! call MDF_Inq_VarID(hid, "obspack_id", varid, status)
  296. ! IF_NOTOK_RETURN(status=1)
  297. ! call MDF_Get_Var(hid, varid, obspack_id, status)
  298. ! IF_NOTOK_RETURN(status=1)
  299. ! call MDF_Close(hid,status)
  300. ! IF_NOTOK_RETURN(status=1)
  301. ! ! determine valid obs and subset arrays; fill flasks structure
  302. ! do iflask = 1,nflasks
  303. ! call goTranslate(obspack_id(iflask),char(0),' ',status)
  304. ! IF_NOTOK_RETURN(status=1)
  305. ! call date2tau(idate_f(:,iflask),itau_center(iflask))
  306. ! select case (sampling_strategy(iflask))
  307. ! case (1) ! 4-hour window
  308. ! itau_start(iflask) = itau_center(iflask)-2*3600
  309. ! itau_end(iflask) = itau_center(iflask)+2*3600
  310. ! case (2) ! 1-hour window
  311. ! itau_start(iflask) = itau_center(iflask)-1800
  312. ! itau_end(iflask) = itau_center(iflask)+1800
  313. ! case (3) ! 90-minute window
  314. ! itau_start(iflask) = itau_center(iflask)-2700
  315. ! itau_end(iflask) = itau_center(iflask)+2700
  316. ! case default
  317. ! write (gol,'("[user_output_flask_init] Flask with obspack_id string ",a,":")') trim(adjustl(obspack_id(iflask)))
  318. ! call goPr
  319. ! write (gol, '(" Unknown sampling strategy = ",i,".")') sampling_strategy(iflask)
  320. ! call goErr
  321. ! status=1
  322. ! return
  323. ! end select
  324. ! enddo
  325. ! if(flask_replicate_forecast) then
  326. ! mask=((itau_center .ge. itaui) .and. (itau_center .lt. itaue)) ! sample only itaui <= obs < itaue
  327. ! else
  328. ! mask=((itau_end .gt. itaui) .and. (itau_start .lt. itaue)) ! sample all obs whose sampling windows fall inside (itaui,itaue)
  329. ! endif
  330. ! nflasks=count(mask) ! note that this changes the value of nflasks
  331. ! write (gol,'("[user_output_flask_init] ",i," obs in time range ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," to ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2,".")') &
  332. ! nflasks,idatei(1:5),idatee(1:5); call goPr
  333. ! else
  334. ! nflasks = 0
  335. ! write (gol,'("[user_output_flask_init] input file ",a," does not exist: nflasks set to zero.")') trim(inFile) ; call goPr
  336. ! endif
  337. ! endif ! myid is root
  338. ! call par_barrier
  339. ! ! jump out to broadcast the final nflasks and get all PEs to allocate array
  340. ! #ifdef MPI
  341. ! call MPI_BCAST(nflasks, 1, MPI_INTEGER, root, MPI_COMM_WORLD, ierr)
  342. ! #endif
  343. ! if(nflasks .eq. 0) then
  344. ! if(allocated(idate_f)) deallocate(idate_f)
  345. ! if(allocated(mask)) deallocate(mask)
  346. ! if(allocated(itau_center)) deallocate(itau_center)
  347. ! if(allocated(itau_start)) deallocate(itau_start)
  348. ! if(allocated(itau_end)) deallocate(itau_end)
  349. ! if(allocated(lat)) deallocate(lat)
  350. ! if(allocated(lon)) deallocate(lon)
  351. ! if(allocated(alt)) deallocate(alt)
  352. ! if(allocated(sampling_strategy)) deallocate(sampling_strategy)
  353. ! if(allocated(obspack_id)) deallocate(obspack_id)
  354. ! if(allocated(flasks)) deallocate(flasks)
  355. ! status=0
  356. ! return
  357. ! endif
  358. ! if(allocated(flasks)) deallocate(flasks) ! avoid double allocation
  359. ! allocate(flasks(nflasks))
  360. ! do iflask=1,nflasks
  361. ! allocate(flasks(iflask)%mix(ntracetloc))
  362. ! allocate(flasks(iflask)%mix_grd(ntracetloc))
  363. ! flasks(iflask)%obspack_id = " "
  364. ! flasks(iflask)%mix = 0.0
  365. ! flasks(iflask)%mix_grd = 0.0
  366. ! flasks(iflask)%nsamples = 0
  367. ! flasks(iflask)%accum_weight = 0.0
  368. ! if(flask_sample_meteo) then
  369. ! flasks(iflask)%u = 0.0
  370. ! flasks(iflask)%v = 0.0
  371. ! flasks(iflask)%blh = 0.0
  372. ! flasks(iflask)%q = 0.0
  373. ! flasks(iflask)%pressure = 0.0
  374. ! flasks(iflask)%temperature = 0.0
  375. ! endif
  376. ! enddo
  377. ! ! root only does these next computations, will be broadcast later
  378. ! if(myid == root) then
  379. ! flasks%lat=pack(lat,mask)
  380. ! flasks%lon=pack(lon,mask)
  381. ! flasks%alt=pack(alt,mask)
  382. ! flasks%obspack_id=pack(obspack_id,mask)
  383. ! flasks%itau_start=pack(itau_start,mask)
  384. ! flasks%itau_center=pack(itau_center,mask)
  385. ! flasks%itau_end=pack(itau_end,mask)
  386. ! ! initialize structure with default and undefined values
  387. ! flasks%region=-1
  388. ! flasks%ifr = -1
  389. ! flasks%jfr = -1
  390. ! flasks%rif = -1e12
  391. ! flasks%rjf = -1e12
  392. ! flasks%ifn = -1
  393. ! flasks%jfn = -1
  394. ! flasks%wcx = -1e12
  395. ! flasks%wcy = -1e12
  396. ! do iflask=1,nflasks
  397. ! call tau2date(flasks(iflask)%itau_center,idatef)
  398. ! if(flask_replicate_forecast) then
  399. ! ! per user_output_flask, move obs within one second of itaui and itaue towards the middle of the
  400. ! ! simulation by one hour.
  401. ! if(abs(flasks(iflask)%itau_center-itaui).lt.1) then
  402. ! write (gol,'("[user_output_flask_init] attention: obspack_id ",a,": ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," at start; moved forward one hour.")') &
  403. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5)
  404. ! call goPr
  405. ! flasks(iflask)%itau_center = flasks(iflask)%itau_center+3600
  406. ! flasks(iflask)%itau_start = flasks(iflask)%itau_start+3600
  407. ! flasks(iflask)%itau_end = flasks(iflask)%itau_end+3600
  408. ! endif
  409. ! if(abs(flasks(iflask)%itau_center-itaue).lt.1) then
  410. ! write (gol,'("[user_output_flask_init] attention: obspack_id ",a,": ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," at end; moved back one hour.")') &
  411. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5)
  412. ! call goPr
  413. ! flasks(iflask)%itau_center=flasks(iflask)%itau_center-3600
  414. ! flasks(iflask)%itau_start = flasks(iflask)%itau_start-3600
  415. ! flasks(iflask)%itau_end = flasks(iflask)%itau_end-3600
  416. ! endif
  417. ! endif
  418. ! if(flasks(iflask)%itau_start .lt. itaui) then
  419. ! if(flask_replicate_forecast) then
  420. ! write (gol,'("[user_output_flask_init] attention: obspack_id ",a,": ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," close to start; sampling truncated.")') &
  421. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5)
  422. ! else
  423. ! write (gol,'("[user_output_flask_init] attention: obspack_id ",a,": ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," close to start; sampling continued from previous run.")') &
  424. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5)
  425. ! endif
  426. ! call goPr
  427. ! ! change itau_start so that averaging time in output file reflects actual averaging period
  428. ! flasks(iflask)%itau_start = itaui
  429. ! endif
  430. ! if(flasks(iflask)%itau_end .gt. itaue) then
  431. ! call tau2date(flasks(iflask)%itau_center,idatef)
  432. ! if(flask_replicate_forecast) then
  433. ! write (gol,'("[user_output_flask_init] attention: obspack_id ",a,": ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," close to end; sampling truncated.")') &
  434. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5)
  435. ! else
  436. ! write (gol,'("[user_output_flask_init] attention: obspack_id ",a,": ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," close to end; sampling will continue in subsequent run.")') &
  437. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5)
  438. ! endif
  439. ! call goPr
  440. ! ! change itau_end so that averaging time in output file reflects actual averaging period
  441. ! flasks(iflask)%itau_end = itaue
  442. ! endif
  443. ! ! assign region and compute indices and slopes weighting factors
  444. ! do region=1, nregions
  445. ! dyr = dy/yref(region)
  446. ! dxr = dx/xref(region)
  447. ! if ((flasks(iflask)%lon .gt. xbeg(region)) .and. &
  448. ! (flasks(iflask)%lon .le. xend(region)) .and. &
  449. ! (flasks(iflask)%lat .gt. ybeg(region)) .and. &
  450. ! (flasks(iflask)%lat .le. yend(region))) then
  451. ! ! Flask is in region
  452. ! ! Check whether an existing region assignment exists.
  453. ! ! If so, assign this region only if it is has a finer
  454. ! ! grid than existing region.
  455. ! new_region = .FALSE.
  456. ! if (flasks(iflask)%region .eq. -1) then
  457. ! flasks(iflask)%region = region
  458. ! new_region = .TRUE.
  459. ! else if(xref(region) > xref(flasks(iflask)%region)) then
  460. ! flasks(iflask)%region = region
  461. ! new_region = .TRUE.
  462. ! endif
  463. ! if(new_region) then
  464. ! ! compute indices and weighting factors
  465. ! flasks(iflask)%rif = (flasks(iflask)%lon-float(xbeg(region)))/dxr + 0.99999
  466. ! flasks(iflask)%rjf = (flasks(iflask)%lat-float(ybeg(region)))/dyr + 0.99999
  467. ! flasks(iflask)%ifr = int(flasks(iflask)%rif) ! i-index of grid cell in which observation is located
  468. ! flasks(iflask)%jfr = int(flasks(iflask)%rjf) ! j-index of grid cell in which observation is located
  469. ! ! write(gol,'(" ",i8," ",f8.2," ",f8.2," (",i3,")",f8.2," ",f8.2," (",i3,")")') \
  470. ! ! flasks(iflask)%obspack_num, \
  471. ! ! flasks(iflask)%lon,flasks(iflask)%rif,flasks(iflask)%ifr, \
  472. ! ! flasks(iflask)%lat,flasks(iflask)%rjf,flasks(iflask)%jfr
  473. ! ! call goPr
  474. ! !fraction from the center of the is-box (-0.5---+0.5)
  475. ! flasks(iflask)%rif = flasks(iflask)%rif-flasks(iflask)%ifr-0.5
  476. ! !idem js
  477. ! flasks(iflask)%rjf = flasks(iflask)%rjf-flasks(iflask)%jfr-0.5
  478. ! !the neighbour for x interpolation
  479. ! if(flasks(iflask)%rif .gt. 0) then
  480. ! flasks(iflask)%ifn = flasks(iflask)%ifr+1
  481. ! else
  482. ! flasks(iflask)%ifn = flasks(iflask)%ifr-1
  483. ! endif
  484. ! !the neighbour for y interpolation
  485. ! if(flasks(iflask)%rjf .gt. 0) then
  486. ! flasks(iflask)%jfn = flasks(iflask)%jfr+1
  487. ! else
  488. ! flasks(iflask)%jfn = flasks(iflask)%jfr-1
  489. ! endif
  490. ! ! x- / y-weighting of grid cell in which observation is located
  491. ! flasks(iflask)%wcx = (1.0-abs(flasks(iflask)%rif)) ! 1.0 ... 0.5
  492. ! flasks(iflask)%wcy = (1.0-abs(flasks(iflask)%rjf)) ! 1.0 ... 0.5
  493. ! !=================================================================
  494. ! ! if index of neighbour is exceeding range of region set
  495. ! ! neighbour = current cell (i.e. no interpolation)
  496. ! ! in case of cyclic x-boundaries take corresponding cyclic i index
  497. ! !=================================================================
  498. ! if (flasks(iflask)%jfn < 1) flasks(iflask)%jfn=1
  499. ! if (flasks(iflask)%jfn > jm(region) ) flasks(iflask)%jfn=jm(region)
  500. ! if (xcyc(region) == 0 ) then
  501. ! ! non-cyclic boundaries
  502. ! if (flasks(iflask)%ifn < 1) flasks(iflask)%ifn=1
  503. ! if (flasks(iflask)%ifn > im(region) ) flasks(iflask)%ifn=im(region)
  504. ! else
  505. ! ! cyclic x-boundaries
  506. ! if (flasks(iflask)%ifn < 1 ) flasks(iflask)%ifn=im(region)
  507. ! if (flasks(iflask)%ifn > im(region) ) flasks(iflask)%ifn=1
  508. ! endif
  509. ! endif ! if new_region
  510. ! endif ! if in region
  511. ! enddo ! regions
  512. ! enddo ! flasks
  513. ! if(flask_verbose) then
  514. ! write(gol,'("[user_output_flask_init] list of observations to be sampled during this simulation:")');call goPr
  515. ! write(gol,'(" flask region longitude (i) latitude (j) altitude date obspack_id")');call goPr
  516. ! do iflask = 1,nflasks
  517. ! if(flasks(iflask)%region > -1) then
  518. ! call tau2date(flasks(iflask)%itau_center,idatef)
  519. ! write(gol,'(" ",i5," ",a," ",f8.2," (",i3,")",f8.2," (",i3,")",f9.1," ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2,":",i2.2, " UTC ",a)') &
  520. ! iflask,trim(adjustl(region_name(flasks(iflask)%region))),flasks(iflask)%lon,flasks(iflask)%ifr,flasks(iflask)%lat, &
  521. ! flasks(iflask)%jfr,flasks(iflask)%alt,idatef,trim(adjustl(flasks(iflask)%obspack_id))
  522. ! call goPr
  523. ! endif
  524. ! enddo
  525. ! endif
  526. ! endif ! myid is root
  527. ! call par_barrier
  528. ! #ifdef MPI
  529. ! do iflask=1, nflasks
  530. ! call MPI_BCAST(flasks(iflask)%lat,1, MY_REAL , &
  531. ! root ,MPI_COMM_WORLD,ierr)
  532. ! call MPI_BCAST(flasks(iflask)%lon,1, MY_REAL , &
  533. ! root ,MPI_COMM_WORLD,ierr)
  534. ! call MPI_BCAST(flasks(iflask)%alt,1, MY_REAL , &
  535. ! root ,MPI_COMM_WORLD,ierr)
  536. ! call MPI_BCAST(flasks(iflask)%obspack_id ,100, MPI_CHARACTER, &
  537. ! root ,MPI_COMM_WORLD,ierr)
  538. ! call MPI_BCAST(flasks(iflask)%itau_start,1, MPI_INTEGER , &
  539. ! root ,MPI_COMM_WORLD,ierr)
  540. ! call MPI_BCAST(flasks(iflask)%itau_center,1, MPI_INTEGER , &
  541. ! root ,MPI_COMM_WORLD,ierr)
  542. ! call MPI_BCAST(flasks(iflask)%itau_end,1, MPI_INTEGER , &
  543. ! root ,MPI_COMM_WORLD,ierr)
  544. ! call MPI_BCAST(flasks(iflask)%region,1, MPI_INTEGER , &
  545. ! root ,MPI_COMM_WORLD,ierr)
  546. ! call MPI_BCAST(flasks(iflask)%nsamples,1, MPI_INTEGER , &
  547. ! root ,MPI_COMM_WORLD,ierr)
  548. ! call MPI_BCAST(flasks(iflask)%accum_weight,1, MY_REAL , &
  549. ! root ,MPI_COMM_WORLD,ierr)
  550. ! call MPI_BCAST(flasks(iflask)%ifr,1, MPI_INTEGER , &
  551. ! root ,MPI_COMM_WORLD,ierr)
  552. ! call MPI_BCAST(flasks(iflask)%jfr,1, MPI_INTEGER , &
  553. ! root ,MPI_COMM_WORLD,ierr)
  554. ! call MPI_BCAST(flasks(iflask)%ifn,1, MPI_INTEGER , &
  555. ! root ,MPI_COMM_WORLD,ierr)
  556. ! call MPI_BCAST(flasks(iflask)%jfn,1, MPI_INTEGER , &
  557. ! root ,MPI_COMM_WORLD,ierr)
  558. ! call MPI_BCAST(flasks(iflask)%rif,1, MY_REAL , &
  559. ! root ,MPI_COMM_WORLD,ierr)
  560. ! call MPI_BCAST(flasks(iflask)%rjf,1, MY_REAL , &
  561. ! root ,MPI_COMM_WORLD,ierr)
  562. ! call MPI_BCAST(flasks(iflask)%wcx,1, MY_REAL , &
  563. ! root ,MPI_COMM_WORLD,ierr)
  564. ! call MPI_BCAST(flasks(iflask)%wcy,1, MY_REAL , &
  565. ! root ,MPI_COMM_WORLD,ierr)
  566. ! enddo
  567. ! #endif
  568. ! call Par_Barrier
  569. ! if(allocated(idate_f)) deallocate(idate_f)
  570. ! if(allocated(mask)) deallocate(mask)
  571. ! if(allocated(itau_center)) deallocate(itau_center)
  572. ! if(allocated(itau_start)) deallocate(itau_start)
  573. ! if(allocated(itau_end)) deallocate(itau_end)
  574. ! if(allocated(lat)) deallocate(lat)
  575. ! if(allocated(lon)) deallocate(lon)
  576. ! if(allocated(alt)) deallocate(alt)
  577. ! if(allocated(sampling_strategy)) deallocate(sampling_strategy)
  578. ! if(allocated(obspack_id)) deallocate(obspack_id)
  579. status=0
  580. return
  581. end subroutine user_output_flask_init
  582. ! !BOP
  583. ! !
  584. ! ! !IROUTINE: user_output_flask_sample
  585. ! !
  586. ! ! !INPUT PARAMETERS:
  587. ! ! region - region number being sampled
  588. ! ! itau_mod - current model time
  589. ! !
  590. ! ! !OUTPUT PARAMETERS: none
  591. ! !
  592. ! ! !DESCRIPTION:
  593. ! ! - sample model at flask locations valid for this region and time
  594. ! !
  595. ! !
  596. ! !EOP
  597. subroutine user_output_flask_sample(region,itau_mod,status)
  598. ! ! This subroutine samples the model at given locations in flasks array
  599. ! use global_data, only : mass_dat, region_dat, conv_dat
  600. ! use Meteo, only : gph_dat, m_dat, humid_dat, temper_dat, pu_dat, pv_dat, phlb_dat
  601. ! use dims, only : lm,jm,ndyn,ndyn_max
  602. ! use GO, only : gol, goErr, goPr, goBug
  603. ! use chem_param, only : fscale
  604. ! use datetime, only : tau2date
  605. ! use dims, only : dy, dx, xref, yref, gtor
  606. ! use dims, only : ybeg
  607. ! use binas, only : ae
  608. ! implicit none
  609. ! input/output
  610. integer, intent(in) :: region
  611. integer(kind=8), intent(in) :: itau_mod
  612. integer, intent(inout) :: status
  613. STATUS=0
  614. ! real,dimension(:,:,:), pointer :: m,gph
  615. ! real,dimension(:,:,:,:), pointer :: rm, rxm, rym, rzm
  616. ! real,dimension(:,:), pointer :: blh ! boundary layer height [m]
  617. ! real,dimension(:,:,:), pointer :: T ! temperature
  618. ! real,dimension(:,:,:), pointer :: phlb ! pressure grid boundaries
  619. ! real,dimension(:,:,:), pointer :: pu ! mass flux x-direction [kg/s]
  620. ! real,dimension(:,:,:), pointer :: pv ! mass flux y-direction [kg/s]
  621. ! real,dimension(:,:,:), pointer :: q ! specific humidity [kg/kg]
  622. ! real,dimension(0:lm(region)) :: height
  623. ! integer :: iflask, offsetj, lfrt, lfrtn, lmr, lfrn
  624. ! integer :: l,itr
  625. ! integer :: n,i,j
  626. ! integer :: i0,i1,j0,j1,l0,l1
  627. ! integer :: ifr,jfr,lfr,ifn,jfn
  628. ! real :: alt,rlf, wcz
  629. ! real :: rmf
  630. ! real :: wcx,wcy,rif,rjf
  631. ! real :: this_weight
  632. ! logical :: dbug = .false.
  633. ! logical :: in_window
  634. ! integer, dimension(6) :: idatem
  635. ! real :: yres,xres,dyy
  636. ! real, dimension(2) :: lat
  637. ! real,dimension(2,2,2) :: u,v
  638. ! real, dimension(2) :: dxx
  639. ! ! --- const ------------------------------
  640. ! character(len=*), parameter :: rname = mname//'/user_output_flask_sample'
  641. ! this_weight=real(ndyn)/real(ndyn_max)
  642. ! ! pointers to global arrays
  643. ! m => m_dat(region)%data
  644. ! rm => mass_dat(region)%rm_t
  645. ! rxm => mass_dat(region)%rxm_t
  646. ! rym => mass_dat(region)%rym_t
  647. ! rzm => mass_dat(region)%rzm_t
  648. ! gph => gph_dat(region)%data
  649. ! blh => conv_dat(region)%blh
  650. ! t => temper_dat(region)%data
  651. ! pu => pu_dat(region)%data
  652. ! pv => pv_dat(region)%data
  653. ! phlb => phlb_dat(region)%data
  654. ! q => humid_dat(region)%data
  655. ! lmr=lm(region)
  656. ! do iflask=1,nflasks
  657. ! ! 1. Is the site in this zoom region?
  658. ! ! 2. Is model time in the sampling window?
  659. ! ! 3. Use slopes to determine tracer concentrations at the site.
  660. ! if (.not. flasks(iflask)%region .eq. region) cycle
  661. ! in_window = .false.
  662. ! if ((flask_replicate_forecast) .and. &
  663. ! (itau_mod .gt. flasks(iflask)%itau_start) .and. &
  664. ! (itau_mod .le. flasks(iflask)%itau_end)) then
  665. ! in_window = .true.
  666. ! endif
  667. ! if ((.not. flask_replicate_forecast) .and. &
  668. ! (itau_mod .ge. flasks(iflask)%itau_start) .and. &
  669. ! (itau_mod .le. flasks(iflask)%itau_end)) then
  670. ! in_window = .true.
  671. ! endif
  672. ! if(in_window) then
  673. ! dbug=.false.
  674. ! alt = flasks(iflask)%alt
  675. ! ifr = flasks(iflask)%ifr
  676. ! ifn = flasks(iflask)%ifn
  677. ! jfr = flasks(iflask)%jfr
  678. ! jfn = flasks(iflask)%jfn
  679. ! rif = flasks(iflask)%rif
  680. ! rjf = flasks(iflask)%rjf
  681. ! wcx = flasks(iflask)%wcx
  682. ! wcy = flasks(iflask)%wcy
  683. ! ! interpolate the altitude to site position...
  684. ! lfr = 1 !layer
  685. ! do l=0,lm(region)
  686. ! height(l) = &
  687. ! wcx * wcy * gph(ifr,jfr,l+1) + &
  688. ! (1.0-wcx) * wcy * gph(ifn,jfr,l+1) + &
  689. ! wcx * (1.0-wcy) * gph(ifr,jfn,l+1) + &
  690. ! (1.0-wcx) * (1.0-wcy) * gph(ifn,jfn,l+1)
  691. ! if(l==0) flasks(iflask)%surface_height = height(0)
  692. ! ! write(gol,'("height(",i2,")=",f10.2," masl.")') l,height(l);call goPr
  693. ! enddo
  694. ! do l=2,lm(region) ! selects layer , note that we start from second layer from surface
  695. ! if(height(l).gt.alt) exit
  696. ! enddo
  697. ! flasks(iflask)%lfr = l
  698. ! select case(l)
  699. ! case(0)
  700. ! if(myid==root) then
  701. ! if (.not.flasks(iflask)%below_surface_warning) then
  702. ! write (gol,'("WARNING: For flask with obspack_id ",a,":")') trim(flasks(iflask)%obspack_id)
  703. ! call goPr
  704. ! write (gol,'(" Sample altitude of ",f8.2," masl is below surface height of ",f8.2," masl.")') &
  705. ! alt,height(0)
  706. ! call goPr
  707. ! write (gol,'(" Will sample at surface.")')
  708. ! call goPr
  709. ! flasks(iflask)%below_surface_warning = .True.
  710. ! endif
  711. ! lfr = 1
  712. ! rlf = -0.5 !surface...
  713. ! endif
  714. ! case default
  715. ! lfr = l !the site layer
  716. ! ! the offset from the center of the layer (-0.5--->+0.5)
  717. ! ! (interpolation is in (m))
  718. ! rlf = (alt-height(l-1))/(height(l)-height(l-1)) - 0.5
  719. ! end select
  720. ! ! write(gol,'("sample with alt=",f10.2," we choose lfr=",i2," with height ",f10.2," masl.")') alt,lfr,height(lfr);call goPr
  721. ! !=================================
  722. ! !the neighbour for z interpolation
  723. ! !=================================
  724. ! if (rlf .gt. 0 ) then
  725. ! lfrn = lfr+1
  726. ! else
  727. ! lfrn = lfr-1
  728. ! endif
  729. ! ! z-weighting of grid cell in which observation is located
  730. ! wcz = (1.0-abs(rlf)) !.0 ... 0.5
  731. ! !=========================================================
  732. ! ! if vertical neighbor is 0 (which does not exist)
  733. ! ! take vertical layer with l=2 for EXTRApolation to ground
  734. ! !=========================================================
  735. ! IF(lfrn == 0) THEN
  736. ! lfrn=2
  737. ! wcz=1.0-rlf ! 1.0 ... 1.5
  738. ! ENDIF
  739. ! IF(lfrn == lmr+1) THEN
  740. ! !=========================================================
  741. ! ! if vertical neighbor is lmr+1 (which does not exist)
  742. ! ! -> no interpolation
  743. ! !=========================================================
  744. ! lfrn=lmr ! no interpolation
  745. ! wcz=1.0
  746. ! ENDIF
  747. ! ! sample tracers
  748. ! do itr=1,ntracetloc
  749. ! ! rm-value is obtained from rm + slopes.
  750. ! ! slope = rxm = (rm*dX/dx *deltaX/2)
  751. ! ! offsetj + itr gives the *absolute* tracer number;
  752. ! ! i.e., across all PEs.
  753. ! offsetj = sum(ntracet_ar(0:myid-1))
  754. ! ! full x,y,z slopes sampling
  755. ! rmf = ( rm(ifr,jfr,lfr,itr) + &
  756. ! 2.0*(rif*rxm(ifr,jfr,lfr,itr) + &
  757. ! rjf*rym(ifr,jfr,lfr,itr) + &
  758. ! rlf*rzm(ifr,jfr,lfr,itr)))/ &
  759. ! m(ifr,jfr,lfr)*fscale(offsetj+itr)
  760. ! flasks(iflask)%mix(itr)=flasks(iflask)%mix(itr)+this_weight*rmf !*fscale(offsetj+itr)
  761. ! ! grid-box sampling
  762. ! rmf = rm(ifr,jfr,lfr,itr)/m(ifr,jfr,lfr)*fscale(offsetj+itr)
  763. ! flasks(iflask)%mix_grd(itr)=flasks(iflask)%mix_grd(itr)+this_weight*rmf !*fscale(offsetj+itr)
  764. ! enddo
  765. ! ! sample meteo
  766. ! if((myid == root) .and. flask_sample_meteo) then
  767. ! rmf = wcx * wcy * blh(ifr,jfr) + &
  768. ! (1.0-wcx) * wcy * blh(ifn,jfr) + &
  769. ! wcx * (1.0-wcy) * blh(ifr,jfn) + &
  770. ! (1.0-wcx) * (1.0-wcy) * blh(ifn,jfn)
  771. ! flasks(iflask)%blh=flasks(iflask)%blh + this_weight*rmf
  772. ! rmf = &
  773. ! wcx * wcy * wcz * T(ifr,jfr,lfr) + &
  774. ! (1.0-wcx) * wcy * wcz * T(ifn,jfr,lfr) + &
  775. ! wcx * (1.0-wcy) * wcz * T(ifr,jfn,lfr) + &
  776. ! (1.0-wcx) * (1.0-wcy) * wcz * T(ifn,jfn,lfr) + &
  777. ! wcx * wcy * (1.0-wcz) * T(ifr,jfr,lfrn) + &
  778. ! (1.0-wcx) * wcy * (1.0-wcz) * T(ifn,jfr,lfrn) + &
  779. ! wcx * (1.0-wcy) * (1.0-wcz) * T(ifr,jfn,lfrn) + &
  780. ! (1.0-wcx) * (1.0-wcy) * (1.0-wcz) * T(ifn,jfn,lfrn)
  781. ! flasks(iflask)%temperature=flasks(iflask)%temperature + this_weight*rmf
  782. ! rmf = &
  783. ! wcx * wcy * wcz * q(ifr,jfr,lfr) + &
  784. ! (1.0-wcx) * wcy * wcz * q(ifn,jfr,lfr) + &
  785. ! wcx * (1.0-wcy) * wcz * q(ifr,jfn,lfr) + &
  786. ! (1.0-wcx) * (1.0-wcy) * wcz * q(ifn,jfn,lfr) + &
  787. ! wcx * wcy * (1.0-wcz) * q(ifr,jfr,lfrn) + &
  788. ! (1.0-wcx) * wcy * (1.0-wcz) * q(ifn,jfr,lfrn) + &
  789. ! wcx * (1.0-wcy) * (1.0-wcz) * q(ifr,jfn,lfrn) + &
  790. ! (1.0-wcx) * (1.0-wcy) * (1.0-wcz) * q(ifn,jfn,lfrn)
  791. ! flasks(iflask)%q=flasks(iflask)%q + this_weight*rmf
  792. ! yres = dy/yref(region)
  793. ! xres = dx/xref(region)
  794. ! do j = jfr,jfn
  795. ! lat(j-jfr+1) = ybeg(region) + 0.5 * yres + yres * (j-1)
  796. ! enddo
  797. ! ! Convert mass fluxes pu and pv to winds, following code
  798. ! ! in diffusion.F90. -Andy Jacobson 4 Oct 12
  799. ! dxx=0.
  800. ! u=0.
  801. ! v=0.
  802. ! lat=0.
  803. ! dxx(:) = ae * xres * gtor * cos(lat(:)*gtor)
  804. ! dyy = ae * yres * gtor
  805. ! l0=min(lfr,lfrn)
  806. ! l1=max(lfr,lfrn)
  807. ! j0=min(jfr,jfn)
  808. ! j1=max(jfr,jfn)
  809. ! i0=min(ifr,ifn)
  810. ! i1=max(ifr,ifn)
  811. ! do l=l0,l1
  812. ! do j=j0,j1
  813. ! do i=i0,i1
  814. ! u(i+1-i0,j+1-j0,l+1-l0) = dxx(j+1-j0)*(pu(i,j,l) + pu(i-1,j,l))*0.5 / m(i,j,l)
  815. ! v(i+1-i0,j+1-j0,l+1-l0) = dyy* (pv(i,j,l) + pv(i,j+1,l))*0.5 / m(i,j,l)
  816. ! enddo
  817. ! enddo
  818. ! enddo
  819. ! rmf = &
  820. ! (((0.5-rlf) * u(1,1,1) + (0.5+rlf) * u(1,1,2)) * wcx * wcy + &
  821. ! ((0.5-rlf) * u(2,1,1) + (0.5+rlf) * u(2,1,2)) * (1.0-wcx) * wcy + &
  822. ! ((0.5-rlf) * u(1,2,1) + (0.5+rlf) * u(1,2,2)) * wcx * (1.0-wcy) + &
  823. ! ((0.5-rlf) * u(2,2,1) + (0.5+rlf) * u(2,2,2)) * (1.0-wcx) * (1.0-wcy))
  824. ! flasks(iflask)%u=flasks(iflask)%u + rmf
  825. ! rmf = &
  826. ! (((0.5-rlf) * v(1,1,1) + (0.5+rlf) * v(1,1,2)) * wcx * wcy + &
  827. ! ((0.5-rlf) * v(2,1,1) + (0.5+rlf) * v(2,1,2)) * (1.0-wcx) * wcy + &
  828. ! ((0.5-rlf) * v(1,2,1) + (0.5+rlf) * v(1,2,2)) * wcx * (1.0-wcy) + &
  829. ! ((0.5-rlf) * v(2,2,1) + (0.5+rlf) * v(2,2,2)) * (1.0-wcx) * (1.0-wcy))
  830. ! flasks(iflask)%v=flasks(iflask)%v + rmf
  831. ! rmf = &
  832. ! (((0.5-rlf) * phlb(ifr,jfr,lfr) + (0.5+rlf) * phlb(ifr,jfr,lfrn)) * wcx * wcy + &
  833. ! ((0.5-rlf) * phlb(ifn,jfr,lfr) + (0.5+rlf) * phlb(ifn,jfr,lfrn)) * (1.0-wcx) * wcy + &
  834. ! ((0.5-rlf) * phlb(ifr,jfn,lfr) + (0.5+rlf) * phlb(ifr,jfn,lfrn)) * wcx * (1.0-wcy) + &
  835. ! ((0.5-rlf) * phlb(ifn,jfn,lfr) + (0.5+rlf) * phlb(ifn,jfn,lfrn)) * (1.0-wcx) * (1.0-wcy))
  836. ! flasks(iflask)%pressure=flasks(iflask)%pressure + this_weight*rmf
  837. ! endif
  838. ! flasks(iflask)%nsamples=flasks(iflask)%nsamples+1
  839. ! flasks(iflask)%accum_weight=flasks(iflask)%accum_weight+this_weight
  840. ! end if
  841. ! end do
  842. ! nullify(m)
  843. ! nullify(rm)
  844. ! nullify(rxm)
  845. ! nullify(rym)
  846. ! nullify(rzm)
  847. ! nullify(gph)
  848. ! nullify(T)
  849. ! nullify(blh)
  850. ! nullify(pu)
  851. ! nullify(pv)
  852. ! nullify(phlb)
  853. end subroutine user_output_flask_sample
  854. ! !BOP
  855. ! !
  856. ! ! !IROUTINE: user_output_flask_evaluate
  857. ! !
  858. ! ! !INPUT PARAMETERS: none
  859. ! !
  860. ! ! !OUTPUT PARAMETERS: none
  861. ! !
  862. ! ! !DESCRIPTION:
  863. ! ! - convert accumulated model mixing ratios to averages
  864. ! !
  865. ! !EOP
  866. ! subroutine user_output_flask_evaluate
  867. ! use GO, only : gol, goErr, goPr, goBug
  868. ! use datetime, only : date2tau, tau2date
  869. ! use dims, only : jm
  870. ! ! average flask samples over accumulated weight
  871. ! integer :: itrace
  872. ! integer :: iflask
  873. ! integer,dimension(6) :: idatef
  874. ! ! --- const ------------------------------
  875. ! character(len=*), parameter :: rname = mname//'/user_output_flask_evaluate'
  876. ! if (nflasks .eq. 0) then
  877. ! return
  878. ! end if
  879. ! do iflask=1,nflasks
  880. ! if((.not. flasks(iflask)%evaluated) .and. (flasks(iflask)%accum_weight .gt. 0.)) then
  881. ! do itrace=1,ntracetloc
  882. ! flasks(iflask)%mix(itrace)=flasks(iflask)%mix(itrace)/flasks(iflask)%accum_weight
  883. ! flasks(iflask)%mix_grd(itrace)=flasks(iflask)%mix_grd(itrace)/flasks(iflask)%accum_weight
  884. ! enddo
  885. ! if(flasks(iflask)%region .eq. 1 .and. ((flasks(iflask)%jfr .eq. 1) .or. (flasks(iflask)%jfr .eq. jm(1)))) then
  886. ! call tau2date(flasks(iflask)%itau_center,idatef)
  887. ! write (gol,'("[user_output_flask_evaluate] attention: obspack_id ",a," at ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," at latitude ",f6.2," degrees; rejecting slopes sampling:")') &
  888. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5),flasks(iflask)%lat
  889. ! call goPr
  890. ! do itrace=1,ntracetloc
  891. ! write (gol,'("[user_output_flask_evaluate] tracer",i4," slopes (not used): ",f6.2," ppm; gridbox (used): ",f6.2," ppm.")') &
  892. ! itrace,1.e6*flasks(iflask)%mix(itrace),1.e6*flasks(iflask)%mix_grd(itrace) ! 1.e6 assumes CO2 here.
  893. ! call goPr
  894. ! ! This is where grid sampling is substituted for slopes sampling
  895. ! flasks(iflask)%mix(itrace) = flasks(iflask)%mix_grd(itrace)
  896. ! end do
  897. ! end if
  898. ! if((myid==root) .and. flask_sample_meteo) then
  899. ! flasks(iflask)%u=flasks(iflask)%u/flasks(iflask)%accum_weight
  900. ! flasks(iflask)%v=flasks(iflask)%v/flasks(iflask)%accum_weight
  901. ! flasks(iflask)%blh=flasks(iflask)%blh/flasks(iflask)%accum_weight
  902. ! flasks(iflask)%q=flasks(iflask)%q/flasks(iflask)%accum_weight
  903. ! flasks(iflask)%pressure=flasks(iflask)%pressure/flasks(iflask)%accum_weight
  904. ! flasks(iflask)%temperature=flasks(iflask)%temperature/flasks(iflask)%accum_weight
  905. ! endif
  906. ! else
  907. ! call tau2date(flasks(iflask)%itau_center,idatef)
  908. ! write (gol,'("[user_output_flask_evaluate] attention: obspack_id ",a," at ",i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2," not evaluated; nsamples is ",4i,".")') &
  909. ! trim(adjustl(flasks(iflask)%obspack_id)), idatef(1:5),flasks(iflask)%nsamples
  910. ! call goPr
  911. ! flasks(iflask)%mix=flask_missing_value
  912. ! flasks(iflask)%mix_grd=flask_missing_value
  913. ! if((myid==root) .and. flask_sample_meteo) then
  914. ! flasks(iflask)%u=flask_missing_value
  915. ! flasks(iflask)%v=flask_missing_value
  916. ! flasks(iflask)%blh=flask_missing_value
  917. ! flasks(iflask)%q=flask_missing_value
  918. ! flasks(iflask)%pressure=flask_missing_value
  919. ! flasks(iflask)%temperature=flask_missing_value
  920. ! endif
  921. ! endif
  922. ! enddo
  923. ! flasks%evaluated = .true. ! prevents double evaluation
  924. ! end subroutine user_output_flask_evaluate
  925. ! !BOP
  926. ! !
  927. ! ! !IROUTINE: user_output_flask_done
  928. ! !
  929. ! ! !OUTPUT PARAMETERS: status integer
  930. ! !
  931. ! ! !DESCRIPTION:
  932. ! ! - call evaluate routine
  933. ! ! - gather results from other PEs
  934. ! ! - write final mixing ratios to output file
  935. ! !
  936. ! !EOP
  937. subroutine user_output_flask_done(status)
  938. ! use GO, only : gol, goErr, goPr, goBug, goTranslate
  939. ! use chem_param, only : maxtrace, names, tracer_name_len, fscale
  940. ! use dims, only : itaui, itaue, region_name
  941. ! use datetime, only : tau2date
  942. ! ! --- in/out ---------------------------------
  943. integer, intent(out) :: status
  944. status=0
  945. ! ! --- const ------------------------------
  946. ! character(len=*), parameter :: rname = mname//'/user_output_flask_done'
  947. ! ! local
  948. ! integer :: hid
  949. ! integer :: dim_obs, dim_ntracet, dim_tracer_name_len, dim_char100
  950. ! integer :: dim_region_name_len,dim_indices
  951. ! integer :: var_obspack_id, var_ntracet !, var_tracer_name_len
  952. ! integer :: var_tracer_names, var_flask
  953. ! integer :: var_nsamples, var_avetime, var_surface_height
  954. ! integer :: var_u,var_v,var_blh,var_q,var_pressure,var_temperature
  955. ! integer :: var_region_name,var_region_indices
  956. ! real, dimension(:,:), allocatable :: mix_all
  957. ! real, dimension(:,:), allocatable :: mix_local
  958. ! integer :: iflask, ipe, itrace
  959. ! integer, dimension(:), allocatable :: recvcounts
  960. ! integer, dimension(:), allocatable :: offsets
  961. ! integer, dimension(:), allocatable :: nsamples
  962. ! character(len=1024) :: attstring
  963. ! integer, dimension(tracer_name_len) :: dimvar_name_len
  964. ! integer, dimension(ntracet) :: dimvar_ntracet
  965. ! integer, dimension(6) :: idatei,idatee,idatef
  966. ! real, dimension(:), allocatable :: avetime
  967. ! call user_output_flask_evaluate
  968. ! call par_barrier
  969. ! if (nflasks .eq. 0 ) then
  970. ! return
  971. ! end if
  972. ! ! write results to output file
  973. ! do iflask = 1,tracer_name_len
  974. ! dimvar_name_len(iflask)=iflask
  975. ! enddo
  976. ! do iflask = 1,ntracet
  977. ! dimvar_ntracet(iflask)=iflask
  978. ! enddo
  979. ! ! recall that myid and root are published from module ParTools, and do
  980. ! ! not depend on the MPI macro being defined.
  981. ! if (myid == root ) then
  982. ! ! new file:
  983. ! call MDF_Create(trim(outFile), MDF_NETCDF, MDF_REPLACE, hid, status )
  984. ! IF_NOTOK_RETURN(status=1)
  985. ! ! define dimensions:
  986. ! call MDF_Def_Dim(hid, 'obs', MDF_UNLIMITED, dim_obs, status )
  987. ! IF_NOTOK_RETURN(status=1)
  988. ! call MDF_Def_Dim(hid, 'tracer', ntracet, dim_ntracet, status )
  989. ! IF_NOTOK_RETURN(status=1)
  990. ! call MDF_Def_Dim(hid, 'tracer_name_len', tracer_name_len, dim_tracer_name_len, status )
  991. ! IF_NOTOK_RETURN(status=1)
  992. ! call MDF_Def_Dim( hid, "char100", 100, dim_char100, status )
  993. ! IF_NOTOK_RETURN(status=1)
  994. ! ! in dims_grid.F90, 10 chars is the region name length
  995. ! call MDF_Def_Dim(hid, 'region_name_len', 10, dim_region_name_len, status )
  996. ! IF_NOTOK_RETURN(status=1)
  997. ! call MDF_Def_Dim(hid, 'grid_indices', 3, dim_indices, status )
  998. ! IF_NOTOK_RETURN(status=1)
  999. ! ! dimension variables:
  1000. ! call MDF_Def_Var(hid, 'obspack_id', MDF_CHAR, (/dim_char100, dim_obs/), var_obspack_id, status )
  1001. ! IF_NOTOK_RETURN(status=1)
  1002. ! ! call MDF_Def_Var(hid, 'tracer', MDF_INT, (/dim_ntracet/), var_ntracet, status )
  1003. ! ! IF_NOTOK_RETURN(status=1)
  1004. ! ! call MDF_Def_Var(hid, 'tracer_name_len', MDF_INT, (/dim_tracer_name_len/), var_tracer_name_len, status )
  1005. ! ! IF_NOTOK_RETURN(status=1)
  1006. ! ! variables:
  1007. ! call MDF_Def_Var(hid, 'flask', MDF_FLOAT, (/dim_ntracet,dim_obs/), var_flask, status )
  1008. ! IF_NOTOK_RETURN(status=1)
  1009. ! call MDF_Def_Var(hid, 'nsamples', MDF_INT, (/dim_obs/), var_nsamples, status )
  1010. ! IF_NOTOK_RETURN(status=1)
  1011. ! call MDF_Def_Var(hid, 'tracer_names', MDF_CHAR, (/dim_tracer_name_len,dim_ntracet/), var_tracer_names, status )
  1012. ! IF_NOTOK_RETURN(status=1)
  1013. ! call MDF_Def_Var(hid, 'averaging_time', MDF_INT, (/dim_obs/), var_avetime, status )
  1014. ! IF_NOTOK_RETURN(status=1)
  1015. ! call MDF_Def_Var(hid, 'surface_height', MDF_FLOAT, (/dim_obs/), var_surface_height, status )
  1016. ! IF_NOTOK_RETURN(status=1)
  1017. ! call MDF_Def_Var(hid, 'region_name', MDF_CHAR, (/dim_region_name_len,dim_obs/), var_region_name, status )
  1018. ! IF_NOTOK_RETURN(status=1)
  1019. ! call MDF_Def_Var(hid, 'region_indices', MDF_INT, (/dim_indices,dim_obs/), var_region_indices, status )
  1020. ! IF_NOTOK_RETURN(status=1)
  1021. ! if(flask_sample_meteo) then
  1022. ! call MDF_Def_Var( hid, 'u', MDF_FLOAT, (/dim_obs/), var_u, status )
  1023. ! IF_NOTOK_RETURN(status=1)
  1024. ! call MDF_Put_Att(hid, var_u,"long_name",values="x-wind",status=status)
  1025. ! IF_NOTOK_RETURN(status=1)
  1026. ! call MDF_Put_Att(hid, var_u,"units",values="m s^-1",status=status)
  1027. ! IF_NOTOK_RETURN(status=1)
  1028. ! call MDF_Put_Att(hid, var_u,"_FillValue",values=flask_missing_value,status=status)
  1029. ! IF_NOTOK_RETURN(status=1)
  1030. ! call MDF_Def_Var( hid, 'v', MDF_FLOAT, (/dim_obs/), var_v, status )
  1031. ! IF_NOTOK_RETURN(status=1)
  1032. ! call MDF_Put_Att(hid, var_v,"long_name",values="y-wind",status=status)
  1033. ! IF_NOTOK_RETURN(status=1)
  1034. ! call MDF_Put_Att(hid, var_v,"units",values="m s^-1",status=status)
  1035. ! IF_NOTOK_RETURN(status=1)
  1036. ! call MDF_Put_Att(hid, var_v,"_FillValue",values=flask_missing_value,status=status)
  1037. ! IF_NOTOK_RETURN(status=1)
  1038. ! call MDF_Def_Var( hid, 'blh', MDF_FLOAT, (/dim_obs/), var_blh, status )
  1039. ! IF_NOTOK_RETURN(status=1)
  1040. ! call MDF_Put_Att(hid, var_blh,"long_name",values="atmosphere_boundary_layer_thickness",status=status)
  1041. ! IF_NOTOK_RETURN(status=1)
  1042. ! call MDF_Put_Att(hid, var_blh,"units",values="m",status=status)
  1043. ! IF_NOTOK_RETURN(status=1)
  1044. ! call MDF_Put_Att(hid, var_blh,"_FillValue",values=flask_missing_value,status=status)
  1045. ! IF_NOTOK_RETURN(status=1)
  1046. ! call MDF_Def_Var( hid, 'q', MDF_FLOAT, (/dim_obs/), var_q, status )
  1047. ! IF_NOTOK_RETURN(status=1)
  1048. ! call MDF_Put_Att(hid, var_q,"long_name",values="mass_fraction_of_water_in_air",status=status)
  1049. ! IF_NOTOK_RETURN(status=1)
  1050. ! call MDF_Put_Att(hid, var_q,"units",values="kg water (kg air)^-1",status=status)
  1051. ! IF_NOTOK_RETURN(status=1)
  1052. ! call MDF_Put_Att(hid, var_q,"_FillValue",values=flask_missing_value,status=status)
  1053. ! IF_NOTOK_RETURN(status=1)
  1054. ! call MDF_Def_Var( hid, 'pressure', MDF_FLOAT, (/dim_obs/), var_pressure, status )
  1055. ! IF_NOTOK_RETURN(status=1)
  1056. ! call MDF_Put_Att(hid, var_pressure,"long_name",values="air_pressure",status=status)
  1057. ! IF_NOTOK_RETURN(status=1)
  1058. ! call MDF_Put_Att(hid, var_pressure,"units",values="Pa",status=status)
  1059. ! IF_NOTOK_RETURN(status=1)
  1060. ! call MDF_Put_Att(hid, var_pressure,"_FillValue",values=flask_missing_value,status=status)
  1061. ! IF_NOTOK_RETURN(status=1)
  1062. ! call MDF_Def_Var( hid, 'temperature', MDF_FLOAT, (/dim_obs/), var_temperature, status )
  1063. ! IF_NOTOK_RETURN(status=1)
  1064. ! call MDF_Put_Att(hid, var_temperature,"long_name",values="air_temperature",status=status)
  1065. ! IF_NOTOK_RETURN(status=1)
  1066. ! call MDF_Put_Att(hid, var_temperature,"units",values="K",status=status)
  1067. ! IF_NOTOK_RETURN(status=1)
  1068. ! call MDF_Put_Att(hid, var_temperature,"_FillValue",values=flask_missing_value,status=status)
  1069. ! IF_NOTOK_RETURN(status=1)
  1070. ! endif
  1071. ! ! add attributes
  1072. ! call MDF_Put_Att(hid, var_flask,"long_name",values="mole_fraction_of_trace_gas_in_air",status=status)
  1073. ! IF_NOTOK_RETURN(status=1)
  1074. ! call MDF_Put_Att(hid, var_flask,"units",values="mol tracer (mol air)^-1",status=status)
  1075. ! IF_NOTOK_RETURN(status=1)
  1076. ! call MDF_Put_Att(hid, var_flask,"_FillValue",values=flask_missing_value,status=status)
  1077. ! IF_NOTOK_RETURN(status=1)
  1078. ! call MDF_Put_Att(hid, var_obspack_id,"comment",values="Use this identifier to match observations with data from input file.",status=status)
  1079. ! IF_NOTOK_RETURN(status=1)
  1080. ! call MDF_Put_Att(hid, var_avetime,"units",values="seconds",status=status)
  1081. ! IF_NOTOK_RETURN(status=1)
  1082. ! call MDF_Put_Att(hid, var_avetime,"comment",values="Amount of model time over which this sample is averaged.",status=status)
  1083. ! IF_NOTOK_RETURN(status=1)
  1084. ! call MDF_Put_Att(hid, var_nsamples,"comment",values="Number of discrete samples in flask average.",status=status)
  1085. ! IF_NOTOK_RETURN(status=1)
  1086. ! call MDF_Put_Att(hid, var_surface_height,"comment",values="Height of the TM5 surface in the flask gridbox",status=status)
  1087. ! IF_NOTOK_RETURN(status=1)
  1088. ! call MDF_Put_Att(hid, var_surface_height,"units",values="meter",status=status)
  1089. ! IF_NOTOK_RETURN(status=1)
  1090. ! call MDF_Put_Att(hid, var_region_name,"comment",values="Name of TM5 zoom region containing sample.",status=status)
  1091. ! IF_NOTOK_RETURN(status=1)
  1092. ! call MDF_Put_Att(hid, var_region_name,"units",values="unitless",status=status)
  1093. ! IF_NOTOK_RETURN(status=1)
  1094. ! call MDF_Put_Att(hid, var_region_indices,"comment",values="Zonal, meridional, and level indices within the model region for grid cell containing sample.",status=status)
  1095. ! IF_NOTOK_RETURN(status=1)
  1096. ! call MDF_Put_Att(hid, var_region_indices,"units",values="unitless",status=status)
  1097. ! IF_NOTOK_RETURN(status=1)
  1098. ! call MDF_Put_Att(hid, MDF_GLOBAL,"input_file",values=inFile,status=status)
  1099. ! IF_NOTOK_RETURN(status=1)
  1100. ! call tau2date(itaui,idatei)
  1101. ! call tau2date(itaue,idatee)
  1102. ! write(attstring,'(i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2,":",i2.2, " UTC")') idatei
  1103. ! call MDF_Put_Att(hid, MDF_GLOBAL,"model_start_date",values=trim(attstring),status=status)
  1104. ! IF_NOTOK_RETURN(status=1)
  1105. ! write(attstring,'(i4.4,"/",i2.2,"/",i2.2," ",i2.2,":",i2.2,":",i2.2, " UTC")') idatee
  1106. ! call MDF_Put_Att(hid, MDF_GLOBAL,"model_end_date",values=trim(attstring),status=status)
  1107. ! IF_NOTOK_RETURN(status=1)
  1108. ! ! finished definition:
  1109. ! call MDF_EndDef(hid, status )
  1110. ! IF_NOTOK_RETURN(status=1)
  1111. ! ! mix_all is root's array to receive all data. Note that
  1112. ! ! ntracet is ntracetloc * npes, so this is implicitly
  1113. ! ! dimensioned by no. PEs. To be completely general, the output
  1114. ! ! tracer array could be 3-dimensional: no. types of tracers *
  1115. ! ! no. flasks * no. ensemble members. In practice, however,
  1116. ! ! we're only interested in two of those dimensions. For inverse
  1117. ! ! runs, we have ensembles of total CO2; for forward runs we
  1118. ! ! instead have one version each of CO2 components (e.g. CO2 due
  1119. ! ! to air-sea exchange). Both of these cases are 2-D, ntracet
  1120. ! ! by nflasks. If you want ensembles of the components, this
  1121. ! ! code will still work, but the two dimensions (components and
  1122. ! ! ensemble) will need to be unwrapped by hand by code reading
  1123. ! ! the flask output file.
  1124. ! allocate(mix_all(ntracet,nflasks))
  1125. ! ! N.B. every PE has a flasks structure, and for nsamples,
  1126. ! ! itaui, and itaue, root's values should be the same as
  1127. ! ! all other PEs, so there's no need for MPI communication.
  1128. ! allocate(avetime(nflasks))
  1129. ! avetime=flasks(:)%itau_end-flasks(:)%itau_start
  1130. ! allocate(nsamples(nflasks))
  1131. ! nsamples=flasks(:)%nsamples
  1132. ! endif ! root only
  1133. ! allocate(mix_local(ntracetloc,nflasks)) ! all PEs including root allocate a send buffer...
  1134. ! ! ...and fill it
  1135. ! do iflask=1,nflasks
  1136. ! mix_local(:,iflask)=flasks(iflask)%mix
  1137. ! enddo
  1138. ! #ifdef MPI
  1139. ! if (myid .eq. root) then
  1140. ! allocate(recvcounts(npes))
  1141. ! allocate(offsets(npes))
  1142. ! offsets(1)=0
  1143. ! do ipe = 1, npes
  1144. ! recvcounts(ipe)=ntracet_ar(ipe-1)
  1145. ! if (ipe .gt. 1) then
  1146. ! offsets(ipe)=sum(recvcounts(1:(ipe-1)))
  1147. ! endif
  1148. ! enddo
  1149. ! else
  1150. ! ! ifort's "-check all" complains severely if the mix_all, offsets, and recvcounts buffers
  1151. ! ! are unallocated, despite the MPI spec's insistence that these buffers are only used
  1152. ! ! by the root process.
  1153. ! allocate(mix_all(1,1))
  1154. ! allocate(recvcounts(1))
  1155. ! allocate(offsets(1))
  1156. ! endif
  1157. ! do iflask=1,nflasks
  1158. ! ! MPI_GATHERV is how root gets all the mix_local values from other
  1159. ! ! PEs. Note that they are in rank-order, i.e. sorted by the myid
  1160. ! ! value, and they include the values from the root process also.
  1161. ! !
  1162. ! ! Note that we use MPI_GATHERV (v for variable data amount for each
  1163. ! ! node) because PEs can have differing numbers of tracers.
  1164. ! call MPI_GATHERV(&
  1165. ! mix_local(:,iflask), ntracetloc, MY_REAL, &
  1166. ! mix_all(:,iflask), recvcounts, offsets, MY_REAL, &
  1167. ! root, MPI_COMM_WORLD, ierr)
  1168. ! if (.not. ierr .eq. MPI_SUCCESS) then
  1169. ! endif
  1170. ! enddo
  1171. ! #else
  1172. ! ! not MPI: root needs to copy its mix_local values to mix_all
  1173. ! mix_all = mix_local
  1174. ! #endif
  1175. ! if (myid == root ) then
  1176. ! do iflask=1,nflasks
  1177. ! call goTranslate( flasks(iflask)%obspack_id,' ',char(0),status)
  1178. ! IF_NOTOK_RETURN(status=1)
  1179. ! enddo
  1180. ! call MDF_Put_Var(hid, var_obspack_id, (/(flasks(iflask)%obspack_id, iflask=1, nflasks)/), status)
  1181. ! IF_NOTOK_RETURN(status=1)
  1182. ! ! call MDF_Put_Var(hid, var_ntracet, dimvar_ntracet, status)
  1183. ! ! IF_NOTOK_RETURN(status=1)
  1184. ! ! call MDF_Put_Var(hid, var_tracer_name_len, dimvar_name_len, status)
  1185. ! ! IF_NOTOK_RETURN(status=1)
  1186. ! call MDF_Put_Var(hid, var_flask, mix_all, status)
  1187. ! IF_NOTOK_RETURN(status=1)
  1188. ! call MDF_Put_Var(hid, var_nsamples, nsamples, status)
  1189. ! IF_NOTOK_RETURN(status=1)
  1190. ! call MDF_Put_Var(hid, var_avetime, avetime, status)
  1191. ! IF_NOTOK_RETURN(status=1)
  1192. ! call MDF_Put_Var(hid, var_surface_height, flasks%surface_height, status)
  1193. ! IF_NOTOK_RETURN(status=1)
  1194. ! call MDF_Put_Var(hid, var_region_indices, flasks%ifr, status,start=(/1,1/),count=(/1,nflasks/))
  1195. ! IF_NOTOK_RETURN(status=1)
  1196. ! call MDF_Put_Var(hid, var_region_indices, flasks%jfr, status,start=(/2,1/),count=(/1,nflasks/))
  1197. ! IF_NOTOK_RETURN(status=1)
  1198. ! call MDF_Put_Var(hid, var_region_indices, flasks%lfr, status,start=(/3,1/),count=(/1,nflasks/))
  1199. ! IF_NOTOK_RETURN(status=1)
  1200. ! do iflask=1,nflasks
  1201. ! call MDF_Put_Var(hid, var_region_name, region_name(flasks(iflask)%region),status,start=(/1,iflask/),count=(/10,1/))
  1202. ! IF_NOTOK_RETURN(status=1)
  1203. ! enddo
  1204. ! call MDF_Put_Var(hid, var_tracer_names, names(1:ntracet), status)
  1205. ! IF_NOTOK_RETURN(status=1)
  1206. ! if(flask_sample_meteo) then
  1207. ! call MDF_Put_Var(hid, var_u, flasks%u, status )
  1208. ! IF_NOTOK_RETURN(status=1)
  1209. ! call MDF_Put_Var(hid, var_v, flasks%v, status )
  1210. ! IF_NOTOK_RETURN(status=1)
  1211. ! call MDF_Put_Var(hid, var_blh, flasks%blh, status )
  1212. ! IF_NOTOK_RETURN(status=1)
  1213. ! call MDF_Put_Var(hid, var_q, flasks%q, status )
  1214. ! IF_NOTOK_RETURN(status=1)
  1215. ! call MDF_Put_Var(hid, var_pressure, flasks%pressure, status )
  1216. ! IF_NOTOK_RETURN(status=1)
  1217. ! call MDF_Put_Var(hid, var_temperature, flasks%temperature, status )
  1218. ! IF_NOTOK_RETURN(status=1)
  1219. ! endif
  1220. ! ! close file:
  1221. ! call MDF_Close(hid, status )
  1222. ! IF_NOTOK_RETURN(status=1)
  1223. ! endif
  1224. ! write (gol,'("[user_output_flask_done] Deallocating arrays and closing output file.")'); call goPr
  1225. ! do iflask = 1,nflasks
  1226. ! if(allocated(flasks(iflask)%mix)) then
  1227. ! deallocate(flasks(iflask)%mix)
  1228. ! endif
  1229. ! if(allocated(flasks(iflask)%mix_grd)) then
  1230. ! deallocate(flasks(iflask)%mix_grd)
  1231. ! endif
  1232. ! enddo
  1233. ! if(allocated(flasks)) then
  1234. ! deallocate(flasks)
  1235. ! endif
  1236. ! if(allocated(mix_local)) then
  1237. ! deallocate(mix_local)
  1238. ! endif
  1239. ! if(allocated(mix_all)) then
  1240. ! deallocate(mix_all)
  1241. ! endif
  1242. ! if(allocated(avetime)) then
  1243. ! deallocate(avetime)
  1244. ! endif
  1245. ! if(allocated(nsamples)) then
  1246. ! deallocate(nsamples)
  1247. ! endif
  1248. ! if(allocated(recvcounts)) then
  1249. ! deallocate(recvcounts)
  1250. ! endif
  1251. ! if(allocated(offsets)) then
  1252. ! deallocate(offsets)
  1253. ! endif
  1254. end subroutine user_output_flask_done
  1255. end module user_output_flask