source: trunk/LMDZ.PLUTO/libf/phypluto/radii_mod.F90 @ 3586

Last change on this file since 3586 was 3585, checked in by debatzbr, 3 weeks ago

Connecting microphysics to radiative transfer + miscellaneous cleans

File size: 4.2 KB
RevLine 
[3184]1!==================================================================
2module radii_mod
3!==================================================================
4!  module to centralize the radii calculations for aerosols
5!==================================================================
[3195]6
[3184]7      ! flag to specify if we assume a constant fixed radius for particles
8      logical,save :: radfixed ! initialized in inifis
9!$OMP THREADPRIVATE(radfixed)
10
11contains
12
13
14!==================================================================
15   subroutine su_aer_radii(ngrid,nlayer,reffrad,nueffrad)
16!==================================================================
17!     Purpose
18!     -------
[3195]19!     Compute the effective radii of haze particles  (TB)
[3184]20!
21!
22!==================================================================
23      use mod_phys_lmdz_para, only : is_master
24      use ioipsl_getin_p_mod, only: getin_p
25      use radinc_h, only: naerkind
[3329]26      use datafile_mod, only: hazerad_file
[3572]27      use aerosol_mod, only: iaero_haze, i_haze
[3585]28      use tracer_h, only: radius, nqtot, nmono
[3184]29      Implicit none
30
31      integer,intent(in) :: ngrid
32      integer,intent(in) :: nlayer
33
34      real, intent(out) :: reffrad(ngrid,nlayer,naerkind)      !aerosols radii (K)
[3195]35      real, intent(out) :: nueffrad(ngrid,nlayer,naerkind)     !variance
[3184]36
[3195]37      integer :: iaer, ia , iq, i_rad
[3184]38
39      do iaer=1,naerkind
[3195]40         print*, 'TB22 iaer',iaer,iaero_haze
41         if(iaer.eq.iaero_haze)then
42           ! Equivalent sphere radius
43           reffrad(1:ngrid,1:nlayer,iaer)=radius(i_haze)*nmono**(1./3.)
44           !reffrad(1:ngrid,1:nlayer,iaer) = 2.e-6 ! haze
45           nueffrad(1:ngrid,1:nlayer,iaer) = 0.02 ! haze
[3184]46         endif
[3195]47      enddo
[3184]48
49   end subroutine su_aer_radii
50!==================================================================
51
52
53!==================================================================
[3195]54   subroutine haze_reffrad_fix(ngrid,nlayer,zzlay,reffrad,nueffrad)
55      !==================================================================
[3184]56!     Purpose
57!     -------
[3195]58!     Compute the effective radii of haze particles
59!     fixed profile of radius (TB)
[3184]60!
61!==================================================================
[3195]62      use radinc_h, only: naerkind
63      USE tracer_h, only:rho_n2,nmono
[3184]64      use comcstfi_mod, only: pi
[3585]65      use aerosol_mod, only: iaero_haze
[3195]66      use datafile_mod
[3184]67      Implicit none
68
[3195]69      integer,intent(in) :: ngrid,nlayer
70      real,intent(in) :: zzlay(ngrid,nlayer)
71      real, intent(out) :: reffrad(ngrid,nlayer,naerkind)      ! haze particles radii (m)
72      real, intent(out) :: nueffrad(ngrid,nlayer,naerkind)     !
[3184]73
[3195]74      real :: zrad
75      real,external :: CBRT
[3184]76
[3195]77      logical, save :: firstcall=.true.
78      !$OMP THREADPRIVATE(firstcall)
[3184]79
[3195]80!     Local variables
81      integer :: iaer,l,ifine,ig
82      real :: radvec(ngrid,nlayer)
[3184]83
[3195]84      !!read altitudes and radius
85      integer Nfine
86      !parameter(Nfine=21)
87      parameter(Nfine=701)
88      character(len=100) :: file_path
89      real,save :: levdat(Nfine),raddat(Nfine)
[3184]90
[3195]91!---------------- INPUT ------------------------------------------------
[3184]92
[3195]93      IF (firstcall) then
94         firstcall=.false.
[3329]95         file_path=trim(datadir)//'/haze_prop/'//hazerad_file
[3195]96         open(223,file=file_path,form='formatted')
97         do ifine=1,Nfine
98            read(223,*) levdat(ifine), raddat(ifine)
99         enddo
100         close(223)
[3353]101         print*, 'Read hazerad from ',file_path
[3195]102       ENDIF
[3184]103
[3195]104       ! in radii mod levs has been put in km
105       DO ig=1,ngrid
106         CALL interp_line(levdat,raddat,Nfine,zzlay(ig,:)/1000,radvec(ig,:),nlayer)
107       enddo
[3184]108
[3195]109       do iaer=1,naerkind
110             if(iaer.eq.iaero_haze)then
111                  ! spherical radius or eq spherical radius
112                  ! TB22: fractal has no impact on reffrad if haze_radproffix
113                  do ig=1,ngrid
114                     do l=1,nlayer
115                        reffrad(ig,l,iaer)=radvec(ig,l)*1.e-9    !  nm => m
116                     enddo
117                  enddo
118                  nueffrad(1:ngrid,1:nlayer,iaer) = 0.02 ! haze
119             endif
120       enddo
[3184]121
[3195]122   end subroutine haze_reffrad_fix
[3184]123!==================================================================
124
125
126end module radii_mod
127!==================================================================
Note: See TracBrowser for help on using the repository browser.