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

Last change on this file since 5254 was 5246, checked in by abarral, 31 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
File size: 1.3 KB
RevLine 
[5246]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 mod_filtreg_p
14  IMPLICIT NONE
15  !
16  INCLUDE "dimensions.h"
17  INCLUDE "paramet.h"
18  INCLUDE "comgeom.h"
[1632]19
[5246]20  !
21  !   ..........    variables  en  arguments     .............
22  !
23  INTEGER :: klevel
24  REAL :: rotin(ijb_v:ije_v,klevel ), rotout( ijb_v:ije_v,klevel )
25  !
26  !   ..........    variables   locales       ................
27  !
28  REAL :: ghy(ijb_v:ije_v,klevel), ghx(ijb_u:ije_u,klevel)
29  !   ........................................................
30  !
31  !
32  INTEGER :: ijb,ije,jjb,jje
[1632]33
[5246]34  jjb=jj_begin-1
35  jje=jj_end+1
36
37  if (pole_nord) jjb=jj_begin
38  if (pole_sud) jje=jj_end-1
39
40  CALL  filtreg_p ( rotin ,jjb_v,jje_v,jjb,jje,jjm, &
41        klevel,2, 1, .FALSE., 1)
42
43  CALL   nxgrad_loc ( klevel, rotin,   ghx ,  ghy            )
44  CALL   rotatf_loc  ( klevel, ghx  ,   ghy , rotout         )
45  !
46  RETURN
47END SUBROUTINE laplacien_rot_loc
Note: See TracBrowser for help on using the repository browser.