source: trunk/LMDZ.VENUS/libf/phyvenus/load_ksi.F @ 2187

Last change on this file since 2187 was 2036, checked in by emillour, 6 years ago

Venus GCM:
Missing initializations of 3rd and 4th indexes of ksive(:,:,:,:)
EM

File size: 4.5 KB
RevLine 
[3]1      SUBROUTINE load_ksi(ksive)
2     
[101]3      use dimphy
[3]4      IMPLICIT none
5
6#include "YOMCST.h"
7#include "comcstVE.h"
8C
9C     ------------------------------------------------------------------
10C
11C     PURPOSE.
12C     --------
13C
14c     This routine loads the longwave matrix of factors Ksi
15c     
16c     The Ksi matrixes have been computed by Vincent Eymet
17C
18C     AUTHOR.
19C     -------
20C        Sebastien Lebonnois
21C
22C     MODIFICATIONS.
23C     --------------
[1301]24C       
25c   New ksi matrix: possibility of different cloud model fct of lat   05/2014
[3]26C     ------------------------------------------------------------------
27C
28C* ARGUMENTS:
29C
30c inputs
31      real   psurf(klon)           ! Surface pressure
32c outputs
[892]33      real   ksive(0:klev+1,0:klev+1,nnuve,nbmat)  ! ksi matrixes in Vincent's file
[3]34
35c local variables
[1301]36      integer i,j,isza,ips,band,pve,sve,nlve
37      integer lat,Nb,m,mat
[3]38      character*9 tmp1
39      character*100 file
[1726]40      CHARACTER*2 str2
41      CHARACTER*3 str3
42      CHARACTER*10 format_lect
[3]43      real   lambda(nnuve)            ! wavelenght in table (mu->m, middle of interval)
44      real   lambdamin(nnuve),lambdamax(nnuve) ! in microns
[1301]45      real   dlambda                  ! in microns
[3]46
[892]47      nlve = klev
[101]48
[1675]49cc      GG modif below
50c----------------------------------
51c   Initialisation of values to 0
52c     (for all vertical levels)
53c----------------------------------
54
[2036]55      ksive(0:klev+1,0:klev+1,1:nnuve,1:nbmat) = 0.0
[1675]56
[3]57c ------------------------
58c Loading the ksi file
59c ------------------------
[101]60
61      file = "ksi_global.txt"
[3]62      open(10,file=file)
63     
[1301]64      read(10,*)
65      read(10,*) nlatve
66      read(10,*)
[3]67
[1301]68      write(*,*) 'This is subroutine load_ksi'
69      write(*,*) 'Nb of lat bands:',nlatve
70     
71      do lat=1,nlatve
72        read(10,*) !line for lat range
73        read(10,*) indexve(lat)
74        read(10,*) nbpsve(lat)
[3]75        read(10,*)
[1301]76        read(10,*) nbszave(lat)
77        read(10,*)
78       
79        do isza=1,nbszave(lat)
80          do ips=1,nbpsve(lat)
81         
82        read(10,*) (tmp1,j=1,3),mat    !line for matrix number
[3]83        read(10,*) (tmp1,j=1,2),pve
[1301]84        psurfve(ips,lat) = pve*1.e5    ! pve in bar, psurfve in Pa
85        read(10,*) (tmp1,j=1,3),sve
86        szave(isza,lat) = cos(sve*RPI/180.) ! conversion in mu0
[3]87        read(10,*)
88        read(10,*) m,Nb
[1675]89cc      GG modif below 
90        if (nlve.le.78.and.m.ne.nlve) then
[3]91         write(*,*) 'This is subroutine load_ksi'
[1301]92         print*,'Dimension problem between ksi.txt and nlve'
[3]93         print*,'N levels = ',m,nlve
94         stop
95        endif
96        if (Nb.ne.nnuve) then
97         write(*,*) 'This is subroutine load_ksi'
[1301]98         print*,'Dimension problem between ksi.txt and nnuve'
[3]99         print*,'N freq = ',Nb,nnuve
100         stop
101        endif
102c     Now reading ksi matrix index "mat"
[1726]103        if ((m+2).ge.100) then
104          write(str3,'(i3.3)') m+2
105          format_lect='('//str3//'e17.9)'
106        else
107          write(str2,'(i2.2)') m+2
108          format_lect='('//str2//'e17.9)'
109        endif
[3]110        do band=1,Nb
111         read(10,*) lambdamin(band),lambdamax(band)
112         do i=0,m+1
[1726]113            read(10,format_lect) (ksive(i,j,band,mat),j=0,m+1) ! no unit
[3]114         enddo                  ! i
115        enddo                     ! band
116c       print*,"Matrice ",mat," lue"
[1301]117c       print*,"   psurf=",psurfve(ips,lat)," bars"
118        if (mat+1.gt.nbmat) then
119         write(*,*) 'This is subroutine load_ksi'
120         print*,'Dimension problem between ksi.txt and nbmat'
121         print*,'(max number of matrixes)'
122         print*,'nbmat (in comcstVE.h) should be raised'
123         stop
124        endif
125
126          enddo    ! ips
127        enddo      ! isza
128      enddo        ! lat
[3]129     
[1301]130      write(*,*) 'Total nb of matrixes:',mat
131     
[3]132      close(10)
133
[1301]134c central wavelength and wavelength width
[3]135      do band=1,nnuve
[1301]136         lambda(band)=(lambdamin(band)+lambdamax(band))/2.*1.e-6   ! in m
137         dlambda     =(lambdamax(band)-lambdamin(band))            ! in microns
[3]138c        print*,band,lambdamin(band),dlambda,lambdamax(band)
139
[1301]140c sign convention for ksi,
141c and taking into account the wavelength width (in microns):
[3]142         do mat=1,nbmat
143         do i=0,nlve+1
144           do j=0,nlve+1
[1301]145              ksive(i,j,band,mat) = +ksive(i,j,band,mat)*dlambda    ! in µm
[3]146           enddo
147         enddo
148         enddo
[1301]149c computing coeff al and bl for Planck luminance
[3]150         al(band) = 2.*RHPLA*RCLUM*RCLUM/(lambda(band))**5.
[1301]151c in W/m²/m
152c We need W/m²/µm :
[3]153     .                * 1.e-6
154         bl(band) = RHPLA*RCLUM/(RKBOL*lambda(band))
155      enddo
156     
157      print*,"LOAD_KSI OK"
158
159      return
160      end
161
Note: See TracBrowser for help on using the repository browser.