source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/laplacien.f90 @ 5118

Last change on this file since 5118 was 5106, checked in by abarral, 4 months ago

Turn coefils.h into lmdz_coefils.f90
Put filtreg.F90 inside lmdz_filtreg.F90
Turn mod_filtreg_p.F90 into lmdz_filtreg_p.F90
Delete obsolete parafilt.h*
(lint) remove spaces between routine name and args

  • 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  USE lmdz_filtreg, ONLY: filtreg
15  IMPLICIT NONE
16  !
17  INCLUDE "dimensions.h"
18  INCLUDE "paramet.h"
19  INCLUDE "comgeom.h"
20
21  !
22  !    .........      variables  en arguments   ..............
23  !
24  INTEGER :: klevel
25  REAL :: teta( ip1jmp1,klevel ), divgra( ip1jmp1,klevel )
26  !
27  !    ............     variables  locales      ..............
28  !
29  REAL :: ghy(ip1jm,llm), ghx(ip1jmp1,llm)
30  !    .......................................................
31
32
33  !
34  CALL SCOPY ( ip1jmp1 * klevel, teta, 1, divgra, 1 )
35
36  CALL filtreg( divgra,  jjp1, klevel,  2, 1, .TRUE., 1 )
37  CALL   grad ( klevel,divgra,   ghx , ghy              )
38  CALL  divergf ( klevel, ghx , ghy  , divgra           )
39
40  RETURN
41END SUBROUTINE laplacien
Note: See TracBrowser for help on using the repository browser.