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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 61 - (show annotations)
Fri Apr 20 14:58:43 2012 UTC (12 years ago) by guez
File size: 1746 byte(s)
No more included file in LMDZE, not even "netcdf.inc".

Created a variable containing the list of common source files in
GNUmakefile. So we now also see clearly files that are specific to
each program.

Split module "histcom". Assembled resulting files in directory
"Histcom".

Removed aliasing in calls to "laplacien".

1 module divergf_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE divergf(klevel, x, y, div)
8
9 ! From libf/dyn3d/divergf.F, version 1.1.1.1 2004/05/19 12:53:05
10
11 ! P. Le Van
12 ! Calcule la divergence à tous les niveaux d'un vecteur de
13 ! composantes x et y. x et y sont des composantes covariantes.
14
15 USE dimens_m, ONLY: iim
16 USE paramet_m, ONLY: iip1, iip2, ip1jm, ip1jmi1, ip1jmp1, jjp1
17 USE comgeom, ONLY: apoln, apols, cuvsurcv, cvusurcu, unsaire
18 USE filtreg_m, ONLY: filtreg
19
20 INTEGER, intent(in):: klevel
21 REAL, intent(in):: x(ip1jmp1, klevel), y(ip1jm, klevel)
22 real, intent(out):: div(ip1jmp1, klevel) ! in (unit of x, y) m-2
23
24 ! Variables locales :
25
26 INTEGER l, ij
27 REAL aiy1(iim) , aiy2(iim)
28 REAL sumypn, sumyps
29
30 !------------------------------------------------------------
31
32 DO l = 1, klevel
33 DO ij = iip2, ip1jm - 1
34 div(ij + 1, l) = cvusurcu(ij+1) * x(ij+1, l) &
35 - cvusurcu(ij) * x(ij , l) + cuvsurcv(ij-iim) * y(ij-iim, l) &
36 - cuvsurcv(ij+1) * y(ij+1, l)
37 ENDDO
38
39 DO ij = iip2, ip1jm, iip1
40 div(ij, l) = div(ij + iim, l)
41 ENDDO
42
43 ! Calcul aux pôles
44
45 DO ij = 1, iim
46 aiy1(ij) = cuvsurcv(ij) * y(ij , l)
47 aiy2(ij) = cuvsurcv(ij+ ip1jmi1) * y(ij+ ip1jmi1, l)
48 ENDDO
49 sumypn = SUM(aiy1) / apoln
50 sumyps = SUM(aiy2) / apols
51
52 DO ij = 1, iip1
53 div(ij , l) = - sumypn
54 div(ij + ip1jm, l) = sumyps
55 ENDDO
56 end DO
57
58 CALL filtreg(div, jjp1, klevel, 2, 2, .TRUE., 1)
59
60 DO l = 1, klevel
61 DO ij = iip2, ip1jm
62 div(ij, l) = div(ij, l) * unsaire(ij)
63 ENDDO
64 ENDDO
65
66 END SUBROUTINE divergf
67
68 end module divergf_m

  ViewVC Help
Powered by ViewVC 1.1.21