p_prep_obs_ORCA25.f90 8.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294
  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. # 9 "<stdin>"
  9. program prep_obs
  10. ! This takes a model restart file, extracts the desired variable
  11. ! and brings into a format that the EnKF V2 can read & treat ('observations.uf').
  12. !
  13. ! !!! AGAIN: THIS USES EnKF VERSION 2 !!!
  14. !
  15. ! Two command line arguments are expected:
  16. ! 1. Path to the nc file of which the data is to be extracted.
  17. ! 2. Variable name that can be found in there.
  18. !
  19. ! Output is written to 'observations.uf'. If lots of files are to be treated,
  20. ! use a shell script to call me and rename output.
  21. !
  22. ! Warning: Currently only the data from the first time step are being read.
  23. ! (No problem with restart files, normally)
  24. !
  25. !
  26. ! TO DO: Add possibility of treating several obs types.
  27. !
  28. !
  29. ! (c) September 2008, Christof König Beatty, Christof.KonigBeatty@uclouvain.be
  30. ! (c) May 2009, generalized by same.
  31. ! (c) Jun 2011, simplified by F. Massonnet
  32. ! (c) April 2016, cleaned by F. Massonnet
  33. use mod_measurement
  34. use netcdf
  35. implicit none
  36. ! NetCDF vars
  37. character(len=99) :: filename, cvarerror, cvarerroru, cvarerrorv
  38. integer :: ncid, ierr, nvar, narg
  39. logical :: ex
  40. character(len=16) :: varname, varnameu, varnamev ! Type of measurement ('a_i_htcX', 'u_ice', 'v_ice', maybe 'v_i_htcX')
  41. character(len=80), parameter :: maskfile = 'mask-ORCA25.nc' !hc!
  42. ! Data vars
  43. integer, parameter :: nx=1442, ny=1050 ! Unfortunately, still hard coded.
  44. real, dimension(nx,ny) :: lons, lats, obsfld, errorfld, obsfldu, obsfldv, errorfldu, errorfldv
  45. integer, dimension(nx,ny) :: mask
  46. integer :: obscnt ! Counts nr of obs's.
  47. ! Other vars
  48. character(len=99) dummy ! To read cmd line args
  49. ! for loops (haha)
  50. integer :: i, j, varID, icomp
  51. ! Ice thickness category stuff
  52. integer, parameter :: nhtc=5 !hc! nr of ice thickn. cat's
  53. real(KIND=8) :: rdate
  54. ! Obs stuff
  55. type (measurement), allocatable :: obs(:)
  56. ! Need to fill:
  57. ! d (val), var (error var), id (iiceconc etc.), lon, lat, depths,
  58. ! ipic, jpic (i/j-pivot point in grid), ns (support, 0: point meas.),
  59. ! a1-4 (bilin. coeff), status (not used)
  60. narg= iargc()
  61. PRINT *, narg
  62. if (narg<=1) then
  63. ! Write info
  64. write(*,*)
  65. write(*,*) " (prep_obs) takes a real obs, extracts the desired variable and outputs"
  66. write(*,*) " it in a format that the EnKF can read & treat ('observations.uf')."
  67. write(*,*)
  68. write(*,*) " A file named mask.nc containing the variables tmaskutil, nav_lon and nav_lat"
  69. write(*,*) " is expected to be in the current directory (ORCA-file)"
  70. write(*,*)
  71. write(*,*) " Three command line arguments are expected:"
  72. write(*,*) " 1. Path to the nc file of which the data is to be extracted."
  73. write(*,*) " 2. Variable name that can be found in there, 'h_i_htc1' or"
  74. write(*,*) " 'sic'. or dxdy_ice"
  75. write(*,*) " 3. A tag with the date, e.g. 19790520"
  76. write(*,*)
  77. write(*,*) " Hope to see you again soon."
  78. write(*,*)
  79. stop "(prep_obs): Stopped."
  80. end if
  81. ! Command line arguments
  82. nvar=narg-1
  83. ! Get them
  84. call getarg(1, dummy)
  85. read(dummy,'(A)') filename
  86. ! Some parameter checking
  87. inquire(file=trim(filename), exist=ex)
  88. if (.not.ex) then
  89. print *, '(p_prep_obs): file does not exist: '// trim(filename)
  90. stop
  91. end if
  92. ! Get mask, lons & lats
  93. ! open the maskfile
  94. ierr = nf90_open(trim(maskfile),nf90_NoWrite,ncid); if (ierr.ne.nf90_noerr) call handle_err(ierr, "opening mask file")
  95. ! Find VarID of tmask & get values
  96. ierr = nf90_inq_varid(ncid, 'tmask', varID); if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID tmask")
  97. ierr = nf90_get_var(ncid, varID, mask) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable tmaks")
  98. ! Find VarID of longitude & get vals
  99. ierr = nf90_inq_varid(ncid, 'nav_lon', varID); if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID nav_lon")
  100. ierr = nf90_get_var(ncid, varID, lons) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable nav_lon")
  101. ! Find VarID of latitude & get vals
  102. ierr = nf90_inq_varid(ncid, 'nav_lat', varID); if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID nav_lat")
  103. ierr = nf90_get_var(ncid, varID, lats) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable nav_lat")
  104. ! Close maskfile
  105. ierr = nf90_close(ncid)
  106. if (ierr.ne.nf90_noerr) call handle_err(ierr, "closing")
  107. allocate( obs(nvar*sum(mask)), STAT=ierr )
  108. if (ierr.ne.0) call handle_err(ierr, "allocating obs") !no netcdf-error! ohwell.
  109. obscnt = 0 ! Keeps track of nr of added obs's.
  110. call getarg(2, dummy)
  111. read(dummy,'(A)') varname
  112. call getarg(3, dummy)
  113. read(dummy,*) rdate
  114. if ( trim(varname).ne.'sic' ) then
  115. write(*,*) ' (prep_obs) Currently only the total sea ice concentration'
  116. write(*,*) ' sic can be processed '
  117. stop " (prep_obs) Aborted"
  118. endif
  119. ! User info
  120. write(*,*) ' (prep_obs) Extracting '//trim(varname)//' from '//trim(filename)
  121. ! Some preparations
  122. obsfld=0.
  123. ! open the netCDF file
  124. ierr = nf90_open(trim(filename),nf90_NoWrite,ncid) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "opening")
  125. ! Read observation data
  126. ! Find VarID of varname
  127. ierr = nf90_inq_varid(ncid, trim(varname), varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID")
  128. ! get values
  129. ierr = nf90_get_var(ncid, varID, obsfld) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable")
  130. ! Find VarID of varname
  131. cvarerror='error_'//varname
  132. ierr = nf90_inq_varid(ncid, cvarerror, varID) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "inquiring varID")
  133. ! get values
  134. ierr = nf90_get_var(ncid, varID, errorfld) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "getting variable")
  135. ! Close file
  136. ierr = nf90_close(ncid) ; if (ierr.ne.nf90_noerr) call handle_err(ierr, "closing")
  137. ! User info - ADAPT ACCORDINGLY
  138. write (*,*) " (prep_obs) Using data >40N and <45S"
  139. ! Loop over space
  140. do i=1,size(mask,1)
  141. do j=1,size(mask,2)
  142. ! Pick out ocean points where data is existent
  143. if ( errorfld(i,j) .GE. 1.0 ) then
  144. ! Limit 'obs' to >40°N or <45°S
  145. if ( (lats(i,j).ge.40) .or. (lats(i,j).le.-45) ) then
  146. obscnt = obscnt + 1
  147. obs(obscnt)%d = obsfld(i,j)/100.0
  148. obs(obscnt)%lon = lons(i,j)
  149. obs(obscnt)%lat = lats(i,j)
  150. obs(obscnt)%ipiv = i ! the i-point of the grid of the model
  151. obs(obscnt)%jpiv = j ! the j-point of the grid of the model
  152. ! Put other data into obs type array
  153. obs(obscnt)%var = (errorfld(i,j)/100.0)**2 ! The variance
  154. obs(obscnt)%id = TRIM(varname)
  155. obs(obscnt)%depths = 0
  156. obs(obscnt)%ns = 0
  157. obs(obscnt)%a1 = 1
  158. obs(obscnt)%a2 = 0
  159. obs(obscnt)%a3 = 0
  160. obs(obscnt)%a4 = 0
  161. obs(obscnt)%status = .TRUE.
  162. obs(obscnt)%i_orig_grid = -1
  163. obs(obscnt)%j_orig_grid = -1
  164. obs(obscnt)%h = -1.0
  165. obs(obscnt)%date = rdate
  166. obs(obscnt)%orig_id = 0
  167. end if ! >40°N or <50°S
  168. end if ! ocean point
  169. end do ! j
  170. end do ! i
  171. !Write data:
  172. inquire(iolength=i)obs(1)
  173. open (11, file='observations.uf', status='replace',form='unformatted', access='direct', recl=i)
  174. do j=1,obscnt
  175. write(11,rec=j)obs(j)
  176. enddo
  177. close(11)
  178. PRINT *, rdate
  179. ! !XXX:
  180. ! ! Write data to textfile, for visual checking
  181. open(12, file='observations.txt')
  182. do j=1,obscnt
  183. write(12,FMT=53) obs(j)
  184. 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)
  185. enddo
  186. close(12)
  187. ! !:XXX
  188. ! Tell user how many obs there were
  189. write(*,*) " (prep_obs) Wrote out this many obs: ", obscnt
  190. write(*,*) " (prep_obs) Number of ocean points : ", sum(mask)
  191. ! Cleanup
  192. if (allocated(obs)) deallocate(obs,STAT=ierr)
  193. write(*,*) ' (prep_obs) End successfully reached'; write(*,*)
  194. contains
  195. subroutine handle_err(status, infomsg)
  196. integer, intent ( in) :: status
  197. character(len = *), intent ( in), optional :: infomsg
  198. if(status /= nf90_noerr) then
  199. if (present(infomsg)) then
  200. print *, '(prep_obs) Error while '//infomsg//' - '//trim(nf90_strerror(status))
  201. else
  202. print *, trim(nf90_strerror(status))
  203. endif ! opt arg
  204. print *,'(prep_obs)'
  205. stop
  206. end if ! check error status
  207. end subroutine handle_err
  208. end program prep_obs