m_obs.F90 9.6 KB

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