m_Generate_element_Si.F90 14 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420
  1. module m_Generate_element_Si
  2. implicit none
  3. public Generate_element_Si
  4. public get_S
  5. integer, parameter, private :: NONE = 0
  6. integer, parameter, private :: TEMPERATURE = 1
  7. integer, parameter, private :: SALINITY = 2
  8. real, parameter, private :: TEM_MIN = -2.5
  9. real, parameter, private :: TEM_MAX = 35.0
  10. real, parameter, private :: SAL_MIN = 5.0
  11. real, parameter, private :: SAL_MAX = 41.0
  12. logical, parameter, private :: VERT_INTERP_GRID = .true.
  13. contains
  14. subroutine Generate_element_Si(S, obstype, fld, depths, nx, ny, nz, t)
  15. use mod_measurement
  16. use m_obs
  17. implicit none
  18. real, dimension(nobs), intent(inout) :: S ! input/output vector
  19. character(len=5), intent(in) :: obstype ! the model fld type in "fld"
  20. integer, intent(in) :: nx,ny,nz ! grid size
  21. real, intent(in) :: fld (nx,ny) ! field to be placed in Si
  22. real, intent(in) :: depths(nx,ny) ! depth mask -- needed for support
  23. integer, intent(in), optional :: t !time of fld
  24. integer :: iobs
  25. integer :: i, j, ip1, jp1
  26. integer :: ix, jy, imin, imax, jmin, jmax, cnt
  27. logical :: isprofile
  28. real :: depth
  29. integer :: ns
  30. real, parameter :: undef = 999.9 ! land points have value huge()
  31. ! TEM, GTEM, SAL and GSAL come from profiles
  32. isprofile = (trim(obstype) .eq. 'SAL' .or.&
  33. trim(obstype) .eq. 'GSAL' .or.&
  34. trim(obstype) .eq. 'TEM' .or.&
  35. trim(obstype) .eq. 'GTEM')
  36. do iobs = 1, nobs
  37. if (trim(obstype) == obs(iobs) % id) then
  38. if (trim(obstype) .ne. 'TSLA' .or. obs(iobs) % date == t) then
  39. ! Get model gridcell
  40. i = obs(iobs) % ipiv
  41. j = obs(iobs) % jpiv
  42. ip1 = min(i + 1, nx)
  43. jp1 = min(j + 1, ny)
  44. depth = obs(iobs) % depth
  45. !TODO: 1. check consistency for ns = 1 vs ns = 0
  46. ! 2. check consistency of running from -ns to +ns (this can
  47. ! lead perhaps for averaginf over -1 0 1 = 3 x 3 instead
  48. ! of 2 x 2 grid cells if ns = 1
  49. if (depth .lt. 10.0 .and. .not. isprofile) then ! satellite data
  50. ns = obs(iobs) % ns
  51. if(ns .lt. 2) then ! point data : zero support
  52. S(iobs) = fld(i, j) * obs(iobs) % a1 &
  53. + fld(ip1, j) * obs(iobs) % a2 &
  54. + fld(ip1, jp1) * obs(iobs) % a3 &
  55. + fld(i, jp1) * obs(iobs) % a4
  56. else ! data support assumed a square of 2ns * 2ns grid cells
  57. imin = max( 1, i - ns)
  58. imax = min(nx, i + ns)
  59. jmin = max( 1, j - ns)
  60. jmax = min(ny, j + ns)
  61. cnt = 0
  62. S(iobs) = 0.0
  63. do jy = jmin, jmax
  64. do ix = imin, imax
  65. ! Removes data on land, absolute values larger than 1000 and NaNs
  66. if (depths(ix, jy) > 1.0 .and. abs(fld(ix, jy)) < 10.0d3 .and. fld(ix, jy) + 1.0d0 /= fld(ix, jy)) then
  67. S(iobs) = S(iobs) + fld(ix, jy)
  68. cnt = cnt + 1
  69. endif
  70. enddo
  71. enddo
  72. if (cnt == 0) then
  73. print *, ' observation on land ', i, j, obs(iobs) % d
  74. stop 'm_Generate_element_Sij: report bug to LB (laurentb@nersc.no)'
  75. end if
  76. S(iobs) = S(iobs) / real(cnt)
  77. endif
  78. elseif(isprofile) then ! in-situ data (in depth)
  79. print *,'(m_Generate_element_Si does not handle profiles yet)'
  80. stop '(m_Generate_element_Si)'
  81. else
  82. stop 'Generate_element_Sij: not a profile but depth is deeper than 10m'
  83. endif
  84. end if ! obs and model are at similar time
  85. end if ! (trim(obstype) == obs(iobs) % id) then
  86. end do
  87. end subroutine Generate_element_Si
  88. ! Get S = HA for in-situ data. Linearly interpolate for obs positioned
  89. ! between the layer centres; otherwise use the layer value for the obs above
  90. ! the middle of the first layer or below the middle of the last layer.
  91. !
  92. ! Note - this procedure parses through all obs for each ensemble member
  93. ! to work out profiles. This indeed invlolves some redundancy because
  94. ! this work could be done only once. However, the penalty (I think) is
  95. ! quite small compared to the time required for reading the fields from
  96. ! files and does not worth modifying (and complicating) the code.
  97. !
  98. subroutine get_S(S, obstag, nobs, obs, iens)
  99. use mod_measurement
  100. use m_insitu
  101. use m_get_mod_fld
  102. use m_io_mod_fld ! CKB, FM
  103. !use m_parse_blkdat
  104. use m_get_mod_xyz ! was: m_parse_blkdat
  105. use m_parameters
  106. implicit none
  107. real, dimension(nobs), intent(inout) :: S
  108. character(*), intent(in) :: obstag
  109. integer, intent(in) :: nobs
  110. type(measurement), dimension(nobs) :: obs
  111. integer, intent(in) :: iens
  112. real, parameter :: ONEMETER = 9806.0
  113. ! obs stuff
  114. !
  115. integer :: p, o
  116. integer, allocatable, dimension(:) :: ipiv, jpiv
  117. real, allocatable, dimension(:) :: a1, a2, a3, a4
  118. ! grid stuff
  119. !
  120. integer :: k
  121. integer :: ni, nj, nk
  122. real :: rdummy
  123. ! vertical stuff
  124. !
  125. real, allocatable, dimension(:) :: zgrid, zcentre, zgrid_prev, zcentre_prev
  126. real, allocatable, dimension(:) :: v, v_prev
  127. ! fields & I/O stuff
  128. !
  129. real, allocatable, dimension(:, :) :: dz2d, v2d, sstbias, mld, offset, z
  130. integer :: tlevel
  131. character(8) :: fieldtag
  132. character(3) :: cmem
  133. character(80) :: fname
  134. real, dimension(2, 2) :: dz_cell, v_cell
  135. real :: dz, depth, z0, z1, z01, delta
  136. integer :: field
  137. field = NONE
  138. if (nobs == 0) then
  139. return
  140. end if
  141. if (master .and. iens == 1) then
  142. if (VERT_INTERP_GRID) then
  143. print *, trim(obstag), ': vertical interpolation in grid space'
  144. else
  145. print *, trim(obstag), ': vertical interpolation in physical space'
  146. end if
  147. end if
  148. !
  149. ! 1. Identify profiles presented in "obs"
  150. !
  151. ! note that profiles are being used in the vertical superobing by each
  152. ! ensemble member...
  153. !
  154. call insitu_setprofiles(obstag, nobs, obs)
  155. allocate(ipiv(nprof))
  156. allocate(jpiv(nprof))
  157. allocate(a1(nprof))
  158. allocate(a2(nprof))
  159. allocate(a3(nprof))
  160. allocate(a4(nprof))
  161. allocate(zgrid(nprof))
  162. allocate(zgrid_prev(nprof))
  163. allocate(zcentre(nprof))
  164. allocate(zcentre_prev(nprof))
  165. allocate(v(nprof))
  166. allocate(v_prev(nprof))
  167. ipiv = obs(pstart(1 : nprof)) % ipiv
  168. jpiv = obs(pstart(1 : nprof)) % jpiv
  169. a1 = obs(pstart(1 : nprof)) % a1
  170. a2 = obs(pstart(1 : nprof)) % a2
  171. a3 = obs(pstart(1 : nprof)) % a3
  172. a4 = obs(pstart(1 : nprof)) % a4
  173. !
  174. ! 2. Map the observations for this ensemble member proceeding by layers
  175. ! to reduce I/O:
  176. !
  177. ! -cycle through layers
  178. ! -find the middle of this layer
  179. ! -cycle through profiles
  180. ! -for each obs between the middle of the prev layer and the
  181. ! middle of this layer
  182. ! -interpolate the field value
  183. ! -write to S
  184. !
  185. ! get grid dimensions
  186. !
  187. !call parse_blkdat('idm ','integer', rdummy, ni)
  188. !call parse_blkdat('jdm ','integer', rdummy, nj)
  189. !call parse_blkdat('kdm ','integer', rdummy, nk)
  190. call get_mod_xyz(ni, nj, nk) ! [CKB,FM] Changed from using m_parse_blkdat
  191. allocate(v2d(ni, nj))
  192. allocate(dz2d(ni, nj))
  193. if (trim(obstag) == 'SAL' .or. trim(obstag) == 'GSAL') then
  194. fieldtag = 'saln '
  195. field = SALINITY
  196. elseif (trim(obstag) == 'TEM' .or. trim(obstag) == 'GTEM') then
  197. fieldtag = 'temp '
  198. field = TEMPERATURE
  199. else
  200. if (master) then
  201. print *, 'ERROR: get_S(): unknown observatioon tag "', trim(obstag), '"'
  202. end if
  203. stop
  204. end if
  205. write(cmem, '(i3.3)') iens
  206. fname = 'forecast'//cmem
  207. if (field == TEMPERATURE .and. prm_prmestexists('sstb')) then
  208. allocate(sstbias(ni, nj))
  209. allocate(mld(ni, nj))
  210. allocate(offset(ni, nj))
  211. allocate(z(ni, nj))
  212. z = 0.0d0
  213. tlevel = 1
  214. call get_mod_fld_new(trim(fname), sstbias, iens, 'sstb ', 0, tlevel, ni, nj)
  215. if (tlevel == -1) then
  216. if (master) then
  217. print *, 'ERROR: get_mod_fld_new(): failed for "sstb"'
  218. end if
  219. stop
  220. end if
  221. call get_mod_fld_new(trim(fname), mld, iens, 'dpmixl ', 0, tlevel, ni, nj)
  222. if (tlevel == -1) then
  223. if (master) then
  224. print *, 'ERROR: get_mod_fld_new(): failed for "dpmixl"'
  225. end if
  226. stop
  227. end if
  228. end if
  229. ! cycle through layers
  230. !
  231. tlevel = 1
  232. do k = 1, nk + 1
  233. if (k == 1) then
  234. zgrid_prev = 0.0
  235. zcentre_prev = 0.0
  236. end if
  237. if (k <= nk) then
  238. ! read the depth and the requested field at this layer
  239. !
  240. call get_mod_fld_new(trim(fname), dz2d, iens, 'dp ', k, tlevel, ni, nj)
  241. if (tlevel == -1) then
  242. if (master) then
  243. print *, 'ERROR: get_mod_fld_new(): failed for "dp"'
  244. end if
  245. stop
  246. end if
  247. call get_mod_fld_new(trim(fname), v2d, iens, fieldtag, k, tlevel, ni, nj)
  248. if (tlevel == -1) then
  249. if (master) then
  250. print *, 'ERROR: get_mod_fld_new(): failed for "', fieldtag, '"'
  251. end if
  252. stop
  253. end if
  254. end if
  255. ! calculate correction from SST bias at this depth
  256. !
  257. if (field == TEMPERATURE .and. prm_prmestexists('sstb')) then
  258. offset = 0.0d0
  259. z = z + dz2d / 2.0 ! at the middle of the layer
  260. where (mld > 0.0d0 .and. mld < 1.0d8) ! < 10000 m
  261. offset = sstbias * exp(-(z / mld) ** 2)
  262. end where
  263. v2d = v2d - offset
  264. z = z + dz2d / 2.0
  265. end if
  266. ! cycle through profiles
  267. !
  268. do p = 1, nprof
  269. if (k <= nk) then
  270. dz_cell(:, :) = dz2d(ipiv(p) : ipiv(p) + 1, jpiv(p) : jpiv(p) + 1)
  271. dz = dz_cell(1, 1) * a1(p) + dz_cell(2, 1) * a2(p)&
  272. + dz_cell(1, 2) * a3(p) + dz_cell(2, 2) * a4(p)
  273. dz = dz / ONEMETER
  274. zgrid(p) = zgrid_prev(p) + dz
  275. zcentre(p) = (zgrid_prev(p) + zgrid(p)) / 2.0
  276. v_cell(:, :) = v2d(ipiv(p) : ipiv(p) + 1, jpiv(p) : jpiv(p) + 1)
  277. v(p) = v_cell(1, 1) * a1(p) + v_cell(2, 1) * a2(p)&
  278. + v_cell(1, 2) * a3(p) + v_cell(2, 2) * a4(p)
  279. else
  280. ! for the lower half of the last layer -- just use the layer value
  281. ! (note that there was no reading in this case, so that
  282. ! v = v_prev)
  283. zcentre(p) = zgrid(p)
  284. end if
  285. if (k == 1) then
  286. v_prev(p) = v(p)
  287. end if
  288. ! cycle through the obs, pick the ones in between the middle of the
  289. ! previous layer and the middle of this layer, interpolate the
  290. ! ensemble field to their locations, and save the results in S
  291. !
  292. z0 = zcentre_prev(p)
  293. z1 = zcentre(p)
  294. z01 = zgrid_prev(p)
  295. if (z1 == z0) then
  296. cycle
  297. end if
  298. do while (pstart(p) <= pend(p))
  299. o = pstart(p)
  300. depth = obs(o) % depth
  301. ! check that this obs is within the current layer
  302. !
  303. if (depth > z1 .and. k <= nk) then
  304. exit ! next profile
  305. elseif (depth >= z0 .and. depth <= z1) then
  306. if (.not. VERT_INTERP_GRID) then
  307. ! interpolate linearly in physical space
  308. !
  309. S(o) = (z1 - depth) / (z1 - z0) * v_prev(p) +&
  310. (depth - z0) / (z1 - z0) * v(p)
  311. else
  312. ! interpolate linearly in the grid space
  313. !
  314. if (depth < z01) then
  315. delta = 0.5d0 * (depth - z0) / (z01 - z0)
  316. else
  317. delta = 0.5d0 + 0.5d0 * (depth - z01) / (z1 - z01)
  318. end if
  319. S(o) = (1.0d0 - delta) * v_prev(p) + delta * v(p)
  320. end if
  321. ! Here we check the range of interpolated ensemble values;
  322. ! the range of observed values is checked in insitu_QC().
  323. !
  324. if (field == SALINITY) then
  325. if ((S(o) < SAL_MIN .or. S(o) > SAL_MAX) .and. master) then
  326. print *, 'WARNING: get_S(): suspicious value (SAL): ',&
  327. 'iens =', iens, ', obs =', o, ', profile = ', p,&
  328. 'depth =', depth, ', S =', S(o)
  329. end if
  330. else if (field == TEMPERATURE) then
  331. if ((S(o) < TEM_MIN .or. S(o) > TEM_MAX) .and. master) then
  332. print *, 'WARNING: get_S(): suspicious value (TEM): ',&
  333. 'iens =', iens, ', obs =', o, ', profile = ', p,&
  334. 'depth =', depth, ', S =', S(o)
  335. end if
  336. end if
  337. else ! k == nk + 1
  338. S(o) = v(p)
  339. end if
  340. ! go to the next obs
  341. !
  342. pstart(p) = pstart(p) + 1
  343. end do ! o
  344. end do ! p
  345. zgrid_prev = zgrid
  346. zcentre_prev = zcentre
  347. v_prev = v
  348. end do ! k
  349. deallocate(dz2d)
  350. deallocate(v2d)
  351. deallocate(v_prev)
  352. deallocate(v)
  353. deallocate(zcentre_prev)
  354. deallocate(zcentre)
  355. deallocate(zgrid_prev)
  356. deallocate(zgrid)
  357. deallocate(a4)
  358. deallocate(a3)
  359. deallocate(a2)
  360. deallocate(a1)
  361. deallocate(jpiv)
  362. deallocate(ipiv)
  363. if (allocated(sstbias)) then
  364. deallocate(sstbias)
  365. deallocate(mld)
  366. deallocate(offset)
  367. deallocate(z)
  368. end if
  369. end subroutine get_S
  370. end module m_Generate_element_Si