source: trunk/LMDZ.PLUTO/libf/phypluto/aerosol_mod.F90 @ 3244

Last change on this file since 3244 was 3195, checked in by afalco, 2 years ago

Pluto PCM:
Imported condense n2 from pluto.old.
Aerosol data from Pluto.old not yet working.
AF

File size: 3.7 KB
Line 
1!==================================================================
2module aerosol_mod
3implicit none
4
5!==================================================================
6
7!  aerosol indexes: these are initialized to be 0 if the
8!                 corresponding aerosol was not activated in callphys.def
9!                 -- otherwise a value is set via iniaerosol
10      integer, save :: iaero_haze = 0
11      integer, save :: i_haze = 0
12      logical, save, protected :: noaero = .false.
13!$OMP THREADPRIVATE(iaero_haze,i_haze,noaero)
14
15! two-layer simple aerosol model
16      integer, save, protected :: iaero_back2lay = 0
17! N-layer aerosol model (replaces the 2-layer and hard-coded clouds)
18      integer,dimension(:), allocatable, save, protected :: iaero_nlay
19!$OMP THREADPRIVATE(iaero_back2lay,iaero_nlay)
20
21! Generic aerosols
22      integer, dimension(:), allocatable, save, protected :: iaero_generic
23      integer, dimension(:), allocatable, save, protected :: i_rgcs_ice
24!$OMP THREADPRIVATE(iaero_generic,i_rgcs_ice)
25
26!==================================================================
27
28contains
29
30  !==================================================================
31   subroutine haze_prof(ngrid,nlayer,zzlay,pplay,pt,reffrad,profmmr)
32!==================================================================
33!     Purpose
34!     -------
35!     Get fixed haze properties
36!     profile of haze (from txt file) and fixed radius profile
37!
38!==================================================================
39      use radinc_h, only: naerkind
40      use datafile_mod
41      use tracer_h
42      use comcstfi_mod, only: r, pi
43
44!-----------------------------------------------------------------------
45!     Arguments
46      Implicit none
47
48      integer,intent(in) :: ngrid
49      integer,intent(in) :: nlayer
50      real,intent(in) :: zzlay(ngrid,nlayer)
51      real,intent(in) :: pplay(ngrid,nlayer)
52      real,intent(in) :: pt(ngrid,nlayer)
53      real, intent(in) :: reffrad(ngrid,nlayer,naerkind)      ! haze particles radii (m)
54
55      real, intent(out) :: profmmr(ngrid,nlayer)              ! mmr haze kg/kg
56
57!     Local variables
58      integer :: iaer,l,ig,ifine
59
60      LOGICAL firstcall
61      SAVE firstcall
62      DATA firstcall/.true./
63
64      !!read altitudes and haze mmrs
65      integer Nfine
66      !parameter(Nfine=21)
67      parameter(Nfine=701)
68      character(len=100) :: file_path
69      real,save :: levdat(Nfine),densdat(Nfine)
70
71!---------------- INPUT ------------------------------------------------
72
73      !! Read data
74      IF (firstcall) then
75        firstcall=.false.
76        file_path=trim(datadir)//'/haze_prop/hazemmr.txt'
77        open(224,file=file_path,form='formatted')
78        do ifine=1,Nfine
79           read(224,*) levdat(ifine), densdat(ifine)
80        enddo
81        close(224)
82        print*, 'TB22 read Haze MMR profile'
83      ENDIF
84
85      !! Interpolate on the model vertical grid
86      do ig=1,ngrid
87        CALL interp_line(levdat,densdat,Nfine,zzlay(ig,:)/1000.,profmmr(ig,:),nlayer)
88      enddo
89
90      !! Get profile Mass mixing ratio from number density:    part.cm-3 --> m-3 --> m3 m-3
91      !                                --> kg m-3 --> kg/kg
92      do iaer=1,naerkind
93            if(iaer.eq.iaero_haze.and.1.eq.2) then !TB22 activate/deactivate mmr or part density
94              !print*, 'Haze profile is fixed'
95              do ig=1,ngrid
96                 do l=1,nlayer
97                    !from number density in cm-3
98                    profmmr(ig,l)=profmmr(ig,l)*1.e6*4./3.*pi*reffrad(ig,l,iaer)**3*rho_q(i_haze)/(pplay(ig,l)/(r*pt(ig,l)))
99                 enddo
100              enddo
101            endif
102      enddo
103   end subroutine haze_prof
104!==================================================================
105
106
107end module aerosol_mod
108!==================================================================
Note: See TracBrowser for help on using the repository browser.