/[lmdze]/trunk/dyn3d/Dissipation/divgrad2.f90
ViewVC logotype

Contents of /trunk/dyn3d/Dissipation/divgrad2.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 76 - (show annotations)
Fri Nov 15 18:45:49 2013 UTC (10 years, 6 months ago) by guez
File size: 1252 byte(s)
Moved everything out of libf.
1 module divgrad2_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE divgrad2(klevel, h, deltapres, lh, divgra, cdivh)
8
9 ! From LMDZ4/libf/dyn3d/divgrad2.F, version 1.1.1.1 2004/05/19 12:53:06
10 ! P. Le Van
11
12 ! Calcul de div(grad) de (pext * h)
13
14 USE comgeom, ONLY: cuvscvgam2, cvuscugam2, unsair_gam2, unsapolnga2, &
15 unsapolsga2
16 USE laplacien_m, ONLY: laplacien
17 USE paramet_m, ONLY: ip1jmp1
18
19 INTEGER, intent(in):: klevel
20 REAL, intent(in):: h(ip1jmp1, klevel), deltapres(ip1jmp1, klevel)
21 integer, intent(in):: lh
22 REAL, intent(out):: divgra(ip1jmp1, klevel)
23 real, intent(in):: cdivh
24
25 ! Variables locales
26 REAL sqrtps(ip1jmp1, klevel)
27 INTEGER iter
28
29 !-----------------------------------------------------------------
30
31 divgra = h
32 CALL laplacien(klevel, divgra)
33 sqrtps = SQRT(deltapres)
34 divgra = divgra * sqrtps
35
36 ! Itération de l'opérateur laplacien_gam
37 DO iter = 1, lh - 2
38 CALL laplacien_gam(klevel, cuvscvgam2, cvuscugam2, unsair_gam2, &
39 unsapolnga2, unsapolsga2, divgra, divgra)
40 ENDDO
41
42 divgra = divgra * sqrtps
43 CALL laplacien(klevel, divgra)
44 divgra = (-1.)**lh * cdivh * divgra / deltapres
45
46 END SUBROUTINE divgrad2
47
48 end module divgrad2_m

  ViewVC Help
Powered by ViewVC 1.1.21