source: LMDZ6/trunk/libf/dyn3d_common/divgrad2.f90

Last change on this file was 5246, checked in by abarral, 23 hours ago

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.9 KB
Line 
1!
2! $Header$
3!
4SUBROUTINE divgrad2 ( klevel, h, deltapres, lh, divgra )
5  !
6  ! P. Le Van
7  !
8  !   ***************************************************************
9  !
10  ! .....   calcul de  (div( grad ))   de (  pext * h ) .....
11  !   ****************************************************************
12  !   h ,klevel,lh et pext  sont des arguments  d'entree pour le s-prg
13  !     divgra     est  un argument  de sortie pour le s-prg
14  !
15  IMPLICIT NONE
16  !
17  INCLUDE "dimensions.h"
18  INCLUDE "paramet.h"
19  INCLUDE "comgeom2.h"
20  INCLUDE "comdissipn.h"
21
22  !    .......    variables en arguments   .......
23  !
24  INTEGER :: klevel
25  REAL :: h( ip1jmp1,klevel ), deltapres( ip1jmp1,klevel )
26  REAL :: divgra( ip1jmp1,klevel)
27  !
28  !    .......    variables  locales    ..........
29  !
30  REAL :: signe, nudivgrs, sqrtps( ip1jmp1,llm )
31  INTEGER :: l,ij,iter,lh
32  !    ...................................................................
33
34  !
35  signe    = (-1.)**lh
36  nudivgrs = signe * cdivh
37
38  CALL SCOPY ( ip1jmp1 * klevel, h, 1, divgra, 1 )
39
40  !
41  CALL laplacien( klevel, divgra, divgra )
42
43  DO l = 1, klevel
44   DO ij = 1, ip1jmp1
45    sqrtps( ij,l ) = SQRT( deltapres(ij,l) )
46   ENDDO
47  ENDDO
48  !
49  DO l = 1, klevel
50    DO ij = 1, ip1jmp1
51     divgra(ij,l) = divgra(ij,l) * sqrtps(ij,l)
52    ENDDO
53  ENDDO
54
55  !    ........    Iteration de l'operateur  laplacien_gam    ........
56  !
57  DO  iter = 1, lh - 2
58   CALL laplacien_gam ( klevel,cuvscvgam2,cvuscugam2,unsair_gam2, &
59         unsapolnga2, unsapolsga2,  divgra, divgra )
60  ENDDO
61  !
62  !    ...............................................................
63
64  DO l = 1, klevel
65    DO ij = 1, ip1jmp1
66      divgra(ij,l) = divgra(ij,l) * sqrtps(ij,l)
67    ENDDO
68  ENDDO
69  !
70  CALL laplacien ( klevel, divgra, divgra )
71  !
72  DO l  = 1,klevel
73  DO ij = 1,ip1jmp1
74  divgra(ij,l) =  nudivgrs * divgra(ij,l) / deltapres(ij,l)
75  ENDDO
76  ENDDO
77
78  RETURN
79END SUBROUTINE divgrad2
Note: See TracBrowser for help on using the repository browser.