/[lmdze]/trunk/dyn3d/dudv2.f90
ViewVC logotype

Contents of /trunk/dyn3d/dudv2.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 1429 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 module dudv2_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE dudv2(teta, pkf, bern, du, dv)
8
9 ! From LMDZ4/libf/dyn3d/dudv2.F, version 1.1.1.1, 2004/05/19 12:53:06
10
11 ! Author: P. Le Van
12
13 ! Objet : calcul du terme de pression (gradient de p / densité) et
14 ! du terme "- gradient de la fonction de Bernouilli". Ces termes
15 ! sont ajoutés à d(ucov)/dt et à d(vcov)/dt.
16
17 USE dimensions, ONLY: iim, llm
18 USE paramet_m, ONLY: iip1, iip2, ip1jm, ip1jmp1
19
20 REAL, INTENT(IN):: teta(ip1jmp1, llm)
21 REAL, INTENT(IN):: pkf(ip1jmp1, llm)
22 real, INTENT(IN):: bern(ip1jmp1, llm)
23 real, intent(inout):: du(ip1jmp1, llm), dv(ip1jm, llm)
24
25 ! Local:
26 INTEGER l, ij
27
28 !-----------------------------------------------------------------
29
30 DO l = 1, llm
31 DO ij = iip2, ip1jm - 1
32 du(ij, l) = du(ij, l) + 0.5 * (teta(ij, l) + teta(ij + 1, l)) &
33 * (pkf(ij, l) - pkf(ij + 1, l)) + bern(ij, l) - bern(ij + 1, l)
34 END DO
35
36 ! correction pour du(iip1, j, l), j=2, jjm
37 ! du(iip1, j, l) = du(1, j, l)
38 DO ij = iip1 + iip1, ip1jm, iip1
39 du(ij, l) = du(ij - iim, l)
40 END DO
41
42 DO ij = 1, ip1jm
43 dv(ij, l) = dv(ij, l) + 0.5 * (teta(ij, l) + teta(ij + iip1, l)) &
44 * (pkf(ij + iip1, l) - pkf(ij, l)) + bern(ij + iip1, l) &
45 - bern(ij, l)
46 END DO
47 END DO
48
49 END SUBROUTINE dudv2
50
51 end module dudv2_m

  ViewVC Help
Powered by ViewVC 1.1.21