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

Last change on this file since 3375 was 3353, checked in by afalco, 19 months ago

Pluto PCM:
Added zrecast & old sedim ;
Choose haze file ;
AF

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