assim.F90 17 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442
  1. ! First include the set of model-wide compiler flags
  2. #include "tm5.inc"
  3. ! Macro
  4. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  5. #define TRACEBACK write (gol,'("in ",a," (",a,i6,")")') rname, __FILE__, __LINE__ ; call goErr
  6. #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if
  7. ! integer, parameter :: sp = selected_real_kind(6, 37)
  8. ! integer, parameter :: dp = selected_real_kind(15, 307)
  9. !=====================================================================
  10. !
  11. ! Central NO2 column data assimilation module
  12. !
  13. ! Interface call by TM5 (in assim_interface_mod.f90):
  14. !
  15. ! call AssimNO2( ntimestep )
  16. !
  17. ! The subroutine AssimNO2 performs a data assimilation time step.
  18. !
  19. ! Henk Eskes, KNMI, January 2003
  20. ! Version 1.0 - Februari 2003
  21. !
  22. ! J.D. Maasakkers, KNMI, July 2013
  23. ! Prototype v3 - July 2013
  24. !
  25. ! Henk Eskes, Mark ter Linden, KNMI, Mar-Sep 2015
  26. ! Interface to TM5-mp-CB05 and to TROPOMI
  27. !======================================================================
  28. module MAssimilation
  29. ! printing, error handling
  30. use GO, only : gol, goPr, goErr
  31. ! NO2 AMF lookup table
  32. use MTAmf, only : TAmfLut
  33. implicit none
  34. private
  35. public :: AssimNO2
  36. !-------------------------------------------------------------
  37. ! integer to count the number of calls to the routine "AssimNO2"
  38. integer :: callcount = 0
  39. integer :: assimcount = 0
  40. ! module name
  41. character(len=*), parameter :: mname = 'MAssimilation'
  42. ! keep filenames in memory
  43. character(256) :: filename_S5P_L2_NO2_filelist
  44. ! character(256) :: terrain_filename
  45. character(256) :: amf_filename
  46. logical :: divideByAMFGeo
  47. ! output directory for OmF netcdf files
  48. character(256) :: outputdir
  49. ! NO2 AMF lookup table (keep in memory)
  50. type(TAmfLut) :: amfLut
  51. ! If true, call the retrieval for both forecast and analysis fields
  52. logical :: computeRetrievalForAnalysis
  53. ! Switch: optional to write OmF information to separate netcdf file
  54. logical :: doWriteOmF
  55. ! Debug: extra retrieval output
  56. logical :: debugMode
  57. contains
  58. subroutine AssimNO2( rcFile, ntimestep, TM5Data, nObs, noxscaling, status )
  59. !======================================================================
  60. !
  61. ! Assimilation of NO2 slant column data
  62. ! Main routine from where all assimilation routines are called
  63. !
  64. ! rcFile : name of the rc (settings) file
  65. ! ntimestep : timestep in seconds between calls to AssimNO2
  66. ! TM5Data : All TM5 fields and grid info from the interface module
  67. ! nObs : nr. of observations assimilated in this timestep
  68. ! noxscaling : an/fc ratio for the TM5 NOx transported field
  69. ! Henk Eskes, KNMI, 2000-2002-2015
  70. !======================================================================
  71. ! --- TM5 interfaces ---
  72. ! TM5 model arrays and variables:
  73. use MTM5Data, only : TTM5Data
  74. ! TM5 date and time routines:
  75. use dims, only : itau
  76. ! use datetime, only : tau2date
  77. use GO, only : TrcFile, Init, Done, ReadRc
  78. ! --- TROPOMI L2 interfaces ---
  79. ! Observational input (slant columns) is stored in this structure
  80. use MTObsTrack, only : TObsTrack, ObsTrackDeallocate
  81. ! Storage for retrieval results (vertical columns)
  82. use MTObsFcInfo, only : TObsFcInfo, ObsFcInfoAllocate, ObsFcInfoDeallocate
  83. ! module to read OMI NO2 slant column data (by tracks)
  84. use MObsRead, only : ObsFileGet
  85. ! module to write OMI NO2 vertical column retrieval data (by tracks)
  86. use TM5IF_module, only : TM5IF_obsfcinfo_write
  87. ! --- DOMINO interfaces ---
  88. ! compute model forecast and observation operator
  89. use MObservationOperator, only : InitOMFHx, GetOMFHx
  90. ! construct superobservations
  91. use MOmFSuper, only : GetOMFHxSuper, TObsInfoReduced, ObsInfoReduced_deallocate
  92. ! Kalman Filter routines
  93. use oi_module, only : AssimilateColumn
  94. ! Terrain height module
  95. ! use terrain, only : terrain_read
  96. ! Error module, use the model vertical column forecast error estimate
  97. use MNO2RetrievalError, only : forecastError
  98. ! NO2 AMF lookup table
  99. use MAmfRead, only : ReadAmfLut
  100. ! Write OmF data to file
  101. use MOmF_output, only : OmF_Output
  102. ! Cloud retrieval correction
  103. ! use cloudcor, only : cloudcor_read
  104. implicit none
  105. ! --- in-out ---
  106. character(*), intent(in) :: rcFile
  107. integer, intent(in) :: ntimestep
  108. type(TTM5Data), intent(inout) :: TM5Data
  109. integer, intent(out) :: nObs
  110. real, dimension(TM5Data%im, TM5Data%jm, TM5Data%lm), intent(inout) :: noxscaling
  111. integer, intent(out) :: status
  112. ! --- local variables ---
  113. character(len=*), parameter :: rname = mname//'/AssimNO2'
  114. type(TrcFile) :: rcF
  115. ! the ratio between analysis and forecast (3D field)
  116. real, dimension(:,:,:), allocatable :: AnFcRatio
  117. ! array of 3D partial NO2 columns per gridbox
  118. real, dimension(:,:,:), allocatable :: no2pcf
  119. ! array of 2D NO2 columns per lat-lon gridbox
  120. real, dimension(:,:), allocatable :: no2col_fc, no2col_an
  121. ! the 2D model column forecast error distribution
  122. real, dimension(:,:), allocatable :: NO2VCForecastError
  123. ! ---------------------------------------------------------
  124. ! Storage of track data: NO2 and cloud info
  125. type(TObsTrack) :: no2Tr
  126. ! observations and model forecast
  127. type(TObsFcInfo) :: obsFcInfo, obsAnInfo
  128. ! clustered superobservations
  129. type(TObsInfoReduced) :: obsFcInfoReduced, obsAnInfoReduced
  130. ! local
  131. integer :: i, l
  132. real :: slc,slcsig,tropfraction
  133. logical :: obsFound, isForecast
  134. integer,parameter :: omf_tape=83552
  135. ! OMIFilelist !JDM
  136. ! integer :: unit, ierror, system
  137. ! character(len=160) :: listfile, command
  138. ! --- begin code ---
  139. callcount = callcount + 1
  140. write(*,1111) callcount
  141. 1111 format(' ------- assimno2 ',i4,' -------')
  142. ! -------------- initialise -------------------
  143. if ( callcount == 1 ) then
  144. ! open rcfile:
  145. call Init( rcF, rcfile, status )
  146. IF_NOTOK_RETURN(status=1)
  147. ! Read the location of the file which contains a list of L2 NO2 files
  148. call ReadRc( rcF, 'domino.inputlist', filename_S5P_L2_NO2_filelist, status, default='list' )
  149. IF_ERROR_RETURN(status=1)
  150. ! Read the location of the orography file
  151. ! call ReadRc( rcF, 'domino.terrain_filename', terrain_filename, status, default='dem.nc' )
  152. ! Read the location of the AMF lookup table file
  153. call ReadRc( rcF, 'domino.amf_file', amf_filename, status, default='no2_amf_lut.nc' )
  154. ! Divide the AMF by AMFgeo after reading
  155. call ReadRc( rcF, 'domino.amf.divide.by.amfgeo', divideByAMFGeo, status, default=.false. )
  156. ! Optional to call observation operator after the assimilation step
  157. call ReadRc( rcF, 'domino.compute.retrieval.for.analysis', computeRetrievalForAnalysis, status, default=.false. )
  158. ! Write OmF statistics to netcdf file
  159. call ReadRc( rcF, 'domino.write.OmF', doWriteOmF, status, default=.true. )
  160. ! Debug mode yes/no
  161. call ReadRc( rcF, 'domino.debug.mode', debugMode, status, default=.false. )
  162. ! Output directory (for OmF netcdf output)
  163. call ReadRc( rcF, 'output.dir', outputdir, status, default='.' )
  164. ! close rcfile:
  165. call Done( rcF, status )
  166. IF_NOTOK_RETURN(status=1)
  167. ! Fill error specification matrices
  168. write(*,112) ForecastError
  169. 112 format(' InitForecastError: Initialising forecast error to ',f6.2,' 1e15 molec/cm2')
  170. ! Read settings for the observation operator
  171. call InitOMFHx( rcFile )
  172. ! Here we read the 90Arc terrain height database to be able to
  173. ! calculate the average terrain height of each pixel. !JDMTH
  174. ! call terrain_read ( terrain_filename )
  175. ! Read the air-mass factor lookup table from file
  176. print *,' Reading NO2 AMF from file : ',trim(amf_filename)
  177. print *,' divide by amfgeo : ',divideByAmfGeo
  178. call ReadAmfLut ( amf_filename, divideByAmfGeo, amfLut, status )
  179. print *,' S5P list file : ',trim(filename_S5P_L2_NO2_filelist)
  180. end if
  181. ! 2D forecast error field
  182. allocate ( NO2VCForecastError(TM5Data%im,TM5Data%jm) )
  183. NO2VCForecastError(:,:) = ForecastError
  184. ! ---------- Allocate storage and read the track matching this model time ----------
  185. call ObsFileGet( filename_S5P_L2_NO2_filelist, itau-ntimestep/2,itau+ntimestep/2, no2Tr, obsFound )
  186. ! At this point a track of NO2 and cloud data, "no2Tr" has
  187. ! been read or the track data record "no2Tr" is empty: obsFound = .false.
  188. if ( obsFound ) then
  189. write(*,'(a,i6)') 'assimNO2: No. of pixels in track ',no2Tr%count
  190. nObs = no2Tr%count
  191. ! allocate 3D partial column field and 2D column fields
  192. allocate ( no2pcf(TM5Data%im,TM5Data%jm,TM5Data%lm) )
  193. allocate ( no2col_fc(TM5Data%im,TM5Data%jm) )
  194. allocate ( no2col_an(TM5Data%im,TM5Data%jm) )
  195. ! Store analysis/forecast ratio, = 1 before the analysis
  196. noxscaling(:,:,:) = 1.0
  197. ! get 3D field of partial NO2 columns (forecast)
  198. call GetNO2PartialColumnField ( TM5Data, noxscaling, no2pcf, no2col_fc )
  199. ! allocate storage for retrieval output
  200. call ObsFcInfoAllocate ( obsFcInfo, no2Tr%count, TM5Data%lm )
  201. ! Calculate model forecast and observation operator
  202. ! store information for individual observations in "ObsFcInfo"
  203. isForecast = .true.
  204. call GetOMFHx( amfLut, no2Tr, TM5Data, no2pcf, obsFcInfo, isForecast, outputdir, debugMode )
  205. ! Write the retrieval data to the level-2 file, based on TM5 forecast
  206. call TM5IF_obsfcinfo_write( no2Tr, obsFcInfo, TM5Data )
  207. ! cluster observations into superobservations
  208. call GetOMFHxSuper( TM5Data%im, TM5Data%jm, TM5Data%lm, no2Tr, obsFcInfo, obsFcInfoReduced, 'f', computeRetrievalForAnalysis )
  209. write(*,1244) obsFcInfo%count,obsFcInfoReduced%count,TM5Data%date
  210. 1244 format(' assimno2: ',i5,' (',i4,') observ., Timestep ',i4,5i3)
  211. ! ----- Assimilation step -----
  212. assimcount = assimcount + 1
  213. ! allocate the helper array
  214. allocate ( anFcRatio(TM5Data%im,TM5Data%jm,TM5Data%lm) )
  215. print *, 'assimno2: assimilating observations'
  216. call AssimilateColumn ( TM5Data%im, TM5Data%jm, TM5Data%lm, NO2VCForecastError, obsFcInfoReduced, no2pcf, anFcRatio )
  217. ! Store analysis/forecast ratio
  218. noxscaling(:,:,:) = anFcRatio(:,:,:)
  219. ! remove helpers
  220. deallocate ( anFcRatio )
  221. ! ----- Calculate model analysis and observation operator -----
  222. if ( computeRetrievalForAnalysis ) then
  223. ! allocate storage for retrieval output
  224. call ObsFcInfoAllocate ( obsAnInfo, no2Tr%count, TM5Data%lm )
  225. ! get 3D field of partial NO2 columns: for analysis, noxscaling <> 1.0
  226. call GetNO2PartialColumnField ( TM5Data, noxscaling, no2pcf, no2col_an )
  227. ! store information for individual observations in "ObsFcInfo"
  228. isForecast = .false.
  229. call GetOMFHx ( amfLut, no2Tr, TM5Data, no2pcf, obsAnInfo, isForecast, outputdir, debugMode )
  230. ! cluster observations into superobservations
  231. ! note: this routine allocates the storage for the superobs
  232. call GetOMFHxSuper ( TM5Data%im, TM5Data%jm, TM5Data%lm, no2Tr, obsAnInfo, obsAnInfoReduced, 'a', computeRetrievalForAnalysis )
  233. end if
  234. ! ----- Write innovation statistics to netcdf file -----
  235. if ( doWriteOmF ) then
  236. if ( computeRetrievalForAnalysis ) then
  237. call OmF_Output( no2Tr, obsFcInfo, obsFcInfoReduced, NO2VCForecastError, TM5Data%im, TM5Data%jm, TM5Data%lon, TM5Data%lat, no2col_fc, TM5Data%date, outputdir, status, obsAnInfo, obsAnInfoReduced, no2col_an )
  238. else
  239. call OmF_Output( no2Tr, obsFcInfo, obsFcInfoReduced, NO2VCForecastError, TM5Data%im, TM5Data%jm, TM5Data%lon, TM5Data%lat, no2col_fc, TM5Data%date, outputdir, status )
  240. end if
  241. end if
  242. ! empty the orbit stack
  243. no2Tr%norbitparts = 0
  244. no2Tr%count = 0
  245. ! remove 2D (im,jm) forecast error field
  246. deallocate ( NO2VCForecastError )
  247. ! remove storage TROPOMI L2 NO2 observations
  248. call ObsTrackDeallocate ( no2Tr )
  249. ! remove storage retrieval results
  250. call ObsFcInfoDeallocate ( obsFcInfo )
  251. if ( computeRetrievalForAnalysis ) then
  252. call ObsFcInfoDeallocate ( obsAnInfo )
  253. end if
  254. ! remove storage superobservations
  255. call ObsInfoReduced_deallocate ( obsFcInfoReduced )
  256. if ( computeRetrievalForAnalysis ) then
  257. call ObsInfoReduced_deallocate ( obsAnInfoReduced )
  258. end if
  259. ! storage for partial column field and column fields
  260. deallocate ( no2pcf )
  261. deallocate ( no2col_fc )
  262. deallocate ( no2col_an )
  263. else ! no observations found
  264. ! write(*,'(a,t40)') ' assimno2:',TM5Data%date
  265. nObs = 0
  266. end if
  267. write(*,1112)
  268. 1112 format(' ------- assimno2 done -------')
  269. end subroutine AssimNO2
  270. subroutine GetNO2PartialColumnField( TM5Data, analysisScaling, no2pcf, no2col )
  271. !
  272. ! extract a 3D partial column field from the TM model field "no2"
  273. ! input : "TM5Data" structure with TM5 fields
  274. ! "analysisScaling" (=1 for forecast, <>1 for analysis),
  275. ! scaling factors resulting from the analysis
  276. ! output : "no2pcf" in 10^15 molecules per cm^2 for each 3D grid box
  277. ! "no2col" total column in 10^15 molecules per cm^2
  278. !
  279. ! Adjusted in DOMINO-3 because the interface passes mixing ratio's
  280. ! while the original code is based on the mass and "rm" arrays
  281. ! Henk Eskes, 2015
  282. ! TM5 model arrays and variables:
  283. use MTM5Data, only : TTM5Data
  284. use physconstants, only : pdiff2moleccm2
  285. implicit none
  286. ! -- in/out --
  287. type(TTM5Data), intent(in) :: TM5Data
  288. real,dimension(TM5Data%im,TM5Data%jm,TM5Data%lm),intent(in) :: analysisScaling
  289. real,dimension(TM5Data%im,TM5Data%jm,TM5Data%lm),intent(out) :: no2pcf
  290. real,dimension(TM5Data%im,TM5Data%jm),intent(out) :: no2col
  291. ! -- local --
  292. integer :: i, j, l
  293. real :: pbot, ptop
  294. real,dimension(:), allocatable :: no2col_zonal
  295. real :: no2col_mean
  296. !
  297. ! Convert from volume mixing ratio to molecules cm^-2
  298. ! using the pressure drop over a layer (in Pa)
  299. !
  300. allocate ( no2col_zonal(TM5Data%jm) )
  301. no2col_zonal(:) = 0.0
  302. no2col(:,:) = 0.0
  303. do i = 1, TM5Data%im
  304. do j = 1, TM5Data%jm
  305. do l = 1, TM5Data%lm
  306. pbot = TM5Data%hyai(l) + TM5Data%hybi(l) * TM5Data%ps(i,j)
  307. ptop = TM5Data%hyai(l+1) + TM5Data%hybi(l+1) * TM5Data%ps(i,j)
  308. no2pcf(i,j,l) = pdiff2moleccm2 * ( pbot - ptop ) * TM5Data%no2(i,j,l) * analysisScaling(i,j,l)
  309. no2col_zonal(j) = no2col_zonal(j) + no2pcf(i,j,l)
  310. no2col(i,j) = no2col(i,j) + no2pcf(i,j,l)
  311. ! if ( i==100 .and. j==100 ) print*,'l, pbot, ptop, no2, scaling ',l,pbot, ptop, TM5Data%no2(i,j,l), analysisScaling(i,j,l)
  312. end do
  313. end do
  314. end do
  315. no2col_zonal(:) = no2col_zonal(:) / real(TM5Data%im)
  316. no2col_mean = sum(no2col_zonal) / real(TM5Data%jm)
  317. if ( isnan(no2col_mean) ) then
  318. print '(a)', "ERROR in GetNO2PartialColumnField: NaN found in the TM5 NO2 field"
  319. stop "stop because of NaN"
  320. end if
  321. ! print *, 'no2col_zonal -90, -60, .. 90 = ',no2col_zonal(1),no2col_zonal(30),no2col_zonal(60),no2col_zonal(90),no2col_zonal(120),no2col_zonal(150),no2col_zonal(180)
  322. ! print *, 'no2col at (59,7) and (34,38) ',sum(no2pcf(59,7,:)),sum(no2pcf(34,38,:))
  323. ! print *, 'no2pcf profile at 5E, 53N ',no2pcf(185,143,:)
  324. print '(a,f10.3)', ' GetNO2PartialColumnField, mean NO2 column = ', no2col_mean
  325. deallocate ( no2col_zonal )
  326. end subroutine GetNO2PartialColumnField
  327. end module MAssimilation