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

    r5140 r5159  
    44SUBROUTINE diverg_gam(klevel,cuvscvgam,cvuscugam,unsairegam , &
    55        unsapolnga,unsapolsga,  x, y,  div )
    6   !
     6
    77  ! P. Le Van
    8   !
     8
    99  !  *********************************************************************
    1010  !  ... calcule la divergence a tous les niveaux d'1 vecteur de compos.
     
    1515  USE lmdz_comgeom
    1616
     17  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     18  USE lmdz_paramet
    1719  IMPLICIT NONE
    18   !
     20
    1921  !  x  et  y  sont des arguments  d'entree pour le s-prog
    2022  !    div      est  un argument  de sortie pour le s-prog
    2123  !
    22   INCLUDE "dimensions.h"
    23   INCLUDE "paramet.h"
    24   !
     24
     25
     26
    2527  !    ..........          variables en arguments    ...................
    26   !
     28
    2729  INTEGER :: klevel
    2830  REAL :: x( ip1jmp1,klevel ),y( ip1jm,klevel ),div( ip1jmp1,klevel )
    2931  REAL :: cuvscvgam(ip1jm),cvuscugam(ip1jmp1),unsairegam(ip1jmp1)
    3032  REAL :: unsapolnga,unsapolsga
    31   !
     33
    3234  !    ...............     variables  locales   .........................
    3335
     
    3739  !    ...................................................................
    3840
    39   !
     41
    4042  DO l = 1,klevel
    41   !
     43
    4244    DO  ij = iip2, ip1jm - 1
    4345     div( ij + 1, l )     = ( &
     
    4648           unsairegam( ij+1 )
    4749    ENDDO
    48   !
     50
    4951  ! ....  correction pour  div( 1,j,l)  ......
    5052  ! ....   div(1,j,l)= div(iip1,j,l) ....
    51   !
     53
    5254  !DIR$ IVDEP
    5355    DO  ij = iip2,ip1jm,iip1
    5456     div( ij,l ) = div( ij + iim,l )
    5557    ENDDO
    56   !
     58
    5759  ! ....  calcul  aux poles  .....
    58   !
     60
    5961    DO  ij  = 1,iim
    6062     aiy1(ij) =    cuvscvgam(    ij       ) * y(     ij     , l )
     
    6365    sumypn = SSUM ( iim,aiy1,1 ) * unsapolnga
    6466    sumyps = SSUM ( iim,aiy2,1 ) * unsapolsga
    65   !
     67
    6668    DO  ij = 1,iip1
    6769     div(     ij    , l ) = - sumypn
Note: See TracChangeset for help on using the changeset viewer.