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

Last change on this file since 1198 was 892, checked in by slebonnois, 12 years ago

SL: Important commit ! Adaptation of Venus physics to parallel computation / template for arch on the LMD servers using ifort / documentation for 1D column physics and for parallel computations

File size: 3.8 KB
Line 
1      SUBROUTINE load_ksi(ksive)
2     
3      use dimphy
4      IMPLICIT none
5
6#include "dimensions.h"
7#include "YOMCST.h"
8#include "comcstVE.h"
9C
10C     ------------------------------------------------------------------
11C
12C     PURPOSE.
13C     --------
14C
15c     This routine loads the longwave matrix of factors Ksi
16c     
17c     The Ksi matrixes have been computed by Vincent Eymet
18C
19C     AUTHOR.
20C     -------
21C        Sebastien Lebonnois
22C
23C     MODIFICATIONS.
24C     --------------
25C        version multimatrice (topographie, sommet nuages): 20/12/2006
26C     ------------------------------------------------------------------
27C
28C* ARGUMENTS:
29C
30c inputs
31      real   psurf(klon)           ! Surface pressure
32      real   ztop(klon)            ! Altitude of the top of cloud deck (km)
33c outputs
34      real   ksive(0:klev+1,0:klev+1,nnuve,nbmat)  ! ksi matrixes in Vincent's file
35
36c local variables
37      integer i,j,ig,band,pve,nlve
38      integer mat,Nb,m,Nmat,nl_init,mat0
39      parameter(nl_init=8)
40      character*9 tmp1
41      character*100 file
42      real   lambda(nnuve)            ! wavelenght in table (mu->m, middle of interval)
43      real   lambdamin(nnuve),lambdamax(nnuve) ! in microns
44      real   dlambda                  ! cm-1 
45
46      nlve = klev
47
48c ------------------------
49c Loading the ksi file
50c ------------------------
51
52      file = "ksi_global.txt"
53      open(10,file=file)
54     
55      do i=1,nl_init-1
56         read(10,*)
57      enddo
58      read(10,*) (tmp1,i=1,4),Nmat
59
60      if (nbmat.ne.Nmat) then
61         write(*,*) 'This is subroutine load_ksi'
62         print*,'Probleme de dimension entre ksi.txt et le param nbmat'
63         print*,'Nb matrices = ',nbmat,Nmat
64         stop
65      endif
66
67      do mat=1,nbmat
68        read(10,*)
69        read(10,*)
70        read(10,*) (tmp1,j=1,2),pve
71        psurfve(mat) = pve*1.e5  ! pve en bar, psurfve en Pa
72        read(10,*) (tmp1,j=1,7),ztopve(mat)
73        ztopve(mat) = ztopve(mat)*1.e-3 ! passage en km
74        read(10,*)
75        read(10,*) m,Nb
76        if (m.ne.nlve) then
77         write(*,*) 'This is subroutine load_ksi'
78         print*,'Probleme de dimension entre ksi.txt et le param nlve'
79         print*,'N levels = ',m,nlve
80         stop
81        endif
82        if (Nb.ne.nnuve) then
83         write(*,*) 'This is subroutine load_ksi'
84         print*,'Probleme de dimension entre ksi.txt et le param nnuve'
85         print*,'N freq = ',Nb,nnuve
86         stop
87        endif
88c     Now reading ksi matrix index "mat"
89        do band=1,Nb
90         read(10,*) lambdamin(band),lambdamax(band)
91         do i=0,m+1
92            read(10,'(100e17.9)') (ksive(i,j,band,mat),j=0,m+1) ! sr/µm/cm¯¹
93         enddo                  ! i
94        enddo                     ! band
95c       print*,"Matrice ",mat," lue"
96c       print*,"   psurf=",psurfve(mat)," bars, Ztop=",ztopve(mat)," km"
97      enddo  ! mat
98     
99      close(10)
100
101c longueur d'onde centrale et largeur de chaque bande
102      do band=1,nnuve
103         lambda(band)=(lambdamin(band)+lambdamax(band))/2.*1.e-6   ! en m
104         dlambda     =(1./lambdamin(band)-1./lambdamax(band))*1.e4 ! en cm-1
105c        print*,band,lambdamin(band),dlambda,lambdamax(band)
106
107c changement de convention (signe) pour ksi,
108c et prise en compte de la largeur de bande (en cm-1):
109         do mat=1,nbmat
110         do i=0,nlve+1
111           do j=0,nlve+1
112              ksive(i,j,band,mat) = -ksive(i,j,band,mat)*dlambda
113           enddo
114         enddo
115         enddo
116c calcul des coeff al et bl pour luminance Planck
117         al(band) = 2.*RHPLA*RCLUM*RCLUM/(lambda(band))**5.
118c cette luminance doit etre en W/m²/sr/µm pour correspondre au calcul
119c des ksi. Ici, elle est en W/m²/sr/m donc il faut mettre un facteur 1.e-6
120     .                * 1.e-6
121         bl(band) = RHPLA*RCLUM/(RKBOL*lambda(band))
122      enddo
123     
124      print*,"LOAD_KSI OK"
125
126      return
127      end
128
Note: See TracBrowser for help on using the repository browser.