source: trunk/LMDZ.GENERIC/libf/phystd/interpolateH2Ocont_CKD.F90 @ 1477

Last change on this file since 1477 was 1315, checked in by milmd, 10 years ago

LMDZ.GENERIC. OpenMP directives added in generic physic. When running in pure OpenMP or hybrid OpenMP/MPI, may have some bugs with condense_cloud and wstats routines.

File size: 5.9 KB
Line 
1     subroutine interpolateH2Ocont_CKD(wn,temp,presS,presF,abcoef,firstcall,ind)
2
3!==================================================================
4!     
5!     Purpose
6!     -------
7!     Calculates the H2O continuum opacity, using a lookup table from
8!     Clough (2005).
9!
10!     Authors
11!     -------
12!     R. Wordsworth (2011)
13!     
14!==================================================================
15
16      use datafile_mod, only: datadir
17      implicit none
18
19      ! input
20      double precision wn                 ! wavenumber             (cm^-1)
21      double precision temp               ! temperature            (Kelvin)
22      double precision presS              ! self-pressure          (Pascals)
23      double precision presF              ! foreign (air) pressure (Pascals)
24
25      ! output
26      double precision abcoef             ! absorption coefficient (m^-1)
27
28      integer nS,nT
29      parameter(nS=1001)
30      parameter(nT=11)
31
32      double precision kB
33      parameter(kB=1.3806488e-23)
34
35      double precision amagatS, amagatF, abcoefS, abcoefF, Nmolec
36      double precision wn_arr(nS)
37      double precision temp_arr(nT)
38      double precision abs_arrS(nS,nT)
39      double precision abs_arrF(nS,nT)
40      double precision data_tmp(nT)
41
42      integer k,ind
43      logical firstcall
44
45      save wn_arr, temp_arr, abs_arrS, abs_arrF !read by master
46
47      character*100 dt_file
48      integer strlen,ios
49
50      amagatS=(273.15/temp)*(presS/101325.0)
51      amagatF=(273.15/temp)*(presF/101325.0)
52
53      if(firstcall)then ! called by sugas_corrk only
54         print*,'----------------------------------------------------'
55         print*,'Initialising H2O continuum from MT_CKD data...'
56
57!     1.1 Open the ASCII files
58
59!$OMP MASTER
60         ! nu array
61         dt_file=TRIM(datadir)//'/continuum_data/H2O_CONT_NU.dat'
62         open(33,file=dt_file,form='formatted',status='old',iostat=ios)
63         if (ios.ne.0) then        ! file not found
64           write(*,*) 'Error from interpolateH2O_cont'
65           write(*,*) 'Data file ',trim(dt_file),' not found.'
66           write(*,*)'Check that your path to datagcm:',trim(datadir)
67           write(*,*)' is correct. You can change it in callphys.def with:'
68           write(*,*)' datadir = /absolute/path/to/datagcm'
69           write(*,*)' Also check that there is a continuum_data/H2O_CONT_NU.dat there.'
70           call abort
71         else
72            do k=1,nS
73               read(33,*) wn_arr(k)
74            enddo
75         endif
76         close(33)
77
78         ! self broadening
79         dt_file=TRIM(datadir)//'/continuum_data/H2O_CONT_SELF.dat'
80         open(34,file=dt_file,form='formatted',status='old',iostat=ios)
81         if (ios.ne.0) then        ! file not found
82           write(*,*) 'Error from interpolateH2O_cont'
83           write(*,*) 'Data file ',trim(dt_file),' not found.'
84           write(*,*)'Check that your path to datagcm:',trim(datadir)
85           write(*,*)' is correct. You can change it in callphys.def with:'
86           write(*,*)' datadir = /absolute/path/to/datagcm'
87           write(*,*)' Also check that there is a continuum_data/H2O_CONT_SELF.dat there.'
88           call abort
89         else
90            do k=1,nS
91               read(34,*) data_tmp
92               abs_arrS(k,1:nT)=data_tmp(1:nT)
93            end do
94         endif
95         close(34)
96
97         ! foreign (N2+O2+Ar) broadening
98         dt_file=TRIM(datadir)//'/continuum_data/H2O_CONT_FOREIGN.dat'
99         open(35,file=dt_file,form='formatted',status='old',iostat=ios)
100         if (ios.ne.0) then        ! file not found
101           write(*,*) 'Error from interpolateH2O_cont'
102           write(*,*) 'Data file ',trim(dt_file),' not found.'
103           write(*,*)'Check that your path to datagcm:',trim(datadir)
104           write(*,*)' is correct. You can change it in callphys.def with:'
105           write(*,*)' datadir = /absolute/path/to/datagcm'
106           write(*,*)' Also check that there is a continuum_data/H2O_CONT_FOREIGN.dat there.'
107           call abort
108         else
109            do k=1,nS
110               read(35,*) data_tmp
111               abs_arrF(k,1:nT)=data_tmp(1:nT)
112            end do
113         endif
114         close(35)
115
116         temp_arr(1)  = 200.
117         temp_arr(2)  = 250.
118         temp_arr(3)  = 300.
119         temp_arr(4)  = 350.
120         temp_arr(5)  = 400.
121         temp_arr(6)  = 450.
122         temp_arr(7)  = 500.
123         temp_arr(8)  = 550.
124         temp_arr(9)  = 600.
125         temp_arr(10) = 650.
126         temp_arr(11) = 700.
127
128         print*,'interpolateH2Ocont: At wavenumber ',wn,' cm^-1'
129         print*,'   temperature ',temp,' K'
130         print*,'   H2O pressure ',presS,' Pa'
131         print*,'   air pressure ',presF,' Pa'
132!$OMP END MASTER
133!$OMP BARRIER
134         
135      endif
136
137      call bilinearbig(nS,nT,wn_arr,temp_arr,abs_arrS,wn,temp,abcoefS,ind)
138!      print*,'the self absorption is ',abcoefS,' cm^2 molecule^-1'
139
140      call bilinearbig(nS,nT,wn_arr,temp_arr,abs_arrF,wn,temp,abcoefF,ind)
141!      print*,'the foreign absorption is ',abcoefF,' cm^2 molecule^-1'
142
143!      print*,'We have ',amagatS,' amagats of H2O vapour'
144!      print*,'and ',amagatF,' amagats of air'
145
146      abcoef = abcoefS*amagatS + abcoefF*amagatF ! Eq. (15) in Clough (1989)
147      abcoef = abcoef*(presS/(presF+presS))      ! take H2O mixing ratio into account
148                                                    ! abs coeffs are given per molecule of H2O
149
150      Nmolec = (presS+presF)/(kB*temp)           ! assume ideal gas
151!      print*,'Total number of molecules per m^3 is',Nmolec
152
153      abcoef = abcoef*Nmolec/(100.0**2)          ! convert to m^-1
154!      print*,'So the total absorption is ',abcoef,' m^-1'
155!      print*,'And optical depth / km : ',1000.0*abcoef
156
157
158      if(wn.gt.500 .and. wn.lt.1400)then
159      elseif(wn.gt.2100 .and. wn.lt.3000)then
160      else
161         abcoef = 0.0
162      endif
163
164      ! unlike for Rayleigh scattering, we do not currently weight by the BB function
165      ! however our bands are normally thin, so this is no big deal.
166
167
168      return
169    end subroutine interpolateH2Ocont_CKD
170
Note: See TracBrowser for help on using the repository browser.