source: trunk/LMDZ.TITAN/libf/phytitan/setspi.F90 @ 1892

Last change on this file since 1892 was 1822, checked in by jvatant, 8 years ago

Preliminary modifs for the optical coupling of haze
+ Moved inits of setspi/v before init of mufi
+ Added access to tarcers in optci/v
+ Some coherence in call to directories
JVO

File size: 7.0 KB
Line 
1      subroutine setspi
2
3!==================================================================
4!     
5!     Purpose
6!     -------
7!     Set up spectral intervals and Planck function in the longwave.
8!     
9!     Authors
10!     -------
11!     Adapted from setspi in the NASA Ames radiative code by
12!     Robin Wordsworth (2009).
13!     
14!     Called by
15!     ---------
16!     callcorrk.F
17!     
18!     Calls
19!     -----
20!     none
21!     
22!==================================================================
23
24      use radinc_h,    only: L_NSPECTI,NTstar,NTstop,NTfac
25      use radcommon_h, only: BWNI,WNOI,DWNI,WAVEI,planckir,sigma
26      use datafile_mod, only: datadir, corrkdir, banddir
27      use comcstfi_mod, only: pi
28
29      implicit none
30
31      logical file_ok
32      integer nw, nt, m, mm, file_entries
33      real*8 a, b, ans, y, bpa, bma, T, dummy
34
35      character(len=30)  :: temp1
36      character(len=200) :: file_id
37      character(len=200) :: file_path
38
39!     C1 and C2 values from Goody and Yung (2nd edition)  MKS units
40!     These values lead to a "sigma" (sigma*T^4) of 5.67032E-8 W m^-2 K^-4
41
42      real*8 :: c1 = 3.741832D-16 ! W m^-2
43      real*8 :: c2 = 1.438786D-2  ! m K
44     
45      real*8 :: lastband(2), plancksum
46
47      !! used to count lines
48      integer :: nb
49      integer :: ierr
50
51      logical forceEC, planckcheck
52
53      real*8 :: x(12) = [ -0.981560634246719D0,  -0.904117256370475D0, &
54      -0.769902674194305D0,  -0.587317954286617D0,                     &
55      -0.367831498998180D0,  -0.125233408511469D0,                     &
56       0.125233408511469D0,   0.367831498998180D0,                     &
57       0.587317954286617D0,   0.769902674194305D0,                     &
58       0.904117256370475D0,   0.981560634246719D0  ]
59
60      real*8 :: w(12) = [  0.047175336386512D0,   0.106939325995318D0, &
61           0.160078328543346D0,   0.203167426723066D0,                 &
62           0.233492536538355D0,   0.249147045813403D0,                 &
63           0.249147045813403D0,   0.233492536538355D0,                 &
64           0.203167426723066D0,   0.160078328543346D0,                 &
65           0.106939325995318D0,   0.047175336386512D0  ]
66      mm=0
67
68      forceEC=.true.
69      planckcheck=.true.
70
71!=======================================================================
72!     Set up spectral bands - wavenumber [cm^(-1)]. Go from smaller to
73!     larger wavenumbers.
74
75      write(temp1,'(i2.2)') L_NSPECTI
76      !file_id='/corrk_data/' // corrkdir(1:LEN_TRIM(corrkdir)) // '/narrowbands_IR.in'
77      file_id='/corrk_data/'//trim(adjustl(banddir))//'/narrowbands_IR.in'
78      file_path=TRIM(datadir)//TRIM(file_id)
79
80      ! check that the file exists
81      inquire(FILE=file_path,EXIST=file_ok)
82      if(.not.file_ok) then
83         write(*,*)'The file ',TRIM(file_path)
84         write(*,*)'was not found by setspi.F90, exiting.'
85         write(*,*)'Check that your path to datagcm:',trim(datadir)
86         write(*,*)' is correct. You can change it in callphys.def with:'
87         write(*,*)' datadir = /absolute/path/to/datagcm'
88         write(*,*)'Also check that the corrkdir you chose in callphys.def exists.'
89         call abort
90      endif
91   
92!$OMP MASTER   
93      nb=0
94      ierr=0
95      ! check that the file contains the right number of bands
96      open(131,file=file_path,form='formatted')
97      read(131,*,iostat=ierr) file_entries
98      do while (ierr==0)
99        read(131,*,iostat=ierr) dummy
100!        write(*,*) 'setspi: file_entries:',dummy,'ierr=',ierr
101        if (ierr==0) nb=nb+1
102      enddo
103      close(131)
104
105      write(*,*) 'setspi: L_NSPECTI = ',L_NSPECTI, 'in the model '
106      write(*,*) '        there are   ',nb, 'entries in ',TRIM(file_path)
107      if(nb.ne.L_NSPECTI) then
108         write(*,*) 'MISMATCH !! I stop here'
109         call abort
110      endif
111
112      ! load and display the data
113      open(111,file=file_path,form='formatted')
114      read(111,*)
115      do M=1,L_NSPECTI-1
116         read(111,*) BWNI(M)
117      end do
118      read(111,*) lastband
119      close(111)
120      BWNI(L_NSPECTI)  =lastband(1)
121      BWNI(L_NSPECTI+1)=lastband(2)
122!$OMP END MASTER
123!$OMP BARRIER
124
125      print*,''
126      print*,'setspi: IR band limits:'
127      do M=1,L_NSPECTI+1
128         print*,m,'-->',BWNI(M),' cm^-1'
129      end do
130
131!     Set up mean wavenumbers and wavenumber deltas.  Units of
132!     wavenumbers is cm^(-1); units of wavelengths is microns.
133
134      do M=1,L_NSPECTI
135         WNOI(M)  = 0.5D0*(BWNI(M+1)+BWNI(M))
136         DWNI(M)  = BWNI(M+1)-BWNI(M)
137         WAVEI(M) = 1.0D+4/WNOI(M)
138      end do
139!     note M=L_NSPECTI+1 after loop due to Fortran bizarreness
140
141!=======================================================================
142!     For each IR wavelength interval, compute the integral of B(T), the
143!     Planck function, divided by the wavelength interval, in cm-1.  The
144!     integration is in MKS units, the final answer is the same as the
145!     original planck.f; W m^-2 wavenumber^-1, where wavenumber is in CM^-1.
146
147      print*,''
148      print*,'setspi: Current Planck integration range:'
149      print*,'T = ',dble(NTstar)/NTfac, ' to ',dble(NTstop)/NTfac,' K.'
150
151      do NW=1,L_NSPECTI
152         a = 1.0D-2/BWNI(NW+1)
153         b = 1.0D-2/BWNI(NW)
154         bpa = (b+a)/2.0D0
155         bma = (b-a)/2.0D0
156         do nt=NTstar,NTstop
157            T   = dble(NT)/NTfac
158            ans = 0.0D0
159
160            do mm=1,12
161               y    = bma*x(mm)+bpa
162               ans  = ans + w(mm)*c1/(y**5*(exp(c2/(y*T))-1.0D0))
163            end do
164
165            planckir(NW,nt-NTstar+1) = ans*bma/(PI*DWNI(NW))
166         end do
167      end do
168         
169      ! force planck=sigma*eps*T^4 for each temperature in array
170      if(forceEC)then
171         print*,'setspi: Force F=sigma*eps*T^4 for all values of T!'
172         do nt=NTstar,NTstop
173            plancksum=0.0D0
174            T=dble(NT)/NTfac
175       
176            do NW=1,L_NSPECTI
177               plancksum=plancksum+  &
178                  planckir(NW,nt-NTstar+1)*DWNI(NW)*pi
179            end do
180
181            do NW=1,L_NSPECTI
182               planckir(NW,nt-NTstar+1)=     &
183                  planckir(NW,nt-NTstar+1)*  &
184                          sigma*(dble(nt)/NTfac)**4/plancksum
185            end do
186         end do
187      endif
188
189      if(planckcheck)then
190         ! check energy conservation at lower temperature boundary
191         plancksum=0.0D0
192         nt=NTstar
193         do NW=1,L_NSPECTI
194            plancksum=plancksum+planckir(NW,nt-NTstar+1)*DWNI(NW)*pi
195         end do
196         print*,'setspi: At lower limit:'
197         print*,'in model sig*T^4 = ',plancksum,' W m^-2'
198         print*,'actual sig*T^4   = ',sigma*(dble(nt)/NTfac)**4,' W m^-2'
199         
200         ! check energy conservation at upper temperature boundary
201         plancksum=0.0D0
202         nt=NTstop
203         do NW=1,L_NSPECTI
204            plancksum=plancksum+planckir(NW,nt-NTstar+1)*DWNI(NW)*pi
205         end do
206         print*,'setspi: At upper limit:'
207         print*,'in model sig*T^4 = ',plancksum,' W m^-2'
208         print*,'actual sig*T^4   = ',sigma*(dble(nt)/NTfac)**4,' W m^-2'
209         print*,''
210      endif
211
212      return
213    end subroutine setspi
Note: See TracBrowser for help on using the repository browser.