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

Last change on this file since 3572 was 3572, checked in by debatzbr, 7 days ago

Remove generic_aerosols and generic_condensation, along with their related variables (useless). RENAME THE VARIABLE AEROHAZE TO OPTICHAZE.

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