/[lmdze]/trunk/phylmd/calbeta.f90
ViewVC logotype

Annotation of /trunk/phylmd/calbeta.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 81 - (hide annotations)
Wed Mar 5 14:38:41 2014 UTC (10 years, 3 months ago) by guez
File size: 1806 byte(s)
 Converted to free source form files which were still in fixed source
form. The conversion was done using the polish mode of the NAG Fortran
Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

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