source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/laplacien_rot_loc.f90 @ 5153

Last change on this file since 5153 was 5136, checked in by abarral, 8 weeks ago

Put comgeom.h, comgeom2.h into modules

  • 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
File size: 1.3 KB
Line 
1SUBROUTINE laplacien_rot_loc( klevel, rotin, rotout,ghx,ghy )
2  !
3  !    P. Le Van
4  !
5  !   ************************************************************
6  !    ...  calcul de  ( rotat x nxgrad )  du rotationnel rotin  .
7  !   ************************************************************
8  !
9  ! klevel et rotin  sont des arguments  d'entree pour le s-prog
10  !  rotout           est  un argument  de sortie pour le s-prog
11  !
12  USE parallel_lmdz
13  USE lmdz_filtreg_p
14  USE lmdz_comgeom
15
16  IMPLICIT NONE
17  !
18  INCLUDE "dimensions.h"
19  INCLUDE "paramet.h"
20
21  !
22  !   ..........    variables  en  arguments     .............
23  !
24  INTEGER :: klevel
25  REAL :: rotin(ijb_v:ije_v,klevel ), rotout( ijb_v:ije_v,klevel )
26  !
27  !   ..........    variables   locales       ................
28  !
29  REAL :: ghy(ijb_v:ije_v,klevel), ghx(ijb_u:ije_u,klevel)
30  !   ........................................................
31  !
32  !
33  INTEGER :: ijb,ije,jjb,jje
34
35  jjb=jj_begin-1
36  jje=jj_end+1
37
38  IF (pole_nord) jjb=jj_begin
39  IF (pole_sud) jje=jj_end-1
40
41  CALL  filtreg_p ( rotin ,jjb_v,jje_v,jjb,jje,jjm, &
42        klevel,2, 1, .FALSE., 1)
43
44  CALL   nxgrad_loc ( klevel, rotin,   ghx ,  ghy            )
45  CALL   rotatf_loc  ( klevel, ghx  ,   ghy , rotout         )
46  !
47
48END SUBROUTINE laplacien_rot_loc
Note: See TracBrowser for help on using the repository browser.