source: trunk/LMDZ.GENERIC/libf/phystd/setspv.F90 @ 995

Last change on this file since 995 was 989, checked in by emillour, 12 years ago

Generic GCM:

  • Some minor changes so that gcm compiles with gfortran:
    • Added option to compile "long lines" (>132 characters) in makegcm_gfortran
    • Removed use of isnan() in physiq.F90 (it is not a standard function)
    • Avoid possible underflow of psat in watercommon_h.F90
    • Adapted the checks on the *IR and *VI band files to be more strict

EM

File size: 4.4 KB
Line 
1      subroutine setspv
2
3!==================================================================
4!     
5!     Purpose
6!     -------
7!     Set up spectral intervals, stellar spectrum and Rayleigh
8!     opacity in the shortwave.
9!     
10!     Authors
11!     -------
12!     Adapted from setspv in the NASA Ames radiative code by
13!     Robin Wordsworth (2009).
14!
15!     Called by
16!     ---------
17!     callcorrk.F
18!     
19!     Calls
20!     -----
21!     ave_stelspec.F
22!     
23!==================================================================
24
25      use radinc_h,    only: L_NSPECTV, corrkdir, banddir
26      use radcommon_h, only: BWNV,BLAMV,WNOV,DWNV,WAVEV, &
27                             STELLARF,TAURAY
28      use datafile_mod, only: datadir
29
30      implicit none
31
32#include "comcstfi.h"
33#include "callkeys.h"
34
35      logical file_ok
36
37      integer N, M, file_entries
38
39      character(len=30)  :: temp1
40      character(len=200) :: file_id
41      character(len=200) :: file_path
42
43      real*8 :: lastband(2)
44
45      real*8 STELLAR(L_NSPECTV)
46      real*8 sum, dummy
47
48      !! used to count lines
49      integer :: nb=0
50      integer :: ierr=0
51
52!=======================================================================
53!     Set up spectral bands - wavenumber [cm^(-1)]. Go from smaller to
54!     larger wavenumbers, the same as in the IR.
55
56      write(temp1,'(i2.2)') L_NSPECTV
57      file_id='/corrk_data/'//trim(adjustl(banddir))//'/narrowbands_VI.in'
58      file_path=TRIM(datadir)//TRIM(file_id)
59
60      ! check that the file exists
61      inquire(FILE=file_path,EXIST=file_ok)
62      if(.not.file_ok) then
63         write(*,*)'The file ',TRIM(file_path)
64         write(*,*)'was not found by setspv.F90, exiting.'
65         write(*,*)'Check that your path to datagcm:',trim(datadir)
66         write(*,*)' is correct. You can change it in callphys.def with:'
67         write(*,*)' datadir = /absolute/path/to/datagcm'
68         write(*,*)'Also check that the corrkdir you chose in callphys.def exists.'
69         call abort
70      endif
71   
72      ! check that the file contains the right number of bands
73      open(131,file=file_path,form='formatted')
74      read(131,*,iostat=ierr) file_entries
75      do while (ierr==0)
76        read(131,*,iostat=ierr) dummy
77        if (ierr==0) nb=nb+1
78      enddo
79      close(131)
80
81      write(*,*) 'setspv: L_NSPECTV = ',L_NSPECTV, 'in the model '
82      write(*,*) '        there are   ',nb, 'entries in ',TRIM(file_path)
83      if(nb.ne.L_NSPECTV) then
84         write(*,*) 'MISMATCH !! I stop here'
85         call abort
86      endif
87
88      ! load and display the data
89      open(111,file=file_path,form='formatted')
90      read(111,*)
91       do M=1,L_NSPECTV-1
92         read(111,*) BWNV(M)
93      end do
94      read(111,*) lastband
95      close(111)
96      BWNV(L_NSPECTV)  =lastband(1)
97      BWNV(L_NSPECTV+1)=lastband(2)
98
99
100      print*,'setspv: VI band limits:'
101      do M=1,L_NSPECTV+1
102         print*,m,'-->',BWNV(M),' cm^-1'
103      end do
104      print*,' '
105
106!     Set up mean wavenumbers and wavenumber deltas.  Units of
107!     wavenumbers is cm^(-1); units of wavelengths is microns.
108
109      do M=1,L_NSPECTV
110         WNOV(M)  = 0.5*(BWNV(M+1)+BWNV(M))
111         DWNV(M)  = BWNV(M+1)-BWNV(M)
112         WAVEV(M) = 1.0E+4/WNOV(M)
113         BLAMV(M) = 0.01/BWNV(M)
114      end do
115      BLAMV(M) = 0.01/BWNV(M) ! wavelength in METERS for aerosol stuff
116!     note M=L_NSPECTV+1 after loop due to Fortran bizarreness
117
118!=======================================================================
119!     Set up stellar spectrum
120
121      write(*,*)'setspv: Interpolating stellar spectrum from the hires data...'
122      call ave_stelspec(STELLAR)
123
124!     Sum the stellar flux, and write out the result. 
125      sum = 0.0 
126      do N=1,L_NSPECTV
127         STELLARF(N) = STELLAR(N) * Fat1AU
128         sum         = sum+STELLARF(N)
129      end do
130      write(6,'("setspv: Stellar flux at 1 AU = ",f7.2," W m-2")') sum
131      print*,' '
132
133
134!=======================================================================
135!     Set up the wavelength independent part of the Rayleigh scattering.
136!     The pressure dependent part will be computed elsewhere (OPTCV).
137!     WAVEV is in microns.  There is no Rayleigh scattering in the IR.
138
139      if(rayleigh) then
140         call calc_rayleigh
141      else
142         print*,'setspv: No Rayleigh scattering, check for NaN in output!'
143         do N=1,L_NSPECTV
144            TAURAY(N) = 1E-16
145         end do
146      endif
147
148      RETURN
149    END subroutine setspv
Note: See TracBrowser for help on using the repository browser.