/[lmdze]/trunk/phylmd/zenang.f
ViewVC logotype

Annotation of /trunk/phylmd/zenang.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 98 - (hide annotations)
Tue May 13 17:23:16 2014 UTC (10 years ago) by guez
File size: 4836 byte(s)
Split inter_barxy.f : one procedure per module, one module per
file. Grouped the files into a directory.

Split orbite.f.

Value of raz_date read from the namelist is taken into account
(resetting the step counter) even if annee_ref == anneeref and day_ref
== dayref. raz_date is no longer modified by gcm main unit. (Following
LMDZ.)

Removed argument klon of interfsur_lim. Renamed arguments lmt_alb,
lmt_rug to alb_new, z0_new (same name as corresponding actual
arguments in interfsurf_hq).

Removed argument klon of interfsurf_hq.

Removed arguments qs and d_qs of diagetpq. Were always
zero. Downgraded arguments d_qw, d_ql of diagetpq to local variables,
they were not used in physiq. Removed all computations for solid water
in diagetpq, was just zero.


Downgraded arguments fs_bound, fq_bound of diagphy to local variables,
they were not used in physiq. Encapsulated in a test on iprt all
computations in diagphy.

Removed parameter nbtr of module dimphy. Replaced it everywhere in the
program by nqmx - 2.

Removed parameter rnpb of procedure physiq. Kept the true case in
physiq and phytrac. Could not work with false case anyway.

Removed arguments klon, llm, airephy of qcheck. Removed argument ftsol
of initrrnpb, was not used.

1 guez 98 module zenang_m
2    
3     IMPLICIT NONE
4    
5     contains
6    
7     SUBROUTINE zenang(longi, gmtime, pdtrad, pmu0, frac)
8    
9     USE dimphy, ONLY : klon
10     USE yomcst, ONLY : r_incl
11     USE phyetat0_m, ONLY : rlat, rlon
12     use nr_util, only: assert, pi
13    
14     ! Author : O. Boucher (LMD/CNRS), d'après les routines "zenith" et
15     ! "angle" de Z.X. Li
16    
17     ! Calcule les valeurs moyennes du cos de l'angle zénithal et
18     ! l'ensoleillement moyen entre "gmtime1" et "gmtime2" connaissant la
19     ! déclinaison, la latitude et la longitude.
20     ! Différent de la routine "angle" en ce sens que "zenang" fournit des
21     ! moyennes de "pmu0" et non des valeurs instantanées.
22     ! Du coup "frac" prend toutes les valeurs entre 0 et 1.
23    
24     ! Date : première version le 13 decembre 1994
25     ! revu pour GCM le 30 septembre 1996
26    
27     REAL, INTENT (IN):: longi
28     ! (longitude vraie de la terre dans son plan solaire a partir de
29     ! l'equinoxe de printemps) (in degrees)
30    
31     REAL, INTENT (IN):: gmtime ! temps universel en fraction de jour
32     REAL, INTENT (IN):: pdtrad ! pas de temps du rayonnement (secondes)
33    
34     REAL, INTENT (OUT):: pmu0(:) ! (klon)
35     ! (cosine of mean zenith angle between "gmtime" and "gmtime+pdtrad")
36    
37     REAL, INTENT (OUT), OPTIONAL:: frac(:) ! (klon)
38     ! (ensoleillement moyen entre gmtime et gmtime+pdtrad)
39    
40     ! Variables local to the procedure:
41    
42     INTEGER i
43     REAL gmtime1, gmtime2
44     REAL deux_pi
45    
46     REAL omega1, omega2, omega
47     ! omega1, omega2 : temps 1 et 2 exprimés en radians avec 0 à midi.
48     ! omega : heure en radians du coucher de soleil
49     ! -omega est donc l'heure en radians de lever du soleil
50    
51     REAL omegadeb, omegafin
52     REAL zfrac1, zfrac2, z1_mu, z2_mu
53     REAL lat_sun ! déclinaison en radians
54     REAL latr ! latitude du point de grille en radians
55    
56     !----------------------------------------------------------------------
57    
58     if (present(frac)) call assert((/size(pmu0), size(frac)/) == klon, &
59     "zenang")
60    
61     deux_pi = 2*pi
62    
63     lat_sun = asin(sin(longi * pi / 180.) * sin(r_incl * pi / 180.))
64     ! Capderou (2003 #784, équation 4.49)
65    
66     gmtime1 = gmtime*86400.
67     gmtime2 = gmtime*86400. + pdtrad
68    
69     DO i = 1, klon
70     latr = rlat(i)*pi/180.
71     omega = 0.0 !--nuit polaire
72     IF (latr>=(pi/2.-lat_sun) .OR. latr<=(-pi/2.-lat_sun)) THEN
73     omega = pi ! journee polaire
74     END IF
75     IF (latr<(pi/2.+lat_sun) .AND. latr>(-pi/2.+lat_sun) .AND. &
76     latr<(pi/2.-lat_sun) .AND. latr>(-pi/2.-lat_sun)) THEN
77     omega = -tan(latr)*tan(lat_sun)
78     omega = acos(omega)
79     END IF
80    
81     omega1 = gmtime1 + rlon(i)*86400.0/360.0
82     omega1 = omega1/86400.0*deux_pi
83     omega1 = mod(omega1+deux_pi, deux_pi)
84     omega1 = omega1 - pi
85    
86     omega2 = gmtime2 + rlon(i)*86400.0/360.0
87     omega2 = omega2/86400.0*deux_pi
88     omega2 = mod(omega2+deux_pi, deux_pi)
89     omega2 = omega2 - pi
90    
91     TEST_OMEGA12: IF (omega1<=omega2) THEN
92     ! on est dans la meme journee locale
93     IF (omega2<=-omega .OR. omega1>=omega .OR. omega<1E-5) THEN
94     ! nuit
95     IF (present(frac)) frac(i) = 0.0
96     pmu0(i) = 0.0
97     ELSE
98     ! jour + nuit / jour
99     omegadeb = max(-omega, omega1)
100     omegafin = min(omega, omega2)
101     IF (present(frac)) frac(i) = (omegafin-omegadeb)/(omega2-omega1)
102     pmu0(i) = sin(latr)*sin(lat_sun) + cos(latr)*cos(lat_sun)*(sin( &
103     omegafin)-sin(omegadeb))/(omegafin-omegadeb)
104     END IF
105     ELSE TEST_OMEGA12
106     !---omega1 GT omega2 -- a cheval sur deux journees
107     !-------------------entre omega1 et pi
108     IF (omega1>=omega) THEN !--nuit
109     zfrac1 = 0.0
110     z1_mu = 0.0
111     ELSE !--jour+nuit
112     omegadeb = max(-omega, omega1)
113     omegafin = omega
114     zfrac1 = omegafin - omegadeb
115     z1_mu = sin(latr)*sin(lat_sun) + cos(latr)*cos(lat_sun)*(sin( &
116     omegafin)-sin(omegadeb))/(omegafin-omegadeb)
117     END IF
118     !---------------------entre -pi et omega2
119     IF (omega2<=-omega) THEN !--nuit
120     zfrac2 = 0.0
121     z2_mu = 0.0
122     ELSE !--jour+nuit
123     omegadeb = -omega
124     omegafin = min(omega, omega2)
125     zfrac2 = omegafin - omegadeb
126     z2_mu = sin(latr)*sin(lat_sun) + cos(latr)*cos(lat_sun)*(sin( &
127     omegafin)-sin(omegadeb))/(omegafin-omegadeb)
128    
129     END IF
130     !-----------------------moyenne
131     IF (present(frac)) frac(i) = (zfrac1+zfrac2)/ &
132     (omega2+deux_pi-omega1)
133     pmu0(i) = (zfrac1*z1_mu+zfrac2*z2_mu)/max(zfrac1+zfrac2, 1.E-10)
134     END IF TEST_OMEGA12
135     END DO
136    
137     END SUBROUTINE zenang
138    
139     end module zenang_m

  ViewVC Help
Powered by ViewVC 1.1.21