/[lmdze]/trunk/phylmd/Thermcell/calltherm.f90
ViewVC logotype

Diff of /trunk/phylmd/Thermcell/calltherm.f90

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

trunk/Sources/phylmd/calltherm.f revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC trunk/phylmd/Thermcell/calltherm.f revision 324 by guez, Wed Feb 6 15:58:03 2019 UTC
# Line 4  module calltherm_m Line 4  module calltherm_m
4    
5  contains  contains
6    
7    subroutine calltherm(dtime, pplay, paprs, pphi, u_seri, v_seri, t_seri, &    subroutine calltherm(pplay, paprs, pphi, u_seri, v_seri, t_seri, q_seri, &
8         q_seri, d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)         d_u_ajs, d_v_ajs, d_t_ajs, d_q_ajs, fm_therm, entr_therm)
9    
10      ! From LMDZ4/libf/phylmd/calltherm.F, version 1.2 2004/12/10 11:27:46      ! From LMDZ4/libf/phylmd/calltherm.F, version 1.2 2004/12/10 11:27:46
11    
12        ! Thermiques.
13    
14        use comconst, only: dtphys
15        USE ctherm_m, ONLY: nsplit_thermals
16      USE dimphy, ONLY: klev, klon      USE dimphy, ONLY: klev, klon
     USE ctherm, ONLY: l_mix_thermals, nsplit_thermals, r_aspect_thermals, &  
          tho_thermals, w2di_thermals  
17      use thermcell_m, only: thermcell      use thermcell_m, only: thermcell
18    
     REAL, intent(in):: dtime  
   
     REAL, intent(inout):: u_seri(klon, klev), v_seri(klon, klev)  
     REAL, intent(inout):: t_seri(klon, klev)  
     real q_seri(klon, klev)  
     REAL, intent(in):: paprs(klon, klev+1)  
19      REAL, intent(in):: pplay(klon, klev)      REAL, intent(in):: pplay(klon, klev)
20        REAL, intent(in):: paprs(klon, klev+1)
21      REAL, intent(in):: pphi(klon, klev)      REAL, intent(in):: pphi(klon, klev)
22        REAL, intent(inout):: u_seri(klon, klev), v_seri(klon, klev)
23        REAL, intent(inout):: t_seri(klon, klev)
24        real, intent(inout):: q_seri(klon, klev)
25    
26      ! Update thermiques      ! Update thermiques
     REAL d_t_ajs(klon, klev), d_q_ajs(klon, klev)  
27      REAL d_u_ajs(klon, klev), d_v_ajs(klon, klev)      REAL d_u_ajs(klon, klev), d_v_ajs(klon, klev)
28        REAL d_t_ajs(klon, klev), d_q_ajs(klon, klev)
29      real fm_therm(klon, klev+1), entr_therm(klon, klev)      real fm_therm(klon, klev+1), entr_therm(klon, klev)
30    
31      ! Variables locales      ! Local:
32    
33      REAL d_t_the(klon, klev), d_q_the(klon, klev)      REAL d_t_the(klon, klev), d_q_the(klon, klev)
34      REAL d_u_the(klon, klev), d_v_the(klon, klev)      REAL d_u_the(klon, klev), d_v_the(klon, klev)
35      !  
36      real, save:: zfm_therm(klon, klev+1), zentr_therm(klon, klev)      real, save:: zfm_therm(klon, klev+1), zentr_therm(klon, klev)
37      real zdt      real zdt
38    
# Line 48  contains Line 49  contains
49      ! tests sur les valeurs negatives de l'eau      ! tests sur les valeurs negatives de l'eau
50      do k=1, klev      do k=1, klev
51         do i=1, klon         do i=1, klon
52            if (.not.q_seri(i, k).ge.0.) then            if (.not.q_seri(i, k) >= 0.) then
53               print*, 'WARN eau<0 avant therm i=', i, ' k=', k, ' dq, q', &               print*, 'WARN eau<0 avant therm i=', i, ' k=', k, ' dq, q', &
54                    d_q_the(i, k), q_seri(i, k)                    d_q_the(i, k), q_seri(i, k)
55               q_seri(i, k)=1.e-15               q_seri(i, k)=1.e-15
# Line 56  contains Line 57  contains
57         enddo         enddo
58      enddo      enddo
59    
60      zdt=dtime/float(nsplit_thermals)      zdt=dtphys/real(nsplit_thermals)
61      do isplit = 1, nsplit_thermals      do isplit = 1, nsplit_thermals
62         CALL thermcell(klon, klev, zdt, pplay, paprs, pphi, u_seri, v_seri, &         CALL thermcell(klon, klev, zdt, pplay, paprs, pphi, u_seri, v_seri, &
63              t_seri, q_seri, d_u_the, d_v_the, d_t_the, d_q_the, zfm_therm, &              t_seri, q_seri, d_u_the, d_v_the, d_t_the, d_q_the, zfm_therm, &
64              zentr_therm, r_aspect_thermals, l_mix_thermals, w2di_thermals, &              zentr_therm)
             tho_thermals)  
65    
66         ! transformation de la derivee en tendance         ! transformation de la derivee en tendance
67         d_t_the=d_t_the*dtime/float(nsplit_thermals)         d_t_the=d_t_the*dtphys/real(nsplit_thermals)
68         d_u_the=d_u_the*dtime/float(nsplit_thermals)         d_u_the=d_u_the*dtphys/real(nsplit_thermals)
69         d_v_the=d_v_the*dtime/float(nsplit_thermals)         d_v_the=d_v_the*dtphys/real(nsplit_thermals)
70         d_q_the=d_q_the*dtime/float(nsplit_thermals)         d_q_the=d_q_the*dtphys/real(nsplit_thermals)
71         fm_therm=fm_therm +zfm_therm/float(nsplit_thermals)         fm_therm=fm_therm +zfm_therm/real(nsplit_thermals)
72         entr_therm=entr_therm +zentr_therm/float(nsplit_thermals)         entr_therm=entr_therm +zentr_therm/real(nsplit_thermals)
73         fm_therm(:, klev+1)=0.         fm_therm(:, klev+1)=0.
74    
75         ! accumulation de la tendance         ! accumulation de la tendance
# Line 87  contains Line 87  contains
87         ! tests sur les valeurs negatives de l'eau         ! tests sur les valeurs negatives de l'eau
88         DO k = 1, klev         DO k = 1, klev
89            DO i = 1, klon            DO i = 1, klon
90               if (.not.q_seri(i, k).ge.0.) then               if (.not.q_seri(i, k) >= 0.) then
91                  print*, 'WARN eau<0 apres therm i=', i, ' k=', k, ' dq, q', &                  print*, 'WARN eau<0 apres therm i=', i, ' k=', k, ' dq, q', &
92                       d_q_the(i, k), q_seri(i, k)                       d_q_the(i, k), q_seri(i, k)
93                  q_seri(i, k)=1.e-15                  q_seri(i, k)=1.e-15

Legend:
Removed from v.134  
changed lines
  Added in v.324

  ViewVC Help
Powered by ViewVC 1.1.21