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

Last change on this file since 1530 was 1530, checked in by emillour, 9 years ago

Venus and Titan GCMs:
Updates in the physics to keep up with updates in LMDZ5 (up to
LMDZ5 trunk, rev 2350) concerning dynamics/physics separation:

  • Adapted makelmdz and makelmdz_fcm script to stop if trying to compile 1d model or newstart or start2archive in parallel.
  • got rid of references to "dimensions.h" in physics. Within physics packages, use nbp_lon (=iim), nbp_lat (=jjmp1) and nbp_lev (=llm) from module mod_grid_phy_lmdz (in phy_common) instead. Only partially done for Titan, because of many hard-coded commons; a necessary first step will be to clean these up (using modules).

EM

File size: 4.0 KB
Line 
1      SUBROUTINE load_ksi(ksive)
2     
3      use dimphy
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     --------------
24C       
25c   New ksi matrix: possibility of different cloud model fct of lat   05/2014
26C     ------------------------------------------------------------------
27C
28C* ARGUMENTS:
29C
30c inputs
31      real   psurf(klon)           ! Surface pressure
32c outputs
33      real   ksive(0:klev+1,0:klev+1,nnuve,nbmat)  ! ksi matrixes in Vincent's file
34
35c local variables
36      integer i,j,isza,ips,band,pve,sve,nlve
37      integer lat,Nb,m,mat
38      character*9 tmp1
39      character*100 file
40      CHARACTER*2 str2
41      real   lambda(nnuve)            ! wavelenght in table (mu->m, middle of interval)
42      real   lambdamin(nnuve),lambdamax(nnuve) ! in microns
43      real   dlambda                  ! in microns
44
45      nlve = klev
46
47c ------------------------
48c Loading the ksi file
49c ------------------------
50
51      file = "ksi_global.txt"
52      open(10,file=file)
53     
54      read(10,*)
55      read(10,*) nlatve
56      read(10,*)
57
58      write(*,*) 'This is subroutine load_ksi'
59      write(*,*) 'Nb of lat bands:',nlatve
60     
61      do lat=1,nlatve
62        read(10,*) !line for lat range
63        read(10,*) indexve(lat)
64        read(10,*) nbpsve(lat)
65        read(10,*)
66        read(10,*) nbszave(lat)
67        read(10,*)
68       
69        do isza=1,nbszave(lat)
70          do ips=1,nbpsve(lat)
71         
72        read(10,*) (tmp1,j=1,3),mat    !line for matrix number
73        read(10,*) (tmp1,j=1,2),pve
74        psurfve(ips,lat) = pve*1.e5    ! pve in bar, psurfve in Pa
75        read(10,*) (tmp1,j=1,3),sve
76        szave(isza,lat) = cos(sve*RPI/180.) ! conversion in mu0
77        read(10,*)
78        read(10,*) m,Nb
79        if (m.ne.nlve) then
80         write(*,*) 'This is subroutine load_ksi'
81         print*,'Dimension problem between ksi.txt and nlve'
82         print*,'N levels = ',m,nlve
83         stop
84        endif
85        if (Nb.ne.nnuve) then
86         write(*,*) 'This is subroutine load_ksi'
87         print*,'Dimension problem between ksi.txt and nnuve'
88         print*,'N freq = ',Nb,nnuve
89         stop
90        endif
91c     Now reading ksi matrix index "mat"
92        write(str2,'(i2.2)') m+2
93        do band=1,Nb
94         read(10,*) lambdamin(band),lambdamax(band)
95         do i=0,m+1
96            read(10,'('//str2//'e17.9)') (ksive(i,j,band,mat),j=0,m+1) ! no unit
97         enddo                  ! i
98        enddo                     ! band
99c       print*,"Matrice ",mat," lue"
100c       print*,"   psurf=",psurfve(ips,lat)," bars"
101        if (mat+1.gt.nbmat) then
102         write(*,*) 'This is subroutine load_ksi'
103         print*,'Dimension problem between ksi.txt and nbmat'
104         print*,'(max number of matrixes)'
105         print*,'nbmat (in comcstVE.h) should be raised'
106         stop
107        endif
108
109          enddo    ! ips
110        enddo      ! isza
111      enddo        ! lat
112     
113      write(*,*) 'Total nb of matrixes:',mat
114     
115      close(10)
116
117c central wavelength and wavelength width
118      do band=1,nnuve
119         lambda(band)=(lambdamin(band)+lambdamax(band))/2.*1.e-6   ! in m
120         dlambda     =(lambdamax(band)-lambdamin(band))            ! in microns
121c        print*,band,lambdamin(band),dlambda,lambdamax(band)
122
123c sign convention for ksi,
124c and taking into account the wavelength width (in microns):
125         do mat=1,nbmat
126         do i=0,nlve+1
127           do j=0,nlve+1
128              ksive(i,j,band,mat) = +ksive(i,j,band,mat)*dlambda    ! in µm
129           enddo
130         enddo
131         enddo
132c computing coeff al and bl for Planck luminance
133         al(band) = 2.*RHPLA*RCLUM*RCLUM/(lambda(band))**5.
134c in W/m²/m
135c We need W/m²/µm :
136     .                * 1.e-6
137         bl(band) = RHPLA*RCLUM/(RKBOL*lambda(band))
138      enddo
139     
140      print*,"LOAD_KSI OK"
141
142      return
143      end
144
Note: See TracBrowser for help on using the repository browser.