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/rotatst.f90

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE rotatst (klevel,x, y, rot )
    5 c
    6 c  P. Le Van
    7 c
    8 c    *****************************************************************
    9 c    .. calcule le rotationnel a tous les niveaux d'1 vecteur de comp. x et y ..
    10 c         x  et  y etant des composantes  covariantes  .....
    11 c    *****************************************************************
    12 c        x  et y     sont des arguments d'entree pour le s-prog
    13 c        rot          est  un argument  de sortie pour le s-prog
    14 c
    15       IMPLICIT NONE
    16 c
    17       INTEGER klevel
    18       INCLUDE "dimensions.h"
    19       INCLUDE "paramet.h"
     4SUBROUTINE rotatst (klevel,x, y, rot )
     5  !
     6  !  P. Le Van
     7  !
     8  !    *****************************************************************
     9  ! .. calcule le rotationnel a tous les niveaux d'1 vecteur de comp. x et y ..
     10  !     x  et  y etant des composantes  covariantes  .....
     11  !    *****************************************************************
     12  !    x  et y     sont des arguments d'entree pour le s-prog
     13  !    rot          est  un argument  de sortie pour le s-prog
     14  !
     15  IMPLICIT NONE
     16  !
     17  INTEGER :: klevel
     18  INCLUDE "dimensions.h"
     19  INCLUDE "paramet.h"
    2020
    21       REAL rot( ip1jm,klevel )
    22       REAL x( ip1jmp1,klevel ), y( ip1jm,klevel )
    23       INTEGER l, ij
    24 c
    25 c
    26       DO 5 l = 1,klevel
    27 c
    28       DO 1 ij = 1, ip1jm - 1
    29       rot( ij,l )  =  (  y( ij+1 , l )  -  y( ij,l )   +
    30      *                 x(ij +iip1, l )  -  x( ij,l )  )
    31    1  CONTINUE
    32 c
    33 c    .... correction pour rot( iip1,j,l)  ....
    34 c
    35 c    ....   rot(iip1,j,l)= rot(1,j,l) ...
    36 CDIR$ IVDEP
    37       DO 2 ij = iip1, ip1jm, iip1
    38       rot( ij,l ) = rot( ij -iim,l )
    39    2  CONTINUE
    40 c
    41    5  CONTINUE
    42       RETURN
    43       END
     21  REAL :: rot( ip1jm,klevel )
     22  REAL :: x( ip1jmp1,klevel ), y( ip1jm,klevel )
     23  INTEGER :: l, ij
     24  !
     25  !
     26  DO l = 1,klevel
     27  !
     28  DO ij = 1, ip1jm - 1
     29  rot( ij,l )  =  (  y( ij+1 , l )  -  y( ij,l )   + &
     30        x(ij +iip1, l )  -  x( ij,l )  )
     31  END DO
     32  !
     33  !    .... correction pour rot( iip1,j,l)  ....
     34  !
     35  !    ....   rot(iip1,j,l)= rot(1,j,l) ...
     36  !DIR$ IVDEP
     37  DO ij = iip1, ip1jm, iip1
     38  rot( ij,l ) = rot( ij -iim,l )
     39  END DO
     40  !
     41  END DO
     42  RETURN
     43END SUBROUTINE rotatst
Note: See TracChangeset for help on using the changeset viewer.