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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 44 - (show annotations)
Wed Apr 13 12:29:18 2011 UTC (13 years, 1 month ago) by guez
File size: 1170 byte(s)
Removed argument "pdteta" of "calfis", because it was not used.

Created module "conf_guide_m", containing procedure
"conf_guide". Moved module variables from "guide_m" to "conf_guide_m".

In module "getparam", removed "ini_getparam" and "fin_getparam" from
generic interface "getpar".

Created module variables in "tau2alpha_m" to replace common "comdxdy".

1 SUBROUTINE dteta1(teta, pbaru, pbarv, dteta)
2
3 ! From LMDZ4/libf/dyn3d/dteta1.F, version 1.1.1.1 2004/05/19 12:53:06
4 ! Auteurs : P. Le Van, F. Forget
5
6 ! Calcul du terme de convergence horizontale du flux d'enthalpie
7 ! potentielle.
8
9 ! dteta est un argument de sortie pour le s-pg
10
11 use dimens_m
12 use paramet_m
13 use logic
14 use filtreg_m, only: filtreg
15
16 IMPLICIT NONE
17
18 REAL, intent(in):: teta(ip1jmp1, llm), pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
19 REAL dteta(ip1jmp1, llm)
20 INTEGER l, ij
21
22 REAL hbyv(ip1jm, llm), hbxu(ip1jmp1, llm)
23
24 !----------------------------------------------------------------
25
26 DO l = 1, llm
27 DO ij = iip2, ip1jm - 1
28 hbxu(ij, l) = pbaru(ij, l) * 0.5 * (teta(ij, l) + teta(ij + 1, l))
29 end DO
30
31 DO ij = iip1+ iip1, ip1jm, iip1
32 hbxu(ij, l) = hbxu(ij - iim, l)
33 end DO
34
35 DO ij = 1, ip1jm
36 hbyv(ij, l)= pbarv(ij, l) * 0.5 * (teta(ij, l) + teta(ij + iip1, l))
37 end DO
38 end DO
39
40 CALL convflu(hbxu, hbyv, llm, dteta)
41
42 ! stockage dans dh de la convergence horizont. filtree' du flux
43 ! d'enthalpie potentielle
44 CALL filtreg(dteta, jjp1, llm, 2, 2, .true., 1)
45
46 END SUBROUTINE dteta1

  ViewVC Help
Powered by ViewVC 1.1.21