Ignore:
Timestamp:
Aug 2, 2024, 9:58:25 PM (7 weeks ago)
Author:
abarral
Message:

Put dimensions.h and paramet.h into modules

File:
1 edited

Legend:

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

    r5105 r5159  
    33
    44SUBROUTINE  grad(klevel, pg,pgx,pgy )
    5   !
     5
    66  !  P. Le Van
    7   !
     7
    88  !    ******************************************************************
    99  ! .. calcul des composantes covariantes en x et y du gradient de g
    10   !
     10
    1111  !    ******************************************************************
    1212  !         pg        est un   argument  d'entree pour le s-prog
    1313  !   pgx  et  pgy    sont des arguments de sortie pour le s-prog
    14   !
     14
     15USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     16  USE lmdz_paramet
    1517  IMPLICIT NONE
    1618  !
    17   INCLUDE "dimensions.h"
    18   INCLUDE "paramet.h"
     19
     20
    1921  INTEGER :: klevel
    2022  REAL :: pg( ip1jmp1,klevel )
    2123  REAL :: pgx( ip1jmp1,klevel ) , pgy( ip1jm,klevel )
    2224  INTEGER :: l,ij
    23   !
    24   !
     25
     26
    2527  DO l = 1,klevel
    26   !
     28
    2729  DO ij = 1, ip1jmp1 - 1
    2830  pgx( ij,l ) = pg( ij +1,l ) - pg( ij,l )
    2931  END DO
    30   !
     32
    3133  !    .... correction pour  pgx(ip1,j,l)  ....
    3234  !    ...    pgx(iip1,j,l)= pgx(1,j,l)  ....
     
    3537  pgx( ij,l ) = pgx( ij -iim,l )
    3638  END DO
    37   !
     39
    3840  DO ij = 1,ip1jm
    3941  pgy( ij,l ) = pg( ij,l ) - pg( ij +iip1,l )
    4042  END DO
    41   !
     43
    4244  END DO
    4345  RETURN
Note: See TracChangeset for help on using the changeset viewer.