/[lmdze]/trunk/Sources/phylmd/Interface_surf/calbeta.f
ViewVC logotype

Annotation of /trunk/Sources/phylmd/Interface_surf/calbeta.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 99 - (hide annotations)
Wed Jul 2 18:39:15 2014 UTC (9 years, 11 months ago) by guez
Original Path: trunk/phylmd/Interface_surf/calbeta.f
File size: 1806 byte(s)
Created procedure test_disvert (following LMDZ). Added procedures
hybrid and funcd in module disvert_m. Upgraded compute_ab from
internal procedure of disvert to module procedure. Added variables y,
ya in module disvert_m. Upgraded s from local variable of procedure
disvert to module variable.

Renamed allowed value of variable vert_sampling in procedure disvert
from "read" to "read_hybrid". Added possibility to read pressure
values, value "read_pressure". Replaced vertical distribution for
value "param" by the distribution "strato_correct" from LMDZ (but kept
the value "param"). In case "tropo", replaced 1 by dsigmin (following
LMDZ). In case "strato", replaced 0.3 by dsigmin (following LMDZ).

Changed computation of bp in procedure compute_ab.

Removed debugindex case in clmain. Removed useless argument rlon of
procedure clmain. Removed useless variables ytaux, ytauy of procedure
clmain.

Removed intermediary variables tsol, qsol, tsolsrf, tslab in procedure
etat0.

Removed variable ok_veget:. coupling with the model Orchid is not
possible. Removed variable ocean: modeling an ocean slab is not
possible.

Removed useless variables tmp_rriv and tmp_rcoa from module
interface_surf.

Moved initialization of variables da, mp, phi in procedure physiq to
to inside the test iflag_con >= 3.

1 guez 81 SUBROUTINE calbeta(dtime, indice, knon, snow, qsol, vbeta, vcal, vdif)
2     USE dimens_m
3     USE indicesol
4     USE dimphy
5     USE conf_gcm_m
6     USE suphec_m
7     IMPLICIT NONE
8     ! ======================================================================
9     ! Auteur(s): Z.X. Li (LMD/CNRS) (adaptation du GCM du LMD)
10     ! date: 19940414
11     ! ======================================================================
12 guez 3
13 guez 81 ! Calculer quelques parametres pour appliquer la couche limite
14     ! ------------------------------------------------------------
15     REAL tau_gl ! temps de relaxation pour la glace de mer
16     ! cc PARAMETER (tau_gl=86400.0*30.0)
17     PARAMETER (tau_gl=86400.0*5.0)
18     REAL mx_eau_sol
19     PARAMETER (mx_eau_sol=150.0)
20    
21     REAL calsol, calsno, calice ! epaisseur du sol: 0.15 m
22     PARAMETER (calsol=1.0/(2.5578E+06*0.15))
23     PARAMETER (calsno=1.0/(2.3867E+06*0.15))
24     PARAMETER (calice=1.0/(5.1444E+06*0.15))
25    
26     INTEGER i
27    
28     REAL dtime
29     REAL snow(klon), qsol(klon)
30     INTEGER indice, knon
31    
32     REAL vbeta(klon)
33     REAL vcal(klon)
34     REAL vdif(klon)
35    
36    
37     IF (indice==is_oce) THEN
38     DO i = 1, knon
39     vcal(i) = 0.0
40     vbeta(i) = 1.0
41     vdif(i) = 0.0
42     END DO
43     END IF
44    
45     IF (indice==is_sic) THEN
46     DO i = 1, knon
47     vcal(i) = calice
48     IF (snow(i)>0.0) vcal(i) = calsno
49     vbeta(i) = 1.0
50     vdif(i) = 1.0/tau_gl
51     ! cc vdif(i) = calice/tau_gl ! c'etait une erreur
52     END DO
53     END IF
54    
55     IF (indice==is_ter) THEN
56     DO i = 1, knon
57     vcal(i) = calsol
58     IF (snow(i)>0.0) vcal(i) = calsno
59     vbeta(i) = min(2.0*qsol(i)/mx_eau_sol, 1.0)
60     vdif(i) = 0.0
61     END DO
62     END IF
63    
64     IF (indice==is_lic) THEN
65     DO i = 1, knon
66     vcal(i) = calice
67     IF (snow(i)>0.0) vcal(i) = calsno
68     vbeta(i) = 1.0
69     vdif(i) = 0.0
70     END DO
71     END IF
72    
73     RETURN
74     END SUBROUTINE calbeta

  ViewVC Help
Powered by ViewVC 1.1.21