/[lmdze]/trunk/Sources/phylmd/clqh.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/clqh.f

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

trunk/libf/phylmd/clqh.f90 revision 70 by guez, Mon Jun 24 15:39:52 2013 UTC trunk/phylmd/clqh.f revision 99 by guez, Wed Jul 2 18:39:15 2014 UTC
# Line 4  module clqh_m Line 4  module clqh_m
4    
5  contains  contains
6    
7    SUBROUTINE clqh(dtime, itime, date0, jour, debut, lafin, rlon, rlat, cufi, &    SUBROUTINE clqh(dtime, itime, jour, debut, rlat, knon, nisurf, knindex, &
8         cvfi, knon, nisurf, knindex, pctsrf, soil_model, tsoil, qsol, &         pctsrf, soil_model, tsoil, qsol, rmu0, co2_ppm, rugos, rugoro, u1lay, &
        ok_veget, ocean, npas, nexca, rmu0, co2_ppm, rugos, rugoro, u1lay, &  
9         v1lay, coef, t, q, ts, paprs, pplay, delp, radsol, albedo, alblw, &         v1lay, coef, t, q, ts, paprs, pplay, delp, radsol, albedo, alblw, &
10         snow, qsurf, precip_rain, precip_snow, fder, taux, tauy, ywindsp, &         snow, qsurf, precip_rain, precip_snow, fder, swnet, fluxlat, &
11         sollw, sollwdown, swnet, fluxlat, pctsrf_new, agesno, d_t, d_q, d_ts, &         pctsrf_new, agesno, d_t, d_q, d_ts, z0_new, flux_t, flux_q, dflux_s, &
12         z0_new, flux_t, flux_q, dflux_s, dflux_l, fqcalving, ffonte, &         dflux_l, fqcalving, ffonte, run_off_lic_0, flux_o, flux_g, tslab, seaice)
        run_off_lic_0, flux_o, flux_g, tslab, seaice)  
13    
14      ! Author: Z. X. Li (LMD/CNRS)      ! Author: Z. X. Li (LMD/CNRS)
15      ! Date: 1993/08/18      ! Date: 1993/08/18
# Line 28  contains Line 26  contains
26      ! Arguments:      ! Arguments:
27      INTEGER, intent(in):: knon      INTEGER, intent(in):: knon
28      REAL, intent(in):: dtime              ! intervalle du temps (s)      REAL, intent(in):: dtime              ! intervalle du temps (s)
     real, intent(in):: date0  
29      REAL u1lay(klon)        ! vitesse u de la 1ere couche (m/s)      REAL u1lay(klon)        ! vitesse u de la 1ere couche (m/s)
30      REAL v1lay(klon)        ! vitesse v de la 1ere couche (m/s)      REAL v1lay(klon)        ! vitesse v de la 1ere couche (m/s)
31    
# Line 56  contains Line 53  contains
53      integer, intent(in):: jour            ! jour de l'annee en cours      integer, intent(in):: jour            ! jour de l'annee en cours
54      real, intent(in):: rmu0(klon)         ! cosinus de l'angle solaire zenithal      real, intent(in):: rmu0(klon)         ! cosinus de l'angle solaire zenithal
55      real rugos(klon)        ! rugosite      real rugos(klon)        ! rugosite
56      integer knindex(klon)      integer, intent(in):: knindex(klon)
57      real, intent(in):: pctsrf(klon, nbsrf)      real, intent(in):: pctsrf(klon, nbsrf)
58      real, intent(in):: rlon(klon), rlat(klon)      real, intent(in):: rlat(klon)
59      real cufi(klon), cvfi(klon)      REAL, intent(in):: co2_ppm            ! taux CO2 atmosphere
     logical ok_veget  
     REAL co2_ppm            ! taux CO2 atmosphere  
     character(len=*), intent(in):: ocean  
     integer npas, nexca  
     ! -- LOOP  
     REAL yu10mx(klon)  
     REAL yu10my(klon)  
     REAL ywindsp(klon)  
     ! -- LOOP  
60    
61      REAL d_t(klon, klev)     ! incrementation de "t"      REAL d_t(klon, klev)     ! incrementation de "t"
62      REAL d_q(klon, klev)     ! incrementation de "q"      REAL d_q(klon, klev)     ! incrementation de "q"
# Line 91  contains Line 79  contains
79      REAL flux_o(klon) ! flux entre l'ocean et l'atmosphere W/m2      REAL flux_o(klon) ! flux entre l'ocean et l'atmosphere W/m2
80      REAL flux_g(klon) ! flux entre l'ocean et la glace de mer W/m2      REAL flux_g(klon) ! flux entre l'ocean et la glace de mer W/m2
81    
     REAL t_grnd  ! temperature de rappel pour glace de mer  
     PARAMETER (t_grnd=271.35)  
     REAL t_coup  
     PARAMETER(t_coup=273.15)  
   
82      INTEGER i, k      INTEGER i, k
83      REAL zx_cq(klon, klev)      REAL zx_cq(klon, klev)
84      REAL zx_dq(klon, klev)      REAL zx_dq(klon, klev)
# Line 121  contains Line 104  contains
104      integer, intent(in):: itime      integer, intent(in):: itime
105      integer nisurf      integer nisurf
106      logical, intent(in):: debut      logical, intent(in):: debut
     logical, intent(in):: lafin  
107      real zlev1(klon)      real zlev1(klon)
108      real fder(klon), taux(klon), tauy(klon)      real fder(klon)
109      real temp_air(klon), spechum(klon)      real temp_air(klon), spechum(klon)
110      real epot_air(klon), ccanopy(klon)      real epot_air(klon), ccanopy(klon)
111      real tq_cdrag(klon), petAcoef(klon), peqAcoef(klon)      real tq_cdrag(klon), petAcoef(klon), peqAcoef(klon)
112      real petBcoef(klon), peqBcoef(klon)      real petBcoef(klon), peqBcoef(klon)
113      real sollw(klon), sollwdown(klon), swnet(klon), swdown(klon)      real swnet(klon), swdown(klon)
114      real p1lay(klon)      real p1lay(klon)
115      !$$$C PB ajout pour soil      !$$$C PB ajout pour soil
116      LOGICAL, intent(in):: soil_model      LOGICAL, intent(in):: soil_model
# Line 137  contains Line 119  contains
119    
120      ! Parametres de sortie      ! Parametres de sortie
121      real fluxsens(klon), fluxlat(klon)      real fluxsens(klon), fluxlat(klon)
122      real tsol_rad(klon), tsurf_new(klon), alb_new(klon)      real tsurf_new(klon), alb_new(klon)
123      real emis_new(klon), z0_new(klon)      real z0_new(klon)
124      real pctsrf_new(klon, nbsrf)      real pctsrf_new(klon, nbsrf)
125      ! JLD      ! JLD
126      real zzpk      real zzpk
# Line 288  contains Line 270  contains
270      endif      endif
271      ccanopy = co2_ppm      ccanopy = co2_ppm
272    
273      CALL interfsurf_hq(itime, dtime, date0, jour, rmu0, &      CALL interfsurf_hq(itime, dtime, jour, rmu0, iim, jjm, nisurf, knon, &
274           klon, iim, jjm, nisurf, knon, knindex, pctsrf,  &           knindex, pctsrf, rlat, debut, soil_model, nsoilmx, tsoil, qsol,  &
275           rlon, rlat, cufi, cvfi,  &           u1lay, v1lay, temp_air, spechum, tq_cdrag, petAcoef, peqAcoef, &
276           debut, lafin, ok_veget, soil_model, nsoilmx, tsoil, qsol, &           petBcoef, peqBcoef, precip_rain, precip_snow, fder, rugos, rugoro, &
277           zlev1,  u1lay, v1lay, temp_air, spechum, epot_air, ccanopy,  &           snow, qsurf, ts, p1lay, psref, radsol, evap, fluxsens, &
278           tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &           fluxlat, dflux_l, dflux_s, tsurf_new, alb_new, alblw, z0_new, &
279           precip_rain, precip_snow, sollw, sollwdown, swnet, swdown, &           pctsrf_new, agesno, fqcalving, ffonte, run_off_lic_0, flux_o, &
280           fder, taux, tauy, &           flux_g, tslab, seaice)
          ywindsp, rugos, rugoro, &  
          albedo, snow, qsurf, &  
          ts, p1lay, psref, radsol, &  
          ocean, npas, nexca, zmasq, &  
          evap, fluxsens, fluxlat, dflux_l, dflux_s,               &  
          tsol_rad, tsurf_new, alb_new, alblw, emis_new, z0_new,  &  
          pctsrf_new, agesno, fqcalving, ffonte, run_off_lic_0, &  
          flux_o, flux_g, tslab, seaice)  
281    
282      do i = 1, knon      do i = 1, knon
283         flux_t(i, 1) = fluxsens(i)         flux_t(i, 1) = fluxsens(i)

Legend:
Removed from v.70  
changed lines
  Added in v.99

  ViewVC Help
Powered by ViewVC 1.1.21