source: LMDZ6/trunk/libf/dyn3d_common/laplacien.f90 @ 5248

Last change on this file since 5248 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.1 KB
Line 
1!
2! $Header$
3!
4SUBROUTINE laplacien ( klevel, teta, divgra )
5  !
6  ! P. Le Van
7  !
8  !   ************************************************************
9  !    ....     calcul de  (div( grad ))   de   teta  .....
10  !   ************************************************************
11  ! klevel et teta  sont des arguments  d'entree pour le s-prog
12  !  divgra     est  un argument  de sortie pour le s-prog
13  !
14  IMPLICIT NONE
15  !
16  INCLUDE "dimensions.h"
17  INCLUDE "paramet.h"
18  INCLUDE "comgeom.h"
19
20  !
21  !    .........      variables  en arguments   ..............
22  !
23  INTEGER :: klevel
24  REAL :: teta( ip1jmp1,klevel ), divgra( ip1jmp1,klevel )
25  !
26  !    ............     variables  locales      ..............
27  !
28  REAL :: ghy(ip1jm,llm), ghx(ip1jmp1,llm)
29  !    .......................................................
30
31
32  !
33  CALL SCOPY ( ip1jmp1 * klevel, teta, 1, divgra, 1 )
34
35  CALL filtreg( divgra,  jjp1, klevel,  2, 1, .TRUE., 1 )
36  CALL   grad ( klevel,divgra,   ghx , ghy              )
37  CALL  divergf ( klevel, ghx , ghy  , divgra           )
38
39  RETURN
40END SUBROUTINE laplacien
Note: See TracBrowser for help on using the repository browser.