Ignore:
Timestamp:
Jul 23, 2024, 7:14:34 PM (8 weeks 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/nxgrad_gam.f90

    r5104 r5105  
    22! $Header$
    33
    4       SUBROUTINE nxgrad_gam( 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       DO l = 1,klevel
    24 c
    25       DO ij = 2, ip1jm
    26       y( ij,l ) = (rot( ij,l ) - rot( ij-1,l )) * cvscuvgam( ij )
    27       END DO
    28 c
    29 c    ..... correction pour  y ( 1,j,l )  ......
    30 c
    31 c    ....    y(1,j,l)= y(iip1,j,l) ....
    32 CDIR$ IVDEP
    33       DO ij = 1, ip1jm, iip1
    34       y( ij,l ) = y( ij +iim,l )
    35       END DO
    36 c
    37       DO ij = iip2,ip1jm
    38       x( ij,l ) = (rot( ij,l ) - rot( ij -iip1,l )) * cuscvugam( ij )
    39       END DO
    40       DO ij = 1,iip1
    41       x(    ij    ,l ) = 0.
    42       x( ij +ip1jm,l ) = 0.
    43       END DO
    44 c
    45       END DO
    46       RETURN
    47       END
     4SUBROUTINE nxgrad_gam( 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  DO l = 1,klevel
     24  !
     25  DO ij = 2, ip1jm
     26  y( ij,l ) = (rot( ij,l ) - rot( ij-1,l )) * cvscuvgam( ij )
     27  END DO
     28  !
     29  !    ..... correction pour  y ( 1,j,l )  ......
     30  !
     31  !    ....    y(1,j,l)= y(iip1,j,l) ....
     32  !DIR$ IVDEP
     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 )) * cuscvugam( ij )
     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 nxgrad_gam
Note: See TracChangeset for help on using the changeset viewer.