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

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE nxgradst (klevel,rot, x, y )
    5 c
    6       IMPLICIT NONE
    7 c    Auteur :  P. Le Van
    8 c
    9 c   ********************************************************************
    10 c      calcul du gradient tourne de pi/2 du rotationnel du vect.v
    11 c   ********************************************************************
    12 c       rot          est un argument  d'entree pour le s-prog
    13 c       x  et y    sont des arguments de sortie pour le s-prog
    14 c
    15       INCLUDE "dimensions.h"
    16       INCLUDE "paramet.h"
    17       INCLUDE "comgeom.h"
     4SUBROUTINE nxgradst (klevel,rot, x, y )
     5  !
     6  IMPLICIT NONE
     7  ! Auteur :  P. Le Van
     8  !
     9  !   ********************************************************************
     10  !  calcul du gradient tourne de pi/2 du rotationnel du vect.v
     11  !   ********************************************************************
     12  !   rot          est un argument  d'entree pour le s-prog
     13  !   x  et y    sont des arguments de sortie pour le s-prog
     14  !
     15  INCLUDE "dimensions.h"
     16  INCLUDE "paramet.h"
     17  INCLUDE "comgeom.h"
    1818
    19       INTEGER klevel
    20       REAL rot( ip1jm,klevel ),x( ip1jmp1,klevel ),y(ip1jm,klevel )
    21       INTEGER l,ij
    22 c
    23       DO 10 l = 1,klevel
    24 c
    25       DO 1  ij = 2, ip1jm
    26       y(ij,l)=( rot(ij,l) - rot(ij-1,l))
    27    1  CONTINUE
    28 c
    29 c    ..... correction pour  y ( 1,j,l )  ......
    30 c
    31 c    ....    y(1,j,l)= y(iip1,j,l) ....
     19  INTEGER :: klevel
     20  REAL :: rot( ip1jm,klevel ),x( ip1jmp1,klevel ),y(ip1jm,klevel )
     21  INTEGER :: l,ij
     22  !
     23  DO l = 1,klevel
     24  !
     25  DO  ij = 2, ip1jm
     26  y(ij,l)=( rot(ij,l) - rot(ij-1,l))
     27  END DO
     28  !
     29  !    ..... correction pour  y ( 1,j,l )  ......
     30  !
     31  !    ....    y(1,j,l)= y(iip1,j,l) ....
    3232
    33       DO 2  ij = 1, ip1jm, iip1
    34       y( ij,l ) = y( ij +iim,l )
    35    2  CONTINUE
    36 c
    37       DO 4  ij = iip2,ip1jm
    38       x(ij,l)= rot(ij,l)-rot(ij-iip1,l)
    39    4  CONTINUE
    40       DO 6 ij = 1,iip1
    41       x(    ij    ,l ) = 0.
    42       x( ij +ip1jm,l ) = 0.
    43    6  CONTINUE
    44 c
    45   10  CONTINUE
    46       RETURN
    47       END
     33  DO  ij = 1, ip1jm, iip1
     34  y( ij,l ) = y( ij +iim,l )
     35  END DO
     36  !
     37  DO  ij = iip2,ip1jm
     38  x(ij,l)= rot(ij,l)-rot(ij-iip1,l)
     39  END DO
     40  DO ij = 1,iip1
     41  x(    ij    ,l ) = 0.
     42  x( ij +ip1jm,l ) = 0.
     43  END DO
     44  !
     45  END DO
     46  RETURN
     47END SUBROUTINE nxgradst
Note: See TracChangeset for help on using the changeset viewer.