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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 45 - (show annotations)
Wed Apr 27 13:00:12 2011 UTC (13 years, 1 month ago) by guez
File size: 891 byte(s)
Split file "histwrite.f90" into "histwrite.f90", "histwrite_real.f90"
and "histvar_seq.f90".

Extracted documentation from "psextbar.f" into "psextbar.txt" (out of SVN).

1 SUBROUTINE psextbar(ps, psexbarxy)
2
3 ! From LMDZ4/libf/dyn3d/psextbar.F, version 1.1.1.1 2004/05/19 12:53:06
4 ! Author: P. Le Van
5
6 ! Objet : calcul des moyennes en x et en y de (pression au sol * aire
7 ! variable)
8 ! Cf. "psextbar.txt".
9
10 use dimens_m
11 use paramet_m
12 use comgeom
13
14 IMPLICIT NONE
15
16 REAL, intent(in):: ps(ip1jmp1)
17 real, intent(out):: psexbarxy(ip1jm)
18
19 ! Local variables:
20 real pext(ip1jmp1)
21 INTEGER l, ij
22
23 !--------------------------------------------------------
24
25 DO ij = 1, ip1jmp1
26 pext(ij) = ps(ij) * aire(ij)
27 ENDDO
28
29 DO ij = 1, ip1jm - 1
30 psexbarxy(ij) = pext(ij) * alpha2(ij) + pext(ij+1) * alpha3(ij+1) &
31 + pext(ij+iip1) * alpha1(ij+iip1) + pext(ij+iip2) * alpha4(ij+iip2)
32 end DO
33
34 ! Correction pour psexbarxy(iip1,j) :
35 DO ij = iip1, ip1jm, iip1
36 psexbarxy(ij) = psexbarxy(ij - iim)
37 end DO
38
39 END SUBROUTINE psextbar

  ViewVC Help
Powered by ViewVC 1.1.21