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

    r5104 r5105  
    22! $Header$
    33
    4       SUBROUTINE gr_u_scal(nx,x_u,x_scal)
    5 c%W%    %G%
    6 c=======================================================================
    7 c
    8 c   Author:    Frederic Hourdin      original: 11/11/92
    9 c   -------
    10 c
    11 c   Subject:
    12 c   ------
    13 c
    14 c   Method:
    15 c   --------
    16 c
    17 c   Interface:
    18 c   ----------
    19 c
    20 c      Input:
    21 c      ------
    22 c
    23 c      Output:
    24 c      -------
    25 c
    26 c=======================================================================
    27       IMPLICIT NONE
    28 c-----------------------------------------------------------------------
    29 c   Declararations:
    30 c   ---------------
     4SUBROUTINE gr_u_scal(nx,x_u,x_scal)
     5  !%W%    %G%
     6  !=======================================================================
     7  !
     8  !   Author:    Frederic Hourdin      original: 11/11/92
     9  !   -------
     10  !
     11  !   Subject:
     12  !   ------
     13  !
     14  !   Method:
     15  !   --------
     16  !
     17  !   Interface:
     18  !   ----------
     19  !
     20  !  Input:
     21  !  ------
     22  !
     23  !  Output:
     24  !  -------
     25  !
     26  !=======================================================================
     27  IMPLICIT NONE
     28  !-----------------------------------------------------------------------
     29  !   Declararations:
     30  !   ---------------
    3131
    32       INCLUDE "dimensions.h"
    33       INCLUDE "paramet.h"
    34       INCLUDE "comgeom.h"
     32  INCLUDE "dimensions.h"
     33  INCLUDE "paramet.h"
     34  INCLUDE "comgeom.h"
    3535
    36 c   Arguments:
    37 c   ----------
     36  !   Arguments:
     37  !   ----------
    3838
    39       INTEGER nx
    40       REAL x_u(ip1jmp1,nx),x_scal(ip1jmp1,nx)
     39  INTEGER :: nx
     40  REAL :: x_u(ip1jmp1,nx),x_scal(ip1jmp1,nx)
    4141
    42 c   Local:
    43 c   ------
     42  !   Local:
     43  !   ------
    4444
    45       INTEGER l,ij
     45  INTEGER :: l,ij
    4646
    47 c-----------------------------------------------------------------------
     47  !-----------------------------------------------------------------------
    4848
    49       DO l=1,nx
    50          DO ij=ip1jmp1,2,-1
    51             x_scal(ij,l)=
    52      s      (aireu(ij)*x_u(ij,l)+aireu(ij-1)*x_u(ij-1,l))
    53      s      /(aireu(ij)+aireu(ij-1))
    54          ENDDO
    55       ENDDO
     49  DO l=1,nx
     50     DO ij=ip1jmp1,2,-1
     51        x_scal(ij,l)= &
     52              (aireu(ij)*x_u(ij,l)+aireu(ij-1)*x_u(ij-1,l)) &
     53              /(aireu(ij)+aireu(ij-1))
     54     ENDDO
     55  ENDDO
    5656
    57       CALL SCOPY(nx*jjp1,x_scal(iip1,1),iip1,x_scal(1,1),iip1)
     57  CALL SCOPY(nx*jjp1,x_scal(iip1,1),iip1,x_scal(1,1),iip1)
    5858
    59       RETURN
    60       END
     59  RETURN
     60END SUBROUTINE gr_u_scal
Note: See TracChangeset for help on using the changeset viewer.