m_obs.f90 12 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437
  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_obs.F90
  10. !
  11. ! Created: 6 Feb 2008
  12. !
  13. ! Last modified: 21 Feb 2008
  14. !
  15. ! Author: Pavel Sakov*
  16. ! NERSC
  17. !
  18. ! Purpose: Generic code to deal with observations.
  19. !
  20. ! Description: This module contains the following functions and subroutines:
  21. ! - obs_setobs
  22. ! reads the observations into allocatable array obs(nobs)
  23. ! of type(measurement)
  24. ! - obs_prepareobs
  25. ! conducts state-dependent pre-processing of observations
  26. ! - obs_prepareuobs
  27. ! conducts state-dependent pre-processing of observations
  28. ! of a given type
  29. ! It also contains the following data:
  30. ! - obs
  31. ! allocatable array of type(measurement)
  32. ! - nobs
  33. ! number of observations (may differ from the size of the
  34. ! array)
  35. !
  36. ! * This file contains some modified code of unknown origin
  37. ! from EnKF package. In particular, the code here supersedes
  38. ! the code from:
  39. ! m_get_nrobs_d.F90
  40. ! m_get_obs_d.F90
  41. !
  42. ! Modifications:
  43. ! 09/11/2012 Geir Arne Waagbo:
  44. ! -- Added support for OSISAF ice drift obs
  45. ! 29/07/2010 PS:
  46. ! -- modified obs_QC(). The maximal increment now does not go to
  47. ! 0 as the innovation increases, but rather is limited by
  48. ! KMAX * sigma_ens
  49. ! 29/06/2010 PS:
  50. ! -- added obs_QC()
  51. ! 26/02/2008 PS:
  52. ! -- put "obs" and "nobs" as public data in this module
  53. ! 15/03/2024 Alison Delhasse:
  54. ! -- Add fake Obs : SICONC from NEMO itself.
  55. module m_obs
  56. use qmpi
  57. use mod_measurement
  58. use m_uobs
  59. use m_insitu
  60. implicit none
  61. !
  62. ! public stuff
  63. !
  64. integer, public :: nobs = -1
  65. type(measurement), allocatable, dimension(:), public :: obs
  66. public obs_readobs
  67. public obs_prepareobs
  68. public obs_QC
  69. !
  70. ! private stuff
  71. !
  72. private obs_testrange
  73. integer, parameter, private :: STRLEN = 512
  74. real, parameter, private :: TEM_MIN = -2.0d0
  75. real, parameter, private :: TEM_MAX = 50.0d0
  76. real, parameter, private :: SAL_MIN = 2.0d0
  77. real, parameter, private :: SAL_MAX = 40.0d0
  78. real, parameter, private :: SSH_MIN = -3.0d0
  79. real, parameter, private :: SSH_MAX = 3.0d0
  80. real, parameter, private :: ICEC_MIN = 0.0d0
  81. real, parameter, private :: ICEC_MAX = 0.999d0 ! [FM] Changed from 0.996 to 0.999
  82. real, parameter, private :: RFB_MIN = 0.0d0 ! FM 2020
  83. real, parameter, private :: RFB_MAX = 10.0d0
  84. real, parameter, private :: VT_I_MIN = 0.0d0 ! FM 2020
  85. real, parameter, private :: VT_I_MAX = 10.0d0
  86. real, parameter, private :: UVICE_MIN = -100.0
  87. real, parameter, private :: UVICE_MAX = 100.0
  88. private obs_prepareuobs, obs_realloc
  89. contains
  90. ! Obtain observations to be used for assimilation from the file
  91. ! "observation.uf". Store the number of observations in "nobs" and the data
  92. ! in the array "obs".
  93. !
  94. subroutine obs_readobs
  95. use m_parameters
  96. logical :: exists = .false.
  97. type(measurement) :: record
  98. integer :: rsize
  99. integer :: ios
  100. integer :: o
  101. CHARACTER(LEN=*), PARAMETER :: &
  102. FMT2 = "(f8.4,X,f8.4,X,a8,X,2(f10.5,X),f4.2,X,2(I3,X),I1,X,4(f5.2,X),L,X,2(I3,X),f5.2,X,I8,X,I1)"
  103. real :: myX
  104. real :: myY
  105. !========== TEST
  106. ! inquire(iolength = rsize) record
  107. ! !open(10, file = 'test.txt', form = 'unformatted',&
  108. ! ! access = 'direct', recl = rsize, status = 'old')
  109. ! allocate(obs(2))
  110. ! open(10, file = 'observations.txt')!, form = 'unformatted',&
  111. ! !access = 'direct', recl = rsize, status = 'old')
  112. ! !read(10, *) obs(1)
  113. !
  114. ! do o = 1, 2
  115. ! read(10, *) obs(o)
  116. ! PRINT *, obs(o)
  117. ! end do
  118. ! close(10)
  119. ! stop
  120. !==========
  121. if (nobs >= 0) then
  122. return
  123. end if
  124. ! Testing existence of file
  125. inquire(file = 'observations.txt', exist = exists)
  126. !inquire(file = 'observations.uf', exist = exists)
  127. if (.not. exists) then
  128. if (master) then
  129. print *, 'ERROR: obs_getnobs(): file "observations.txt" does not exist'
  130. end if
  131. stop
  132. end if
  133. inquire(iolength = rsize) record
  134. open(10, file = 'observations.txt')!, form = 'unformatted',&
  135. ! EXPERIMENTAL
  136. !open(10, file = 'observations.uf', form = 'unformatted',&
  137. ! access = 'direct', recl = rsize, status = 'old')!, form = 'unformatted',&
  138. !access = 'direct', recl = rsize, status = 'old')
  139. ! END EXPERIMENTAL
  140. ! I guess there is no other way to work out the length other than read the
  141. ! file in fortran - PS
  142. !
  143. o = 1
  144. do while (.true.)
  145. read(10, *, iostat = ios) record
  146. if (ios /= 0) then
  147. nobs = o - 1
  148. exit
  149. end if
  150. o = o + 1
  151. enddo
  152. allocate(obs(nobs))
  153. ! PS - there were problem with using rewind(): g95 reported:
  154. ! "Cannot REWIND a file opened for DIRECT access". Therefore reopen.
  155. !
  156. close(10)
  157. open(10, file = 'observations.txt')!, form = 'unformatted',&
  158. ! BEGIN EXPERIMENTAL
  159. !open(10, file = 'observations.uf', form = 'unformatted',&
  160. ! access = 'direct', recl = rsize, status = 'old')
  161. ! -- END EXPERIMENTAL
  162. do o = 1, nobs
  163. read(10, *) obs(o)
  164. call ucase(obs(o) % id)
  165. !PRINT *, obs(o)
  166. enddo
  167. close(10)
  168. if (RFACTOR1 /= 1.0d0) then
  169. do o = 1, nobs
  170. obs(o) % var = obs(o) % var * RFACTOR1
  171. end do
  172. end if
  173. call uobs_get(obs % id, nobs, master)
  174. call obs_testrange
  175. end subroutine obs_readobs
  176. subroutine obs_testrange
  177. integer :: o, uo, nbad
  178. real :: dmin, dmax
  179. if (master) then
  180. print '(a)', ' EnKF: testing range for each type of obs '
  181. end if
  182. do uo = 1, nuobs
  183. if (trim(unique_obs(uo)) == 'SST' .or. trim(unique_obs(uo)) == 'TEM'&
  184. .or. trim(unique_obs(uo)) == 'GTEM') then
  185. dmin = TEM_MIN
  186. dmax = TEM_MAX
  187. elseif (trim(unique_obs(uo)) == 'SAL'&
  188. .or. trim(unique_obs(uo)) == 'GSAL') then
  189. dmin = SAL_MIN
  190. dmax = SAL_MAX
  191. elseif (trim(unique_obs(uo)) == 'SLA'&
  192. .or. trim(unique_obs(uo)) == 'TSLA'&
  193. .or. trim(unique_obs(uo)) == 'SSH') then
  194. dmin = SSH_MIN
  195. dmax = SSH_MAX
  196. elseif (trim(unique_obs(uo)) == 'ICEC') then
  197. dmin = ICEC_MIN
  198. dmax = ICEC_MAX
  199. elseif (trim(unique_obs(uo)) == 'AT_I'& ! [FM] Added as we assimilate total ice conc. (opposed to indiv. category
  200. .or. trim(unique_obs(uo)) == 'SICON'&
  201. .or. trim(unique_obs(uo)) == 'SIC') then ! [AD] Test EnKF with NEMO assimilating itself (total si conc. = siconc)
  202. print *, 'm_obs: ', trim(unique_obs(uo)), ' will be assim'
  203. dmin = ICEC_MIN
  204. dmax = ICEC_MAX
  205. elseif (trim(unique_obs(uo)) == 'RFB') then ! FM added 2020
  206. dmin = RFB_MIN
  207. dmax = RFB_MAX
  208. elseif (trim(unique_obs(uo)) == 'VT_I') then ! FM added 2021
  209. dmin = VT_I_MIN
  210. dmax = VT_I_MAX
  211. elseif (trim(unique_obs(uo)) == 'V_ICE'&
  212. .or. trim(unique_obs(uo)) == 'U_ICE') then
  213. dmin = UVICE_MIN
  214. dmax = UVICE_MAX
  215. elseif (trim(unique_obs(uo)) == 'U2D_I'& ! [FM] OSISAF 2-day sea ice drift converted to m/s and interpolated onto ORCA
  216. .OR. trim(unique_obs(uo)) == 'V2D_I') THEN
  217. dmin = UVICE_MIN
  218. dmax = UVICE_MAX
  219. elseif ((index(trim(unique_obs(uo)),'DX') .gt. 0) &
  220. .or. (index(trim(unique_obs(uo)),'DY') .gt. 0)) then
  221. ! The type can be DX1,DX2,..,DX5,DY1,..DY5
  222. dmin = UVICE_MIN
  223. dmax = UVICE_MAX
  224. else
  225. dmin = -1.0d6
  226. dmax = 1.0d6
  227. print *, 'ERROR: obs_testrange(): "', trim(unique_obs(uo)), '": unknown type'
  228. stop
  229. end if
  230. nbad = 0
  231. do o = uobs_begin(uo), uobs_end(uo)
  232. if (obs(o) % status .and.&
  233. (obs(o) % d < dmin .or. obs(o) % d > dmax)) then
  234. obs(o) % status = .false.
  235. nbad = nbad + 1
  236. end if
  237. end do
  238. if (master) then
  239. print '(a, a, a, i6, a)', ' ', trim(unique_obs(uo)), ': ', nbad, ' outliers'
  240. end if
  241. end do
  242. if (master) then
  243. print *
  244. end if
  245. end subroutine obs_testrange
  246. ! Prepare observations before allocating matrices S, D, and A in EnKF().
  247. ! This invloves mainly thinning, superobing, or sorting.
  248. !
  249. ! Note that generically this processing can not be completely outsourced
  250. ! to the preprocessing stage, at least for in-situ data, because its thinning
  251. ! involves reading ensemble members for layer depth information.
  252. !
  253. subroutine obs_prepareobs()
  254. implicit none
  255. integer :: iuobs
  256. if (master) then
  257. print '(a)', ' EnKF: preparing observations'
  258. end if
  259. do iuobs = 1, nuobs
  260. call obs_prepareuobs(trim(unique_obs(iuobs)))
  261. end do
  262. ! calculate again the number of observation of each type (that could change
  263. ! in prepare_obs)
  264. call uobs_get(obs % id, nobs, master)
  265. end subroutine obs_prepareobs
  266. ! Prepare (thin, superob) observations of type "obstag".
  267. !
  268. subroutine obs_prepareuobs(obstag)
  269. character(*), intent(in) :: obstag
  270. character(STRLEN) :: fname
  271. if (trim(obstag) == 'SAL' .or. trim(obstag) == 'TEM' .or.&
  272. trim(obstag) == 'GSAL' .or. trim(obstag) == 'GTEM') then
  273. call insitu_prepareobs(trim(obstag), nobs, obs)
  274. if (master) then
  275. write(fname, '(a, ".nc")') trim(obstag)
  276. print *, 'Writing "', trim(obstag), '" obs to be assimilated to "',&
  277. trim(fname), '"'
  278. call insitu_writeprofiles(fname, trim(obstag), nobs, obs);
  279. end if
  280. else
  281. ! do nothing for obs of other types for now
  282. end if
  283. call obs_realloc
  284. end subroutine obs_prepareuobs
  285. subroutine obs_realloc()
  286. type(measurement), allocatable :: newobs(:)
  287. if (nobs < 0 .or. nobs == size(obs)) then
  288. return
  289. end if
  290. allocate(newobs(nobs))
  291. newobs = obs(1 : nobs)
  292. deallocate(obs)
  293. allocate(obs(nobs))
  294. obs = newobs
  295. deallocate(newobs)
  296. end subroutine obs_realloc
  297. subroutine obs_QC(m, S)
  298. use m_parameters
  299. implicit none
  300. integer :: m
  301. real :: S(nobs, m)
  302. integer :: nmodified(nuobs)
  303. real :: so(m), smean, svar
  304. integer :: o, uo
  305. real :: ovar, inn, newovar
  306. if (master) then
  307. print *, 'Starting generic observation QC'
  308. end if
  309. nmodified = 0
  310. do uo = 1, nuobs
  311. do o = uobs_begin(uo), uobs_end(uo)
  312. so = S(o, :);
  313. smean = sum(so) / m ! must be 0...
  314. svar = sum((so - smean) ** 2) / real(m - 1)
  315. ovar = obs(o) % var
  316. inn = obs(o) % d - smean
  317. obs(o) % var = sqrt((svar + ovar) ** 2 +&
  318. svar * (inn / KFACTOR) ** 2) - svar
  319. if (svar > 0 .and. obs(o) % var / ovar > 2.0d0) then
  320. nmodified(uo) = nmodified(uo) + 1
  321. end if
  322. end do
  323. end do
  324. if (master) then
  325. do uo = 1, nuobs
  326. print *, ' ', trim(unique_obs(uo)), ':'
  327. print *, ' # of observations:', uobs_end(uo) - uobs_begin(uo) + 1
  328. print *, ' (of them) substantially modified:', nmodified(uo)
  329. end do
  330. end if
  331. end subroutine obs_QC
  332. end module m_obs