optics.F90 66 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749
  1. #define TRACEBACK write (gol,'("in ",a," (",a,i6,")")') rname, __FILE__, __LINE__ ; call goErr
  2. #define IF_NOTOK_RETURN(action) if (status/=0) then; TRACEBACK; action; return; end if
  3. #define IF_ERROR_RETURN(action) if (status> 0) then; TRACEBACK; action; return; end if
  4. !
  5. #include "tm5.inc"
  6. !
  7. !-----------------------------------------------------------------------------
  8. ! TM5 !
  9. !-----------------------------------------------------------------------------
  10. !BOP
  11. !
  12. ! !MODULE: OPTICS
  13. !
  14. ! !DESCRIPTION: Optics module to calculate optical depth from m7 output,
  15. ! based on the AOP_Package op Michael Kahnert.
  16. !
  17. ! The optics code should be used in the following way (see
  18. ! examples in photolysis.F90, ecearth_optics.F90, and
  19. ! user_output_aerocom.F90):
  20. !
  21. ! 1) prepare the optics calculation by calling
  22. ! 'OPTICS_INIT' --> lookuptables etc.
  23. ! this routine reads the wavelengths, lookupable and calculates
  24. ! refr. indices at these wavelengths.
  25. !
  26. ! 2) allocate AOP arrays aop_out_ext/a/g with
  27. ! (n_gridcells, n_wavelengths, n_split), with:
  28. ! 'n_split' = 1 for (split == .false.) or
  29. ! 'n_split' = 11 for (split == .true. ), ie.
  30. ! partial contributions by
  31. ! Total, SO4, BC, OC, SS, DU, NO3, Water, Fine, Fine Dust, Fine SS
  32. ! additional fields are also provided for split==.true. in
  33. ! aop_out_add, which has to have size
  34. ! (n_gridcells, n_wavelengths, n_add) with nadd = 2 for
  35. ! surface PM10 dry extinction and surface PM10 dry absorption
  36. ! 3) Compute AOP for current conditions by calling 'OPTICS_AOP_GET'
  37. ! 4) done: 'OPTICS_DONE'
  38. !
  39. ! IMPORTANT: *) Skipped the ZOOM options! (temporary)
  40. ! *) OC is actually POM. Remember converting OC to POM
  41. ! when sending it to optics_calculate_aop
  42. !\\
  43. !\\
  44. ! !INTERFACE:
  45. !
  46. MODULE OPTICS
  47. !
  48. ! !USES:
  49. !
  50. use GO, only : gol, goErr, goPr
  51. Use mo_aero_m7, only : nmod
  52. Use global_data, only : rcfile
  53. use GO, only : TrcFile, Init, Done, ReadRc
  54. Use Dims, only : nregions
  55. IMPLICIT NONE
  56. PRIVATE
  57. !
  58. ! !PUBLIC MEMBER FUNCTIONS:
  59. !
  60. public :: optics_init, optics_done ! init/done methods for a wavelendep object
  61. public :: optics_aop_get ! compute aerosol optical properties
  62. !
  63. ! !PRIVATE DATA MEMBERS:
  64. !
  65. type(TrcFile) :: rcF
  66. character(len=256) :: lookuptable, refractive_indices
  67. !
  68. ! !PUBLIC TYPES:
  69. !
  70. ! wavelength type (to be used by methods using the optics)
  71. type, public :: wavelendep
  72. real :: wl ! user requested wavelength unit = um (e.g. 0.550)
  73. real, dimension(7) :: n ! SO4, BC, OC, SOA, SS, DU, WATER
  74. real, dimension(7) :: k ! SO4, BC, OC, SOA, SS, DU, WATER
  75. logical :: split, insitu
  76. end type wavelendep
  77. !
  78. ! !PRIVATE TYPES:
  79. !
  80. ! AOP input type and field
  81. type aopi
  82. real, dimension(nmod) :: SO4, NO3, BC, OC, SOA, SS, DU, H2O, numdens, rg, rgd
  83. end type aopi
  84. type(aopi), dimension(:), allocatable :: aop_in
  85. ! characteristics of the lookup-tables
  86. integer, parameter :: n_rii = 15
  87. integer, parameter :: n_rir = 40
  88. integer, parameter :: n_x = 100
  89. real,dimension(n_rii) :: lkval ! -log img part refr. index
  90. real,dimension(n_rii) :: kval ! img part refr. index, 10^(-lkval)
  91. real,dimension(n_rir) :: n1r ! real part refr. index
  92. Real, Dimension(n_x) :: xs
  93. Real, Dimension(n_x,n_rir,n_rii),Target :: cext_159, a_159, g_159
  94. real, dimension(n_x,n_rir,n_rii),Target :: cext_200, a_200, g_200
  95. character(len=*), parameter :: mname = 'Optics'
  96. ! lookup table information for interpolation to wavelength properties
  97. Integer, Parameter :: opacdim = 61 ! Wavelength dimension of OPAC data
  98. Integer, Parameter :: echamhamdim = 49 ! Wavelength dimension of ECHAM-HAM data
  99. Integer, Parameter :: segelsteindim = 1261 ! Wavelength dimension of Segelstein data
  100. Real, Dimension(:,:), allocatable :: opac, echamham, segelstein
  101. !
  102. ! !REVISION HISTORY:
  103. ! Implemented by Maarten Krol 03/2009
  104. ! Extended by Joost Aan de Brugh
  105. !
  106. ! 6 Feb 2011 - Achim Strunk - complete revision
  107. ! - worked on DECOUPLING optics routines
  108. ! from (optics)_output, in order to
  109. ! (re)establish a flexible way of using it
  110. ! - remaining parts have been moved to
  111. ! (the new routine) user_output_optics
  112. !
  113. ! 24 Jun 2011 - Achim Strunk - added NO3 explicitly in order to allow
  114. ! for a slightly better split of the
  115. ! optical properties of (SO4+NO3)
  116. ! 20 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  117. !
  118. ! !REMARKS:
  119. !
  120. !EOP
  121. !------------------------------------------------------------------------
  122. CONTAINS
  123. !--------------------------------------------------------------------------
  124. ! TM5 !
  125. !--------------------------------------------------------------------------
  126. !BOP
  127. !
  128. ! !IROUTINE: OPTICS_INIT
  129. !
  130. ! !DESCRIPTION: Initialize a wavelendep object: Input/lookuptables are
  131. ! opened and read in, and wavelength dependent parameters are
  132. ! calculated.
  133. !\\
  134. !\\
  135. ! !INTERFACE:
  136. !
  137. SUBROUTINE OPTICS_INIT( nwav, wdep, status )
  138. !
  139. ! !USES:
  140. !
  141. USE MDF, ONLY : MDF_OPEN, MDF_NETCDF, MDF_READ, MDF_Get_Var, MDF_Close, MDF_Inq_VarID
  142. !
  143. ! !INPUT PARAMETERS:
  144. !
  145. integer, intent(in) :: nwav
  146. !
  147. ! !OUTPUT PARAMETERS:
  148. !
  149. type(wavelendep), dimension(nwav), intent(inout) :: wdep
  150. integer, intent(out) :: status
  151. !
  152. ! !REMARKS: read by each core (FIXME?)
  153. !
  154. !EOP
  155. !------------------------------------------------------------------------
  156. !BOC
  157. integer :: fid, varid, i
  158. character(len=*), parameter :: rname = mname//'/Optics_Init'
  159. ! --- begin --------------------------------
  160. allocate( opac (7, opacdim ) )
  161. allocate( echamham (5, echamhamdim ) )
  162. allocate( segelstein(3, segelsteindim) )
  163. ! get filenames from rcfile
  164. call Init( rcF, rcfile, status )
  165. IF_NOTOK_RETURN(status=1)
  166. call ReadRc( rcF, 'optics.lookuptable', lookuptable, status )
  167. IF_NOTOK_RETURN(status=1)
  168. call ReadRc( rcF, 'optics.refractive_indices', refractive_indices, status )
  169. IF_NOTOK_RETURN(status=1)
  170. ! read lookup table
  171. CALL MDF_Open( TRIM(lookuptable), MDF_NETCDF, MDF_READ, fid, status )
  172. IF_NOTOK_RETURN(status=1)
  173. CALL MDF_Inq_VarID( fid, 'mr', varid, status )
  174. IF_NOTOK_RETURN(status=1)
  175. CALL MDF_Get_Var( fid, varid, n1r, status )
  176. IF_NOTOK_RETURN(status=1)
  177. CALL MDF_Inq_VarID( fid, 'mi', varid, status )
  178. IF_NOTOK_RETURN(status=1)
  179. CALL MDF_Get_Var( fid, varid, kval, status )
  180. IF_NOTOK_RETURN(status=1)
  181. lkval = -log10(kval)
  182. CALL MDF_Inq_VarID( fid, 'x', varid, status )
  183. IF_NOTOK_RETURN(status=1)
  184. CALL MDF_Get_Var( fid, varid, xs, status )
  185. IF_NOTOK_RETURN(status=1)
  186. CALL MDF_Inq_VarID( fid, 'ext_159', varid, status )
  187. IF_NOTOK_RETURN(status=1)
  188. CALL MDF_Get_Var( fid, varid, cext_159, status )
  189. IF_NOTOK_RETURN(status=1)
  190. CALL MDF_Inq_VarID( fid, 'ext_200', varid, status )
  191. IF_NOTOK_RETURN(status=1)
  192. CALL MDF_Get_Var( fid, varid, cext_200, status )
  193. IF_NOTOK_RETURN(status=1)
  194. CALL MDF_Inq_VarID( fid, 'a_159', varid, status )
  195. IF_NOTOK_RETURN(status=1)
  196. CALL MDF_Get_Var( fid, varid, a_159, status )
  197. IF_NOTOK_RETURN(status=1)
  198. CALL MDF_Inq_VarID( fid, 'a_200', varid, status )
  199. IF_NOTOK_RETURN(status=1)
  200. CALL MDF_Get_Var( fid, varid, a_200, status )
  201. IF_NOTOK_RETURN(status=1)
  202. CALL MDF_Inq_VarID( fid, 'g_159', varid, status )
  203. IF_NOTOK_RETURN(status=1)
  204. CALL MDF_Get_Var( fid, varid, g_159, status )
  205. IF_NOTOK_RETURN(status=1)
  206. CALL MDF_Inq_VarID( fid, 'g_200', varid, status )
  207. IF_NOTOK_RETURN(status=1)
  208. CALL MDF_Get_Var( fid, varid, g_200, status )
  209. IF_NOTOK_RETURN(status=1)
  210. CALL MDF_Close( fid, status )
  211. IF_NOTOK_RETURN(status=1)
  212. ! Read refractive indices
  213. CALL MDF_Open( TRIM(refractive_indices), MDF_NETCDF, MDF_READ, fid, status )
  214. IF_NOTOK_RETURN(status=1)
  215. ! Get Opac data
  216. CALL MDF_Inq_VarID( fid, 'Opac', varid, status )
  217. IF_NOTOK_RETURN(status=1)
  218. CALL MDF_Get_Var( fid, varid, opac, status )
  219. IF_NOTOK_RETURN(status=1)
  220. ! Get ECHAM-HAM data
  221. CALL MDF_Inq_VarID( fid, 'ECHAM-HAM', varid, status )
  222. IF_NOTOK_RETURN(status=1)
  223. CALL MDF_Get_Var( fid, varid, echamham, status )
  224. IF_NOTOK_RETURN(status=1)
  225. ! Get Segelstein data
  226. CALL MDF_Inq_VarID( fid, 'Segelstein', varid, status )
  227. IF_NOTOK_RETURN(status=1)
  228. CALL MDF_Get_Var( fid, varid, segelstein, status )
  229. IF_NOTOK_RETURN(status=1)
  230. CALL MDF_Close( fid, status )
  231. IF_NOTOK_RETURN(status=1)
  232. call optics_wavelen_init( wdep, status )
  233. IF_ERROR_RETURN( status=1 )
  234. write(gol,*) 'Optical parameters:'; call goPr
  235. do i = 1, nwav
  236. write(gol,*) 'Wavelength :', wdep(i)%wl ; call goPr
  237. write(gol,*) ' SO4 (real/img) :', wdep(i)%n(1), wdep(i)%k(1) ; call goPr
  238. write(gol,*) ' BC (real/img) :', wdep(i)%n(2), wdep(i)%k(2) ; call goPr
  239. write(gol,*) ' OC (real/img) :', wdep(i)%n(3), wdep(i)%k(3) ; call goPr
  240. write(gol,*) ' SOA (real/img) :', wdep(i)%n(4), wdep(i)%k(4) ; call goPr
  241. write(gol,*) ' SS (real/img) :', wdep(i)%n(5), wdep(i)%k(5) ; call goPr
  242. write(gol,*) ' DU (real/img) :', wdep(i)%n(6), wdep(i)%k(6) ; call goPr
  243. write(gol,*) ' H2O (real/img) :', wdep(i)%n(7), wdep(i)%k(7) ; call goPr
  244. enddo
  245. ! Done
  246. ! -------------
  247. call Done( rcF, status )
  248. IF_NOTOK_RETURN(status=1)
  249. deallocate( opac, echamham, segelstein )
  250. status = 0
  251. END SUBROUTINE OPTICS_INIT
  252. !EOC
  253. !--------------------------------------------------------------------------
  254. ! TM5 !
  255. !--------------------------------------------------------------------------
  256. !BOP
  257. !
  258. ! !IROUTINE: OPTICS_DONE
  259. !
  260. ! !DESCRIPTION: dummy for now
  261. !\\
  262. !\\
  263. ! !INTERFACE:
  264. !
  265. SUBROUTINE OPTICS_DONE( status )
  266. !
  267. ! !OUTPUT PARAMETERS:
  268. !
  269. integer, intent(out) :: status
  270. !
  271. ! !REVISION HISTORY:
  272. ! 6 Feb 2011 - Achim Strunk -
  273. !
  274. ! !REMARKS:
  275. !
  276. !EOP
  277. !------------------------------------------------------------------------
  278. !BOC
  279. ! ok
  280. status = 0
  281. END SUBROUTINE OPTICS_DONE
  282. !EOC
  283. !--------------------------------------------------------------------------
  284. ! TM5 !
  285. !--------------------------------------------------------------------------
  286. !BOP
  287. !
  288. ! !IROUTINE: OPTICS_WAVELEN_INIT
  289. !
  290. ! !DESCRIPTION: Initialise parameters which are depending on given
  291. ! wavelengths.
  292. !\\
  293. !\\
  294. ! !INTERFACE:
  295. !
  296. SUBROUTINE OPTICS_WAVELEN_INIT( wdep, status )
  297. !
  298. ! !INPUT/OUTPUT PARAMETERS:
  299. !
  300. ! wavelength properties (wavelength itself and real/img part of refractive index)
  301. type(wavelendep), intent(inout), dimension(:) :: wdep
  302. !
  303. ! !OUTPUT PARAMETERS:
  304. !
  305. integer, intent(out) :: status
  306. !
  307. ! !REVISION HISTORY:
  308. ! 6 Feb 2011 - Achim Strunk -
  309. !
  310. ! !REMARKS:
  311. !
  312. !EOP
  313. !------------------------------------------------------------------------
  314. !BOC
  315. character(len=*), parameter :: rname = mname//'/optics_wavelen_init'
  316. integer :: nwl, i, idx
  317. real :: wl, h
  318. real :: nscale, kscale
  319. ! Real part n and imaginary part k of refractive index
  320. ! for each wavelength:
  321. !>>> TvN
  322. ! The refractive index for 'sulfate' is taken from
  323. ! the OPAC database (Hess et al., 1998;
  324. ! Koepke et al., MPI report no. 243, 1997).
  325. ! The value used is that of 'sulfate solution',
  326. ! i.e. particles consisting of 75% of sulfuric acid (H2SO4),
  327. ! based on Fenn et al. (chapter 18 in Handbook of Geophysics
  328. ! and Space Environment, 1985).
  329. ! This is in line with Kinne et al. (JGR, 2003),
  330. ! who write that refractive indices for sulfate
  331. ! are usually based on 75% sulfuric acid solution.
  332. ! Actually, the OPAC refractive index agrees very well
  333. ! with the expression given by Boucher and Anderson (JGR, 1995)
  334. ! for H2SO4 at visible wavelengths.
  335. ! Thus, the OPAC data can be considered to apply to pure H2SO4,
  336. ! which is consistent of our application of mixing rules.
  337. ! For BC, the OPAC refractive index is scaled to one of
  338. ! the values proposed by Bond and Bergstrom (2006),
  339. ! valid at 550 nm (see their Table 5).
  340. ! Selected values for high, medium and low absorption are
  341. ! 1.95 + 0.79 i, 1.85 + 0.71 i, and 1.75 + 0.63 i, respectively.
  342. ! We select the low-absorption value,
  343. ! because it produces results in best agreement
  344. ! with AAOD from MODIS Collection 6 Deep Blue.
  345. ! Note that the medium-absorption value 1.85 + 0.71 i
  346. ! was used in ECHAM simulations by Stier et al. (2007),
  347. ! and found to give reasonable results.
  348. ! Lowenthal et al. (Atmos. Environ., 2000)
  349. ! give a value of 1.90 + 0.6 i.
  350. ! The reference value used in the scaling
  351. ! is the OPAC value at 550 nm: 1.75 + 0.44 i.
  352. ! It would be better to include the scaling
  353. ! in the input file.
  354. !nscale = 1.0 ! for using OPAC
  355. !kscale = 1.0 ! for using OPAC
  356. !nscale = 1.95/1.75
  357. !kscale = 0.79/0.44
  358. nscale = 1.85/1.75
  359. kscale = 0.71/0.44
  360. !nscale = 1.75/1.75
  361. !kscale = 0.63/0.44
  362. !<<< TvN
  363. nwl = size(wdep)
  364. do i = 1, nwl
  365. wl = wdep(i)%wl
  366. ! Interpolate Opac data
  367. findOpac: Do idx = 1,opacdim
  368. If(opac(1,idx) .gt. wl) exit findOpac
  369. End Do findOpac
  370. If(idx .gt. opacdim) then
  371. idx = opacdim
  372. h = 1.0
  373. Else If(idx .eq. 1) then
  374. idx = 2
  375. h = 0.0
  376. Else
  377. h = (wl-opac(1,idx-1))/(opac(1,idx)-opac(1,idx-1))
  378. End If
  379. ! SO4
  380. wdep(i)%n(1) = opac(2,idx-1)+h*(opac(2,idx)-opac(2,idx-1))
  381. wdep(i)%k(1) = opac(3,idx-1)+h*(opac(3,idx)-opac(3,idx-1))
  382. ! BC
  383. !>>> TvN
  384. !wdep(i)%n(2) = opac(4,idx-1)+h*(opac(4,idx)-opac(4,idx-1))
  385. !wdep(i)%k(2) = opac(5,idx-1)+h*(opac(5,idx)-opac(5,idx-1))
  386. wdep(i)%n(2) = nscale * ( opac(4,idx-1)+h*(opac(4,idx)-opac(4,idx-1)) )
  387. wdep(i)%k(2) = kscale * ( opac(5,idx-1)+h*(opac(5,idx)-opac(5,idx-1)) )
  388. !<<< TvN
  389. ! SS
  390. wdep(i)%n(5) = opac(6,idx-1)+h*(opac(6,idx)-opac(6,idx-1))
  391. wdep(i)%k(5) = opac(7,idx-1)+h*(opac(7,idx)-opac(7,idx-1))
  392. ! Interpolate ECHAM-HAM data
  393. findEchamham: Do idx = 1,echamhamdim
  394. If(echamham(1,idx) .gt. wl) exit findEchamham
  395. End Do findEchamham
  396. If(idx .gt. echamhamdim) then
  397. idx = echamhamdim
  398. h = 1.0
  399. Else If(idx .eq. 1) then
  400. idx = 2
  401. h = 0.0
  402. Else
  403. h = (wl-echamham(1,idx-1))/(echamham(1,idx)-echamham(1,idx-1))
  404. End If
  405. ! OC
  406. !>>> TvN
  407. ! The 'ECHAM-HAM' data currently used for POM
  408. ! are based on the data from Fenn et al. (1985)
  409. ! for the 'water soluble' component,
  410. ! but at a reduced number of wavelengths up to 15 um.
  411. ! It would be better to use the original table
  412. ! in the input file.
  413. !<<< TvN
  414. wdep(i)%n(3) = echamham(2,idx-1)+h*(echamham(2,idx)-echamham(2,idx-1))
  415. wdep(i)%k(3) = echamham(3,idx-1)+h*(echamham(3,idx)-echamham(3,idx-1))
  416. ! SOA
  417. ! >>TB
  418. ! For now (March 2017) we use OC indices for SOA
  419. ! <<TB
  420. wdep(i)%n(4) = echamham(2,idx-1)+h*(echamham(2,idx)-echamham(2,idx-1))
  421. wdep(i)%k(4) = echamham(3,idx-1)+h*(echamham(3,idx)-echamham(3,idx-1))
  422. ! DU
  423. wdep(i)%n(6) = echamham(4,idx-1)+h*(echamham(4,idx)-echamham(4,idx-1))
  424. wdep(i)%k(6) = echamham(5,idx-1)+h*(echamham(5,idx)-echamham(5,idx-1))
  425. ! Interpolate Segelstein data
  426. findSegelstein: Do idx = 1,segelsteindim
  427. If(segelstein(1,idx) .gt. wl) exit findSegelstein
  428. End Do findSegelstein
  429. If(idx .gt. segelsteindim) then
  430. idx = segelsteindim
  431. h = 1.0
  432. Else If(idx .eq. 1) then
  433. idx = 2
  434. h = 0.0
  435. Else
  436. h = (wl-segelstein(1,idx-1))/(segelstein(1,idx)-segelstein(1,idx-1))
  437. End If
  438. ! H2O
  439. wdep(i)%n(7) = segelstein(2,idx-1)+h*(segelstein(2,idx)-segelstein(2,idx-1))
  440. wdep(i)%k(7) = segelstein(3,idx-1)+h*(segelstein(3,idx)-segelstein(3,idx-1))
  441. enddo
  442. status=0
  443. END SUBROUTINE OPTICS_WAVELEN_INIT
  444. !EOC
  445. !--------------------------------------------------------------------------
  446. ! TM5 !
  447. !--------------------------------------------------------------------------
  448. !BOP
  449. !
  450. ! !IROUTINE: OPTICS_GET
  451. !
  452. ! !DESCRIPTION: Main optical properties routine. Here the interpolated
  453. ! values for extinction coefficient, single scattering
  454. ! albedo and assymetry parameter are retrieved and returned.
  455. !\\
  456. !\\
  457. ! !INTERFACE:
  458. !
  459. PURE SUBROUTINE OPTICS_GET(m_eff, xg, Cext, a, g, cext_table, a_table, g_table, status, gol )
  460. !
  461. ! !INPUT PARAMETERS:
  462. !
  463. complex, intent(in) :: m_eff
  464. real, intent(in) :: xg
  465. real, dimension(:,:,:), intent(in) :: cext_table, a_table, g_table
  466. !
  467. ! !OUTPUT PARAMETERS:
  468. !
  469. real, intent(out) :: Cext, a, g
  470. integer, intent(inout) :: status
  471. character(len=*), intent(inout) :: gol
  472. !
  473. ! !REVISION HISTORY:
  474. ! 15 Jul 2010 - P. Le Sager - Added check on i_n (out-of-bound)
  475. ! 6 Feb 2011 - Achim Strunk -
  476. !
  477. ! !REMARKS:
  478. ! - By using "pure" subroutine, we cannot use any of the goPr, goErr,
  479. ! IF_NOTOK_RETURN, ... routines. Traceback is limited:
  480. ! 1) only one statement can be recorded in variable gol
  481. ! 2) the calling routine should issue the "call goErr"
  482. !
  483. !EOP
  484. !------------------------------------------------------------------------
  485. !BOC
  486. real :: n, k, n1, k1, dk1, dk2, lk
  487. real :: modrad, modrad1, dr, dr1, slope, cext1, a1, g1
  488. integer :: i
  489. integer :: i_n, i_k, i_knew
  490. character(len=*), parameter :: rname = mname//'/Optics_Get'
  491. ! --- begin --------------------------------
  492. status = 0
  493. n=real(m_eff)
  494. k=imag(m_eff)
  495. if(k.lt.kval(1))then
  496. k1=kval(1)
  497. i_knew=1
  498. elseif(k.gt.kval(15))then
  499. k1=kval(15)
  500. i_knew=15
  501. else
  502. get_k: do i=2,15
  503. if(k.lt.kval(i))then
  504. dk1=k-kval(i-1)
  505. dk2=kval(i)-k
  506. if(dk1.le.dk2)then
  507. k1=kval(i-1)
  508. i_knew=i-1
  509. else
  510. k1=kval(i)
  511. i_knew=i
  512. endif
  513. exit get_k
  514. endif
  515. enddo get_k
  516. endif
  517. lk=-log10(k1)
  518. !#n1=float(int(50*n+0.5))/50.
  519. !do i_n = 1, n_rir
  520. ! if (abs(n1 - n1r(i_n)) < 1e-4) exit
  521. !enddo
  522. !i_n = 1 + int((n-1.12)*50+0.5)
  523. !AJS: I guess n is a number on the (increasing) n1r axis; search nearest index:
  524. i_n = size(n1r)
  525. do i = 1, size(n1r)
  526. if ( n <= n1r(i) ) then
  527. i_n = i
  528. exit
  529. end if
  530. end do
  531. if ( i_n > 1 ) then
  532. if ( abs(n-n1r(i_n-1)) < abs(n-n1r(i_n)) ) i_n = i_n - 1
  533. else if ( i_n < n_rir ) then
  534. if ( abs(n-n1r(i_n+1)) < abs(n-n1r(i_n)) ) i_n = i_n + 1
  535. end if
  536. do i_k = 1, n_rii
  537. if (abs(lk - lkval(i_k)) < 1e-4) exit
  538. enddo
  539. ! ! PLS - test : ik can be determined without the preceding loop "do i_k = 1, n_rii"
  540. ! if (i_k.ne.i_knew) then
  541. ! status = 1
  542. ! write (gol,'(" PLSPLS ik NE iknew = ",2(i2,2x))')i_k,i_knew
  543. ! endif
  544. ! following the "get_k" loop above, the only way to get into this is to
  545. ! have a NaN for k in the first place ?
  546. if (i_k > n_rii) then
  547. status = 1
  548. write(gol,*)'FATAL ERROR: i_k value outside LUT'
  549. ! write (gol,'(" lk = ",E16.4)')lk
  550. ! write (gol,'(" k1 = ",E16.4)')k1
  551. ! write (gol,'(" k = ",E16.4)')k
  552. ! write (gol,'(" n = ",E16.4)')n
  553. ! do i_n = 1, 15
  554. ! write (gol,'(" lkval(",i2,") = ",E16.4)')i_n,lkval(i_n)
  555. ! call goPr
  556. ! write (gol,'(" kval(",i2,") = ",E16.4)')i_n,kval(i_n)
  557. ! call goPr
  558. ! enddo
  559. return
  560. endif
  561. ! Added check (15-7-2010 - P. Le Sager)
  562. if (i_n > n_rir) then
  563. status = 1
  564. write(gol,*)'FATAL ERROR: i_n value out of range'
  565. return
  566. endif
  567. !>>> TvN
  568. ! Since xs(1) equals zero a problem may occur when xg is negative,
  569. ! because modrad.gt.xg would become true for i=1 in that case,
  570. ! while modrad1, Cext1, a1 and g1 are not yet set.
  571. ! It is not clear if negative xg values can ever occur,
  572. ! but if they do that should be prevented when calculating rg.
  573. !
  574. ! However, the problem may perhaps already occur
  575. ! when xg equals zero, because of the finite machine precision.
  576. !
  577. ! In any case, it is desired to initialize modrad1, Cext1, a1 and g1.
  578. ! Cext1, a1 and g1 should be set to their table entries for i=1,
  579. ! which are all zero:
  580. Cext1 = cext_table(1,i_n,i_k)
  581. a1 = a_table(1,i_n,i_k)
  582. g1 = g_table(1,i_n,i_k)
  583. ! modrad1 can be initialized to any value different from xs(1),
  584. ! to prevent division by zero.
  585. modrad1=xs(1)-9.99e-4
  586. ! This combination will force slope to zero
  587. ! and Cext, a and g to the table entries for i=1 (zero),
  588. ! in case modrad.gt.xg is true for i=1.
  589. !<<< TvN
  590. get_values: do i = 1, n_x
  591. modrad = xs(i)
  592. a = a_table(i,i_n, i_k)
  593. g = g_table(i,i_n, i_k)
  594. cext = cext_table(i,i_n, i_k)
  595. ! With small concentrations, like in the stratosphere, M7 does not trust its radii.
  596. ! See m7_averageproperties -> zinsvol. The M7-radius goes to zero
  597. ! Modrad may never be larger than xg the first time. Modrad1 is not set,
  598. ! will be zero (or something worse) and dr will be zero (or something worse).
  599. ! slope is demolished, makeing all values NaN. Therefore, it is modrad .gt. xg
  600. ! instead of modrad .ge. xg
  601. !
  602. ! PLS-TRANSLATION - It boils down to: "on the first iteration of this loop, if modrad=xg and
  603. ! you go into the if-statement below, you are in trouble, because modrad1 can be
  604. ! anything. To prevent that, replace GE with GT to avoid going into the if-statement at the
  605. ! first iteration."
  606. !
  607. if(modrad.gt.xg)then
  608. dr=modrad-modrad1
  609. dr1=xg-modrad1
  610. slope=(Cext-Cext1)/dr
  611. Cext=Cext1+slope*dr1
  612. slope=(a-a1)/dr
  613. a=a1+slope*dr1
  614. slope=(g-g1)/dr
  615. g=g1+slope*dr1
  616. exit get_values
  617. endif
  618. modrad1=modrad
  619. Cext1=Cext
  620. a1=a
  621. g1=g
  622. enddo get_values
  623. END SUBROUTINE OPTICS_GET
  624. !EOC
  625. !--------------------------------------------------------------------------
  626. ! TM5 !
  627. !--------------------------------------------------------------------------
  628. !BOP
  629. !
  630. ! !IROUTINE: GET_REFR_IDX
  631. !
  632. ! !DESCRIPTION: Compute refractive index of internally mixed aerosols by use
  633. ! of effective medium theory for the size-dependent aerosol
  634. ! mixtures assumed in M7.
  635. !\\
  636. !\\
  637. ! !INTERFACE:
  638. !
  639. PURE SUBROUTINE GET_REFR_IDX(wdep, SO4, BC, OC, SOA, SS, DU, water, mode, m_eff, status, gol)
  640. !
  641. ! !USES:
  642. !
  643. use binas, only: rol
  644. use chem_param, only: ss_density, dust_density, carbon_density
  645. use chem_param, only: pom_density, so4_density, soa_density
  646. !
  647. ! !INPUT PARAMETERS:
  648. !
  649. type(wavelendep), intent(in) :: wdep ! wavelength properties (wavelength, re/img part of refractive index)
  650. real, intent(in) :: SO4, BC, OC,SOA ! mass mixing ratios or concentrations of sulphate, black carbon, organic carbon
  651. real, intent(in) :: SS, DU, water ! sea salt, dust, and water
  652. integer, intent(in) :: mode ! mode number (M7)
  653. !
  654. ! !OUTPUT PARAMETERS:
  655. !
  656. complex, intent(out) :: m_eff ! effective refractive index of mixture
  657. integer, intent(out) :: status
  658. character(len=*), intent(inout) :: gol
  659. !
  660. ! !REVISION HISTORY:
  661. ! 12 Aug 2008 - Michael Kahnert, SMHI
  662. ! 6 Feb 2011 - Achim Strunk -
  663. !
  664. ! !REMARKS:
  665. ! - see remarks of OPTICS_GET subroutine about PURE routine
  666. !
  667. !EOP
  668. !------------------------------------------------------------------------
  669. !BOC
  670. character(len=*), parameter :: rname = mname//'/get_refr_idx'
  671. ! refractive indices
  672. complex :: m_SO4, m_BC, m_OC, m_SOA, m_SS, m_DU, m_water
  673. ! volume fractions
  674. real :: v_SO4, v_BC, v_OC, v_SOA, v_SS, v_DU, v_water, water_iv
  675. integer :: i_test
  676. real :: vtot, v2
  677. complex :: m00, m0, m1, m2
  678. real :: rpls, ipls
  679. ! --- begin --------------------------------
  680. ! Get the refractive indices from the lookup-tables and put them into complex numbers.
  681. m_so4 = cmplx( wdep%n(1),wdep%k(1) ) ! H2-SO4 + NH4NO3
  682. m_bc = cmplx( wdep%n(2),wdep%k(2) ) ! BC
  683. m_oc = cmplx( wdep%n(3),wdep%k(3) ) ! POM
  684. m_soa = cmplx( wdep%n(4),wdep%k(4) ) ! SOA
  685. m_ss = cmplx( wdep%n(5),wdep%k(5) ) ! SS
  686. m_du = cmplx( wdep%n(6),wdep%k(6) ) ! DU
  687. m_water = cmplx( wdep%n(7),wdep%k(7) ) ! Water
  688. status = 0
  689. ! no mixing for mode=6,7:
  690. if(mode.ge.6)then
  691. m_eff=m_DU
  692. return
  693. endif
  694. ! compute volume fractions:
  695. v_SO4=0.
  696. v_BC=0.
  697. v_OC=0.
  698. v_SOA=0.
  699. v_SS=0.
  700. v_DU=0.
  701. v_water=0.
  702. vtot=0.
  703. ! Added sanity check (15-7-2010 - P. Le Sager) : Avoid negative water
  704. ! mixing ratio!
  705. ! The bruggeman logically assumes that v_water is between 0 and 1, but
  706. ! this is never checked in the call chain :
  707. ! ECEarth_Optics_Step -> calculate_aop -> get_refr_idx [here] ->
  708. ! Bruggeman
  709. ! We do it here, with a warning since it reflects a problem upstream:
  710. if(water.lt.0.0)then
  711. !write (gol,*)" WARNING - [Get_refr_idx] : negative relative humidity..." ; call goPr
  712. !write (gol,*)" WARNING - [Get_refr_idx] : .....set to 0" ; call goPr
  713. water_iv=0.0
  714. else
  715. water_iv=water
  716. endif
  717. if(mode.le.4)then
  718. v_SO4=SO4/so4_density
  719. v_water=water_iv/rol
  720. vtot=vtot+v_SO4+v_water
  721. endif
  722. if(mode.le.5)then
  723. !v_OC=OC/pom_density
  724. v_SOA=SOA/soa_density
  725. vtot=vtot+v_SOA
  726. end if
  727. if(mode.ge.2.and.mode.le.5)then
  728. v_BC=BC/carbon_density
  729. v_OC=OC/pom_density
  730. vtot=vtot+v_BC+v_OC
  731. endif
  732. if(mode.ge.3.and.mode.le.4)then
  733. v_SS=SS/ss_density
  734. vtot=vtot+v_SS
  735. endif
  736. if(mode.ge.3.and.mode.ne.5)then
  737. v_DU=DU/dust_density
  738. vtot=vtot+v_DU
  739. endif
  740. ! If vtot is zero, we will get 0.0/0.0's causing NaNs. In that case, the
  741. ! refractive index does not matter and will be set to (1.0,1.0e-9). The
  742. ! reason not to take (1.0,0.0) is that someone with humour might take
  743. ! the logarithm of the imaginary part. Dust particles get their usual
  744. ! refractive index, because they already returned m_DU. But that does
  745. ! not matter, because there are zero aerosols in this case.
  746. If (vtot .le. 1e-20) Then
  747. m_eff = Cmplx(1.0,1.0e-9)
  748. Else
  749. v_SO4=v_SO4/vtot
  750. v_BC=v_BC/vtot
  751. v_OC=v_OC/vtot
  752. v_SOA=v_SOA/vtot
  753. v_SS=v_SS/vtot
  754. v_DU=v_DU/vtot
  755. v_water=v_water/vtot
  756. !-----------------------------------------------------------------------
  757. ! effective medium computations for each mode
  758. !-----------------------------------------------------------------------
  759. if(mode.eq.1)then
  760. ! Bruggeman mixing rule for SO4 OC and water:
  761. m1=m_SO4
  762. m2=m_SOA
  763. vtot=v_SO4+v_SOA
  764. v2=v_SOA/vtot
  765. call Bruggeman(m1,m2,v2,m0)
  766. m1=m0
  767. m2=m_water
  768. v2=v_water
  769. call Bruggeman(m1,m2,v2,m0)
  770. elseif(mode.eq.2)then
  771. ! iterative Bruggeman mixing rule for SO4, OC, and water:
  772. m1=m_SO4
  773. m2=m_OC
  774. vtot=v_SO4+v_OC
  775. v2=v_OC/vtot
  776. call Bruggeman(m1,m2,v2,m00)
  777. m1=m00
  778. m2=m_SOA
  779. vtot=vtot+v_SOA
  780. v2=v_SOA/vtot
  781. call Bruggeman(m1,m2,v2,m00)
  782. m1=m00
  783. m2=m_water
  784. vtot=vtot+v_water
  785. v2=v_water/vtot
  786. call Bruggeman(m1,m2,v2,m00)
  787. ! Maxwell-Garnett mixing rule for BC inclusions:
  788. m1=m00
  789. m2=m_BC
  790. v2=v_BC
  791. call Maxwell_Garnett(m1,m2,v2,m0)
  792. elseif(mode.eq.3.or.mode.eq.4)then
  793. ! iterative Bruggeman mixing rule for SO4, OC, SS, and water:
  794. m1=m_SO4
  795. m2=m_OC
  796. vtot=v_SO4+v_OC
  797. if ( vtot < TINY( vtot ) ) then
  798. v2=0.0
  799. else
  800. v2=v_OC/vtot
  801. end if
  802. call Bruggeman(m1,m2,v2,m00)
  803. m1=m00
  804. m2=m_SOA
  805. vtot=vtot+v_SOA
  806. if ( vtot < TINY( vtot ) ) then
  807. v2=0.0
  808. else
  809. v2=v_SOA/vtot
  810. end if
  811. call Bruggeman(m1,m2,v2,m00)
  812. m1=m00
  813. m2=m_SS
  814. vtot=vtot+v_SS
  815. if ( vtot < TINY( vtot ) ) then
  816. v2=0.0
  817. else
  818. v2=v_SS/vtot
  819. end if
  820. call Bruggeman(m1,m2,v2,m00)
  821. m1=m00
  822. m2=m_water
  823. vtot=vtot+v_water
  824. v2=v_water/vtot
  825. call Bruggeman(m1,m2,v2,m00)
  826. ! iterative Maxwell-Garnett mixing rule for BC and dust
  827. ! inclusions:
  828. m1=m00
  829. m2=m_BC
  830. vtot=vtot+v_BC
  831. if ( vtot < TINY( vtot ) ) then
  832. v2=0.0
  833. else
  834. v2=v_BC/vtot
  835. end if
  836. call Maxwell_Garnett(m1,m2,v2,m00)
  837. m1=m00
  838. m2=m_DU
  839. v2=v_DU
  840. call Maxwell_Garnett(m1,m2,v2,m0)
  841. elseif(mode.eq.5)then
  842. m1=m_SOA
  843. m2=m_OC
  844. vtot=v_SOA+v_OC
  845. v2=v_OC/vtot
  846. call Bruggeman(m1,m2,v2,m00)
  847. ! Maxwell-Garnett mixing rule for BC inclusions:
  848. m1=m00
  849. m2=m_BC
  850. v2=v_BC
  851. call Maxwell_Garnett(m1,m2,v2,m0)
  852. endif
  853. m_eff = m0
  854. End If
  855. ! Debug : trap for a NAN (13-7-2010 - P. Le Sager)
  856. rpls=real(m_eff)
  857. ipls=imag(m_eff)
  858. IF ((rpls.NE.rpls).or.(ipls.NE.ipls)) then
  859. status = 1
  860. write (gol,'(" GET_REFR_IDX-NAN: ", 3(E16.4,2x),i4,2x,7(E16.4,2x))') rpls, ipls, vtot, mode,&
  861. & SO4,BC,OC,SOA,SS,DU,water
  862. endif
  863. END SUBROUTINE GET_REFR_IDX
  864. !EOC
  865. !--------------------------------------------------------------------------
  866. ! TM5 !
  867. !--------------------------------------------------------------------------
  868. !BOP
  869. !
  870. ! !IROUTINE: BRUGGEMAN
  871. !
  872. ! !DESCRIPTION: Compute effective refractive index of a mixture of 2 components
  873. ! by use of the Bruggeman mixing rule
  874. !\\
  875. !\\
  876. ! !INTERFACE:
  877. !
  878. PURE SUBROUTINE BRUGGEMAN(m1,m2,v2,m0)
  879. !
  880. ! !INPUT PARAMETERS:
  881. !
  882. complex, intent(in) :: m1,m2
  883. real, intent(in) :: v2
  884. !
  885. ! !OUTPUT PARAMETERS:
  886. !
  887. complex, intent(out) :: m0
  888. !
  889. ! !REVISION HISTORY:
  890. ! 12 Aug 2008 - Michael Kahnert, SMHI
  891. ! 6 Feb 2011 - Achim Strunk -
  892. !
  893. ! !REMARKS:
  894. !
  895. !EOP
  896. !------------------------------------------------------------------------
  897. !BOC
  898. complex m1s,m2s,mt
  899. real fac1,fac2
  900. if(v2.eq.1.0)then
  901. m0=m2
  902. return
  903. elseif(v2.eq.0.0)then
  904. m0=m1
  905. return
  906. endif
  907. fac1=2.-3.*v2
  908. fac2=3.*v2-1.
  909. m1s=m1**2
  910. m2s=m2**2
  911. mt=m1s*fac1+m2s*fac2
  912. m0=1./16.*mt**2+0.5*m1s*m2s
  913. m0=csqrt(m0)
  914. m0=m0+0.25*mt
  915. m0=csqrt(m0)
  916. END SUBROUTINE BRUGGEMAN
  917. !EOC
  918. !--------------------------------------------------------------------------
  919. ! TM5 !
  920. !--------------------------------------------------------------------------
  921. !BOP
  922. !
  923. ! !IROUTINE: MAXWELL_GARNETT
  924. !
  925. ! !DESCRIPTION: Compute effective refractive index for a medium consisting of
  926. ! a matrix with refractive index m1 and inclusions with refractive
  927. ! index m2 and volume fraction v2 by use of the Maxwell-Garnett
  928. ! mixing rule.
  929. !\\
  930. !\\
  931. ! !INTERFACE:
  932. !
  933. PURE SUBROUTINE MAXWELL_GARNETT( m1, m2, v2, m0)
  934. !
  935. ! !INPUT PARAMETERS:
  936. !
  937. complex, intent(in) :: m1, m2
  938. real, intent(in) :: v2
  939. !
  940. ! !OUTPUT PARAMETERS:
  941. !
  942. complex, intent(out) :: m0
  943. !
  944. ! !REVISION HISTORY:
  945. ! 12 Aug 2008 - Michael Kahnert, SMHI
  946. ! 6 Feb 2011 - Achim Strunk -
  947. !
  948. ! !REMARKS:
  949. !
  950. !EOP
  951. !------------------------------------------------------------------------
  952. !BOC
  953. complex :: m1s,m2s
  954. real :: fac1,fac2
  955. fac1=3.0-2.0*v2
  956. fac2=3.0-v2
  957. m1s=m1**2
  958. m2s=m2**2
  959. m0=m2s*(fac1*m1s+2.0*v2*m2s)/(v2*m1s+fac2*m2s)
  960. m0=csqrt(m0)
  961. END SUBROUTINE MAXWELL_GARNETT
  962. !EOC
  963. !--------------------------------------------------------------------------
  964. ! TM5 !
  965. !--------------------------------------------------------------------------
  966. !BOP
  967. !
  968. ! !IROUTINE: OPTICS_CALCULATE_AOP
  969. !
  970. ! !DESCRIPTION: This routine writes on aop_out_* (module wide parameters)
  971. ! the retrieved aerosol properties. The caller has to ensure
  972. ! that these fields have been allocated properly.
  973. ! IMPORTANT: OC is actually POM.
  974. ! Remember converting OC to POM when sending it to this method.
  975. !\\
  976. !\\
  977. ! !INTERFACE:
  978. !
  979. SUBROUTINE OPTICS_CALCULATE_AOP( nwl, wdep, lvec, ecearth_units, &
  980. aop_out_ext, aop_out_a, aop_out_g, status, aop_out_add )
  981. !
  982. ! !USES:
  983. !
  984. use binas, only : rol, twopi
  985. use chem_param, only : ss_density, dust_density, carbon_density
  986. use chem_param, only : pom_density, so4_density, soa_density
  987. Use mo_aero_m7, only : nmod, cmedr2mmedr, sigma
  988. !
  989. ! !INPUT PARAMETERS:
  990. !
  991. integer, intent(in) :: nwl
  992. type(wavelendep), intent(in), dimension(nwl) :: wdep ! wavelength depending properties
  993. integer, intent(in) :: lvec
  994. logical, intent(in) :: ecearth_units
  995. !
  996. ! !OUTPUT PARAMETERS:
  997. !
  998. Real, Dimension(:,:,:), intent(out) :: aop_out_ext ! extinctions
  999. Real, Dimension(:,:), intent(out) :: aop_out_a ! single scattering albedo
  1000. Real, Dimension(:,:), intent(out) :: aop_out_g ! assymetry factor
  1001. integer, intent(out) :: status
  1002. Real, Dimension(:,:,:), intent(out), optional :: aop_out_add ! additional parameters
  1003. !
  1004. ! !REVISION HISTORY:
  1005. ! 12 Aug 2008 - Michael Kahnert, SMHI
  1006. ! 6 Feb 2011 - Achim Strunk -
  1007. ! 23 Jan 2013 - Narcisa Banda - included OMP (PLS: commented in TM5-MP)
  1008. !
  1009. ! !REMARKS:
  1010. !
  1011. !EOP
  1012. !------------------------------------------------------------------------
  1013. !BOC
  1014. real, dimension(:), allocatable :: NCsca, incext
  1015. real :: Cexti, ai, gi, NCscai, xg
  1016. complex :: m_eff
  1017. real, dimension(:), allocatable :: lnsigma
  1018. integer :: i, imode, ivec!, lss, lee
  1019. integer :: statusomp
  1020. Logical :: coarse
  1021. real :: totvoldry, modfrac
  1022. ! real :: t1, t2 , omp_get_wtime
  1023. Real, Dimension(:,:,:), Pointer :: cext_table, a_table, g_table
  1024. ! --- const ------------------------------
  1025. character(len=*), parameter :: rname = mname//'/optics_calculate_AOP'
  1026. ! --- begin --------------------------------
  1027. allocate( NCsca ( lvec ) )
  1028. ! allocate( NCscai( lvec ) )
  1029. ! allocate( Cexti ( lvec ) )
  1030. ! allocate( ai ( lvec ) )
  1031. ! allocate( gi ( lvec ) )
  1032. ! allocate( xg ( lvec ) )
  1033. ! allocate( m_eff ( lvec ) )
  1034. allocate( incext( lvec ) )
  1035. !t1= omp_get_wtime()
  1036. status = 0
  1037. !pls! !$OMP PARALLEL &
  1038. !pls! !$OMP default (none) &
  1039. !pls! !$OMP shared (nwl, lvec, NCsca, incext, &
  1040. !pls! !$OMP wdep, aop_in, aop_out_Ext, aop_out_g, aop_out_a, aop_out_add, sigma, cmedr2mmedr,&
  1041. !pls! !$OMP cext_200, a_200, g_200, cext_159, a_159, g_159, status, gol) &
  1042. !pls! !$OMP private (lnsigma, i, imode, modfrac, coarse, totvoldry, lss, lee, ivec, &
  1043. !pls! !$OMP NCscai, Cexti, ai, gi, xg, m_eff, cext_table, a_table, g_table, statusomp )
  1044. !pls! call my_omp_domain (1, lvec, lss, lee)
  1045. ! Sulphate based on OPAC (Hess et al., 1998):
  1046. !=======================================================================
  1047. ! Get refractive indices of each component at the given wavelength:
  1048. !=======================================================================
  1049. do i = 1, nwl ! loop over wavelengths
  1050. if( wdep(i)%split .or. wdep(i)%insitu ) then
  1051. allocate( lnsigma( nmod ) )
  1052. lnsigma = log(sigma)
  1053. end if
  1054. aop_out_Ext(:,i,:) = 0.0
  1055. aop_out_g (:,i) = 0.0
  1056. aop_out_a (:,i) = 0.0
  1057. if( wdep(i)%insitu ) aop_out_add(:,i,:) = 0.0
  1058. NCsca (:) = 0.0
  1059. do imode = 1, 7 ! loop over M7 modes
  1060. coarse = (imode .eq. 4 .or. imode .eq. 7)
  1061. If (coarse) then
  1062. cext_table => cext_200
  1063. a_table => a_200
  1064. g_table => g_200
  1065. Else
  1066. cext_table => cext_159
  1067. a_table => a_159
  1068. g_table => g_159
  1069. End if
  1070. !=======================================================================
  1071. ! Compute effective refractive index of internally mixed aerosols
  1072. ! for each grid cell and mode:
  1073. !=======================================================================
  1074. do ivec = 1, lvec
  1075. !write(1001,*) aop_in(ivec)%SO4(imode), aop_in(ivec)%NO3(imode)
  1076. !write(1002,*) aop_in(ivec)%SOA(imode)
  1077. !write(1003,*) aop_in(ivec)%BC(imode), aop_in(ivec)%OC(imode)
  1078. !write(1004,*) aop_in(ivec)%SS(imode), aop_in(ivec)%DU(imode)
  1079. call get_refr_idx( wdep(i), &
  1080. aop_in(ivec)%SO4(imode) + aop_in(ivec)%NO3(imode), & ! H2-SO4 + NH4NO3
  1081. aop_in(ivec)%BC (imode), aop_in(ivec)%OC (imode), &
  1082. aop_in(ivec)%SOA (imode), &
  1083. aop_in(ivec)%SS (imode), aop_in(ivec)%DU (imode), &
  1084. aop_in(ivec)%h2o(imode), imode, m_eff, statusomp, gol)
  1085. if (statusomp ==1) then
  1086. ! Problem tracked to emilnox, should not happen anymore
  1087. ! but keep the printout and hack for now
  1088. !FIX to finish crescendo
  1089. write (gol,'(" Problem with GET_REFR_IDX-NAN inputs: ", 9(E16.4,2x))') &
  1090. aop_in(ivec)%SO4(imode), aop_in(ivec)%NO3(imode), aop_in(ivec)%h2o(imode), &
  1091. aop_in(ivec)%SOA(imode),aop_in(ivec)%BC(imode), aop_in(ivec)%OC(imode),&
  1092. aop_in(ivec)%SS(imode), aop_in(ivec)%DU(imode)
  1093. call GoErr
  1094. ! Assume edge case not caught. Set m_eff to default (1.0,1.0e-9), same as in ref_idx
  1095. ! (subroutine problems with inputs SO4 and WATER?)
  1096. status = 0
  1097. m_eff= Cmplx(1.0,1.0e-9)
  1098. ! If all edge cases were handled correctly, that should be:
  1099. !status = 1
  1100. !IF_ERROR_RETURN( status=1 )
  1101. endif
  1102. ! cmk added towpi for new netcdf lookup table
  1103. xg = twopi*aop_in(ivec)%rg(imode) / wdep(i)%wl
  1104. !=======================================================================
  1105. ! get aerosol optical properties from data base for each mode
  1106. !=======================================================================
  1107. ! add extra safeguard for negative xg. It is unphysical, but have a safeguard anyway
  1108. ! added for refr_idx_nan problem
  1109. if (xg .gt. 0.0) then
  1110. call Optics_Get(m_eff, xg, Cexti, ai, gi, cext_table, a_table, g_table, statusomp, gol )
  1111. else
  1112. Cexti=0.0
  1113. ai=1.0
  1114. gi=1.0
  1115. end if
  1116. if (statusomp ==1) then
  1117. call GoErr
  1118. status = 1
  1119. IF_ERROR_RETURN( status=1 )
  1120. endif
  1121. ! Multiply Cext with lambda^2 to get the cross section.
  1122. Cexti = Cexti*(wdep(i)%wl**2)
  1123. ! this here is extinction coefficient in this mode
  1124. incext(ivec) = aop_in(ivec)%numdens(imode) * Cexti
  1125. ! sum up partial coefficients
  1126. Aop_out_ext(ivec,i,1) = Aop_out_Ext(ivec,i,1) + incext(ivec)
  1127. ! scattering portion
  1128. NCscai = ai * incext(ivec)
  1129. ! sum up weights for average (both albedo and asymmetry)
  1130. NCsca (ivec) = NCsca (ivec) + NCscai
  1131. aop_out_g(ivec,i) = aop_out_g(ivec,i) + NCscai * gi
  1132. end do
  1133. ! Split extinction to separate contributions from constituents in modes.
  1134. ! A volume mixing is assumed (in contrast to the explicit mixing in get_refr_ind).
  1135. if( wdep(i)%split .or. wdep(i)%insitu) then
  1136. do ivec = 1, lvec
  1137. if (wdep(i)%split) then
  1138. ! The fine-mode contributions to the extinction
  1139. ! includes the contributions from particles
  1140. ! with (wet) diameters smaller than 1 micron.
  1141. ! For wet particles, only part of the accumulation mode
  1142. ! should be included, and the coarse mode should be excluded.
  1143. if (.not.coarse) then
  1144. ! Currently, the contribution of the accumulation mode
  1145. ! is approximated using weighting by volume scaling factor modfrac.
  1146. ! For extinction, area weighting would probably be more appropriate!!
  1147. if (imode .eq. 3 .or. imode .eq. 6 ) then
  1148. ! - convert number mean radius to volume mean radius (by cmedr2mmedr(imode))
  1149. ! - 1 micron diameter --> radius is 0.5 microns (rg is also in microns)
  1150. modfrac = 0.5 + 0.5 * ERF( log( 0.5 / (aop_in(ivec)%rg(imode) * cmedr2mmedr(imode)) ) / &
  1151. (sqrt(2.0) * lnsigma(imode)) )
  1152. else
  1153. ! Include full nucleation and Aitken mode contributions.
  1154. modfrac = 1.0
  1155. endif
  1156. aop_out_ext(ivec,i,10) = aop_out_ext(ivec,i,10) + modfrac * incext(ivec)
  1157. endif
  1158. ! total volume from so4/no3/bc/oc/ss/du in this mode (ATTENTION: DRY!!)
  1159. ! take no3 as so4
  1160. totvoldry = aop_in(ivec)%so4(imode)/so4_density + aop_in(ivec)%no3(imode)/so4_density + &
  1161. aop_in(ivec)%bc (imode)/carbon_density + aop_in(ivec)%oc (imode)/pom_density + &
  1162. aop_in(ivec)%soa (imode)/soa_density + &
  1163. aop_in(ivec)%ss (imode)/ss_density + aop_in(ivec)%du (imode)/dust_density
  1164. ! check whether there is some volume available
  1165. ! otherwise assign zeros to extinction increments
  1166. if( totvoldry < tiny(totvoldry) ) then
  1167. write(gol,'("WARNING: no volume in mode (",i3,"). assigning zero extinctions")') imode; call goPr
  1168. cycle
  1169. end if
  1170. ! H2-SO4 contribution
  1171. aop_out_ext(ivec,i,2) = aop_out_ext(ivec,i,2) + incext(ivec) * (aop_in(ivec)%so4(imode)/so4_density ) / totvoldry
  1172. ! BC contribution
  1173. aop_out_ext(ivec,i,3) = aop_out_ext(ivec,i,3) + incext(ivec) * (aop_in(ivec)%bc (imode)/carbon_density) / totvoldry
  1174. ! POM contribution
  1175. aop_out_ext(ivec,i,4) = aop_out_ext(ivec,i,4) + incext(ivec) * (aop_in(ivec)%oc (imode)/pom_density ) / totvoldry
  1176. ! SOA contribution
  1177. aop_out_ext(ivec,i,5) = aop_out_ext(ivec,i,5) + incext(ivec) * (aop_in(ivec)%soa (imode)/soa_density ) / totvoldry
  1178. ! SS contribution
  1179. aop_out_ext(ivec,i,6) = aop_out_ext(ivec,i,6) + incext(ivec) * (aop_in(ivec)%ss (imode)/ss_density ) / totvoldry
  1180. ! DU contribution
  1181. aop_out_ext(ivec,i,7) = aop_out_ext(ivec,i,7) + incext(ivec) * (aop_in(ivec)%du (imode)/dust_density ) / totvoldry
  1182. ! NH4NO3 contribution
  1183. aop_out_ext(ivec,i,8) = aop_out_ext(ivec,i,8) + incext(ivec) * (aop_in(ivec)%no3(imode)/so4_density ) / totvoldry
  1184. ! Fine-mode contributions for dust and sea salt
  1185. if (.not.coarse) then
  1186. aop_out_ext(ivec,i,11) = aop_out_ext(ivec,i,11) + incext(ivec) * (aop_in(ivec)%du (imode)/dust_density ) / totvoldry * modfrac
  1187. aop_out_ext(ivec,i,12) = aop_out_ext(ivec,i,12) + incext(ivec) * (aop_in(ivec)%ss (imode)/ss_density ) / totvoldry * modfrac
  1188. endif
  1189. endif
  1190. ! Water contribution:
  1191. ! Get optical properties without water, the difference will be extinction due to
  1192. ! water existence
  1193. ! - mis-use gi for this
  1194. gi = 0.0
  1195. call get_refr_idx( wdep(i), &
  1196. aop_in(ivec)%SO4(imode) + aop_in(ivec)%NO3(imode), &
  1197. aop_in(ivec)%BC (imode), aop_in(ivec)%OC (imode), &
  1198. aop_in(ivec)%SOA (imode), &
  1199. aop_in(ivec)%SS (imode), aop_in(ivec)%DU (imode), &
  1200. gi, imode, m_eff, statusomp, gol)
  1201. if (statusomp ==1) then
  1202. write (gol,'("Problem with GET_REFR_IDX-NAN inputs: ", 9(E16.4,2x))') &
  1203. aop_in(ivec)%SO4(imode), aop_in(ivec)%NO3(imode), aop_in(ivec)%h2o(imode), &
  1204. aop_in(ivec)%SOA(imode),aop_in(ivec)%BC(imode), aop_in(ivec)%OC(imode),&
  1205. aop_in(ivec)%SS(imode), aop_in(ivec)%DU(imode)
  1206. call GoErr
  1207. ! Assume edge case not caught. Set m_eff to default (1.0,1.0e-9), same as in ref_idx
  1208. ! (subroutine problems with inputs SO4 and WATER?)
  1209. status = 0
  1210. m_eff= Cmplx(1.0,1.0e-9)
  1211. ! If all edge cases were handled correctly, that should be:
  1212. !status = 1
  1213. !IF_ERROR_RETURN( status=1 )
  1214. !status = 1
  1215. endif
  1216. ! here we need the dry radius!!!
  1217. !>>> TvN
  1218. ! 2*pi should be included (see comment above)
  1219. !xg = aop_in(ivec)%rgd(imode) / wdep(i)%wl
  1220. xg = twopi*aop_in(ivec)%rgd(imode) / wdep(i)%wl
  1221. !<<< TvN
  1222. ! TB
  1223. ! add extra safeguard for negative xg, unphysical but have a safeguard
  1224. ! added for refr_idx_nan problem
  1225. if (xg .gt. 0.0) then
  1226. call Optics_Get(m_eff, xg, Cexti, ai, gi, cext_table, a_table, g_table, statusomp, gol )
  1227. else
  1228. Cexti=0.0
  1229. ai=1.0
  1230. gi=1.0
  1231. end if
  1232. if (statusomp ==1) then
  1233. call GoErr
  1234. status = 1
  1235. IF_ERROR_RETURN( status=1 )
  1236. endif
  1237. Cexti = Cexti*(wdep(i)%wl**2)
  1238. if (wdep(i)%split) then
  1239. ! add difference to water subarray
  1240. Aop_out_ext(ivec,i,9) = aop_out_ext(ivec,i,9) + (incext(ivec) - aop_in(ivec)%numdens(imode) * Cexti)
  1241. endif
  1242. if (wdep(i)%insitu) then
  1243. ! Surface dry extinction and absorption:
  1244. !>>> TvN
  1245. ! Remove cut off for the total values:
  1246. !modfrac = 0.5 + 0.5 * ERF( log( 5.0 / (aop_in(ivec)%rgd(imode) * cmedr2mmedr(imode)) ) / &
  1247. ! (sqrt(2.0) * lnsigma(imode)) )
  1248. ! extinction and absorption (extinction-scattering):
  1249. !Aop_out_add(ivec,i,1) = aop_out_add(ivec,i,1) + modfrac * aop_in(ivec)%numdens(imode) * Cexti
  1250. !Aop_out_add(ivec,i,2) = aop_out_add(ivec,i,2) + modfrac * aop_in(ivec)%numdens(imode) * Cexti * (1. - ai)
  1251. aop_out_add(ivec,i,1) = aop_out_add(ivec,i,1) + aop_in(ivec)%numdens(imode) * Cexti
  1252. aop_out_add(ivec,i,2) = aop_out_add(ivec,i,2) + aop_in(ivec)%numdens(imode) * Cexti * (1. - ai)
  1253. aop_out_add(ivec,i,3) = aop_out_add(ivec,i,3) + aop_in(ivec)%numdens(imode) * Cexti * ai * gi
  1254. ! Add fine-mode contributions
  1255. ! For dry aerosol, the fine-mode optical properties include
  1256. ! the full accumulation mode, but not the coarse mode:
  1257. if (.not.coarse) then
  1258. aop_out_add(ivec,i,4) = aop_out_add(ivec,i,4) + aop_in(ivec)%numdens(imode) * Cexti
  1259. aop_out_add(ivec,i,5) = aop_out_add(ivec,i,5) + aop_in(ivec)%numdens(imode) * Cexti * (1. - ai)
  1260. endif
  1261. !<<< TvN
  1262. endif
  1263. end do ! ivec
  1264. end if
  1265. enddo ! modes
  1266. if (ecearth_units) then
  1267. ! return extinction due to absorption
  1268. ! and asymmetry factor multiplied by extinction due to scattering
  1269. ! and convert um**2/m**3 into 1/m (as for extinction below)
  1270. Aop_out_a(:,i) = ( Aop_out_Ext(:,i,1) - NCsca(:) ) * 1.e-12
  1271. Aop_out_g(:,i) = Aop_out_g(:,i) * 1.e-12
  1272. else
  1273. ! return single-scattering albedo and asymmetry factor
  1274. ! take into account small extinction values
  1275. where( Aop_out_Ext(:,i,1) > tiny(0.0) )
  1276. Aop_out_a(:,i) = NCsca(:) / Aop_out_Ext(:,i,1)
  1277. elsewhere
  1278. ! No extinction -> Fill 1.0 for albedo because it looks clean.
  1279. Aop_out_a(:,i) = 1.0
  1280. endwhere
  1281. ! take into account small extinction values
  1282. where( NCsca(:) > tiny(0.0) )
  1283. Aop_out_g(:,i) = Aop_out_g(:,i) / NCsca(:)
  1284. elsewhere
  1285. ! No scattering at all -> Fill 1.0 for asymmetry because it looks clean.
  1286. Aop_out_g(:,i) = 1.0
  1287. endwhere
  1288. endif
  1289. ! convert um**2/m**3 into 1/m
  1290. Aop_out_Ext(:,i,:) = Aop_out_Ext(:,i,:) * 1e-12
  1291. if( wdep(i)%insitu) then
  1292. ! take into account small extinction values
  1293. where( aop_out_add(:,i,1) - aop_out_add(:,i,2) > tiny(0.0) )
  1294. aop_out_add(:,i,3) = aop_out_add(:,i,3) / (aop_out_add(:,i,1)-aop_out_add(:,i,2))
  1295. elsewhere
  1296. ! No scattering at all -> Fill 1.0 for asymmetry because it looks clean.
  1297. aop_out_add(:,i,3) = 1.0
  1298. endwhere
  1299. Aop_out_add(:,i,1) = aop_out_add(:,i,1) * 1e-12
  1300. Aop_out_add(:,i,2) = aop_out_add(:,i,2) * 1e-12
  1301. Aop_out_add(:,i,4) = aop_out_add(:,i,4) * 1e-12
  1302. Aop_out_add(:,i,5) = aop_out_add(:,i,5) * 1e-12
  1303. endif
  1304. if( wdep(i)%split .or. wdep(i)%insitu ) then
  1305. deallocate( lnsigma )
  1306. endif
  1307. !=======================================================================
  1308. enddo ! loop over wavelengths
  1309. Nullify(Cext_table)
  1310. Nullify(a_table)
  1311. Nullify(g_table)
  1312. !$OMP END PARALLEL
  1313. if (status==1) then
  1314. call goPr
  1315. IF_NOTOK_RETURN(status=1)
  1316. endif
  1317. !do imode = 1,7
  1318. ! print *, 'Radius,mode :', imode, sum(aop_in(:)%rg(imode))/lvec
  1319. ! print *, 'numden,mode :', imode, sum(aop_in(:)%numdens(imode))/lvec
  1320. !enddo
  1321. deallocate( NCsca, incext )
  1322. !do i = 1,nwl
  1323. ! print *, 'AOD per grid box:', wdep(i)%wl, sum(Aop_out_Ext(:,i,1))/lvec
  1324. !enddo
  1325. ! ok
  1326. status = 0
  1327. END SUBROUTINE OPTICS_CALCULATE_AOP
  1328. !EOC
  1329. !--------------------------------------------------------------------------
  1330. ! TM5 !
  1331. !--------------------------------------------------------------------------
  1332. !BOP
  1333. !
  1334. ! !IROUTINE: OPTICS_AOP_GET
  1335. !
  1336. ! !DESCRIPTION: Initialise the fields "aop_in" and then calculate the
  1337. ! optical properties through a call to optics_calculate_aop.
  1338. !\\
  1339. !\\
  1340. ! !INTERFACE:
  1341. !
  1342. SUBROUTINE OPTICS_AOP_GET( lvec, region, nwav, wdep, ncontr, ecearth_units, &
  1343. aop_out_ext, aop_out_a, aop_out_g, status, aop_out_add )
  1344. !
  1345. ! !USES:
  1346. !
  1347. USE TM5_DISTGRID, ONLY : dgrid, Get_DistGrid
  1348. use Meteo, only : Set
  1349. Use Meteodata, only : gph_dat, m_dat
  1350. Use Dims, only : im, jm, lm
  1351. use global_data, only : region_dat, mass_dat
  1352. Use chem_param, only : inus_n, iso4nus, isoanus, nmod
  1353. use chem_param, only : iais_n, iso4ais, ibcais, ipomais, isoaais
  1354. Use chem_param, only : iacs_n, iso4acs, ibcacs, ipomacs, isoaacs, issacs, iduacs, ino3_a
  1355. use chem_param, only : imsa
  1356. use chem_param, only : icos_n, iso4cos, ibccos, ipomcos, isoacos, isscos, iducos
  1357. use chem_param, only : iaii_n, ibcaii, ipomaii, isoaaii
  1358. use chem_param, only : iaci_n, icoi_n, iduaci, iducoi
  1359. use chem_param, only : h2so4_factor, nh4no3_factor
  1360. use chem_param, only : so4_density, nh4no3_density, msa_density
  1361. Use m7_data, only : h2o_mode, rw_mode, rwd_mode
  1362. !
  1363. ! !INPUT PARAMETERS:
  1364. !
  1365. Integer, Intent(In) :: region, lvec
  1366. Integer, Intent(In) :: nwav, ncontr
  1367. type(wavelendep), dimension(nwav), Intent(In) :: wdep
  1368. logical, intent(in) :: ecearth_units
  1369. !
  1370. ! !OUTPUT PARAMETERS:
  1371. !
  1372. real, dimension(lvec,nwav,ncontr), intent(out) :: aop_out_ext ! extinctions
  1373. real, dimension(lvec,nwav), intent(out) :: aop_out_a ! single scattering albedo
  1374. real, dimension(lvec,nwav), intent(out) :: aop_out_g ! assymetry factor
  1375. integer, intent(out) :: status
  1376. real, dimension(:,:,:), intent(out), optional :: aop_out_add ! additional parameters
  1377. !
  1378. ! !REVISION HISTORY:
  1379. ! 29 Nov 2010 - Achim Strunk - v0
  1380. ! 24 Jun 2011 - Achim Strunk - Added NO3 to allow for explicit
  1381. ! AOD split of (SO4+NO3)
  1382. ! 20 Jun 2012 - P. Le Sager - adapted for lon-lat MPI domain decomposition
  1383. !
  1384. ! !REMARKS:
  1385. !
  1386. !EOP
  1387. !------------------------------------------------------------------------
  1388. !BOC
  1389. character(len=*), parameter :: rname = mname//'/optics_aop_get'
  1390. real, dimension(:,:,:,:), pointer :: rm
  1391. real, dimension(:,:,:), pointer :: m
  1392. real, dimension(:,:,:), allocatable :: volume
  1393. Integer :: i, j, l, iloop, i1, i2, j1, j2, lmr
  1394. ! --- start ------------------------------
  1395. ! ensure met fields being available
  1396. call Set( gph_dat(region), status, used=.true. )
  1397. ! air & tracers mass
  1398. m => m_dat(region)%data
  1399. rm => mass_dat(region)%rm
  1400. ! tile grid size
  1401. CALL GET_DISTGRID( dgrid(region), I_STRT=i1, I_STOP=i2, J_STRT=j1, J_STOP=j2 )
  1402. ! Generalize to allow for reduced number of levels
  1403. ! when called from ECEarth_Optics_Step
  1404. !lmr=lm(region)
  1405. lmr = lvec / ( (i2-i1+1)*(j2-j1+1) )
  1406. allocate( aop_in(lvec) )
  1407. do i = 1, nmod
  1408. aop_in(:)%so4 (i) = 0.0 ; aop_in(:)%bc (i) = 0.0
  1409. aop_in(:)%oc (i) = 0.0 ; aop_in(:)%soa (i) = 0.0
  1410. aop_in(:)%ss (i) = 0.0
  1411. aop_in(:)%du (i) = 0.0 ; aop_in(:)%h2o (i) = 0.0
  1412. aop_in(:)%numdens(i) = 0.0 ; aop_in(:)%rg (i) = 0.0
  1413. aop_in(:)%rgd (i) = 0.0 ; aop_in(:)%no3 (i) = 0.0
  1414. end do
  1415. !>>> TvN
  1416. ! In M7 sulphate is assumed to be H2-SO4 with corresponding particle density so4_density
  1417. ! The sulphate mass should therefore also include the small contribution from the H atoms
  1418. ! NUS
  1419. aop_in(:)%so4(1) = reshape( 1.e9 * h2so4_factor * rm(i1:i2,j1:j2,1:lmr,iso4nus) / &
  1420. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1421. aop_in(:)%soa(1) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,isoanus) / &
  1422. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1423. ! AIS
  1424. aop_in(:)%so4(2) = reshape( 1.e9 * h2so4_factor * rm(i1:i2,j1:j2,1:lmr,iso4ais) / &
  1425. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1426. aop_in(:)%bc (2) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ibcais ) / &
  1427. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1428. aop_in(:)%oc (2) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ipomais) / &
  1429. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1430. aop_in(:)%soa(2) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,isoaais) / &
  1431. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1432. ! ACS (additional: NO3)
  1433. ! The contribution from methane sulfonate (MSA-) aerosol is added
  1434. ! to that for sulfate.
  1435. ! As the addition is done by volume,
  1436. ! we need to account for the difference in densities
  1437. ! (as done below for ammonium nitrate).
  1438. aop_in(:)%so4(3) = reshape( 1.e9 * ( h2so4_factor * rm(i1:i2,j1:j2,1:lmr,iso4acs) + &
  1439. (so4_density / msa_density) * rm(i1:i2,j1:j2,1:lmr,imsa) ) / &
  1440. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1441. ! Since nh4no3_density is the density of NH4NO3, the contribution from NH4 should be included.
  1442. ! Moreover, assuming the same refractive index for NH4NO3 as for H2-SO4,
  1443. ! the contributions from both components can be added by volume;
  1444. ! thus we need to account for the difference in densities.
  1445. ! Estimates of the refractive index of NH4NO3 are available from literature
  1446. ! (e.g. Lowenthal et al., Atmos. Environ., 2000).
  1447. ! For practical purposes, it can be set equal to the value used for sulfate,
  1448. ! i.e. the value for a solution containing 75% H2SO4 (Fenn et al., 1985).
  1449. aop_in(:)%no3(3) = reshape( 1.e9 * nh4no3_factor * (so4_density / nh4no3_density) * &
  1450. rm(i1:i2,j1:j2,1:lmr,ino3_a ) / &
  1451. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1452. aop_in(:)%bc (3) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ibcacs ) / &
  1453. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1454. aop_in(:)%oc (3) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ipomacs) / &
  1455. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1456. aop_in(:)%soa(3) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,isoaacs) / &
  1457. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1458. aop_in(:)%ss (3) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,issacs ) / &
  1459. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1460. aop_in(:)%du (3) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,iduacs ) / &
  1461. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1462. ! COS
  1463. aop_in(:)%so4(4) = reshape( 1.e9 * h2so4_factor * rm(i1:i2,j1:j2,1:lmr,iso4cos) / &
  1464. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1465. !<<< TvN
  1466. aop_in(:)%bc (4) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ibccos ) / &
  1467. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1468. aop_in(:)%oc (4) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ipomcos) / &
  1469. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1470. aop_in(:)%soa(4) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,isoacos) / &
  1471. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1472. aop_in(:)%ss (4) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,isscos ) / &
  1473. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1474. aop_in(:)%du (4) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,iducos ) / &
  1475. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1476. ! AII
  1477. aop_in(:)%bc (5) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ibcaii ) / &
  1478. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1479. aop_in(:)%oc (5) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,ipomaii) / &
  1480. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1481. aop_in(:)%soa(5) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,isoaaii) / &
  1482. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1483. ! ACI
  1484. aop_in(:)%du (6) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,iduaci ) / &
  1485. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1486. ! COI
  1487. aop_in(:)%du (7) = reshape( 1.e9 * rm(i1:i2,j1:j2,1:lmr,iducoi ) / &
  1488. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1489. ! Water in (hydrophillic) modes
  1490. aop_in(:)%h2o(1) = reshape( 1.e9 * h2o_mode(region,1)%d3(i1:i2,j1:j2,1:lmr) / &
  1491. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1492. aop_in(:)%h2o(2) = reshape( 1.e9 * h2o_mode(region,2)%d3(i1:i2,j1:j2,1:lmr) / &
  1493. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1494. aop_in(:)%h2o(3) = reshape( 1.e9 * h2o_mode(region,3)%d3(i1:i2,j1:j2,1:lmr) / &
  1495. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1496. aop_in(:)%h2o(4) = reshape( 1.e9 * h2o_mode(region,4)%d3(i1:i2,j1:j2,1:lmr) / &
  1497. m(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1498. aop_in(:)%rg (1) = reshape( 1.e6 * rw_mode (region,1)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1499. aop_in(:)%rg (2) = reshape( 1.e6 * rw_mode (region,2)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1500. aop_in(:)%rg (3) = reshape( 1.e6 * rw_mode (region,3)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1501. aop_in(:)%rg (4) = reshape( 1.e6 * rw_mode (region,4)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1502. aop_in(:)%rg (5) = reshape( 1.e6 * rw_mode (region,5)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1503. aop_in(:)%rg (6) = reshape( 1.e6 * rw_mode (region,6)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1504. aop_in(:)%rg (7) = reshape( 1.e6 * rw_mode (region,7)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1505. ! dry radius for soluble modes / rest equals the usual radii
  1506. aop_in(:)%rgd(1) = reshape( 1.e6 * rwd_mode(region,1)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1507. aop_in(:)%rgd(2) = reshape( 1.e6 * rwd_mode(region,2)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1508. aop_in(:)%rgd(3) = reshape( 1.e6 * rwd_mode(region,3)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1509. aop_in(:)%rgd(4) = reshape( 1.e6 * rwd_mode(region,4)%d3(i1:i2,j1:j2,1:lmr), (/lvec/) )
  1510. aop_in(:)%rgd(5) = aop_in(:)%rg (5)
  1511. aop_in(:)%rgd(6) = aop_in(:)%rg (6)
  1512. aop_in(:)%rgd(7) = aop_in(:)%rg (7)
  1513. ! volume for number density
  1514. allocate( volume( i1:i2, j1:j2, 1:lmr ) )
  1515. do j = j1, j2
  1516. volume(:,j,:) = ( gph_dat(region)%data(i1:i2, j, 2:lmr+1) - &
  1517. gph_dat(region)%data(i1:i2, j, 1:lmr ) ) * &
  1518. region_dat(region)%dxyp(j) ! m3
  1519. end do
  1520. aop_in(:)%numdens(1) = reshape( rm(i1:i2,j1:j2,1:lmr,inus_n) / volume, (/lvec/) )
  1521. aop_in(:)%numdens(2) = reshape( rm(i1:i2,j1:j2,1:lmr,iais_n) / volume, (/lvec/) )
  1522. aop_in(:)%numdens(3) = reshape( rm(i1:i2,j1:j2,1:lmr,iacs_n) / volume, (/lvec/) )
  1523. aop_in(:)%numdens(4) = reshape( rm(i1:i2,j1:j2,1:lmr,icos_n) / volume, (/lvec/) )
  1524. aop_in(:)%numdens(5) = reshape( rm(i1:i2,j1:j2,1:lmr,iaii_n) / volume, (/lvec/) )
  1525. aop_in(:)%numdens(6) = reshape( rm(i1:i2,j1:j2,1:lmr,iaci_n) / volume, (/lvec/) )
  1526. aop_in(:)%numdens(7) = reshape( rm(i1:i2,j1:j2,1:lmr,icoi_n) / volume, (/lvec/) )
  1527. deallocate( volume )
  1528. ! check valid ranges in particle sizes (might be zero)
  1529. where( aop_in%rg (1) .lt. 1.E-15 ) aop_in%rg (1) = 1.E-15
  1530. where( aop_in%rgd(1) .lt. 1.E-15 ) aop_in%rgd(1) = 1.E-15
  1531. where( aop_in%rg (2) .lt. 1.E-15 ) aop_in%rg (2) = 1.E-15
  1532. where( aop_in%rgd(2) .lt. 1.E-15 ) aop_in%rgd(2) = 1.E-15
  1533. where( aop_in%rg (3) .lt. 1.E-15 ) aop_in%rg (3) = 1.E-15
  1534. where( aop_in%rgd(3) .lt. 1.E-15 ) aop_in%rgd(3) = 1.E-15
  1535. where( aop_in%rg (4) .lt. 1.E-15 ) aop_in%rg (4) = 1.E-15
  1536. where( aop_in%rgd(4) .lt. 1.E-15 ) aop_in%rgd(4) = 1.E-15
  1537. where( aop_in%rg (5) .lt. 1.E-15 ) aop_in%rg (5) = 1.E-15
  1538. where( aop_in%rgd(5) .lt. 1.E-15 ) aop_in%rgd(5) = 1.E-15
  1539. where( aop_in%rg (6) .lt. 1.E-15 ) aop_in%rg (6) = 1.E-15
  1540. where( aop_in%rgd(6) .lt. 1.E-15 ) aop_in%rgd(6) = 1.E-15
  1541. where( aop_in%rg (7) .lt. 1.E-15 ) aop_in%rg (7) = 1.E-15
  1542. where( aop_in%rgd(7) .lt. 1.E-15 ) aop_in%rgd(7) = 1.E-15
  1543. nullify(rm)
  1544. nullify(m)
  1545. !
  1546. aop_out_ext=0.0
  1547. aop_out_a=0.0
  1548. aop_out_g=0.0
  1549. if (present(aop_out_add)) then
  1550. call optics_calculate_aop( nwav, wdep, lvec, ecearth_units, &
  1551. aop_out_ext, aop_out_a, aop_out_g, status, aop_out_add )
  1552. else
  1553. call optics_calculate_aop( nwav, wdep, lvec, ecearth_units, &
  1554. aop_out_ext, aop_out_a, aop_out_g, status )
  1555. endif
  1556. IF_NOTOK_RETURN(status=1)
  1557. ! OK
  1558. Deallocate( aop_in )
  1559. status = 0
  1560. END SUBROUTINE OPTICS_AOP_GET
  1561. !EOC
  1562. END MODULE OPTICS