Ignore:
Timestamp:
Oct 21, 2024, 2:58:45 PM (22 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/nxgrad.f90

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