p_prep_obs_ORCA1.F90 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339
  1. program prep_obs
  2. ! This takes a model restart file, extracts the desired variable
  3. ! and brings into a format that the EnKF V2 can read & treat ('observations.uf').
  4. !
  5. ! !!! AGAIN: THIS USES EnKF VERSION 2 !!!
  6. !
  7. ! Two command line arguments are expected:
  8. ! 1. Path to the nc file of which the data is to be extracted.
  9. ! 2. Variable name that can be found in there.
  10. !
  11. ! Output is written to 'observations.uf'. If lots of files are to be treated,
  12. ! use a shell script to call me and rename output.
  13. !
  14. ! Warning: Currently only the data from the first time step are being read.
  15. ! (No problem with restart files, normally)
  16. !
  17. !
  18. ! TO DO: Add possibility of treating several obs types.
  19. !
  20. !
  21. ! (c) September 2008, Christof König Beatty, Christof.KonigBeatty@uclouvain.be
  22. ! (c) May 2009, generalized by same.
  23. ! (c) Jun 2011, simplified by F. Massonnet
  24. ! (c) April 2016, cleaned by F. Massonnet
  25. use mod_measurement
  26. use netcdf
  27. implicit none
  28. ! NetCDF vars
  29. character(len=99) :: filename, cvarerror, cvarerroru, cvarerrorv
  30. integer :: ncid, ierr, nvar, narg
  31. logical :: ex
  32. character(len=16) :: varname, varnameu, varnamev ! Type of measurement ('a_i_htcX', 'u_ice', 'v_ice', maybe 'v_i_htcX', 'siconc' if model forced by itself)
  33. !!!!!TAG-DEV-AD : change mask-ORCA1.nc into mask-eORCA1.nc
  34. ! character(len=80), parameter :: maskfile = 'mask-ORCA1.nc' !hc!
  35. character(len=80), parameter :: maskfile = 'mask-eORCA1.nc' !hc!
  36. ! Data vars
  37. !!!!!TAG-DEV-AD : adapted coordinate for eORCA1, mlon mlat mx my for model dim
  38. integer, parameter :: mx=360, my=331 ! Unfortunately, still hard coded.
  39. real, dimension(mx,my) :: mlons, mlats
  40. !!!!!TAG-DEV-AD : add OSI-SAF dim = obs dim = ox,oy
  41. integer, parameter :: ox=432, oy=432 ! Unfortunately, still hard coded.
  42. real, dimension(ox,oy) :: olons, olats, errorfld, obsfld, obsfldu, obsfldv, errorfldu, errorfldv
  43. REAL :: obsmin, obsmax, errmin, errmax
  44. REAL :: latmin_NH = 40.0 !76.0 Assim only circle more or less with Svlbard latitudes
  45. REAL :: latmax_NH = 90.0 !82.0
  46. REAL :: latmin_SH = 40.0 ! Same for SH (sign will be added)
  47. REAL :: latmax_SH = 90.0
  48. integer, dimension(mx,my) :: mask
  49. integer :: obscnt, obscnt2, cpt, cptemin, cptemax, cptomin, cptomax ! Counts nr of obs's.
  50. ! Other vars
  51. character(len=99) dummy ! To read cmd line args
  52. ! for loops (haha)
  53. integer :: i, j, varID, icomp
  54. ! Ice thickness category stuff
  55. integer, parameter :: nhtc=5 !hc! nr of ice thickn. cat's
  56. real(KIND=8) :: rdate
  57. ! Obs stuff
  58. type (measurement), allocatable :: obs(:)
  59. ! Need to fill:
  60. ! d (val), var (error var), id (iiceconc etc.), lon, lat, depths,
  61. ! ipic, jpic (i/j-pivot point in grid), ns (support, 0: point meas.),
  62. ! a1-4 (bilin. coeff), status (not used)
  63. narg= iargc()
  64. PRINT *, narg
  65. if (narg<=1) then
  66. ! Write info
  67. write(*,*)
  68. write(*,*) " (prep_obs) takes a real obs, extracts the desired variable and outputs"
  69. write(*,*) " it in a format that the EnKF can read & treat ('observations.uf')."
  70. write(*,*)
  71. write(*,*) " A file named mask.nc containing the variables tmaskutil, nav_lon and nav_lat"
  72. write(*,*) " is expected to be in the current directory (ORCA-file)"
  73. write(*,*)
  74. write(*,*) " Three command line arguments are expected:"
  75. write(*,*) " 1. Path to the nc file of which the data is to be extracted."
  76. write(*,*) " 2. Variable name that can be found in there, 'h_i_htc1' or"
  77. write(*,*) " 'sic'. or dxdy_ice"
  78. write(*,*) " 3. A tag with the date, e.g. 19790520"
  79. write(*,*)
  80. write(*,*) " Hope to see you again soon."
  81. write(*,*)
  82. stop "(prep_obs): Stopped."
  83. end if
  84. ! Command line arguments
  85. nvar=narg-1
  86. ! Get them
  87. call getarg(1, dummy)
  88. read(dummy,'(A)') filename
  89. ! Some parameter checking
  90. inquire(file=trim(filename), exist=ex)
  91. if (.not.ex) then
  92. print *, '(p_prep_obs): file does not exist: '// trim(filename)
  93. stop
  94. end if
  95. ! Get mask, lons & lats
  96. ! open the maskfile
  97. ierr = nf90_open(trim(maskfile),nf90_NoWrite,ncid); if (ierr.ne.nf90_noerr) call handle_err(ierr, "opening mask file")
  98. ! Find VarID of tmask & get values
  99. ierr = nf90_inq_varid(ncid, 'tmask', varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID tmask")
  100. ierr = nf90_get_var(ncid, varID, mask) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable tmaks")
  101. ! Find VarID of longitude & get vals
  102. ierr = nf90_inq_varid(ncid, 'nav_lon', varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID nav_lon")
  103. ierr = nf90_get_var(ncid, varID, mlons) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable nav_lon")
  104. ! Find VarID of latitude & get vals
  105. ierr = nf90_inq_varid(ncid, 'nav_lat', varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID nav_lat")
  106. ierr = nf90_get_var(ncid, varID, mlats) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable nav_lat")
  107. ! Close maskfile
  108. ierr = nf90_close(ncid)
  109. if (ierr.ne.nf90_noerr) call handle_err(ierr, "closing")
  110. allocate( obs(nvar*sum(mask)), STAT=ierr )
  111. if (ierr.ne.0) call handle_err(ierr, "allocating obs") !no netcdf-error! ohwell.
  112. obscnt = 0 ! Keeps track of nr of added obs's.
  113. call getarg(2, dummy)
  114. read(dummy,'(A)') varname
  115. call getarg(3, dummy)
  116. read(dummy,*) rdate
  117. IF ( TRIM(varname) .eq. 'rfb' ) THEN
  118. WRITE(*,*) "Handling ", TRIM(varname)
  119. ! Min and max values for error used to screen the data (any data with
  120. ! standard deviation in between those values will be selected
  121. obsmin = 0.01
  122. obsmax = 10.0
  123. errmin = 0.01
  124. errmax = 1.0
  125. ELSEIF ( TRIM(varname) .eq. 'vt_i') THEN
  126. WRITE(*,*) "Handling ", TRIM(varname)
  127. obsmin = 0.01
  128. obsmax = 50.0
  129. errmin = 0.01
  130. errmax = 1.0
  131. ELSEIF ( TRIM(varname) .eq. 'at_i') THEN
  132. WRITE(*,*) "Handling ", TRIM(varname)
  133. obsmin = 0.001
  134. obsmax = 1.0
  135. errmin = 0.001
  136. errmax = 0.5
  137. ELSEIF ( TRIM(varname) .eq. 'siconc') THEN
  138. WRITE(*,*) "Handling ", TRIM(varname)
  139. obsmin = 0.001
  140. obsmax = 1.0
  141. errmin = 0.001
  142. errmax = 0.5
  143. ELSEIF ( TRIM(varname) .eq. 'ice_conc') THEN ! OSI-SAF-450
  144. WRITE(*,*) "Handling ", TRIM(varname)
  145. obsmin = 0.0
  146. obsmax = 101.0
  147. errmin = 0.0001
  148. errmax = 60.0
  149. ELSE
  150. WRITE(*,*) " (prep_obs) Currently only the variables rfb (sea ice freeboard),"
  151. WRITE(*,*) " vt_i (total sea ice volume)"
  152. WRITE(*,*) " at_i (total sea ice concentration)"
  153. WRITE(*,*) " can be processed "
  154. STOP "(prep_obs) Aborted"
  155. ENDIF
  156. ! User info
  157. WRITE(*,*) "(prep_obs) Extracting "//TRIM(varname)//" from "//TRIM(filename)
  158. ! Some preparations
  159. obsfld=0.
  160. ! open the netCDF file
  161. ierr = nf90_open(trim(filename),nf90_NoWrite,ncid) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "opening")
  162. ! Read observation data
  163. ! Find VarID of longitude & get vals from obs
  164. ierr = nf90_inq_varid(ncid, 'lon', varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID lon obs")
  165. ierr = nf90_get_var(ncid, varID, olons) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable lon obs")
  166. ! Find VarID of latitude & get vals
  167. ierr = nf90_inq_varid(ncid, 'lat', varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID lat obs")
  168. ierr = nf90_get_var(ncid, varID, olats) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable lat obs")
  169. ! Find VarID of varname (variable to assim)
  170. WRITE(*,*) "varname="//trim(varname)
  171. ierr = nf90_inq_varid(ncid, trim(varname), varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID obs")
  172. ! get values
  173. ierr = nf90_get_var(ncid, varID, obsfld) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting var in obs")
  174. WRITE(*,*) "OK var"//trim(varname)
  175. ! Find VarID of varname (error)
  176. cvarerror=TRIM(varname)//'_sd'
  177. WRITE(*,*) "cvarerror="//trim(varname)//"_sd"
  178. ierr = nf90_inq_varid(ncid, cvarerror, varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID obs")
  179. !! get values
  180. ierr = nf90_get_var(ncid, varID, errorfld) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting error var obs")
  181. ! Close file
  182. ierr = nf90_close(ncid) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "closing")
  183. ! User info - ADAPT ACCORDINGLY
  184. WRITE (*,*) " (prep_obs) Using data >40N and <45S"
  185. obscnt2=0
  186. cpt=0
  187. cptemin=0
  188. cptemax=0
  189. cptomin=0
  190. cptomax=0
  191. WRITE(*,*) 'obs min:',obsmin,'obs max:',obsmax,'err min:',errmin,'err max:',errmax
  192. ! Loop over space
  193. DO i = 1, SIZE(olats, 1)
  194. DO j = 1, SIZE(olats, 2)
  195. IF (obsfld(i,j) .GT. 0.0 ) THEN
  196. cpt = cpt + 1
  197. !WRITE(*,*) 'error(i,j): ', i, j, errorfld(i,j)
  198. !WRITE(*,*) 'obs(i,j): ',i,j, obsfld(i,j)
  199. !WRITE(*,*) 'obs: ', (obsfld(i,j))
  200. END IF
  201. ! Pick out ocean points where data is existent
  202. !IF ( (errorfld(i,j)) .GT. errmin &
  203. ! .AND. (errorfld(i,j)) .LT. errmax &
  204. ! .AND. obsfld(i,j) .GT. obsmin &
  205. ! .AND. obsfld(i,j) .LT. obsmax &
  206. ! ) THEN
  207. IF ( (errorfld(i,j)**2) .GT. (errmin**2) ) THEN
  208. cptemin = cptemin + 1
  209. WRITE(*,*) 'error: ', errmin**2, (errorfld(i,j)**2), errmax**2
  210. PAUSE
  211. IF ( (errorfld(i,j)**2) .LT. errmax**2 ) THEN
  212. cptemax = cptemax + 1
  213. !IF ( (obsfld(i,j)) .GT. obsmin ) THEN
  214. ! cptomin = cptomin + 1
  215. ! IF ( (obsfld(i,j)) .LT. obsmax ) THEN
  216. ! cptomax = cptomax + 1
  217. ! .AND. (errorfld(i,j)) .LT. errmax &
  218. ! .AND. obsfld(i,j) .GT. obsmin &
  219. ! .AND. obsfld(i,j) .LT. obsmax &
  220. ! ) THEN
  221. obscnt2 = obscnt2 + 1
  222. ! Limit 'obs' spatially
  223. IF ( ( olats(i,j) .GE. latmin_NH &
  224. .AND. olats(i,j) .LE. latmax_NH ) &
  225. .OR.( olats(i,j) .LE. (-latmin_SH) &
  226. .AND. olats(i,j) .GE. (-latmax_SH) ) &
  227. ) THEN
  228. obscnt = obscnt + 1
  229. obs(obscnt)%d = obsfld(i,j)
  230. obs(obscnt)%lon = olons(i,j)
  231. obs(obscnt)%lat = olats(i,j)
  232. obs(obscnt)%ipiv = i ! the i-point of the grid of the model
  233. obs(obscnt)%jpiv = j ! the j-point of the grid of the model
  234. ! Put other data into obs type array
  235. obs(obscnt)%var = (errorfld(i,j))**2 ! The variance
  236. obs(obscnt)%id = TRIM(varname)
  237. obs(obscnt)%depths = 0
  238. obs(obscnt)%ns = 0
  239. obs(obscnt)%a1 = 1
  240. obs(obscnt)%a2 = 0
  241. obs(obscnt)%a3 = 0
  242. obs(obscnt)%a4 = 0
  243. obs(obscnt)%status = .TRUE.
  244. obs(obscnt)%i_orig_grid = -1
  245. obs(obscnt)%j_orig_grid = -1
  246. obs(obscnt)%h = -1.0
  247. obs(obscnt)%date = rdate
  248. obs(obscnt)%orig_id = 0
  249. END IF ! err max
  250. END IF ! Spatial selection
  251. END IF ! if valid point
  252. END DO ! j
  253. END DO ! i
  254. WRITE(*,*) 'Nb obscnt: ', obscnt
  255. WRITE(*,*) 'Nb obscnt2: ', obscnt2
  256. WRITE(*,*) 'Compteur obs > 0: ', cpt
  257. WRITE(*,*) 'Compteur t err min: ', cptemin
  258. WRITE(*,*) 'Compteur t err max: ', cptemax
  259. WRITE(*,*) 'Compteur t obs min: ', cptomin
  260. WRITE(*,*) 'Compteur t obs max: ', cptomax
  261. !Write data:
  262. INQUIRE(iolength=i)obs(1)
  263. OPEN (11, file='observations.uf', status='replace',form='unformatted', access='direct', recl=i)
  264. DO j = 1, obscnt
  265. WRITE(11, rec=j)obs(j)
  266. ENDDO
  267. CLOSE(11)
  268. ! Write data to textfile, for visual checking
  269. OPEN(12, file = 'observations.txt')
  270. DO j = 1, obscnt
  271. WRITE(12, FMT = 53) obs(j)
  272. 53 FORMAT(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)
  273. ENDDO
  274. CLOSE(12)
  275. ! Tell user how many obs there were
  276. WRITE(*,*) " (prep_obs) Wrote out this many obs: ", obscnt
  277. WRITE(*,*) " (prep_obs) Number of ocean points : ", sum(mask)
  278. ! Cleanup
  279. IF (allocated(obs)) deallocate(obs,STAT=ierr)
  280. WRITE(*,*) ' (prep_obs) End successfully reached'; WRITE(*,*)
  281. contains
  282. subroutine handle_err(status, infomsg)
  283. integer, intent ( in) :: status
  284. character(len = *), intent ( in), optional :: infomsg
  285. if(status /= nf90_noerr) then
  286. if (present(infomsg)) then
  287. print *, '(prep_obs) Error while '//infomsg//' - '//trim(nf90_strerror(status))
  288. else
  289. print *, trim(nf90_strerror(status))
  290. endif ! opt arg
  291. print *,'(prep_obs)'
  292. stop
  293. end if ! check error status
  294. end subroutine handle_err
  295. end program prep_obs