source: LMDZ6/trunk/libf/dyn3dmem/laplacien_rot_loc.f90 @ 5281

Last change on this file since 5281 was 5281, checked in by abarral, 3 days ago

Turn 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.4 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 comgeom_mod_h
13  USE parallel_lmdz
14  USE mod_filtreg_p
15  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
16USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
17          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
18IMPLICIT NONE
19  !
20
21
22
23  !
24  !   ..........    variables  en  arguments     .............
25  !
26  INTEGER :: klevel
27  REAL :: rotin(ijb_v:ije_v,klevel ), rotout( ijb_v:ije_v,klevel )
28  !
29  !   ..........    variables   locales       ................
30  !
31  REAL :: ghy(ijb_v:ije_v,klevel), ghx(ijb_u:ije_u,klevel)
32  !   ........................................................
33  !
34  !
35  INTEGER :: ijb,ije,jjb,jje
36
37  jjb=jj_begin-1
38  jje=jj_end+1
39
40  if (pole_nord) jjb=jj_begin
41  if (pole_sud) jje=jj_end-1
42
43  CALL  filtreg_p ( rotin ,jjb_v,jje_v,jjb,jje,jjm, &
44        klevel,2, 1, .FALSE., 1)
45
46  CALL   nxgrad_loc ( klevel, rotin,   ghx ,  ghy            )
47  CALL   rotatf_loc  ( klevel, ghx  ,   ghy , rotout         )
48  !
49  RETURN
50END SUBROUTINE laplacien_rot_loc
Note: See TracBrowser for help on using the repository browser.