source: trunk/LMDZ.TITAN/libf/muphytitan/mmp_optics.f90 @ 1926

Last change on this file since 1926 was 1926, checked in by jvatant, 7 years ago

1) Microphysics diags / outputs :


+ Add supplementary diagnostics outputs for microphysics ( precip, flux, rc ... ) ( new muphy_diag.F90 module )
+ Correct the outputs of microphys tracers to be in X/m-3 to be comparable to "standard values"

+ Also update the deftank callphys.def with latest revs modifs for microphysics

2) Condensation / chemistry updates :


+ Moved chemistry AFTER microphysics

  • To have mufi condensation before photochem
  • Chemistry called last coherent with the fact that it brings back fields to equilibrium

+ If 2D chemistry, make zonally averaged fields go through mufi and chem condensation

to have non saturated profiles in input of photochemistry
( other 'short' processes neglected as 2D -> no diurnal cycle, just seasonal evolution )

+ Also corrected the positivity check ( took Mars GCM syntax ) after chemistry ( could previously lead to negs )

3) Noticed a weird behaviour ( bug? ) :


+ If generalize the use of arrays *_indx for tracers, to get rid of ugly "iq+nmicro",

it ends up with weird results / crash in optim mode ( ok in debug ) but didn't find out why ...

--JVO

File size: 15.3 KB
Line 
1! Copyright 2017 Université de Reims Champagne-Ardenne
2! Contributor: J. Burgalat (GSMA, URCA)
3! email of the author : jeremie.burgalat@univ-reims.fr
4!
5! This software is a computer program whose purpose is to compute
6! microphysics processes using a two-moments scheme.
7!
8! This library is governed by the CeCILL license under French law and
9! abiding by the rules of distribution of free software.  You can  use,
10! modify and/ or redistribute the software under the terms of the CeCILL
11! license as circulated by CEA, CNRS and INRIA at the following URL
12! "http://www.cecill.info".
13!
14! As a counterpart to the access to the source code and  rights to copy,
15! modify and redistribute granted by the license, users are provided only
16! with a limited warranty  and the software's author,  the holder of the
17! economic rights,  and the successive licensors  have only  limited
18! liability.
19!
20! In this respect, the user's attention is drawn to the risks associated
21! with loading,  using,  modifying and/or developing or reproducing the
22! software by the user in light of its specific status of free software,
23! that may mean  that it is complicated to manipulate,  and  that  also
24! therefore means  that it is reserved for developers  and  experienced
25! professionals having in-depth computer knowledge. Users are therefore
26! encouraged to load and test the software's suitability as regards their
27! requirements in conditions enabling the security of their systems and/or
28! data to be ensured and,  more generally, to use and operate it in the
29! same conditions as regards security.
30!
31! The fact that you are presently reading this means that you have had
32! knowledge of the CeCILL license and that you accept its terms.
33
34!! file: mmp_optics.f90
35!! summary: Interface for YAMMS aerosols optical properties calculations.
36!! author: J. Burgalat
37!! date: 2017
38MODULE MMP_OPTICS
39  !! Optical properties of spherical/fractal aerosols using moments
40  !!
41  !!
42  !! The module contains an initialization function, [mmp_optics(module):mmp_init_aer_optics(function)],
43  !! that must be called before any calls of the other methods. On failure, it returns .false. and
44  !! consequently, all calls to the other methods will fail !
45  !!
46  !! If openMP is enabled the call to [mmp_optics(module):mmp_init_aer_optics(function)] should be
47  !! done by a single thread.
48  !!
49  !! Then the module provides 4 four public methods to compute optical properties in infrared and
50  !! visible channels as a function of moments of the size-distribution:
51  !!
52  !! - EXT, the total extinction opacity.
53  !! - SSA, the single scattering albedo.
54  !! - ASF, the asymetry factor.
55  !!
56  !! Fractals and spherical aerosols are calculated sperately, but each EXT, SSA and ASF should be added
57  !! to get the global optical properties.
58  USE MMP_GLOBALS
59  USE DATASETS
60
61  IMPLICIT NONE
62
63  PRIVATE
64  PUBLIC :: mmp_optic_file ! from mmp_globals :)
65  PUBLIC :: mmp_initialize_optics
66  PUBLIC :: mmp_sph_optics_vis,mmp_sph_optics_ir
67  PUBLIC :: mmp_fra_optics_vis,mmp_fra_optics_ir
68
69  ! OPTICAL PROPERTIES !
70
71  !> Extinction opacty table (spherical,IR).
72  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: ext_s_i
73  !> Single scattering albedo table (spherical,IR).
74  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: sca_s_i
75  !> Asymetry factor table (spherical,IR).
76  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: asf_s_i
77  !> Extinction opacty table (fractal,IR).
78  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: ext_f_i
79  !> Single scattering albedo table (fractal,IR).
80  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: sca_f_i
81  !> Asymetry factor table (fractal,IR).
82  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: asf_f_i
83
84  !> Extinction opacty table (spherical,VIS).
85  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: ext_s_v
86  !> Single scattering albedo table (spherical,VIS).
87  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: sca_s_v
88  !> Asymetry factor table (spherical,VIS).
89  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: asf_s_v
90  !> Extinction opacty table (fractal,VIS).
91  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: ext_f_v
92  !> Single scattering albedo table (fractal,VIS).
93  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: sca_f_v
94  !> Asymetry factor table (fractal,VIS).
95  REAL(kind=8), DIMENSION(:,:), ALLOCATABLE, SAVE :: asf_f_v
96
97
98  INTEGER, SAVE      :: mmp_nrc    = -1  !! Size of radius grid.
99
100  !> Characteristic radius grid
101  REAL(kind=8), DIMENSION(:), ALLOCATABLE, SAVE :: mmp_rc
102
103  CONTAINS
104
105  SUBROUTINE mmp_initialize_optics(path)
106    !! Initialize optics data for aerosols optical properties computation.
107    !!
108    !! @note
109    !! If the subroutine fails to initialize parameters, the run is aborted.
110    !!
111    !! @warning
112    !! The method assumes YAMMS model has been already intialized correctly !
113    !!
114    !! @warning
115    !! If OpenMP is activated, this subroutine must be called in an $OMP SINGLE statement as it
116    !! initializes global variables that are not thread private.
117    !!
118    !! '''
119    !! !$OMP SINGLE
120    !! call mmp_initialize(...)
121    !! !$OMP END SINGLE
122    CHARACTER(len=*), INTENT(in) :: path !! Path of NetCDF look-up tables file.
123    LOGICAL :: ret
124    WRITE(*,'(a)') "*** mmp_init_aer_optics speaking ***"
125    WRITE(*,'(a)') "I'm about to initialize look-up tables of aerosols optical properties."
126    WRITE(*,'(a)') "If something's wrong... I will abort the program !"
127    IF (.NOT.mm_ini) THEN
128      call abort_program(error("[mmp_init_aer_optics] Too bad mmp_initialize has not been called yet !",2))
129    ENDIF
130    !  look-up tables
131    ret = read_lookup_tables(path)
132    IF (.NOT.ret) &
133      call abort_program(error("[mmp_init_aer_optics] Failed to retrieve data.",2))
134  END SUBROUTINE mmp_initialize_optics
135
136  FUNCTION mmp_sph_optics_vis(M0,M3,iwn,ext,sca,ssa,asf) RESULT(ret)
137    !! Compute optical properties of the spherical mode in the visible range.
138    REAL(kind=mm_wp), INTENT(in)  :: M0  !! 0th order moment of the spherical mode (m-2).
139    REAL(kind=mm_wp), INTENT(in)  :: M3  !! 3rd order moment of the spherical mode (m3.m-2).
140    INTEGER, INTENT(in)           :: iwn !! Index of the wavenumber to compute
141    REAL(kind=mm_wp), INTENT(out) :: ext !! Extinction opacity.
142    REAL(kind=mm_wp), INTENT(out) :: sca !! Scattering.
143    REAL(kind=mm_wp), INTENT(out) :: ssa !! Single scattering albedo.
144    REAL(kind=mm_wp), INTENT(out) :: asf !! Asymetry factor.
145    LOGICAL                       :: ret !! true on success, false otherwise.
146    INTEGER          :: i,ridx
147    REAL(kind=mm_wp) :: rc1,rc2,rx,rc
148    ret = .false.
149    IF (mmp_nrc == -1) RETURN
150    ret = .true.
151    rc = mm_get_rcs(M0,M3)
152    ridx = mmp_nrc
153    DO i=1, mmp_nrc
154      IF (rc < mmp_rc(i)) THEN
155        ridx = i-1
156        EXIT
157      ENDIF
158    ENDDO
159    IF (ridx == 0) THEN
160      ! out of range lower bound
161      ext = ext_s_v(1,iwn)
162      sca = sca_s_v(1,iwn)
163      asf = asf_s_v(1,iwn)
164      ssa = sca/ext
165    ELSE IF (ridx == mmp_nrc) THEN
166      ! out of range upper bound
167      ext = ext_s_v(mmp_nrc,iwn)
168      sca = sca_s_v(mmp_nrc,iwn)
169      asf = asf_s_v(mmp_nrc,iwn)
170      ssa = sca/ext
171    ELSE
172      ! in range: interpolate
173      rc1 = mmp_rc(ridx) ; rc2 = mmp_rc(ridx+1)
174      rx = (rc-rc1)/(rc2-rc1)
175      ext = exp(log(ext_s_v(ridx,iwn))*(1d0-rx) + log(ext_s_v(ridx+1,iwn))*rx)
176      sca = exp(log(sca_s_v(ridx,iwn))*(1d0-rx) + log(sca_s_v(ridx+1,iwn))*rx)
177      asf = asf_s_v(ridx,iwn)*(1d0-rx) + asf_s_v(ridx+1,iwn)*rx
178      ssa = sca/ext
179    ENDIF
180    ! scale by M0
181    ext = ext * M0
182    RETURN
183  END FUNCTION mmp_sph_optics_vis
184
185  FUNCTION mmp_sph_optics_ir(M0,M3,iwn,ext,sca,ssa,asf) RESULT(ret)
186    !! Compute optical properties of the spherical mode in the infra-red range.
187    REAL(kind=mm_wp), INTENT(in)  :: M0  !! 0th order moment of the spherical mode (m-2).
188    REAL(kind=mm_wp), INTENT(in)  :: M3  !! 3rd order moment of the spherical mode (m3.m-2).
189    INTEGER, INTENT(in)           :: iwn !! Index of the wavenumber to compute
190    REAL(kind=mm_wp), INTENT(out) :: ext !! Extinction opacity.
191    REAL(kind=mm_wp), INTENT(out) :: sca !! Scattering.
192    REAL(kind=mm_wp), INTENT(out) :: ssa !! Single scattering albedo.
193    REAL(kind=mm_wp), INTENT(out) :: asf !! Asymetry factor.
194    LOGICAL                       :: ret !! true on success, false otherwise.
195    INTEGER          :: i,ridx
196    REAL(kind=mm_wp) :: rc1,rc2,rx,rc
197    ret = .false.
198    IF (mmp_nrc == -1) RETURN
199    ret = .true.
200    rc = mm_get_rcs(M0,M3)
201    ridx = mmp_nrc
202    DO i=1, mmp_nrc
203      IF (rc < mmp_rc(i)) THEN
204        ridx = i-1
205        EXIT
206      ENDIF
207    ENDDO
208    IF (ridx == 0) THEN
209      ! out of range lower bound
210      ext = ext_s_i(1,iwn)
211      sca = sca_s_i(1,iwn)
212      asf = asf_s_i(1,iwn)
213      ssa = sca/ext
214    ELSE IF (ridx == mmp_nrc) THEN
215      ! out of range upper bound
216      ext = ext_s_i(mmp_nrc,iwn)
217      sca = sca_s_i(mmp_nrc,iwn)
218      asf = asf_s_i(mmp_nrc,iwn)
219      ssa = sca/ext
220    ELSE
221      ! in range: interpolate
222      rc1 = mmp_rc(ridx) ; rc2 = mmp_rc(ridx+1)
223      rx = (rc-rc1)/(rc2-rc1)
224      ext = exp(log(ext_s_i(ridx,iwn))*(1d0-rx) + log(ext_s_i(ridx+1,iwn))*rx)
225      sca = exp(log(sca_s_i(ridx,iwn))*(1d0-rx) + log(sca_s_i(ridx+1,iwn))*rx)
226      asf = asf_s_i(ridx,iwn)*(1d0-rx) + asf_s_i(ridx+1,iwn)*rx
227      ssa = sca/ext
228    ENDIF
229    ! scale by M0
230    ext = ext * M0
231    RETURN
232  END FUNCTION mmp_sph_optics_ir
233
234  FUNCTION mmp_fra_optics_vis(M0,M3,iwn,ext,sca,ssa,asf) RESULT(ret)
235    !! Compute optical properties of the spherical mode in the visible range.
236    REAL(kind=mm_wp), INTENT(in)  :: M0  !! 0th order moment of the fractal mode (m-2).
237    REAL(kind=mm_wp), INTENT(in)  :: M3  !! 3rd order moment of the fractal mode (m3.m-2).
238    INTEGER, INTENT(in)           :: iwn !! Index of the wavenumber to compute.
239    REAL(kind=mm_wp), INTENT(out) :: ext !! Extinction opacity.
240    REAL(kind=mm_wp), INTENT(out) :: sca !! Scattering.
241    REAL(kind=mm_wp), INTENT(out) :: ssa !! Single scattering albedo.
242    REAL(kind=mm_wp), INTENT(out) :: asf !! Asymetry factor.
243    LOGICAL                       :: ret !! true on success, false otherwise.
244    INTEGER          :: i,ridx
245    REAL(kind=mm_wp) :: rc1,rc2,rx,rc
246    ret = .false.
247    IF (mmp_nrc == -1) RETURN
248    ret = .true.
249    rc = mm_get_rcs(M0,M3)
250    ridx = mmp_nrc
251    DO i=1, mmp_nrc
252      IF (rc < mmp_rc(i)) THEN
253        ridx = i-1
254        EXIT
255      ENDIF
256    ENDDO
257    IF (ridx == 0) THEN
258      ! out of range lower bound
259      ext = ext_f_v(1,iwn)
260      sca = sca_f_v(1,iwn)
261      asf = asf_f_v(1,iwn)
262      ssa = sca/ext
263    ELSE IF (ridx == mmp_nrc) THEN
264      ! out of range upper bound
265      ext = ext_f_v(mmp_nrc,iwn)
266      sca = sca_f_v(mmp_nrc,iwn)
267      asf = asf_f_v(mmp_nrc,iwn)
268      ssa = sca/ext
269    ELSE
270      ! in range: interpolate
271      rc1 = mmp_rc(ridx) ; rc2 = mmp_rc(ridx+1)
272      rx = (rc-rc1)/(rc2-rc1)
273      ext = exp(log(ext_f_v(ridx,iwn))*(1d0-rx) + log(ext_f_v(ridx+1,iwn))*rx)
274      sca = exp(log(sca_f_v(ridx,iwn))*(1d0-rx) + log(sca_f_v(ridx+1,iwn))*rx)
275      asf = asf_f_v(ridx,iwn)*(1d0-rx) + asf_f_v(ridx+1,iwn)*rx
276      ssa = sca/ext
277    ENDIF
278    ! scale by M0
279    ext = ext * M0
280    RETURN
281  END FUNCTION mmp_fra_optics_vis
282
283  FUNCTION mmp_fra_optics_ir(M0,M3,iwn,ext,sca,ssa,asf) RESULT(ret)
284    !! Compute optical properties of the spherical mode in the infra-red range.
285    REAL(kind=mm_wp), INTENT(in)  :: M0  !! 0th order moment of the spherical mode (m-2).
286    REAL(kind=mm_wp), INTENT(in)  :: M3  !! 3rd order moment of the spherical mode (m3.m-2).
287    INTEGER, INTENT(in)           :: iwn !! Index of the wavenumber to compute
288    REAL(kind=mm_wp), INTENT(out) :: ext !! Extinction opacity.
289    REAL(kind=mm_wp), INTENT(out) :: sca !! Scattering.
290    REAL(kind=mm_wp), INTENT(out) :: ssa !! Single scattering albedo.
291    REAL(kind=mm_wp), INTENT(out) :: asf !! Asymetry factor.
292    LOGICAL                       :: ret !! true on success, false otherwise.
293    INTEGER          :: i,ridx
294    REAL(kind=mm_wp) :: rc1,rc2,rx,rc
295    ret = .false.
296    IF (mmp_nrc == -1) RETURN
297    ret = .true.
298    rc = mm_get_rcs(M0,M3)
299    ridx = mmp_nrc
300    DO i=1, mmp_nrc
301      IF (rc < mmp_rc(i)) THEN
302        ridx = i-1
303        EXIT
304      ENDIF
305    ENDDO
306    IF (ridx == 0) THEN
307      ! out of range lower bound
308      ext = ext_f_i(1,iwn)
309      sca = sca_f_i(1,iwn)
310      asf = asf_f_i(1,iwn)
311      ssa = sca/ext
312    ELSE IF (ridx == mmp_nrc) THEN
313      ! out of range upper bound
314      ext = ext_f_i(mmp_nrc,iwn)
315      sca = sca_f_i(mmp_nrc,iwn)
316      asf = asf_f_i(mmp_nrc,iwn)
317      ssa = sca/ext
318    ELSE
319      ! in range: interpolate
320      rc1 = mmp_rc(ridx) ; rc2 = mmp_rc(ridx+1)
321      rx = (rc-rc1)/(rc2-rc1)
322      ext = exp(log(ext_f_i(ridx,iwn))*(1d0-rx) + log(ext_f_i(ridx+1,iwn))*rx)
323      sca = exp(log(sca_f_i(ridx,iwn))*(1d0-rx) + log(sca_f_i(ridx+1,iwn))*rx)
324      asf = asf_f_i(ridx,iwn)*(1d0-rx) + asf_f_i(ridx+1,iwn)*rx
325      ssa = sca/ext
326    ENDIF
327    ! scale by M0
328    ext = ext * M0
329    RETURN
330  END FUNCTION mmp_fra_optics_ir
331
332  FUNCTION read_lookup_tables(path) RESULT(ret)
333    !! Read look-up tables.
334    CHARACTER(len=*), INTENT(in) :: path !! Path of the look-up tables netcdf file.
335    LOGICAL                      :: ret  !! .true. on success, .false. otherwise.
336    REAL(kind=mm_wp), DIMENSION(:), ALLOCATABLE :: sigmas_vi,sigmas_ir
337
338    TYPE(DSET2D) :: dset
339    ! data(nrc,ni|nv)
340    ! INFRARED
341    ret = read_dset(path,"ext_s_i",dset)
342    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'ext_s_i' table" ; RETURN ; ENDIF
343    ext_s_i = dset%data ; sigmas_ir = dset%y ; mmp_rc = dset%x
344    ret = read_dset(path,"ext_f_i",dset)
345    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'ext_f_i' table" ; RETURN ; ENDIF
346    ext_f_i = dset%data
347    ret = read_dset(path,"sca_s_i",dset)
348    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'sca_s_i' table" ; RETURN ; ENDIF
349    sca_s_i = dset%data
350    ret = read_dset(path,"sca_f_i",dset)
351    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'sca_f_i' table" ; RETURN ; ENDIF
352    sca_f_i = dset%data
353    ret = read_dset(path,"asf_s_i",dset)
354    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'asf_s_i' table" ; RETURN ; ENDIF
355    asf_s_i = dset%data
356    ret = read_dset(path,"asf_f_i",dset)
357    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'asf_f_i' table" ; RETURN ; ENDIF
358    asf_f_i = dset%data
359    ! VISIBLE
360    ret = read_dset(path,"ext_s_v",dset)
361    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'ext_s_v' table" ; RETURN ; ENDIF
362    ext_s_v = dset%data ; sigmas_vi = dset%y
363    ret = read_dset(path,"ext_f_v",dset)
364    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'ext_f_v' table" ; RETURN ; ENDIF
365    ext_f_v = dset%data
366    ret = read_dset(path,"sca_s_v",dset)
367    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'sca_s_v' table" ; RETURN ; ENDIF
368    sca_s_v = dset%data
369    ret = read_dset(path,"sca_f_v",dset)
370    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'sca_f_v' table" ; RETURN ; ENDIF
371    sca_f_v = dset%data
372    ret = read_dset(path,"asf_s_v",dset)
373    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'asf_s_v' table" ; RETURN ; ENDIF
374    asf_s_v = dset%data
375    ret = read_dset(path,"asf_f_v",dset)
376    IF (.NOT.ret) THEN ; WRITE(*,'(a)') "[read_tables] cannot read 'asf_f_v' table" ; RETURN ; ENDIF
377    asf_f_v = dset%data
378    mmp_nrc = SIZE(mmp_rc)
379    ret = .true.
380    RETURN
381  END FUNCTION read_lookup_tables
382
383END MODULE MMP_OPTICS
384
Note: See TracBrowser for help on using the repository browser.