Ignore:
Timestamp:
Jul 23, 2024, 7:14:34 PM (3 months ago)
Author:
abarral
Message:

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/rotatf.f90

    r5104 r5105  
    22! $Header$
    33
    4       SUBROUTINE rotatf (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    Only difference with rotat: CALL to filtreg.
    12 c********************************************************************
    13 c   klevel, x  et y   sont des arguments d'entree pour le s-prog
    14 c        rot          est  un argument  de sortie pour le s-prog
    15 c
    16       IMPLICIT NONE
    17 c
    18       INCLUDE "dimensions.h"
    19       INCLUDE "paramet.h"
    20       INCLUDE "comgeom.h"
    21 c
    22 c   .....  variables en arguments  ......
    23 c
    24       INTEGER klevel
    25       REAL rot( ip1jm,klevel )
    26       REAL x( ip1jmp1,klevel ), y( ip1jm,klevel )
    27 c
    28 c  ...   variables  locales  ...
    29 c
    30       INTEGER l, ij
    31 c
    32 c
    33       DO  l = 1,klevel
    34 c
    35         DO   ij = 1, ip1jm - 1
    36          rot( ij,l )  =    y( ij+1 , l )  -  y( ij,l )   +
    37      *                   x(ij +iip1, l )  -  x( ij,l ) 
    38         ENDDO
    39 c
    40 c    .... correction pour rot( iip1,j,l)  ....
    41 c    ....   rot(iip1,j,l)= rot(1,j,l) ...
    42 CDIR$ IVDEP
    43         DO  ij = iip1, ip1jm, iip1
    44          rot( ij,l ) = rot( ij -iim,l )
    45         ENDDO
    46 c
    47       END DO
     4SUBROUTINE rotatf (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  ! Only difference with rotat: CALL to filtreg.
     12  !********************************************************************
     13  !   klevel, x  et y   sont des arguments d'entree pour le s-prog
     14  !        rot          est  un argument  de sortie pour le s-prog
     15  !
     16  IMPLICIT NONE
     17  !
     18  INCLUDE "dimensions.h"
     19  INCLUDE "paramet.h"
     20  INCLUDE "comgeom.h"
     21  !
     22  !   .....  variables en arguments  ......
     23  !
     24  INTEGER :: klevel
     25  REAL :: rot( ip1jm,klevel )
     26  REAL :: x( ip1jmp1,klevel ), y( ip1jm,klevel )
     27  !
     28  !  ...   variables  locales  ...
     29  !
     30  INTEGER :: l, ij
     31  !
     32  !
     33  DO  l = 1,klevel
     34  !
     35    DO   ij = 1, ip1jm - 1
     36     rot( ij,l )  =    y( ij+1 , l )  -  y( ij,l )   + &
     37           x(ij +iip1, l )  -  x( ij,l )
     38    ENDDO
     39  !
     40  !    .... correction pour rot( iip1,j,l)  ....
     41  !    ....   rot(iip1,j,l)= rot(1,j,l) ...
     42  !DIR$ IVDEP
     43    DO  ij = iip1, ip1jm, iip1
     44     rot( ij,l ) = rot( ij -iim,l )
     45    ENDDO
     46  !
     47  END DO
    4848
    49         CALL filtreg( rot, jjm, klevel, 2, 2, .FALSE., 1 )
    50      
    51         DO l = 1, klevel
    52           DO ij = 1, ip1jm
    53            rot(ij,l) = rot(ij,l) * unsairez(ij)
    54           ENDDO
    55         ENDDO
    56 c
    57 c
    58       RETURN
    59       END
     49    CALL filtreg( rot, jjm, klevel, 2, 2, .FALSE., 1 )
     50
     51    DO l = 1, klevel
     52      DO ij = 1, ip1jm
     53       rot(ij,l) = rot(ij,l) * unsairez(ij)
     54      ENDDO
     55    ENDDO
     56  !
     57  !
     58  RETURN
     59END SUBROUTINE rotatf
Note: See TracChangeset for help on using the changeset viewer.