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

Diff of /trunk/phylmd/zenang.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 118 by guez, Thu Dec 18 17:30:24 2014 UTC revision 125 by guez, Fri Feb 6 15:00:28 2015 UTC
# Line 6  contains Line 6  contains
6    
7    SUBROUTINE zenang(longi, gmtime, pdtrad, mu0, frac)    SUBROUTINE zenang(longi, gmtime, pdtrad, mu0, frac)
8    
     USE dimphy, ONLY: klon  
     USE yomcst, ONLY: r_incl  
     USE phyetat0_m, ONLY: rlat, rlon  
     use nr_util, only: assert, pi  
   
9      ! Author: O. Boucher (LMD/CNRS), d'après les routines "zenith" et      ! Author: O. Boucher (LMD/CNRS), d'après les routines "zenith" et
10      ! "angle" de Z.X. Li      ! "angle" de Z.X. Li
11    
# Line 18  contains Line 13  contains
13      ! septembre 1996      ! septembre 1996
14    
15      ! Calcule les valeurs moyennes du cos de l'angle zénithal et      ! Calcule les valeurs moyennes du cos de l'angle zénithal et
16      ! l'ensoleillement moyen entre "gmtime" et "gmtime+pdtrad"      ! l'ensoleillement moyen entre "gmtime" et "gmtime + pdtrad"
17      ! connaissant la déclinaison, la latitude et la longitude.      ! connaissant la déclinaison, la latitude et la longitude.
18      ! Différent de la routine "angle" en ce sens que "zenang" fournit      ! Différent de la routine "angle" en ce sens que "zenang" fournit
19      ! des moyennes de "mu0" et non des valeurs instantanées.  Du coup      ! des moyennes de "mu0" et non des valeurs instantanées. Du coup
20      ! "frac" prend toutes les valeurs entre 0 et 1.      ! "frac" prend toutes les valeurs entre 0 et 1. Cf. Capderou (2003
21        ! 784, equation 9.11).
22    
23        USE dimphy, ONLY: klon
24        USE yomcst, ONLY: r_incl
25        USE phyetat0_m, ONLY: rlat, rlon
26        use nr_util, only: assert, pi, twopi
27    
28      REAL, INTENT(IN):: longi      REAL, INTENT(IN):: longi
29      ! longitude vraie de la terre dans son plan solaire à partir de      ! longitude vraie de la terre dans son plan solaire à partir de
# Line 41  contains Line 42  contains
42    
43      INTEGER i      INTEGER i
44      REAL gmtime1, gmtime2      REAL gmtime1, gmtime2
     REAL deux_pi  
   
45      REAL omega1, omega2 ! temps 1 et 2 exprimés en radians avec 0 à midi      REAL omega1, omega2 ! temps 1 et 2 exprimés en radians avec 0 à midi
46    
47      REAL omega ! heure en rad du coucher de soleil      REAL omega ! heure en rad du coucher de soleil
# Line 56  contains Line 55  contains
55      !----------------------------------------------------------------------      !----------------------------------------------------------------------
56    
57      if (present(frac)) call assert((/size(mu0), size(frac)/) == klon, "zenang")      if (present(frac)) call assert((/size(mu0), size(frac)/) == klon, "zenang")
       
     deux_pi = 2*pi  
58    
59      lat_sun = asin(sin(longi * pi / 180.) * sin(r_incl * pi / 180.))      lat_sun = asin(sin(longi * pi / 180.) * sin(r_incl * pi / 180.))
60      ! Capderou (2003 784, equation 4.49)      ! Capderou (2003 784, equation 4.49)
# Line 78  contains Line 75  contains
75         END IF         END IF
76    
77         omega1 = gmtime1 + rlon(i)*86400.0/360.0         omega1 = gmtime1 + rlon(i)*86400.0/360.0
78         omega1 = omega1/86400.0*deux_pi         omega1 = omega1/86400.0*twopi
79         omega1 = mod(omega1+deux_pi, deux_pi)         omega1 = mod(omega1+twopi, twopi)
80         omega1 = omega1 - pi         omega1 = omega1 - pi
81    
82         omega2 = gmtime2 + rlon(i)*86400.0/360.0         omega2 = gmtime2 + rlon(i)*86400.0/360.0
83         omega2 = omega2/86400.0*deux_pi         omega2 = omega2/86400.0*twopi
84         omega2 = mod(omega2+deux_pi, deux_pi)         omega2 = mod(omega2+twopi, twopi)
85         omega2 = omega2 - pi         omega2 = omega2 - pi
86    
87         IF (omega1<=omega2) THEN         IF (omega1<=omega2) THEN
# Line 111  contains Line 108  contains
108               omegadeb = max(-omega, omega1)               omegadeb = max(-omega, omega1)
109               omegafin = omega               omegafin = omega
110               zfrac1 = omegafin - omegadeb               zfrac1 = omegafin - omegadeb
111               z1_mu = sin(latr)*sin(lat_sun) + cos(latr)*cos(lat_sun)*(sin( &               z1_mu = sin(latr) * sin(lat_sun) + cos(latr) * cos(lat_sun) &
112                    omegafin)-sin(omegadeb))/(omegafin-omegadeb)                    * (sin(omegafin) - sin(omegadeb)) / (omegafin - omegadeb)
113            END IF            END IF
114            ! entre -pi et omega2            ! entre -pi et omega2
115            IF (omega2<=-omega) THEN ! nuit            IF (omega2<=-omega) THEN ! nuit
# Line 122  contains Line 119  contains
119               omegadeb = -omega               omegadeb = -omega
120               omegafin = min(omega, omega2)               omegafin = min(omega, omega2)
121               zfrac2 = omegafin - omegadeb               zfrac2 = omegafin - omegadeb
122               z2_mu = sin(latr)*sin(lat_sun) + cos(latr)*cos(lat_sun)*(sin( &               z2_mu = sin(latr) * sin(lat_sun) + cos(latr) * cos(lat_sun) &
123                    omegafin)-sin(omegadeb))/(omegafin-omegadeb)                    * (sin(omegafin) - sin(omegadeb)) / (omegafin - omegadeb)
   
124            END IF            END IF
125            ! moyenne            ! moyenne
126            IF (present(frac)) frac(i) = (zfrac1+zfrac2)/ (omega2+deux_pi-omega1)            IF (present(frac)) frac(i) = (zfrac1+zfrac2)/ (omega2+twopi-omega1)
127            mu0(i) = (zfrac1*z1_mu+zfrac2*z2_mu)/max(zfrac1+zfrac2, 1.E-10)            mu0(i) = (zfrac1*z1_mu+zfrac2*z2_mu)/max(zfrac1+zfrac2, 1.E-10)
128         END IF         END IF
129      END DO      END DO

Legend:
Removed from v.118  
changed lines
  Added in v.125

  ViewVC Help
Powered by ViewVC 1.1.21