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

Contents of /trunk/dyn3d/caldyn.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 91 - (show annotations)
Wed Mar 26 17:18:58 2014 UTC (10 years, 2 months ago) by guez
File size: 3505 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 module caldyn_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE caldyn(itau, ucov, vcov, teta, ps, masse, pk, pkf, phis, phi, &
8 dudyn, dv, dteta, dp, w, pbaru, pbarv, time_0, conser)
9
10 ! From dyn3d/caldyn.F, version 1.1.1.1, 2004/05/19 12:53:06
11 ! Author: P. Le Van
12 ! Objet : calcul des tendances dynamiques
13
14 use advect_m, only: advect
15 USE comgeom, ONLY: airesurg, constang_2d
16 use convmas_m, only: convmas
17 USE dimens_m, ONLY: iim, jjm, llm
18 USE disvert_m, ONLY: ap, bp
19 use dteta1_m, only: dteta1
20 use dudv1_m, only: dudv1
21 use dudv2_m, only: dudv2
22 use flumass_m, only: flumass
23 use massbar_m, only: massbar
24 use massbarxy_m, only: massbarxy
25 use massdair_m, only: massdair
26 USE paramet_m, ONLY: iip1, ip1jmp1, jjp1, llmp1
27 use sortvarc_m, only: sortvarc
28 use tourpot_m, only: tourpot
29 use vitvert_m, only: vitvert
30
31 INTEGER, INTENT(IN):: itau
32 REAL, INTENT(IN):: ucov(:, :, :) ! (iim + 1, jjm + 1, llm) vent covariant
33 REAL, INTENT(IN):: vcov(:, :, :) ! (iim + 1, jjm, llm) ! vent covariant
34 REAL, INTENT(IN):: teta(ip1jmp1, llm)
35 REAL, INTENT (IN):: ps(ip1jmp1)
36 real, intent(out):: masse(ip1jmp1, llm)
37 REAL, INTENT(IN):: pk(iip1, jjp1, llm)
38 REAL, INTENT(IN):: pkf(ip1jmp1, llm)
39 REAL, INTENT(IN):: phis(ip1jmp1)
40 REAL, INTENT(IN):: phi(ip1jmp1, llm)
41 REAL dudyn(:, :, :) ! (iim + 1, jjm + 1, llm)
42 real dv((iim + 1) * jjm, llm)
43 REAL, INTENT(out):: dteta(ip1jmp1, llm)
44 real, INTENT(out):: dp(ip1jmp1)
45 REAL, INTENT(out):: w(:, :, :) ! (iim + 1, jjm + 1, llm)
46 REAL, intent(out):: pbaru(ip1jmp1, llm), pbarv((iim + 1) * jjm, llm)
47 REAL, intent(in):: time_0
48 LOGICAL, INTENT(IN):: conser
49
50 ! Local:
51 REAL vcont((iim + 1) * jjm, llm), ucont(ip1jmp1, llm)
52 REAL ang(iim + 1, jjm + 1, llm), p(ip1jmp1, llmp1)
53 REAL massebx(ip1jmp1, llm), masseby((iim + 1) * jjm, llm)
54 REAL vorpot(iim + 1, jjm, llm)
55 real ecin(ip1jmp1, llm), convm(ip1jmp1, llm)
56 REAL bern(ip1jmp1, llm)
57 REAL massebxy(iim + 1, jjm, llm)
58 INTEGER ij, l
59
60 !-----------------------------------------------------------------------
61
62 CALL covcont(llm, ucov, vcov, ucont, vcont)
63 forall (l = 1: llm + 1) p(:, l) = ap(l) + bp(l) * ps
64 CALL massdair(p, masse)
65 CALL massbar(masse, massebx, masseby)
66 CALL massbarxy(masse, massebxy)
67 CALL flumass(massebx, masseby, vcont, ucont, pbaru, pbarv)
68 CALL dteta1(teta, pbaru, pbarv, dteta)
69 CALL convmas(pbaru, pbarv, convm)
70 dp = convm(:, 1) / airesurg
71 CALL vitvert(convm, w)
72 CALL tourpot(vcov, ucov, massebxy, vorpot)
73 CALL dudv1(vorpot, pbaru, pbarv, dudyn(:, 2: jjm, :), dv)
74 CALL enercin(vcov, ucov, vcont, ucont, ecin)
75 CALL bernoui(ip1jmp1, llm, phi, ecin, bern)
76 CALL dudv2(teta, pkf, bern, dudyn, dv)
77
78 forall (l = 1: llm) ang(:, :, l) = ucov(:, :, l) + constang_2d
79 CALL advect(ang, vcov, teta, w, massebx, masseby, dudyn, dv, dteta)
80
81 ! Warning problème de périodicité de dv sur les PC Linux. Problème
82 ! d'arrondi probablement. Observé sur le code compilé avec pgf90
83 ! 3.0-1.
84 DO l = 1, llm
85 DO ij = 1, (iim + 1) * jjm, iip1
86 IF (dv(ij, l)/=dv(ij+iim, l)) THEN
87 dv(ij+iim, l) = dv(ij, l)
88 END IF
89 END DO
90 END DO
91
92 ! Sorties éventuelles des variables de contrôle :
93 IF (conser) CALL sortvarc(itau, ucov, teta, ps, masse, pk, phis, vorpot, &
94 phi, bern, dp, time_0)
95
96 END SUBROUTINE caldyn
97
98 end module caldyn_m

  ViewVC Help
Powered by ViewVC 1.1.21