m_insitu.f90 24 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842
  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_insitu.F90
  10. !
  11. ! Created: 6 Feb 2008
  12. !
  13. ! Last modified: 13 Feb 2008
  14. !
  15. ! Author: Pavel Sakov
  16. ! NERSC
  17. !
  18. ! Purpose: The code to deal with insitu observations.
  19. !
  20. ! Description: This module contains the following subroutines:
  21. ! - insitu_setprofiles
  22. ! breaks the measurements into profiles and returns
  23. ! arrays of start and end indices for each profile
  24. ! - insitu_writeprofiles
  25. ! writes profiles to a netCDF file
  26. ! - insitu_prepareobs
  27. ! sorts out the measurements within profiles so they
  28. ! go in surface to bottom order and thins the measurements
  29. ! by keeping max 1 measurements per layer of the first
  30. ! ensemble member
  31. ! It also contains the following data:
  32. ! nprof
  33. ! - the number of profiles
  34. ! pstart(nprof)
  35. ! - start indices for each profile in the array "obs" of
  36. ! type(measurement) stored in module m_obs
  37. ! pend(nprof)
  38. ! - end indices for each profile
  39. !
  40. ! Modifications:
  41. ! 30/7/2010 PS: added profile pivot points to profile output
  42. ! files (SAL.nc etc.)
  43. ! 29/7/2010 PS: some rather minor changes, including interface
  44. ! of insitu_writeforecast()
  45. ! 13/02/2008 PS: added insitu_writeprofiles()
  46. ! 26/02/2008 PS: put "nprof", "pstart" and "pend" as public data
  47. ! in this module
  48. ! 20/04/2008 PS: added insitu_QC() and insitu_writeforecast()
  49. ! 29/07/2010 PS: removed insitu_QC(). There is a generic obs QC
  50. ! procedure in m_obs.F90 now.
  51. module m_insitu
  52. use mod_measurement
  53. !use m_parse_blkdat
  54. use m_get_mod_xyz
  55. use m_get_mod_fld
  56. use m_io_mod_fld
  57. use qmpi
  58. implicit none
  59. !
  60. ! public stuff
  61. !
  62. integer, allocatable, dimension(:), public :: pstart
  63. integer, allocatable, dimension(:), public :: pend
  64. integer, public :: nprof
  65. public insitu_setprofiles
  66. public insitu_prepareobs
  67. public insitu_writeprofiles
  68. !
  69. ! private stuff
  70. !
  71. real, parameter, private :: ONEMETER = 9806.0
  72. integer, parameter, private :: STRLEN = 512
  73. ! The portion of the layer thickness at which the variability in
  74. ! vertical data will be used for estimating the vertical representativeness
  75. ! error.
  76. !
  77. real, parameter, private :: VARCOEFF1 = 0.15
  78. ! A factor by which a calculated vertical representativeness error variance
  79. ! will be reduced if the data is in different layers
  80. !
  81. real, parameter, private :: VARCOEFF2 = 2.0
  82. ! Write information about this profile. Set to < 1 to switch off.
  83. !
  84. integer, parameter, private :: PDEBUGINFO = 0
  85. ! Integers used to tag the fields (to avoid parsing the string tags)
  86. !
  87. integer, parameter, private :: NONE = 0
  88. integer, parameter, private :: TEMPERATURE = 1
  89. integer, parameter, private :: SALINITY = 2
  90. real, parameter, private :: TEM_MIN = -2.0
  91. real, parameter, private :: TEM_MAX = 35.0
  92. real, parameter, private :: SAL_MIN = 5.0
  93. real, parameter, private :: SAL_MAX = 41.0
  94. ! Maximum allowed deviation between the observation and ensemble mean in
  95. ! terms of combined standard deviation.
  96. !
  97. real, parameter, private :: SAL_MAXRATIO = 10.0
  98. real, parameter, private :: TEM_MAXRATIO = 5.0
  99. ! If an observation is not considered an outlier, the observation error
  100. ! variance is modified so that the distance between the observation and the
  101. ! endemble mean is within DIST_MAX * sqrt(sigma_obs^2 + sigma_ens^2).
  102. ! Bigger values of DIST_MAX result in a more violent assimilation.
  103. !
  104. real, parameter, private :: DIST_MAX = 2.0
  105. contains
  106. ! Work out the number of profiles, each identified by "obs % i_orig_grid"
  107. ! and return start id of the first and the last obs in the profile in
  108. ! arrays "pstart" and "pend". "pstart" and "pend" are publicly available
  109. ! arrays stored in this module.
  110. !
  111. subroutine insitu_setprofiles(obstag, nobs, obs)
  112. character(*), intent(in) :: obstag
  113. integer, intent(in) :: nobs
  114. type(measurement), dimension(:), intent(inout) :: obs
  115. integer, allocatable, dimension(:) :: tmp, tmp1
  116. integer :: o, o1, o2, p, nobsp
  117. type(measurement), allocatable, dimension(:) :: tmpobs
  118. if (nobs == 0) then
  119. return
  120. end if
  121. if (allocated(pstart)) then
  122. deallocate(pstart)
  123. deallocate(pend)
  124. end if
  125. ! find the very first obs of the right kind
  126. !
  127. o1 = 1
  128. do while (trim(obs(o1) % id) /= trim(obstag) .and. o1 <= nobs)
  129. o1 = o1 + 1
  130. end do
  131. if (o1 > nobs) then
  132. return
  133. end if
  134. ! find the very last obs of the right kind
  135. !
  136. o2 = nobs
  137. do while (trim(obs(o2) % id) /= trim(obstag) .and. o2 >= 0)
  138. o2 = o2 - 1
  139. end do
  140. nprof = 1
  141. do o = 2, o2
  142. if (obs(o) % ipiv /= obs(o - 1) % ipiv .or.&
  143. obs(o) % jpiv /= obs(o - 1) % jpiv .or.&
  144. obs(o) % date /= obs(o - 1) % date) then
  145. nprof = nprof + 1
  146. end if
  147. end do
  148. allocate(pstart(nprof))
  149. allocate(pend(nprof))
  150. ! identify profiles
  151. !
  152. ! PS: This is a tricky cycle but it seems it is doing the job. Do not
  153. ! meddle with it.
  154. !
  155. pend = 0
  156. nprof = 1
  157. pstart(1) = o1
  158. do o = o1, o2
  159. ! find obs from the same profile
  160. !
  161. if (trim(obs(o) % id) == trim(obstag) .and.&
  162. ((obs(o) % i_orig_grid > 0 .and.&
  163. obs(o) % i_orig_grid == obs(pstart(nprof)) % i_orig_grid) .or.&
  164. (obs(o) % i_orig_grid <= 0 .and.&
  165. obs(o) % ipiv == obs(pstart(nprof)) % ipiv .and.&
  166. obs(o) % jpiv == obs(pstart(nprof)) % jpiv .and.&
  167. obs(o) % date == obs(pstart(nprof)) % date))) then
  168. pend(nprof) = o
  169. cycle
  170. end if
  171. if (trim(obs(o) % id) /= trim(obstag)) then
  172. print *, 'ERROR: insitu_setprofiles(): obs id does not match processed obs tag'
  173. stop
  174. end if
  175. ! if there were no obs of the right type in this profile yet,
  176. ! then pend(nprof) has not been set yet and therefore the condition
  177. ! below will yield "false"
  178. !
  179. if (pend(nprof) >= pstart(nprof)) then
  180. nprof = nprof + 1
  181. end if
  182. if (PDEBUGINFO > 0) then
  183. print *, ' DEBUG: new profile #', nprof, ', o =', o, ', id =', obs(o) % i_orig_grid
  184. end if
  185. pstart(nprof) = o
  186. pend(nprof) = o
  187. end do
  188. if (pend(nprof) < pstart(nprof)) then
  189. nprof = nprof - 1
  190. end if
  191. ! truncate "pstat" and "pend" to length "nprof"
  192. !
  193. allocate(tmp(nprof))
  194. tmp = pstart(1 : nprof)
  195. deallocate(pstart)
  196. allocate(pstart(nprof))
  197. pstart = tmp
  198. tmp = pend(1 : nprof)
  199. deallocate(pend)
  200. allocate(pend(nprof))
  201. pend = tmp
  202. deallocate(tmp)
  203. ! for glider data - sort observations in each profile by increasing depth
  204. !
  205. if (trim(obstag) == 'GSAL'.or. trim(obstag) == 'GTEM') then
  206. allocate(tmp(nobs))
  207. allocate(tmp1(nobs))
  208. allocate(tmpobs(nobs))
  209. do p = 1, nprof
  210. nobsp = pend(p) - pstart(p) + 1
  211. do o = 1, nobsp
  212. tmp(o) = o
  213. end do
  214. !
  215. ! (using procedure from pre_local_analysis())
  216. !
  217. call order(dble(nobsp), obs(pstart(p) : pend(p)) % depth,&
  218. dble(nobsp), tmp, tmp1)
  219. tmpobs(1 : nobsp) = obs(pstart(p) : pend(p))
  220. do o = 1, nobsp
  221. obs(pstart(p) + o - 1) = tmpobs(tmp1(o))
  222. end do
  223. end do
  224. deallocate(tmp, tmp1, tmpobs)
  225. end if
  226. end subroutine insitu_setprofiles
  227. ! 1. Sort out the obs within profiles so that they are stored in order of
  228. ! increasing depth.
  229. ! 2. Thin observations by keeping a single obs within a layer using the
  230. ! layers from the first ensemble member
  231. !
  232. subroutine insitu_prepareobs(obstag, nobs, obs)
  233. character(*), intent(in) :: obstag
  234. integer, intent(inout) :: nobs
  235. type(measurement), dimension(:), intent(inout) :: obs
  236. ! profiles
  237. !
  238. integer, allocatable, dimension(:) :: pnow
  239. integer :: nobs_max
  240. integer :: p, o
  241. type(measurement), allocatable, dimension(:) :: profile
  242. integer, allocatable, dimension(:) :: ipiv, jpiv
  243. real, allocatable, dimension(:) :: a1, a2, a3, a4
  244. real, allocatable, dimension(:) :: z1, z2
  245. integer :: nrev
  246. integer :: ndel
  247. integer :: oo
  248. real :: rdummy
  249. integer :: k, nk, ni, nj
  250. character(80) :: fname
  251. integer :: tlevel
  252. real, allocatable, dimension(:, :) :: dz2d
  253. real, dimension(2, 2) :: dz_cell
  254. real :: dz, zcentre
  255. integer :: best
  256. logical :: isrogue
  257. ! As we thin the measurements within each layer, it still may be a good
  258. ! idea to update the obs error variance if the variability within the layer
  259. ! is big enough. `dmin' and `dmax' give the min and max measured values
  260. ! within the layer.
  261. !
  262. real :: dmin, dmax
  263. real :: var1, var2
  264. integer :: nobsnew, nobs_thistype, nobs_othertype
  265. if (master) then
  266. print '(a, a, a)', ' insitu_prepareobs(', trim(obstag), '):'
  267. print '(a, i6)', ' total # of obs = ', nobs
  268. end if
  269. if (nobs == 0) then
  270. return
  271. end if
  272. call insitu_setprofiles(trim(obstag), nobs, obs)
  273. if (master) then
  274. print '(a, a, a, i6)', ' # of obs of type "', trim(obstag), '" = ',&
  275. sum(pend(1 : nprof) - pstart(1 : nprof)) + nprof
  276. print '(a, i4)', ' # of profiles = ', nprof
  277. end if
  278. ! find the maximal # of obs in a single profile
  279. !
  280. nobs_max = 0
  281. do p = 1, nprof
  282. nobs_max = max(nobs_max, pend(p) - pstart(p) + 1)
  283. end do
  284. if (master) then
  285. print '(a, i4)', ' max # of obs in a profile before thinning = ', nobs_max
  286. end if
  287. ! reverse the obs in profiles that go from bottom to surface
  288. !
  289. allocate(profile(nobs_max))
  290. nrev = 0
  291. do p = 1, nprof
  292. if (obs(pstart(p)) % depth > obs(pend(p)) % depth) then
  293. profile(1 : pend(p) - pstart(p) + 1) = obs(pstart(p) : pend(p))
  294. do o = 0, pend(p) - pstart(p)
  295. obs(pstart(p) + o) = profile(pend(p) - o)
  296. end do
  297. nrev = nrev + 1
  298. end if
  299. end do
  300. deallocate(profile)
  301. if (nrev > 0 .and. master) then
  302. print *, ' ', nrev, ' profile(s) reversed'
  303. end if
  304. ! check for rogue obs
  305. !
  306. ndel = 0
  307. do p = 1, nprof
  308. isrogue = .false.
  309. do o = pstart(p) + 1, pend(p)
  310. ! shift the remaining obs in this profile one obs down
  311. !
  312. if (obs(o) % depth <= obs(o - 1) % depth) then
  313. isrogue = .true.
  314. do oo = o + 1, pend(p)
  315. obs(oo - 1) = obs(oo)
  316. end do
  317. ndel = ndel + 1
  318. pend(p) = pend(p) - 1
  319. end if
  320. end do
  321. if (isrogue .and. master) then
  322. print *, ' a rogue obs detected in profile # ', p
  323. end if
  324. end do
  325. if (ndel > 0 .and. master) then
  326. print *, ' ', ndel, 'rogue obs deleted'
  327. end if
  328. !
  329. ! Now to the thinning of the profiles.
  330. !
  331. allocate(ipiv(nprof))
  332. allocate(jpiv(nprof))
  333. allocate(a1(nprof))
  334. allocate(a2(nprof))
  335. allocate(a3(nprof))
  336. allocate(a4(nprof))
  337. ipiv = obs(pstart(1 : nprof)) % ipiv
  338. jpiv = obs(pstart(1 : nprof)) % jpiv
  339. a1 = obs(pstart(1 : nprof)) % a1
  340. a2 = obs(pstart(1 : nprof)) % a2
  341. a3 = obs(pstart(1 : nprof)) % a3
  342. a4 = obs(pstart(1 : nprof)) % a4
  343. ! get the grid dimensions
  344. !
  345. !call parse_blkdat('kdm ','integer', rdummy, nk)
  346. !call parse_blkdat('idm ','integer', rdummy, ni)
  347. !call parse_blkdat('jdm ','integer', rdummy, nj)
  348. call get_mod_xyz(ni, nj, nk) ! CKB,FM Changed from using m_parse_blkdat
  349. ! get the data file name
  350. !
  351. if (trim(obstag) /= 'SAL' .and. trim(obstag) /= 'TEM' .and.&
  352. trim(obstag) /= 'GSAL'.and. trim(obstag) /= 'GTEM') then
  353. print *, 'ERROR: get_S(): unknown observation tag "', trim(obstag), '"'
  354. stop
  355. end if
  356. fname = 'forecast001'
  357. allocate(z1(nprof))
  358. allocate(z2(nprof))
  359. allocate(pnow(nprof))
  360. allocate(dz2d(ni, nj))
  361. ! data thinning cycle
  362. !
  363. if (master) then
  364. print *, ' maximum one observation per layer will be retained after thinning'
  365. end if
  366. tlevel = 1
  367. z1 = 0.0
  368. pnow = pstart
  369. if (master .and. PDEBUGINFO > 0) then
  370. p = PDEBUGINFO
  371. print *, 'DEBUG dumping the info for profile #', p
  372. print *, 'DEBUG p =', p, ': lon =', obs(pstart(p)) % lon, ', lat =', obs(pstart(p)) % lat
  373. print *, 'DEBUG now dumping the layer depths:'
  374. end if
  375. ! mark all obs of this type as bad; unmask the best obs within a layer
  376. !
  377. do o = 1, nobs
  378. if (trim(obs(o) % id) == trim(obstag)) then
  379. obs(o) % status = .false.
  380. end if
  381. end do
  382. do k = 1, nk
  383. !call get_mod_fld_new(trim(fname), dz2d, 1, 'dp ', k, tlevel, ni, nj)
  384. ! [CKB,FM]
  385. call io_mod_fld(dz2d, 1, (/ 1 /), 'dp ', 2, &
  386. k, tlevel, ni, nj, 'get',FLOAT(obs(1)%date))
  387. do p = 1, nprof
  388. dz_cell(:, :) = dz2d(ipiv(p) : ipiv(p) + 1, jpiv(p) : jpiv(p) + 1)
  389. dz = dz_cell(1, 1) * a1(p) + dz_cell(2, 1) * a2(p)&
  390. + dz_cell(1, 2) * a3(p) + dz_cell(2, 2) * a4(p)
  391. dz = dz / ONEMETER
  392. z2(p) = z1(p) + dz
  393. zcentre = (z1(p) + z2(p)) / 2.0
  394. best = -1
  395. dmin = 1.0d+10
  396. dmax = -1.0d+10
  397. if (master .and. PDEBUGINFO > 0 .and. p == PDEBUGINFO) then
  398. print *, 'DEBUG p =', p, ', k =', k, ', z =', z1(p), '-', z2(p)
  399. end if
  400. do while (pnow(p) <= pend(p))
  401. o = pnow(p)
  402. ! check that the depth is within the layer
  403. !
  404. if (obs(o) % depth > z2(p)) then
  405. ! go to next profile; this obs will be dealt with when
  406. ! processing the next layer
  407. exit
  408. end if
  409. ! from this point on, the obs counter will be increased at the
  410. ! end of this loop
  411. ! store profile and layer number (overwrite the original profile
  412. ! id and vertical counter value)
  413. !
  414. obs(o) % i_orig_grid = p
  415. obs(o) % j_orig_grid = k
  416. obs(o) % h = z2(p) - z1(p)
  417. if (obs(o) % depth < z1(p)) then
  418. pnow(p) = pnow(p) + 1
  419. cycle ! next obs
  420. end if
  421. ! update `dmin' and `dmax'
  422. !
  423. dmin = min(dmin, obs(o) % d)
  424. dmax = max(dmax, obs(o) % d)
  425. if (best < 1) then
  426. best = o
  427. obs(best) % status = .true.
  428. else if (abs(obs(o) % depth - zcentre) < abs(obs(best) % depth - zcentre)) then
  429. obs(best) % status = .false. ! thrash the previous best obs
  430. best = o
  431. obs(best) % status = .true.
  432. end if
  433. pnow(p) = pnow(p) + 1
  434. end do ! o
  435. ! update the observation error variance if the difference between
  436. ! `dmin' and `dmax' is big enough
  437. !
  438. if (best < 1) then
  439. cycle
  440. end if
  441. if (.false.) then ! out for now; use the closest obs instead
  442. if (dmax - dmin > 0) then
  443. obs(best) % var = sqrt(obs(best) % var + ((dmax - dmin) / 2) ** 2)
  444. end if
  445. end if
  446. end do ! p
  447. z1 = z2
  448. end do ! k
  449. ! There are a number of ways the vertical variability can be
  450. ! used for updating the obs error variance.
  451. !
  452. ! Below, the following approach is used.
  453. !
  454. ! Calculate two estimates for vertical gradient using the closest data
  455. ! points (if available). Estimate the difference at (VARCOEFF1 * h)
  456. ! vertical distance from the current obs, where VARCOEFF1 is the portion
  457. ! of the layer thickness (typically around 0.1-0.3), and h is the layer
  458. ! thickness. Use the square of this difference as an estimate for the
  459. ! respresentation error variance. If the closest obs is in another layer
  460. ! -- decrease this estimate by a factor of VARCOEFF2 (typically around 2).
  461. ! Use the largest estimate between the two (when both are avalaible).
  462. !
  463. do p = 1, nprof
  464. do o = pstart(p), pend(p)
  465. k = obs(o) % j_orig_grid
  466. if (obs(o) % status) then
  467. var1 = -999.0
  468. var2 = -999.0
  469. if (o - 1 >= pstart(p)) then
  470. var1 = ((obs(o) % d - obs(o - 1) % d) /&
  471. (obs(o) % depth - obs(o - 1) % depth) * obs(o) % h * VARCOEFF1) ** 2
  472. if (obs(o - 1) % j_orig_grid /= k) then
  473. var1 = var1 / VARCOEFF2
  474. end if
  475. end if
  476. if (o + 1 <= pend(p)) then
  477. var2 = ((obs(o) % d - obs(o + 1) % d) /&
  478. (obs(o) % depth - obs(o + 1) % depth) * obs(o) % h * VARCOEFF1) ** 2
  479. if (obs(o + 1) % j_orig_grid /= k) then
  480. var2 = var2 / VARCOEFF2
  481. end if
  482. end if
  483. if (var1 < 0.0 .and. var2 < 0.0) then
  484. cycle
  485. end if
  486. obs(o) % var = obs(o) % var + max(var1, var2)
  487. end if
  488. end do
  489. end do
  490. if (master .and. PDEBUGINFO > 0) then
  491. p = PDEBUGINFO
  492. print *, 'DEBUG now dumping the obs info:'
  493. do o = pstart(p), pend(p)
  494. print *, 'DEBUG o =', o, ', status =', obs(o) % status, &
  495. ', d =', obs(o) % d, ', z =', obs(o) % depth,&
  496. ', k =', obs(o) % j_orig_grid, ', h =', obs(o) % h,&
  497. ', var =', obs(o) % var
  498. end do
  499. end if
  500. deallocate(dz2d)
  501. deallocate(pnow)
  502. deallocate(z2)
  503. deallocate(z1)
  504. deallocate(a4)
  505. deallocate(a3)
  506. deallocate(a2)
  507. deallocate(a1)
  508. deallocate(jpiv)
  509. deallocate(ipiv)
  510. ! now compact the obs array
  511. !
  512. nobsnew = 0
  513. nobs_thistype = 0
  514. nobs_othertype = 0
  515. do o = 1, nobs
  516. if (obs(o) % status) then
  517. nobsnew = nobsnew + 1
  518. obs(nobsnew) = obs(o)
  519. if (trim(obs(o) % id) == trim(obstag)) then
  520. nobs_thistype = nobs_thistype + 1
  521. else
  522. nobs_othertype = nobs_othertype + 1
  523. end if
  524. end if
  525. end do
  526. obs(nobsnew + 1 : nobs) % status = .false.
  527. nobs = nobsnew
  528. ! replace the original profiles by the thinned ones
  529. !
  530. call insitu_setprofiles(trim(obstag), nobs, obs)
  531. if (master) then
  532. print *, ' thinning completed:', nobs_thistype, ' "', trim(obstag), '" obs retained'
  533. if (nobs_othertype > 0) then
  534. print *, ' ', nobs_othertype, 'obs of other type(s) retained'
  535. end if
  536. end if
  537. end subroutine insitu_prepareobs
  538. ! Write profiles to a NetCDF file
  539. !
  540. subroutine insitu_writeprofiles(fname, obstag, nobs, obs)
  541. use nfw_mod
  542. character(*), intent(in) :: fname
  543. character(*), intent(in) :: obstag
  544. integer, intent(inout) :: nobs
  545. type(measurement), dimension(:), intent(inout) :: obs
  546. ! profiles
  547. !
  548. integer :: p
  549. integer :: npoints, npoints_max
  550. ! I/O
  551. !
  552. integer :: ncid
  553. integer :: nprof_id(1), nk_id(1), dids(2)
  554. integer :: lat_id, lon_id, ipiv_id, jpiv_id, npoints_id, depth_id, v_id, variance_id
  555. character(STRLEN) :: varname
  556. real(8), allocatable, dimension(:, :) :: v
  557. if (.not. allocated(pstart)) then
  558. call insitu_setprofiles(trim(obstag), nobs, obs)
  559. end if
  560. call nfw_create(fname, nf_write, ncid)
  561. call nfw_def_dim(fname, ncid, 'nprof', nprof, nprof_id(1))
  562. call nfw_def_var(fname, ncid, 'lat', nf_double, 1, nprof_id, lat_id)
  563. call nfw_def_var(fname, ncid, 'lon', nf_double, 1, nprof_id, lon_id)
  564. call nfw_def_var(fname, ncid, 'ipiv', nf_int, 1, nprof_id, ipiv_id)
  565. call nfw_def_var(fname, ncid, 'jpiv', nf_int, 1, nprof_id, jpiv_id)
  566. call nfw_def_var(fname, ncid, 'npoints', nf_int, 1, nprof_id, npoints_id)
  567. npoints_max = maxval(pend - pstart) + 1
  568. call nfw_def_dim(fname, ncid, 'nk', npoints_max, nk_id(1))
  569. dids(1) = nk_id(1)
  570. dids(2) = nprof_id(1)
  571. call nfw_def_var(fname, ncid, 'depth', nf_double, 2, dids, depth_id)
  572. if (trim(obstag) == 'SAL' .or. trim(obstag) == 'GSAL') then
  573. varname = 'salt'
  574. else if (trim(obstag) == 'TEM' .or. trim(obstag) == 'GTEM') then
  575. varname = 'temp'
  576. else
  577. varname = trim(obstag)
  578. end if
  579. call nfw_def_var(fname, ncid, trim(varname), nf_double, 2, dids, v_id)
  580. call nfw_def_var(fname, ncid, 'variance', nf_double, 2, dids, variance_id)
  581. call nfw_enddef(fname, ncid)
  582. call nfw_put_var_double(fname, ncid, lat_id, obs(pstart) % lat)
  583. call nfw_put_var_double(fname, ncid, lon_id, obs(pstart) % lon)
  584. call nfw_put_var_int(fname, ncid, ipiv_id, obs(pstart) % ipiv)
  585. call nfw_put_var_int(fname, ncid, jpiv_id, obs(pstart) % jpiv)
  586. call nfw_put_var_int(fname, ncid, npoints_id, pend - pstart + 1)
  587. ! depth
  588. !
  589. allocate(v(npoints_max, nprof))
  590. v = -999.0
  591. do p = 1, nprof
  592. npoints = pend(p) - pstart(p) + 1
  593. v(1 : npoints, p) = obs(pstart(p) : pend(p)) % depth
  594. end do
  595. call nfw_put_var_double(fname, ncid, depth_id, v)
  596. ! data
  597. !
  598. v = -999.0
  599. do p = 1, nprof
  600. npoints = pend(p) - pstart(p) + 1
  601. v(1 : npoints, p) = obs(pstart(p) : pend(p)) % d
  602. end do
  603. call nfw_put_var_double(fname, ncid, v_id, v)
  604. ! data error variance
  605. !
  606. v = -999.0
  607. do p = 1, nprof
  608. npoints = pend(p) - pstart(p) + 1
  609. v(1 : npoints, p) = obs(pstart(p) : pend(p)) % var
  610. end do
  611. call nfw_put_var_double(fname, ncid, variance_id, v)
  612. call nfw_close(fname, ncid)
  613. deallocate(v)
  614. deallocate(pstart)
  615. deallocate(pend)
  616. end subroutine insitu_writeprofiles
  617. ! This subroutine appends the interpolated ensemble mean and the ensemble
  618. ! error variance to the assimilated profile data SAL.nc or TEM.nc. It also
  619. ! overwrites the observation error variance with latest values.
  620. !
  621. subroutine insitu_writeforecast(obstag, nobs, nrens, S, obs)
  622. use nfw_mod
  623. implicit none
  624. character(*), intent(in) :: obstag
  625. integer, intent(in) :: nobs
  626. integer, intent(in) :: nrens
  627. real, dimension(nobs, nrens), intent(in) :: S
  628. type(measurement), dimension(nobs), intent(inout) :: obs
  629. character(STRLEN) :: fname
  630. real, dimension(nobs) :: Smean, Svar
  631. integer :: i, p
  632. integer :: ncid
  633. integer :: dids(2)
  634. integer :: v_id, variance_id
  635. integer :: npoints_max, npoints
  636. real(8), allocatable, dimension(:, :) :: v
  637. ! need to set profiles for the given observation type
  638. !
  639. call insitu_setprofiles(obstag, nobs, obs)
  640. write(fname, '(a, ".nc")') trim(obstag)
  641. print *, 'Appending interpolated forecast for "', trim(obstag),&
  642. '" to "', trim(fname), '"'
  643. Smean = sum(S, DIM = 2) / nrens
  644. Svar = 0.0
  645. do i = 1, nobs
  646. Svar(i) = sum((S(i, :) - Smean(i)) ** 2)
  647. end do
  648. Svar = Svar / real(nrens - 1)
  649. call nfw_open(fname, nf_write, ncid)
  650. call nfw_inq_dimid(fname, ncid, 'nk', dids(1))
  651. call nfw_inq_dimid(fname, ncid, 'nprof', dids(2))
  652. call nfw_redef(fname, ncid)
  653. call nfw_def_var(fname, ncid, 'forecast', nf_double, 2, dids, v_id)
  654. call nfw_def_var(fname, ncid, 'forecast_variance', nf_double, 2, dids, variance_id)
  655. call nfw_enddef(fname, ncid)
  656. npoints_max = maxval(pend - pstart) + 1
  657. allocate(v(npoints_max, nprof))
  658. v = -999.0
  659. do p = 1, nprof
  660. npoints = pend(p) - pstart(p) + 1
  661. v(1 : npoints, p) = Smean(pstart(p) : pend(p))
  662. end do
  663. call nfw_put_var_double(fname, ncid, v_id, v)
  664. v = -999.0
  665. do p = 1, nprof
  666. npoints = pend(p) - pstart(p) + 1
  667. v(1 : npoints, p) = Svar(pstart(p) : pend(p))
  668. end do
  669. call nfw_put_var_double(fname, ncid, variance_id, v)
  670. ! update observation error variance
  671. !
  672. call nfw_redef(fname, ncid)
  673. call nfw_rename_var(fname, ncid, 'variance', 'variance_orig')
  674. call nfw_def_var(fname, ncid, 'variance', nf_double, 2, dids, variance_id)
  675. call nfw_enddef(fname, ncid)
  676. v = -999.0
  677. do p = 1, nprof
  678. npoints = pend(p) - pstart(p) + 1
  679. v(1 : npoints, p) = obs(pstart(p) : pend(p)) % var
  680. end do
  681. call nfw_put_var_double(fname, ncid, variance_id, v)
  682. call nfw_close(fname, ncid)
  683. deallocate(v)
  684. end subroutine insitu_writeforecast
  685. end module m_insitu