Ignore:
Timestamp:
Oct 21, 2024, 2:58:45 PM (23 hours ago)
Author:
abarral
Message:

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d_common/laplacien_rot.f90

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE laplacien_rot ( klevel, rotin, rotout,ghx,ghy )
    5 c
    6 c    P. Le Van
    7 c
    8 c   ************************************************************
    9 c    ...  calcul de  ( rotat x nxgrad )  du rotationnel rotin  .
    10 c   ************************************************************
    11 c
    12 c    klevel et rotin  sont des arguments  d'entree pour le s-prog
    13 c      rotout           est  un argument  de sortie pour le s-prog
    14 c
    15       IMPLICIT NONE
    16 c
    17       INCLUDE "dimensions.h"
    18       INCLUDE "paramet.h"
    19       INCLUDE "comgeom.h"
     4SUBROUTINE laplacien_rot ( klevel, rotin, rotout,ghx,ghy )
     5  !
     6  !    P. Le Van
     7  !
     8  !   ************************************************************
     9  !    ...  calcul de  ( rotat x nxgrad )  du rotationnel rotin  .
     10  !   ************************************************************
     11  !
     12  ! klevel et rotin  sont des arguments  d'entree pour le s-prog
     13  !  rotout           est  un argument  de sortie pour le s-prog
     14  !
     15  IMPLICIT NONE
     16  !
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
     19  INCLUDE "comgeom.h"
    2020
    21 c
    22 c   ..........    variables  en  arguments     .............
    23 c
    24       INTEGER klevel
    25       REAL rotin( ip1jm,klevel ), rotout( ip1jm,klevel )
    26 c
    27 c   ..........    variables   locales       ................
    28 c
    29       REAL ghy(ip1jm,klevel), ghx(ip1jmp1,klevel)
    30 c   ........................................................
    31 c
    32 c
    33       CALL  filtreg ( rotin ,   jjm, klevel,   2, 1, .FALSE., 1 )
     21  !
     22  !   ..........    variables  en  arguments     .............
     23  !
     24  INTEGER :: klevel
     25  REAL :: rotin( ip1jm,klevel ), rotout( ip1jm,klevel )
     26  !
     27  !   ..........    variables   locales       ................
     28  !
     29  REAL :: ghy(ip1jm,klevel), ghx(ip1jmp1,klevel)
     30  !   ........................................................
     31  !
     32  !
     33  CALL  filtreg ( rotin ,   jjm, klevel,   2, 1, .FALSE., 1 )
    3434
    35       CALL   nxgrad ( klevel, rotin,   ghx ,  ghy               )
    36       CALL   rotatf  ( klevel, ghx  ,   ghy , rotout             )
    37 c
    38       RETURN
    39       END
     35  CALL   nxgrad ( klevel, rotin,   ghx ,  ghy               )
     36  CALL   rotatf  ( klevel, ghx  ,   ghy , rotout             )
     37  !
     38  RETURN
     39END SUBROUTINE laplacien_rot
Note: See TracChangeset for help on using the changeset viewer.