m_point2nc.f90 11 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393
  1. # 0 "<stdin>"
  2. # 0 "<built-in>"
  3. # 0 "<command-line>"
  4. # 1 "/usr/include/stdc-predef.h" 1 3 4
  5. # 17 "/usr/include/stdc-predef.h" 3 4
  6. # 2 "<command-line>" 2
  7. # 1 "<stdin>"
  8. # 10 "<stdin>"
  9. ! File: m_point2nc.F90
  10. !
  11. ! Created: 6 July 2010
  12. !
  13. ! Last modified: 6/7/2010
  14. !
  15. ! Author: Pavel Sakov
  16. ! NERSC
  17. !
  18. ! Purpose: Output of assimilation related information for selected points
  19. ! to files in NetCDF format, 1 file per point.
  20. !
  21. ! Description: This module reads a list of points from a file "point2nc.txt"
  22. ! in the working NetCDF directory. It then dumps the
  23. ! assimilation related information for these points in NetCDF
  24. ! format to files named enkf_III,JJJ.nc, where III and JJJ - i
  25. ! and j grid coordinates.
  26. !
  27. ! Modifications: PS 4/8/2010 "point2nc.txt" now allows comments etc. E.g. put
  28. ! "#" in front of an entry to comment it out.
  29. module m_point2nc
  30. use m_parameters
  31. implicit none
  32. integer, private :: FID = 31
  33. integer, parameter, private :: STRLEN = 512
  34. public p2nc_init
  35. public p2nc_testthiscell
  36. public p2nc_writeobs
  37. public p2nc_storeforecast
  38. public p2nc_writeforecast
  39. integer, private :: npoints
  40. integer, allocatable, dimension(:), private :: icoords, jcoords
  41. real(4), allocatable, dimension(:, :, :) :: forecast
  42. contains
  43. ! Initialise the point output.
  44. !
  45. subroutine p2nc_init()
  46. use qmpi
  47. character(STRLEN) :: line
  48. integer :: iostatus
  49. integer :: i, j, n
  50. npoints = 0
  51. open(FID, file = trim(POINTFNAME), status = 'old', iostat = iostatus)
  52. if (iostatus /= 0) then
  53. if (master) then
  54. print *, 'WARNING: could not open "', trim(POINTFNAME), '" for reading'
  55. print *, ' no point output will be performed'
  56. end if
  57. return
  58. end if
  59. do while (.true.)
  60. read(FID, '(a)', iostat = iostatus) line
  61. if (iostatus == 0) then
  62. read(line, *, iostat = iostatus) i, j
  63. if (iostatus == 0) then
  64. npoints = npoints + 1
  65. end if
  66. else
  67. exit
  68. end if
  69. end do
  70. close(FID)
  71. if (master) then
  72. print '(a, i3, a)', ' p2nc: ', npoints, ' points specified'
  73. end if
  74. allocate(icoords(npoints), jcoords(npoints))
  75. open(FID, file = trim(POINTFNAME), status = 'old', iostat = iostatus)
  76. if (iostatus /= 0) then
  77. print *, 'ERROR: point2nc: I/O problem'
  78. stop
  79. end if
  80. n = 0
  81. do while (n < npoints)
  82. read(FID, '(a)', iostat = iostatus) line
  83. if (iostatus == 0) then
  84. read(line, *, iostat = iostatus) i, j
  85. if (iostatus == 0) then
  86. n = n + 1
  87. icoords(n) = i
  88. jcoords(n) = j
  89. if (master) then
  90. print '(a, i3, a, i4, a, i4)', ' point', n, ': i =', i, ', j =', j
  91. end if
  92. end if
  93. end if
  94. end do
  95. close(FID)
  96. if (master) then
  97. print *
  98. end if
  99. end subroutine p2nc_init
  100. ! Test if the output is requested for the point (i, j)
  101. !
  102. function p2nc_testthiscell(i, j)
  103. logical :: p2nc_testthiscell
  104. integer, intent(in) :: i, j
  105. integer :: p
  106. p2nc_testthiscell = .false.
  107. do p = 1, npoints
  108. if (i == icoords(p) .and. j == jcoords(p)) then
  109. p2nc_testthiscell = .true.
  110. return
  111. end if
  112. end do
  113. end function p2nc_testthiscell
  114. ! Write the assimilation parameters (local observations and the X5 matrices)
  115. ! to the point output files.
  116. !
  117. subroutine p2nc_writeobs(i, j, nlobs, nens, X5, lon, lat, depth, rfactor,&
  118. ids, lobs, Hx, S, ss, lfactors)
  119. use mod_measurement
  120. use m_obs
  121. use nfw_mod
  122. integer, intent(in) :: i, j, nlobs, nens
  123. real, intent(in) :: X5(nens, nens)
  124. real, intent(in) :: lon(1), lat(1), depth(1)
  125. real, intent(in), optional :: rfactor(1)
  126. integer, intent(in), optional :: ids(nlobs)
  127. type(measurement), intent(in), optional :: lobs(nlobs)
  128. real, intent(in), optional :: Hx(nlobs)
  129. real, intent(in), optional :: S(nlobs, nens)
  130. real, intent(in), optional :: ss(nlobs), lfactors(nlobs)
  131. character(STRLEN) :: fname
  132. character(STRLEN) :: typename
  133. integer :: ncid
  134. integer :: dids(2)
  135. integer :: vid_ids, vid_lon, vid_lat, vid_val, vid_var, vid_hx, vid_s, vid_x5
  136. integer :: vid_a1, vid_a2, vid_a3, vid_a4, vid_otype, vid_ss, vid_lfactors
  137. integer :: otype(nlobs)
  138. integer :: o, ot
  139. write(fname, '(a, i0.3, ",", i0.3, ".nc")') 'enkf_', i, j
  140. call nfw_create(fname, nf_write, ncid)
  141. call nfw_def_dim(fname, ncid, 'p', nlobs, dids(2))
  142. call nfw_def_dim(fname, ncid, 'm', nens, dids(1))
  143. if (nlobs > 0) then
  144. call nfw_def_var(fname, ncid, 'obs_ids', nf_int, 1, dids(2), vid_ids)
  145. call nfw_def_var(fname, ncid, 'Hx', nf_double, 1, dids(2), vid_hx)
  146. call nfw_def_var(fname, ncid, 'lon', nf_double, 1, dids(2), vid_lon)
  147. call nfw_def_var(fname, ncid, 'lat', nf_double, 1, dids(2), vid_lat)
  148. call nfw_def_var(fname, ncid, 'obs_val', nf_double, 1, dids(2), vid_val)
  149. call nfw_def_var(fname, ncid, 'obs_var', nf_double, 1, dids(2), vid_var)
  150. call nfw_def_var(fname, ncid, 'a1', nf_double, 1, dids(2), vid_a1)
  151. call nfw_def_var(fname, ncid, 'a2', nf_double, 1, dids(2), vid_a2)
  152. call nfw_def_var(fname, ncid, 'a3', nf_double, 1, dids(2), vid_a3)
  153. call nfw_def_var(fname, ncid, 'a4', nf_double, 1, dids(2), vid_a4)
  154. call nfw_def_var(fname, ncid, 'obs_type', nf_int, 1, dids(2), vid_otype)
  155. call nfw_def_var(fname, ncid, 'S', nf_double, 2, dids, vid_s)
  156. call nfw_def_var(fname, ncid, 's', nf_double, 1, dids(2), vid_ss)
  157. call nfw_def_var(fname, ncid, 'lfactors', nf_double, 1, dids(2), vid_lfactors)
  158. end if
  159. dids(2) = dids(1)
  160. call nfw_def_var(fname, ncid, 'X5', nf_double, 2, dids, vid_x5)
  161. call nfw_put_att_double(fname, ncid, nf_global, 'lon', nf_double, 1, lon)
  162. call nfw_put_att_double(fname, ncid, nf_global, 'lat', nf_double, 1, lat)
  163. call nfw_put_att_double(fname, ncid, nf_global, 'depth', nf_double, 1, depth)
  164. call nfw_put_att_double(fname, ncid, nf_global, 'rfactor', nf_double, 1, rfactor)
  165. do ot = 1, nuobs
  166. write(typename, '(a, i1)') 'obstype', ot
  167. call nfw_put_att_text(fname, ncid, nf_global, typename, len_trim(unique_obs(ot)), trim(unique_obs(ot)))
  168. end do
  169. call nfw_enddef(fname, ncid)
  170. if (nlobs > 0) then
  171. call nfw_put_var_double(fname, ncid, vid_hx, Hx)
  172. call nfw_put_var_int(fname, ncid, vid_ids, ids)
  173. call nfw_put_var_double(fname, ncid, vid_lon, lobs % lon)
  174. call nfw_put_var_double(fname, ncid, vid_lat, lobs % lat)
  175. call nfw_put_var_double(fname, ncid, vid_val, lobs % d)
  176. call nfw_put_var_double(fname, ncid, vid_var, lobs % var)
  177. call nfw_put_var_double(fname, ncid, vid_a1, lobs % a1)
  178. call nfw_put_var_double(fname, ncid, vid_a2, lobs % a2)
  179. call nfw_put_var_double(fname, ncid, vid_a3, lobs % a3)
  180. call nfw_put_var_double(fname, ncid, vid_a4, lobs % a4)
  181. otype = 0
  182. do o = 1, nlobs
  183. do ot = 1, nuobs
  184. if (trim(lobs(o) % id) == trim(unique_obs(ot))) then
  185. otype(o) = ot
  186. end if
  187. end do
  188. end do
  189. call nfw_put_var_int(fname, ncid, vid_otype, otype)
  190. call nfw_put_var_double(fname, ncid, vid_s, transpose(S))
  191. call nfw_put_var_double(fname, ncid, vid_ss, ss)
  192. call nfw_put_var_double(fname, ncid, vid_lfactors, lfactors)
  193. end if
  194. call nfw_put_var_double(fname, ncid, vid_x5, transpose(X5))
  195. call nfw_close(fname, ncid)
  196. end subroutine p2nc_writeobs
  197. ! Store the values of the forecast field No. `fid' in each output point to
  198. ! the variable `forecast'.
  199. !
  200. subroutine p2nc_storeforecast(ni, nj, nrens, nfields, fid, field)
  201. integer, intent(in) :: ni, nj ! size of grid
  202. integer, intent(in) :: nrens
  203. integer, intent(in) :: nfields
  204. integer, intent(in) :: fid
  205. real(4), dimension(ni * nj, nrens), intent(in) :: field
  206. integer :: n
  207. if (npoints == 0) then
  208. return
  209. end if
  210. if (.not. allocated(forecast)) then
  211. allocate(forecast(nrens, npoints, nfields))
  212. end if
  213. do n = 1, npoints
  214. forecast(:, n, fid) = field((jcoords(n) - 1) * ni + icoords(n), :)
  215. end do
  216. end subroutine p2nc_storeforecast
  217. ! This procedure consolidates all forecast fields for each output point
  218. ! together in the variable `forecast' on the master node, and then writes
  219. ! them to the appropriate NetCDF files.
  220. !
  221. subroutine p2nc_writeforecast
  222. use qmpi
  223. use distribute
  224. use nfw_mod
  225. use mod_analysisfields
  226. implicit none
  227. character(STRLEN) :: fname
  228. integer :: p, k, nf
  229. character(8) :: varname
  230. integer kstart
  231. integer ncid, dids(2), varid, nf2
  232. if (.not. master) then
  233. call send(forecast(:, :, my_first_iteration : my_last_iteration), 0, 0)
  234. return ! leave writing to master
  235. else
  236. do p = 2, qmpi_num_proc ! here p is the MPI node ID
  237. call receive(forecast(:, :, first_iteration(p) : last_iteration(p)), p - 1, 0)
  238. end do
  239. end if
  240. ! only master keeps working here
  241. !
  242. do p = 1, npoints
  243. write(fname, '(a, i0.3, ",", i0.3, ".nc")') 'enkf_', icoords(p), jcoords(p)
  244. call nfw_open(fname, nf_write, ncid)
  245. call nfw_redef(fname, ncid)
  246. call nfw_inq_dimid(fname, ncid, 'm', dids(1))
  247. call nfw_enddef(fname, ncid)
  248. kstart = -1
  249. do k = 1, numfields
  250. if (kstart == -1) then
  251. kstart = k
  252. varname = fieldnames(k)
  253. end if
  254. ! check if there are more fields for this variable
  255. !
  256. if (k < numfields .and. fieldnames(k + 1) == varname) then
  257. cycle
  258. end if
  259. ! this is the last field for this variable - write the variable
  260. !
  261. nf = k - kstart + 1
  262. call nfw_redef(fname, ncid)
  263. if (nf == 1) then
  264. call nfw_def_var(fname, ncid, trim(varname), nf_float, 1, dids(1), varid)
  265. else
  266. if (.not. nfw_dim_exists(ncid, 'k')) then
  267. call nfw_def_dim(fname, ncid, 'k', nf, dids(2))
  268. else
  269. call nfw_inq_dimid(fname, ncid, 'k', dids(2))
  270. call nfw_inq_dimlen(fname, ncid, dids(2), nf2)
  271. if (nf /= nf2) then
  272. print *, 'ERROR: p2nc_writeforecast(): varname = "', trim(varname),&
  273. '", # levels = ', nf, '# levels in "', trim(fname), '" =', nf2
  274. print *, 'ERROR: p2nc_writeforecast(): returning'
  275. end if
  276. end if
  277. call nfw_def_var(fname, ncid, trim(varname), nf_float, 2, dids, varid)
  278. end if
  279. call nfw_enddef(fname, ncid)
  280. call nfw_put_var_real(fname, ncid, varid, forecast(:, p, kstart : kstart + nf - 1))
  281. kstart = -1
  282. end do
  283. call nfw_close(fname, ncid)
  284. end do
  285. end subroutine p2nc_writeforecast
  286. end module m_point2nc