/[lmdze]/trunk/phylmd/Interface_surf/climb_hq_up.f90
ViewVC logotype

Annotation of /trunk/phylmd/Interface_surf/climb_hq_up.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 296 - (hide annotations)
Thu Jul 26 13:50:13 2018 UTC (5 years, 11 months ago) by guez
Original Path: trunk/phylmd/Interface_surf/climb_hq_up.f
File size: 1492 byte(s)
Create procedure climb_hq_up from part of procedure clqh (following LMDZ).

1 guez 296 module climb_hq_up_m
2    
3     IMPLICIT none
4    
5     contains
6    
7     subroutine climb_hq_up(d_t, d_q, cq, dq, ch, dh, flux_t, flux_q, dtime, pkf, &
8     t, q)
9    
10     USE dimphy, ONLY: klev
11     USE suphec_m, ONLY: rcpd
12    
13     REAL, intent(out):: d_t(:, :) ! (knon, klev) incrementation de "t"
14     REAL, intent(out):: d_q(:, :) ! (knon, klev) incrementation de "q"
15     REAL, intent(in), dimension(:, :):: cq, dq, ch, dh ! (knon, klev)
16    
17     REAL, intent(in):: flux_t(:) ! (knon)
18     ! (diagnostic) flux de chaleur sensible (Cp T) à la surface,
19     ! positif vers le bas, W / m2
20    
21     REAL, intent(out):: flux_q(:) ! (knon)
22     ! flux de la vapeur d'eau à la surface, en kg / (m**2 s)
23    
24     REAL, intent(in):: dtime ! intervalle du temps (s)
25     REAL, intent(in):: pkf(:, :) ! (knon, klev)
26     REAL, intent(in):: t(:, :) ! (knon, klev) temperature (K)
27     REAL, intent(in):: q(:, :) ! (knon, klev) humidite specifique (kg / kg)
28    
29     ! Local:
30     REAL h(size(flux_t), klev) ! (knon, klev) enthalpie potentielle
31     INTEGER k
32     REAL local_q(size(flux_t), klev) ! (knon, klev)
33    
34     !----------------------------------------------------------------------
35    
36     h(:, 1) = ch(:, 1) + dh(:, 1) * flux_t * dtime
37     local_q(:, 1) = cq(:, 1) + dq(:, 1) * flux_q * dtime
38    
39     DO k = 2, klev
40     h(:, k) = ch(:, k) + dh(:, k) * h(:, k - 1)
41     local_q(:, k) = cq(:, k) + dq(:, k) * local_q(:, k - 1)
42     ENDDO
43    
44     d_t = h / pkf / RCPD - t
45     d_q = local_q - q
46    
47     end subroutine climb_hq_up
48    
49     end module climb_hq_up_m

  ViewVC Help
Powered by ViewVC 1.1.21