/[lmdze]/trunk/libf/dyn3d/caladvtrac.f90
ViewVC logotype

Contents of /trunk/libf/dyn3d/caladvtrac.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 71 - (show annotations)
Mon Jul 8 18:12:18 2013 UTC (10 years, 9 months ago) by guez
File size: 1390 byte(s)
No reason to call inidissip in ce0l.

In inidissip, set random seed to 1 beacuse PGI compiler does not
accept all zeros.

dq was computed needlessly in caladvtrac. Arguments masse and dq of
calfis not used.

Replaced real*8 by double precision.

Pass arrays with inverted order of vertical levels to conflx instead
of creating local variables for this inside conflx.

1 module caladvtrac_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE caladvtrac(q, pbaru, pbarv, p, masse, teta, pk)
8
9 ! From dyn3d/caladvtrac.F, version 1.3 2005/04/13 08:58:34
10 ! Authors: F. Hourdin, P. Le Van, F. Forget, F. Codron
11 ! F. Codron (10/99) : ajout humidité spécifique pour eau vapeur
12 ! Schéma de Van Leer
13
14 ! Calcul des tendances advection des traceurs (dont l'humidité)
15
16 use advtrac_m, only: advtrac
17 use conf_gcm_m, only: iapp_tracvl
18 use dimens_m, only: iim, jjm, llm, nqmx
19 use paramet_m, only: ip1jmp1
20 use qminimum_m, only: qminimum
21
22 real, intent(inout):: q(:, :, :, :) ! (iim + 1, jjm + 1, llm, nqmx)
23 REAL, intent(in):: pbaru(ip1jmp1, llm), pbarv((iim + 1) * jjm, llm)
24 REAL, intent(in):: p(iim + 1, jjm + 1, llm + 1)
25 real, intent(in):: masse(iim + 1, jjm + 1, llm)
26 REAL, intent(in):: teta(ip1jmp1, llm)
27 real, intent(in):: pk(ip1jmp1, llm)
28
29 ! Local:
30 INTEGER l, iapptrac
31 REAL finmasse(iim + 1, jjm + 1, llm)
32
33 !------------------------------------------------
34
35 ! Advection:
36 CALL advtrac(pbaru, pbarv, p, masse, q, iapptrac, teta, pk)
37
38 IF (iapptrac == iapp_tracvl) THEN
39 forall (l = 1:llm) finmasse(:, :, l) = p(:, :, l) - p(:, :, l+1)
40
41 ! Uniquement pour l'eau vapeur et liquide:
42 CALL qminimum(q, 2, finmasse)
43 ENDIF
44
45 END SUBROUTINE caladvtrac
46
47 end module caladvtrac_m

  ViewVC Help
Powered by ViewVC 1.1.21