/[lmdze]/trunk/dyn3d/addfi.f
ViewVC logotype

Annotation of /trunk/dyn3d/addfi.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 91 - (hide annotations)
Wed Mar 26 17:18:58 2014 UTC (10 years, 2 months ago) by guez
File size: 2616 byte(s)
Removed unused variables lock_startdate and time_stamp of module
calendar.

Noticed that physiq does not change the surface pressure. So removed
arguments ps and dpfi of subroutine addfi. dpfi was always 0. The
computation of ps in addfi included some averaging at the poles. In
principle, this does not change ps but in practice it does because of
finite numerical precision. So the results of the simulation are
changed. Removed arguments ps and dpfi of calfis. Removed argument
d_ps of physiq.

du at the poles is not computed by dudv1, so declare only the
corresponding latitudes in dudv1. caldyn passes only a section of the
array dudyn as argument.

Removed variable niadv of module iniadvtrac_m.

Declared arguments of exner_hyb as assumed-shape arrays and made all
other horizontal sizes in exner_hyb dynamic. This allows the external
program test_disvert to use exner_hyb at a single horizontal position.

1 guez 37 module addfi_m
2 guez 3
3 guez 37 IMPLICIT NONE
4 guez 3
5 guez 37 contains
6 guez 3
7 guez 91 SUBROUTINE addfi(ucov, vcov, teta, q, dufi, dvfi, dtetafi, dqfi)
8 guez 3
9 guez 70 ! From dyn3d/addfi.F, v 1.1.1.1 2004/05/19 12:53:06
10 guez 3
11 guez 70 ! Addition of the physical tendencies
12 guez 37
13 guez 70 USE comconst, ONLY: dtphys
14     USE comgeom, ONLY: aire, apoln, apols
15 guez 71 USE dimens_m, ONLY: iim, jjm, llm, nqmx
16 guez 37
17 guez 71 ! First and second components of the covariant velocity:
18     REAL, intent(inout):: ucov((iim + 1) * (jjm + 1), llm)
19     REAL, intent(inout):: vcov((iim + 1) * jjm, llm)
20 guez 37
21 guez 71 REAL, intent(inout):: teta((iim + 1) * (jjm + 1), llm)
22     ! potential temperature
23 guez 37
24 guez 71 real, intent(inout):: q((iim + 1) * (jjm + 1), llm, nqmx)
25 guez 37
26 guez 71 ! Tendencies:
27     REAL, intent(in):: dufi((iim + 1) * (jjm + 1), llm)
28     REAL, intent(in):: dvfi((iim + 1) * jjm, llm)
29     real, intent(in):: dtetafi((iim + 1) * (jjm + 1), llm)
30     REAL, intent(in):: dqfi((iim + 1) * (jjm + 1), llm, nqmx)
31    
32 guez 70 ! Local variables :
33     REAL xpn(iim), xps(iim), tpn, tps
34     INTEGER j, k, iq, ij
35     REAL, PARAMETER:: qtestw = 1e-15, qtestt = 1e-40
36 guez 37
37     !-----------------------------------------------------------------------
38    
39 guez 71 teta = teta + dtetafi * dtphys
40 guez 37
41 guez 70 DO k = 1, llm
42     DO ij = 1, iim
43     xpn(ij) = aire(ij) * teta(ij , k)
44 guez 71 xps(ij) = aire(ij+(iim + 1) * jjm) * teta(ij+(iim + 1) * jjm, k)
45 guez 3 ENDDO
46 guez 70 tpn = SUM(xpn)/ apoln
47     tps = SUM(xps)/ apols
48 guez 3
49 guez 71 DO ij = 1, iim + 1
50 guez 70 teta(ij , k) = tpn
51 guez 71 teta(ij+(iim + 1) * jjm, k) = tps
52 guez 3 ENDDO
53 guez 37 ENDDO
54 guez 3
55 guez 70 DO k = 1, llm
56 guez 71 DO j = iim + 2, (iim + 1) * jjm
57 guez 70 ucov(j, k)= ucov(j, k) + dufi(j, k) * dtphys
58 guez 37 ENDDO
59     ENDDO
60 guez 3
61 guez 71 vcov = vcov + dvfi * dtphys
62 guez 3
63 guez 37 DO iq = 1, 2
64 guez 70 DO k = 1, llm
65 guez 71 DO j = 1, (iim + 1) * (jjm + 1)
66     q(j, k, iq)= q(j, k, iq) + dqfi(j, k, iq) * dtphys
67     q(j, k, iq)= MAX(q(j, k, iq), qtestw)
68 guez 37 ENDDO
69     ENDDO
70     ENDDO
71 guez 3
72 guez 71 DO iq = 3, nqmx
73 guez 70 DO k = 1, llm
74 guez 71 DO j = 1, (iim + 1) * (jjm + 1)
75     q(j, k, iq)= q(j, k, iq) + dqfi(j, k, iq) * dtphys
76     q(j, k, iq)= MAX(q(j, k, iq), qtestt)
77 guez 37 ENDDO
78     ENDDO
79     ENDDO
80 guez 3
81 guez 71 DO iq = 1, nqmx
82 guez 70 DO k = 1, llm
83     DO ij = 1, iim
84 guez 71 xpn(ij) = aire(ij) * q(ij , k, iq)
85     xps(ij) = aire(ij+(iim + 1) * jjm) * q(ij+(iim + 1) * jjm, k, iq)
86 guez 3 ENDDO
87 guez 70 tpn = SUM(xpn)/apoln
88     tps = SUM(xps)/apols
89 guez 3
90 guez 71 DO ij = 1, iim + 1
91     q(ij , k, iq) = tpn
92     q(ij+(iim + 1) * jjm, k, iq) = tps
93 guez 3 ENDDO
94 guez 37 ENDDO
95     ENDDO
96 guez 3
97 guez 37 END SUBROUTINE addfi
98    
99     end module addfi_m

  ViewVC Help
Powered by ViewVC 1.1.21