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

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE rotat (klevel, x, y, rot )
    5 c
    6 c     Auteur : P.Le Van
    7 c**************************************************************
    8 c.  calcule le rotationnel
    9 c    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   klevel, 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       INCLUDE "dimensions.h"
    18       INCLUDE "paramet.h"
    19       INCLUDE "comgeom.h"
    20 c
    21 c   .....  variables en arguments  ......
    22 c
    23       INTEGER klevel
    24       REAL rot( ip1jm,klevel )
    25       REAL x( ip1jmp1,klevel ), y( ip1jm,klevel )
    26 c
    27 c  ...   variables  locales  ...
    28 c
    29       INTEGER l, ij
    30 c
    31 c
    32       DO  10 l = 1,klevel
    33 c
    34         DO   ij = 1, ip1jm - 1
    35          rot( ij,l )  =    y( ij+1 , l )  -  y( ij,l )   +
    36      *                   x(ij +iip1, l )  -  x( ij,l ) 
    37         ENDDO
    38 c
    39 c    .... correction pour rot( iip1,j,l)  ....
    40 c    ....   rot(iip1,j,l)= rot(1,j,l) ...
    41 CDIR$ IVDEP
    42         DO  ij = iip1, ip1jm, iip1
    43          rot( ij,l ) = rot( ij -iim,l )
    44         ENDDO
    45 c
    46   10  CONTINUE
     4SUBROUTINE rotat (klevel, x, y, rot )
     5  !
     6  ! Auteur : P.Le Van
     7  !**************************************************************
     8  !.  calcule le rotationnel
     9  ! a tous les niveaux d'1 vecteur de comp. x et y ..
     10  !   x  et  y etant des composantes  covariantes  ...
     11  !********************************************************************
     12  !   klevel, 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  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
     19  INCLUDE "comgeom.h"
     20  !
     21  !   .....  variables en arguments  ......
     22  !
     23  INTEGER :: klevel
     24  REAL :: rot( ip1jm,klevel )
     25  REAL :: x( ip1jmp1,klevel ), y( ip1jm,klevel )
     26  !
     27  !  ...   variables  locales  ...
     28  !
     29  INTEGER :: l, ij
     30  !
     31  !
     32  DO l = 1,klevel
     33  !
     34    DO   ij = 1, ip1jm - 1
     35     rot( ij,l )  =    y( ij+1 , l )  -  y( ij,l )   + &
     36           x(ij +iip1, l )  -  x( ij,l )
     37    ENDDO
     38  !
     39  !    .... correction pour rot( iip1,j,l)  ....
     40  !    ....   rot(iip1,j,l)= rot(1,j,l) ...
     41  !DIR$ IVDEP
     42    DO  ij = iip1, ip1jm, iip1
     43     rot( ij,l ) = rot( ij -iim,l )
     44    ENDDO
     45  !
     46  END DO
    4747
    48 ccc        CALL filtreg( rot, jjm, klevel, 2, 2, .FALSE., 1 )
    49      
    50         DO l = 1, klevel
    51           DO ij = 1, ip1jm
    52            rot(ij,l) = rot(ij,l) * unsairez(ij)
    53           ENDDO
    54         ENDDO
    55 c
    56 c
    57       RETURN
    58       END
     48  !cc        CALL filtreg( rot, jjm, klevel, 2, 2, .FALSE., 1 )
     49
     50    DO l = 1, klevel
     51      DO ij = 1, ip1jm
     52       rot(ij,l) = rot(ij,l) * unsairez(ij)
     53      ENDDO
     54    ENDDO
     55  !
     56  !
     57  RETURN
     58END SUBROUTINE rotat
Note: See TracChangeset for help on using the changeset viewer.