source: trunk/libf/phytitan/heating.F @ 21

Last change on this file since 21 was 3, checked in by slebonnois, 14 years ago

Creation de repertoires:

  • chantiers : pour communiquer sur nos projets de modifs
  • documentation : pour stocker les docs

Ajout de:

  • libf/phytitan : physique de Titan
  • libf/chimtitan: chimie de Titan
  • libf/phyvenus : physique de Venus
File size: 2.8 KB
Line 
1       SUBROUTINE heating(dist,rmu0,fract,sol_htg,swnet)
2
3      IMPLICIT NONE
4
5
6c=======================================================================
7c
8c   Object:  Computation of the solar heating rate
9c                    SOL_HTG(klon,klev)
10c
11c   Arguments:
12c   ----------
13c
14c      Input:
15c      ------
16c
17c dist-----input-R- distance astronomique terre-soleil
18c rmu0-----input-R- cosinus de l'angle zenithal
19c fract----input-R- duree d'ensoleillement normalisee
20c        p(klon,nl)    pressure (level)
21c
22c      Output:
23c      -------
24c sol_htg-----output-R- echauffement atmospherique (visible) (K/s)
25c swnet-------output-R- flux solaire net (+ vers le bas)     (W/m2)
26c
27c=======================================================================
28c-----------------------------------------------------------------------
29c   Declarations:
30c   -------------
31
32#include "dimensions.h"
33#include "dimphy.h"
34
35      INTEGER NLEVEL,NLAYER,NSPECV
36      PARAMETER(NLAYER=llm,NLEVEL=NLAYER+1)
37      PARAMETER (NSPECV=24)
38c
39
40c   Arguments:
41c   ----------
42
43
44      real dist, rmu0(klon), fract(klon)
45
46      real sol_htg(klon,klev)
47      real swnet(klon,klev+1)
48     
49c   Local:
50c   ------
51
52      INTEGER I,J,IG,K,IPRINT,ilat,nq
53 
54c   COMMONS for interface with local subroutines:
55c   ---------------------------------------------
56
57      REAL UBARI,UBARV,UBAR0
58      REAL  CH4(NLEVEL),XN2(NLEVEL),H2(NLEVEL),AR(NLEVEL)
59      REAL  XMU(NLEVEL),GAS1(NLAYER),COLDEN(NLAYER)
60      REAL FNETV(klon,NLEVEL),FUPV(klon,NLEVEL,NSPECV) 
61      REAL FDV(klon,NLEVEL,NSPECV),FMNETV(klon,NLEVEL)
62      REAL CSUBP,RSFI,RSFV,F0PI
63
64      COMMON /UBARED/ UBARI,UBARV,UBAR0
65
66      COMMON /GASS/ CH4,XN2
67     &              ,H2,AR
68     &              ,XMU,GAS1
69     &              ,COLDEN
70
71      COMMON /FLUXvV/ FNETV,     
72     &               FUPV,
73     &               FDV,
74     &               FMNETV
75
76      COMMON /PLANT/ CSUBP,RSFI,RSFV,F0PI
77
78
79c==================================================================
80
81         fnetv  = 0.0
82         sol_htg= 0.0
83         swnet  = 0.0
84c pour sorties dans gfluxv...
85         iprint = 0
86
87         DO ig=1,klon
88            IF(fract(ig).LT.1.e-5) THEN
89               DO j=1,nlayer
90                  sol_htg(ig,j)=0.
91               ENDDO
92            ELSE
93               ubar0=rmu0(ig)
94
95               CALL sfluxv(iprint,ig,dist)           ! #3
96
97               fnetv(ig,:) = fnetv(ig,:) *fract(ig)   ! >0 vers le haut
98c >0 vers le bas + conversion en W/m2:
99               swnet(ig,:) = -1.e-3*fnetv(ig,:)         
100               
101               DO j=1,nlayer
102                  sol_htg(ig,j)=                           ! K/s
103     s            (fnetv(ig,j+1)-fnetv(ig,j))
104     s                              /(colden(j)*csubp)
105               ENDDO
106            ENDIF
107         ENDDO
108
109      RETURN
110 191  FORMAT(F8.2,1P10E10.2)
111 192  FORMAT(a8,1P10E10.2)
112      END
Note: See TracBrowser for help on using the repository browser.