m_prep_4_EnKF.f90 27 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761
  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_prep_4_EnKF.F90
  10. !
  11. ! Created: ???
  12. !
  13. ! Last modified: 29/06/2010
  14. !
  15. ! Purpose: Calculation of HA ("S")
  16. !
  17. ! Description: Calculates HA by going sequentially through each data type.
  18. !
  19. ! Modifications:
  20. ! 09/11/2012 Geir Arne Waagbo:
  21. ! - Added support for OSISAF ice drift obs
  22. ! 29/07/2010 PS:
  23. ! - merged insitu_QC() with generic obs_QC(). Moved
  24. ! insitu_writeforecast() to the point after QC.
  25. ! 29/06/2010 PS:
  26. ! - added generic observation QC: increase the observation
  27. ! error when observation and ensemble mean are much too far
  28. ! away than expected
  29. ! Prior history:
  30. ! Not documented.
  31. module m_prep_4_EnKF
  32. integer, parameter, private :: STRLEN = 512
  33. private read_mean_ssh
  34. contains
  35. ! This subroutine uses the observation and ensembles from the model
  36. ! to prepare the input to the EnKF analysis scheme.
  37. ! The output from this routine is used directly in the global analysis
  38. ! while the output has to be run through a "filter" to be used in the
  39. ! local analysis scheme.
  40. ! S = HA (ensemble observation anomalies)
  41. ! d = d - Hx (innovations)
  42. !
  43. ! S is calculated in two steps:
  44. ! 1. S = HE
  45. ! 2. S = S - repmat(s, 1, m),
  46. ! where s = mean(S')';
  47. ! Note that in reality (with HYCOM) H is different for each member...
  48. ! So that HX must be read "HX" rather than "H * X".
  49. !
  50. subroutine prep_4_EnKF(nrens, enslist, d, S, depths, meandx, nx, ny, nz)
  51. use qmpi, only : master, stop_mpi
  52. use mod_measurement
  53. use m_obs
  54. use m_Generate_element_Si
  55. use m_get_mod_fld
  56. use m_read_icemod
  57. use m_parameters
  58. implicit none
  59. integer, intent(in) :: nx, ny, nz ! Model size
  60. integer, intent(in) :: nrens ! Size of ensemble
  61. integer, dimension(:),intent(in) :: enslist ! [CKB,FM] List of existing ens members
  62. real, intent(in) :: depths(nx, ny)
  63. real, intent(in) :: meandx ! mean grid size
  64. real, intent(inout) :: d(nobs)
  65. real, intent(inout) :: S(nobs, nrens)
  66. real :: x(nobs)
  67. integer :: i, j, m, iens
  68. real*4, dimension(nx,ny) :: fldr4
  69. real :: readfld(nx, ny), ai1(nx,ny), ai2(nx,ny), ai3(nx,ny), ai4(nx,ny), ai5(nx,ny), uice(nx,ny), vice(nx,ny)
  70. real :: vi1(nx,ny), vi2(nx,ny), vi3(nx,ny), vi4(nx,ny), vi5(nx,ny)
  71. real :: vs1(nx,ny), vs2(nx,ny), vs3(nx,ny), vs4(nx,ny), vs5(nx,ny)
  72. ! hard-coded for now
  73. integer, parameter :: drnx = 152, drny = 132
  74. real*4, dimension(drnx, drny) :: modzon, modmer
  75. integer, parameter :: drnx_osisaf = 119, drny_osisaf = 177
  76. real*4, dimension(drnx_osisaf, drny_osisaf) :: dX, dY
  77. integer :: reclSLA, ios, reclDRIFT
  78. character*3 :: cmem
  79. character*2 :: day
  80. character*1 :: offset
  81. logical :: ex
  82. character(STRLEN) :: fname
  83. integer :: iuobs
  84. ! FANF: For track assim we launch m_Generate_Si for each day (t=1:Wd)
  85. ! which fills in S at the approriate indices.
  86. ! Wd is is the assimilation cycle (i.e. 7 days)
  87. !
  88. integer :: Wd, t
  89. integer :: tlevel
  90. real :: field2(nx, ny), field3(nx, ny) ! auxiliary fields (e.g. mean SSH,
  91. ! field bias estimate etc.)
  92. integer :: nthisobs, thisobs(nobs)
  93. if (any(obs(:) % id == 'TSLA ')) then
  94. Wd = 6
  95. else
  96. Wd = 0
  97. endif
  98. ! security check
  99. !
  100. if (any(obs(:) % id == 'SSH ') .or. any(obs(:) % id == 'SLA ')) then
  101. if (any(obs(:) % id == 'SLA ')) then
  102. inquire(exist = ex, file = 'model_SLA.uf')
  103. if (.not.ex) then
  104. if (master) print *,'model_SLA.uf does not exist'
  105. call stop_mpi()
  106. end if
  107. end if
  108. if (any(obs(:) % id == 'SSH ')) then
  109. inquire(exist = ex, file = 'model_SSH.uf')
  110. if (.not.ex) then
  111. if (master) print *,'model_SSH.uf does not exist'
  112. call stop_mpi()
  113. end if
  114. end if
  115. end if
  116. ! construct S=HA
  117. !
  118. do iuobs = 1, nuobs
  119. if (master) then
  120. print *, 'prep_4_EnKF: now preparing "', trim(unique_obs(iuobs)), '" observations'
  121. end if
  122. if (trim(unique_obs(iuobs)) == 'ICEC') then
  123. do iens = 1, nrens
  124. write(cmem,'(i3.3)') iens
  125. tlevel = 1
  126. call get_mod_fld_new(trim('forecast'//cmem), readfld, iens,&
  127. 'icec', 0, tlevel, nx, ny)
  128. if (tlevel == -1) then
  129. if (master) then
  130. print *, 'ERROR: get_mod_fld_new(): failed for "icec"'
  131. end if
  132. stop
  133. end if
  134. call Generate_element_Si(S(:, iens), unique_obs(iuobs),&
  135. readfld, depths, nx, ny, nz, 0)
  136. end do
  137. ! [FM, May 2013: for LIM3 sea ice model]
  138. elseif (trim(unique_obs(iuobs)) == 'AT_I') then
  139. do iens = 1, nrens
  140. write(cmem,'(i3.3)') iens
  141. tlevel = 1
  142. call io_mod_fld(ai1,iens,enslist, &
  143. 'a_i_htc1', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  144. call io_mod_fld(ai2,iens,enslist, &
  145. 'a_i_htc2', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  146. call io_mod_fld(ai3,iens,enslist, &
  147. 'a_i_htc3', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  148. call io_mod_fld(ai4,iens,enslist, &
  149. 'a_i_htc4', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  150. call io_mod_fld(ai5,iens,enslist, &
  151. 'a_i_htc5', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  152. if (tlevel == -1) then
  153. if (master) then
  154. print *, 'ERROR: io_mod_fld_new(): failed for "at_i"'
  155. end if
  156. stop
  157. end if
  158. ! Multipply by 100 to match obs conventions
  159. readfld=(ai1+ai2+ai3+ai4+ai5) * 100.0
  160. call Generate_element_Si(S(:, iens), unique_obs(iuobs),&
  161. readfld, depths, nx, ny, nz, 0)
  162. end do
  163. ! freeboard
  164. elseif(trim(unique_obs(iuobs)) == 'VT_I') then
  165. do iens = 1, nrens
  166. write(cmem, '(i3.3)') iens
  167. tlevel = 1
  168. call io_mod_fld(ai1,iens,enslist, &
  169. 'a_i_htc1', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  170. call io_mod_fld(ai2,iens,enslist, &
  171. 'a_i_htc2', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  172. call io_mod_fld(ai3,iens,enslist, &
  173. 'a_i_htc3', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  174. call io_mod_fld(ai4,iens,enslist, &
  175. 'a_i_htc4', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  176. call io_mod_fld(ai5,iens,enslist, &
  177. 'a_i_htc5', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  178. call io_mod_fld(vi1,iens,enslist, &
  179. 'v_i_htc1', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  180. call io_mod_fld(vi2,iens,enslist, &
  181. 'v_i_htc2', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  182. call io_mod_fld(vi3,iens,enslist, &
  183. 'v_i_htc3', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  184. call io_mod_fld(vi4,iens,enslist, &
  185. 'v_i_htc4', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  186. call io_mod_fld(vi5,iens,enslist, &
  187. 'v_i_htc5', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  188. if (tlevel == -1) then
  189. if (master) then
  190. print *, 'ERROR: io_mod_fld_nex(): failed for "SIFB"'
  191. end if
  192. stop
  193. end if
  194. readfld=(vi1+vi2+vi3+vi4+vi5)
  195. call Generate_element_Si(S(:, iens), unique_obs(iuobs),&
  196. readfld, depths, nx, ny, nz, 0)
  197. end do
  198. ! freeboard
  199. elseif(trim(unique_obs(iuobs)) == 'RFB') then
  200. do iens = 1, nrens
  201. write(cmem, '(i3.3)') iens
  202. tlevel = 1
  203. call io_mod_fld(ai1,iens,enslist, &
  204. 'a_i_htc1', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  205. call io_mod_fld(ai2,iens,enslist, &
  206. 'a_i_htc2', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  207. call io_mod_fld(ai3,iens,enslist, &
  208. 'a_i_htc3', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  209. call io_mod_fld(ai4,iens,enslist, &
  210. 'a_i_htc4', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  211. call io_mod_fld(ai5,iens,enslist, &
  212. 'a_i_htc5', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  213. call io_mod_fld(vi1,iens,enslist, &
  214. 'v_i_htc1', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  215. call io_mod_fld(vi2,iens,enslist, &
  216. 'v_i_htc2', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  217. call io_mod_fld(vi3,iens,enslist, &
  218. 'v_i_htc3', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  219. call io_mod_fld(vi4,iens,enslist, &
  220. 'v_i_htc4', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  221. call io_mod_fld(vi5,iens,enslist, &
  222. 'v_i_htc5', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  223. call io_mod_fld(vs1,iens,enslist, &
  224. 'v_s_htc1', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  225. call io_mod_fld(vs2,iens,enslist, &
  226. 'v_s_htc2', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  227. call io_mod_fld(vs3,iens,enslist, &
  228. 'v_s_htc3', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  229. call io_mod_fld(vs4,iens,enslist, &
  230. 'v_s_htc4', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  231. call io_mod_fld(vs5,iens,enslist, &
  232. 'v_s_htc5', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  233. if (tlevel == -1) then
  234. if (master) then
  235. print *, 'ERROR: io_mod_fld_nex(): failed for "SIFB"'
  236. end if
  237. stop
  238. end if
  239. readfld=(((vi1+vi2+vi3+vi4+vi5) * (1024.0 - 899.5) - 330 * (vs1+vs2+vs3+vs4+vs5)) / &
  240. 1024.0-0.25*(vs1 +vs2+vs3+vs4+vs5))
  241. !readfld=(((vi1+vi2+vi3+vi4+vi5) * (1024.0 - 899.5) - 330 * (vs1+vs2+vs3+vs4+vs5)) / 1024.0 - 0.25 * (vs1+vs2+vs3+vs4+vs5)) / (ai1+ai2+ai3+ai4+ai5)
  242. ! Conversion of models' sea ice thickness and snow thickness to
  243. ! model's freeboard using fixed densities for snow (330 kg/m3), ice
  244. ! (899.5 kg/m3 = average of MYI and FYI from Guerreiro et al. 2017
  245. ! and seawater (1024 kg/m3). The model freeboard is then lowered by
  246. ! 25% of the snow depth to account for the fact that the radar
  247. ! measurement underestimates the actual freeboard due to the lower
  248. ! propagation speed of the wave into the snow than in the air.
  249. ! Everything is converted from grid cell mean to in situ by
  250. ! dividing by concentration (if it is not zero). See exchanges
  251. ! e-mail with Sara Fleury 7 December 2020.
  252. call Generate_element_Si(S(:, iens), unique_obs(iuobs),&
  253. readfld, depths, nx, ny, nz, 0)
  254. end do
  255. elseif (trim(unique_obs(iuobs)) == 'SST') then
  256. do iens = 1, nrens
  257. write(cmem,'(i3.3)') iens
  258. tlevel = 1
  259. call get_mod_fld_new(trim('forecast'//cmem), readfld, iens,&
  260. 'tn', 1, tlevel, nx, ny)
  261. PRINT *, "FRANCOIS"
  262. if (tlevel == -1) then
  263. if (master) then
  264. print *, 'ERROR: get_mod_fld_new(): failed for "SST"'
  265. end if
  266. stop
  267. end if
  268. if (prm_prmestexists('sstb')) then
  269. tlevel = 1
  270. call get_mod_fld_new(trim('forecast'//cmem), field2, iens,&
  271. 'sstb', 0, tlevel, nx, ny)
  272. if (tlevel == -1) then
  273. if (master) then
  274. print *, 'ERROR: get_mod_fld_new(): failed for "sstb"'
  275. end if
  276. stop
  277. end if
  278. readfld = readfld - field2
  279. end if
  280. call Generate_element_Si(S(:, iens), unique_obs(iuobs),&
  281. readfld, depths, nx, ny, nz, 0)
  282. end do
  283. elseif (trim(unique_obs(iuobs)) == 'SLA' .or.&
  284. trim(unique_obs(iuobs)) == 'TSLA') then
  285. if (trim(unique_obs(iuobs)) == 'TSLA') then
  286. call read_mean_ssh(field2, nx, ny)
  287. end if
  288. inquire(iolength=reclSLA) fldr4
  289. ! FANF loop over each day of the week
  290. do t = 0, Wd
  291. if (trim(unique_obs(iuobs)) == 'TSLA') then
  292. write(day,'(i2.2)') t
  293. fname = trim('model_TSSH_'//day//'.uf')
  294. else
  295. fname = 'model_SLA.uf'
  296. endif
  297. if (master) then
  298. print *, 'TSLA, day', t, ': nobs = ',&
  299. count(obs(uobs_begin(iuobs) : uobs_end(iuobs)) % date == t)
  300. end if
  301. do iens = 1, nrens
  302. open(10, file = trim(fname), access = 'direct',&
  303. status = 'old', recl = reclSLA, action = 'read')
  304. read(10, rec = iens, iostat = ios) fldr4
  305. if (ios /= 0) then
  306. if (master) print *, 'Error reading ', trim(fname), ', member #', iens
  307. call stop_mpi()
  308. end if
  309. close(10)
  310. readfld = fldr4
  311. if (prm_prmestexists('msshb')) then
  312. write(cmem,'(i3.3)') iens
  313. tlevel = 1
  314. call get_mod_fld_new(trim('forecast'//cmem), field3, iens,&
  315. 'msshb', 0, tlevel, nx, ny)
  316. if (tlevel == -1) then
  317. if (master) then
  318. print *, 'ERROR: get_mod_fld_new(): failed for "msshb"'
  319. end if
  320. stop
  321. end if
  322. readfld = readfld - field3 ! mean SSH bias for this member
  323. end if
  324. if (trim(unique_obs(iuobs)) == 'TSLA') then
  325. readfld = readfld - field2 ! mean SSH
  326. end if
  327. call Generate_element_Si(S(:, iens), unique_obs(iuobs),&
  328. readfld, depths, nx, ny, nz, t)
  329. end do
  330. if (master) then
  331. print *, 'forming S, day', t
  332. print *, ' # of non-zero ens observations = ', count(S /= 0.0)
  333. print *, ' # of zero ens observations = ', count(S == 0.0)
  334. print *, ' # of non-zero observations for member 1 = ', count(S(:, 1) /= 0.0)
  335. end if
  336. end do
  337. elseif (trim(unique_obs(iuobs)) == 'SAL' .or.&
  338. trim(unique_obs(iuobs)) == 'TEM' .or.&
  339. trim(unique_obs(iuobs)) == 'GSAL' .or.&
  340. trim(unique_obs(iuobs)) == 'GTEM') then
  341. if (master) then
  342. print *, ' Interpolating ensemble vectors to the locations of "',&
  343. trim(unique_obs(iuobs)), '" observations'
  344. end if
  345. !
  346. ! for each ensemble member process all profiles "in parallel",
  347. ! reading the fields layer by layer
  348. !
  349. do iens = 1, nrens
  350. call get_S(S(:, iens), trim(unique_obs(iuobs)), nobs, obs, iens)
  351. end do
  352. if (master) then
  353. print *, ' Interpolation completed'
  354. end if
  355. elseif ((trim(unique_obs(iuobs)) == 'U_ICE') .or. trim(unique_obs(iuobs)) == 'V_ICE') then
  356. do iens = 1, nrens
  357. ! [FM] Read the file
  358. !inquire(iolength=reclDRIFT) modzon, modmer
  359. !open(10, file = 'model_ICEDRIFT.uf', access = 'direct',&
  360. ! status = 'old', recl = reclDRIFT, action = 'read')
  361. !read(10, rec = iens, iostat = ios) modzon, modmer
  362. !close(10)
  363. !if (ios /= 0) then
  364. ! if (master) then
  365. ! print *,'ERROR: could not read ensemble ice drift for member ', iens
  366. ! end if
  367. ! call stop_mpi()
  368. !end if
  369. call io_mod_fld(uice,iens,enslist, &
  370. 'u_ice', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  371. call io_mod_fld(vice,iens,enslist, &
  372. 'v_ice', 1, 0, 1, nx,ny, 'get',FLOAT(obs(1)%date))
  373. do m = 1, nobs
  374. i = obs(m) % i_orig_grid
  375. j = obs(m) % j_orig_grid
  376. if (trim(obs(m) % id) == 'U_ICE') then
  377. S(m, iens) = uice(i, j)
  378. elseif (trim(obs(m) % id) == 'V_ICE') then
  379. S(m, iens) = vice(i, j)
  380. end if
  381. end do
  382. end do
  383. elseif ((trim(unique_obs(iuobs)) == 'U2D_I') .OR. trim(unique_obs(iuobs)) == 'V2D_I' ) THEN
  384. ! ADDED BY FM FRANCOIS MASSONNET. u_ice_2d or v_ice_2d is the sea ice u or v-velocity
  385. ! obtained as follows:
  386. ! 1) Rotate OSISAF Low resolution 2-day sea ice drift in a {east,north}
  387. ! reference frame
  388. ! 2) Interpolate to the ORCA grid
  389. ! 3) Rotate to align with the ORCA grid
  390. ! 4) Multiply by 1000 and divide by 2*86400 to convert the 2-day
  391. ! displacement from km to m/s
  392. DO iens=1,nrens
  393. CALL read_icemod(uice,iens,enslist,'iicevelu',nx,ny)
  394. CALL read_icemod(vice,iens,enslist,'iicevelv',nx,ny)
  395. DO m = 1, nobs
  396. i = obs(m) % i_orig_grid
  397. j = obs(m) % j_orig_grid
  398. IF (trim(obs(m) % id) == 'U2D_I') THEN
  399. S(m,iens) = uice(i,j)
  400. ELSEIF (trim(obs(m) % id) == 'V2D_I') THEN
  401. S(m,iens) = vice(i,j)
  402. END IF
  403. END DO ! nobs
  404. END DO ! iens
  405. elseif ((index(unique_obs(iuobs),'DX') > 0 ) .or. (index(unique_obs(iuobs),'DY') > 0)) then
  406. ! OSISAF Ice drift observations (d-2-offset -> d-offset)
  407. !print *, 'Ice drift observation type: ', unique_obs(iuobs)
  408. offset = unique_obs(iuobs)(3:3)
  409. ! Use offset (1,2,3,4 or 5) to open correct model drift file
  410. inquire(iolength=reclDRIFT) dX, dY
  411. open(10, file = 'model_ICEDRIFT_OSISAF'//offset//'.uf', access = 'direct',&
  412. status = 'old', recl = reclDRIFT, action = 'read')
  413. do iens = 1, nrens
  414. read(10, rec = iens, iostat = ios) dX, dY
  415. if (ios /= 0) then
  416. if (master) then
  417. print *,'ERROR: could not read ensemble ice drift for member ', iens
  418. end if
  419. call stop_mpi()
  420. end if
  421. do m = 1, nobs
  422. i = obs(m) % i_orig_grid
  423. j = obs(m) % j_orig_grid
  424. if (index(obs(m)%id,'DX') > 0) then
  425. S(m, iens) = dX(i, j)
  426. elseif (index(obs(m)%id,'DY') > 0) then
  427. S(m, iens) = dY(i, j)
  428. end if
  429. end do
  430. end do
  431. close(10)
  432. else
  433. if (master) then
  434. print *,'ERROR: unknown obs type ' // trim(unique_obs(iuobs))
  435. end if
  436. call stop_mpi()
  437. end if
  438. end do ! iuobs
  439. ! some generic QC - relax fitting if the model and obs are too far apart
  440. !
  441. call obs_QC(nrens, S)
  442. ! add calculated HA to to observations-<type>.nc files for each data type
  443. !
  444. do iuobs = 1, nuobs
  445. if (master) then
  446. nthisobs = 0
  447. do m = 1, nobs
  448. if (trim(unique_obs(iuobs)) == trim(obs(m) % id)) then
  449. nthisobs = nthisobs + 1
  450. thisobs(nthisobs) = m
  451. end if
  452. end do
  453. ! add forecast values to the observation-<TYPE>.nc files
  454. !
  455. call add_forecast(unique_obs(iuobs), S(thisobs(1 : nthisobs), :), obs(thisobs(1 : nthisobs)))
  456. ! append the superobed values (and modified observation error
  457. ! variances) to the file with pre-processed observations (SAL.nc,
  458. ! TEM.nc, GSAL.nc or GTEM.nc)
  459. !
  460. if (trim(unique_obs(iuobs)) == 'SAL' .or.&
  461. trim(unique_obs(iuobs)) == 'TEM' .or.&
  462. trim(unique_obs(iuobs)) == 'GSAL' .or.&
  463. trim(unique_obs(iuobs)) == 'GTEM') then
  464. call insitu_writeforecast(unique_obs(iuobs), nobs, nrens, S, obs)
  465. end if
  466. end if
  467. end do
  468. if (master) then
  469. print *, 'm_prep_4_EnKF: end calculating S = HA'
  470. end if
  471. x = sum(S, DIM = 2) / real(nrens) ! [ FM ] The mean forecast interpolated in the obs.space
  472. if (master) print*,'m_prep_4_EnKF: end calculating Hx'
  473. if (master) then
  474. print *, 'Hx range = ', minval(x), '-', maxval(x)
  475. print *, 'mean(Hx) = ', sum(x) / real(nobs)
  476. end if
  477. if (master) then
  478. print *, 'observation range = ', minval(obs % d), '-', maxval(obs % d)
  479. print *, 'mean(observation) = ', sum(obs % d) / nobs
  480. end if
  481. ! Compute HA = HE - mean(HE)
  482. !
  483. if (master) print*,'prep_4_EnKF(): calculating S = S - x'
  484. do j = 1, nrens
  485. S(:, j) = S(:, j) - x ! [ FM ] This is really where we switch from actual model data to anomalies
  486. enddo
  487. ! Compute innovation
  488. !
  489. d = obs % d - x ! [ FM ] This is exactly was is also done in add_forecast. This is the mean innovation.
  490. if (master) then
  491. print *, ' innovation range = ', minval(d), '-', maxval(d)
  492. if (minval(d) < -1000.0d0) then
  493. print *, 'm_prep_4_EnKF: error: innovation too small detected'
  494. call stop_mpi()
  495. end if
  496. if (maxval(d) > 1000.0d0) then
  497. print *, 'm_prep_4_EnKF: error: innovation too big detected'
  498. call stop_mpi()
  499. end if
  500. end if
  501. end subroutine prep_4_EnKF
  502. subroutine read_mean_ssh(mean_ssh, nx, ny)
  503. use qmpi
  504. use m_parameters
  505. integer, intent(in) :: nx, ny
  506. real, intent(out):: mean_ssh(nx, ny)
  507. logical :: exists
  508. inquire(file = trim(MEANSSHFNAME), exist = exists)
  509. if (.not. exists) then
  510. if (master) then
  511. print *,'ERROR: read_mean_ssh(): file "', trim(MEANSSHFNAME), '" not found'
  512. end if
  513. stop
  514. end if
  515. open (10, file = trim(MEANSSHFNAME), status = 'unknown',form = 'unformatted', action = 'read')
  516. read (10) mean_ssh
  517. close (10)
  518. end subroutine read_mean_ssh
  519. ! This subroutine adds forecast observations (i.e Hx) to the NetCDF
  520. ! observation files for each data type.
  521. !
  522. subroutine add_forecast(obstag, S, obs)
  523. use mod_measurement
  524. use nfw_mod
  525. implicit none
  526. character(OBSTYPESTRLEN), intent(in) :: obstag
  527. real, dimension(:, :), intent(in) :: S
  528. type(measurement), dimension(:) :: obs
  529. character(STRLEN) :: fname
  530. logical :: exists
  531. integer :: ncid
  532. integer :: dids(2), dimlen
  533. logical :: addsobs
  534. integer :: for_id, inn_id, forvar_id, slon_id, slat_id,&
  535. sdepth_id, sipiv_id, sjpiv_id, sd_id, svar_id,&
  536. newvar_id
  537. real, allocatable, dimension(:) :: x, Svar, innovation
  538. integer :: m, p, o
  539. write(fname, '(a, a, a)') 'observations-', trim(obstag), '.nc'
  540. inquire(file = trim(fname), exist = exists)
  541. if (.not. exists) then
  542. print *, 'file "', trim(fname), 'not found, skip adding forecast'
  543. return
  544. else
  545. print *, 'dumping forecast to "', trim(fname), '"'
  546. end if
  547. p = size(S, DIM = 1)
  548. m = size(S, DIM = 2)
  549. allocate(x(p), Svar(p), innovation(p))
  550. x = sum(S, DIM = 2) / real(m); ! [ FM the mean of S=HA ]
  551. Svar = 0.0
  552. do o = 1, p
  553. Svar(o) = sum((S(o, :) - x(o))** 2) ! [ FM thus each row of Svar is the variance (see below) of the forecast]
  554. end do
  555. Svar = Svar / real(m - 1)
  556. innovation = obs % d - x ! [ FM ] the innovation for the mean forecast (or mean of the innovation forecasts)
  557. addsobs = .false.
  558. call nfw_open(fname, nf_write, ncid)
  559. call nfw_inq_dimid(fname, ncid, 'nobs', dids(1))
  560. call nfw_inq_dimlen(fname, ncid, dids(1), dimlen)
  561. call nfw_redef(fname, ncid)
  562. if (dimlen == p) then
  563. dids(2) = dids(1)
  564. elseif (.not. nfw_dim_exists(ncid, 'nsobs')) then
  565. addsobs = .true.
  566. call nfw_def_dim(fname, ncid, 'nsobs', p, dids(2))
  567. call nfw_def_var(fname, ncid, 'slon', nf_float, 1, dids(2), slon_id)
  568. call nfw_def_var(fname, ncid, 'slat', nf_float, 1, dids(2), slat_id)
  569. call nfw_def_var(fname, ncid, 'sdepth', nf_float, 1, dids(2), sdepth_id)
  570. call nfw_def_var(fname, ncid, 'sipiv', nf_int, 1, dids(2), sipiv_id)
  571. call nfw_def_var(fname, ncid, 'sjpiv', nf_int, 1, dids(2), sjpiv_id)
  572. call nfw_def_var(fname, ncid, 'sd', nf_float, 1, dids(2), sd_id)
  573. call nfw_def_var(fname, ncid, 'svar', nf_float, 1, dids(2), svar_id)
  574. end if
  575. if (.not. nfw_var_exists(ncid, 'innovation')) then
  576. call nfw_def_var(fname, ncid, 'innovation', nf_double, 1, dids(2), inn_id)
  577. else
  578. call nfw_inq_varid(fname, ncid, 'innovation', inn_id)
  579. end if
  580. if (.not. nfw_var_exists(ncid, 'forecast')) then
  581. call nfw_def_var(fname, ncid, 'forecast', nf_double, 1, dids(2), for_id)
  582. else
  583. call nfw_inq_varid(fname, ncid, 'forecast', for_id)
  584. end if
  585. if (.not. nfw_var_exists(ncid, 'forecast_variance')) then
  586. call nfw_def_var(fname, ncid, 'forecast_variance', nf_double, 1, dids(2), forvar_id)
  587. else
  588. call nfw_inq_varid(fname, ncid, 'forecast_variance', forvar_id)
  589. end if
  590. if (.not. addsobs) then
  591. if (dimlen == p) then
  592. if (.not. nfw_var_exists(ncid, 'new_var')) then
  593. call nfw_def_var(fname, ncid, 'new_var', nf_double, 1, dids(2), newvar_id)
  594. else
  595. call nfw_inq_varid(fname, ncid, 'new_var', newvar_id)
  596. end if
  597. else
  598. if (.not. nfw_var_exists(ncid, 'new_svar')) then
  599. call nfw_inq_dimid(fname, ncid, 'nsobs', dids(2))
  600. call nfw_def_var(fname, ncid, 'new_svar', nf_double, 1, dids(2), newvar_id)
  601. else
  602. call nfw_inq_varid(fname, ncid, 'new_svar', newvar_id)
  603. end if
  604. end if
  605. end if
  606. call nfw_enddef(fname, ncid)
  607. call nfw_put_var_double(fname, ncid, forvar_id, Svar)
  608. call nfw_put_var_double(fname, ncid, for_id, x)
  609. call nfw_put_var_double(fname, ncid, inn_id, innovation)
  610. if (addsobs) then
  611. call nfw_put_var_double(fname, ncid, slon_id, obs % lon)
  612. call nfw_put_var_double(fname, ncid, slat_id, obs % lat)
  613. call nfw_put_var_double(fname, ncid, sdepth_id, obs % depth)
  614. call nfw_put_var_int(fname, ncid, sipiv_id, obs % ipiv)
  615. call nfw_put_var_int(fname, ncid, sjpiv_id, obs % jpiv)
  616. call nfw_put_var_double(fname, ncid, sd_id, obs % d)
  617. call nfw_put_var_double(fname, ncid, svar_id, obs % var)
  618. else
  619. call nfw_put_var_double(fname, ncid, newvar_id, obs % var)
  620. end if
  621. call nfw_close(fname, ncid)
  622. deallocate(x)
  623. deallocate(Svar)
  624. deallocate(innovation)
  625. end subroutine add_forecast
  626. end module m_prep_4_EnKF