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

    r5136 r5159  
    55  USE lmdz_comgeom
    66
     7  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     8  USE lmdz_paramet
    79  IMPLICIT NONE
    810
    911  !=======================================================================
    10   !
     12
    1113  !   Auteur:  P. Le Van
    1214  !   -------
    13   !
     15
    1416  !   Objet:
    1517  !   ------
    16   !
     18
    1719  ! **********************************************************************
    1820  ! calcul des moyennes en x et en y de (pression au sol*aire variable) ..
    1921  ! **********************************************************************
    20   !
     22
    2123  !     ps          est un  argum. d'entree  pour le s-pg ..
    2224  !     psexbarxy   est un  argum. de sortie pour le s-pg ..
    23   !
     25
    2426  !   Methode:
    2527  !   --------
    26   !
     28
    2729  !    A chaque point scalaire P (i,j) est affecte 4 coefficients d'aires
    2830  !   alpha1(i,j)  calcule  au point ( i+1/4,j-1/4 )
     
    3032  !   alpha3(i,j)  calcule  au point ( i-1/4,j+1/4 )
    3133  !   alpha4(i,j)  calcule  au point ( i-1/4,j-1/4 )
    32   !
     34
    3335  !    Avec  alpha1(i,j) = aire(i+1/4,j-1/4)/ aire(i,j)
    34   !
     36
    3537  !    N.B .  Pour plus de details, voir s-pg  ...  iniconst ...
    36   !
    37   !
    38   !
     38
     39
     40
    3941  !   alpha4 .         . alpha1    . alpha4
    4042  !    (i,j)             (i,j)       (i+1,j)
    41   !
     43
    4244  !         P .        U .          . P
    4345  !       (i,j)       (i,j)         (i+1,j)
    44   !
     46
    4547  !   alpha3 .         . alpha2    .alpha3
    4648  !    (i,j)              (i,j)     (i+1,j)
    47   !
     49
    4850  !         V .        Z .          . V
    4951  !       (i,j)
    50   !
     52
    5153  !   alpha4 .         . alpha1    .alpha4
    5254  !   (i,j+1)            (i,j+1)   (i+1,j+1)
    53   !
     55
    5456  !         P .        U .          . P
    5557  !      (i,j+1)                    (i+1,j+1)
    56   !
    57   !
    58   !
    59   !
     58
     59
     60
     61
    6062  !                   On  a :
    61   !
     63
    6264  !    pbarx(i,j) = Pext(i  ,j) * ( alpha1(i  ,j) + alpha2(i,j))      +
    6365  !             Pext(i+1,j) * ( alpha3(i+1,j) + alpha4(i+1,j) )
    6466  ! localise  au point  ... U (i,j) ...
    65   !
     67
    6668  !    pbary(i,j) = Pext(i,j  ) * ( alpha2(i,j  ) + alpha3(i,j  )     +
    6769  !             Pext(i,j+1) * ( alpha1(i,j+1) + alpha4(i,j+1)
    6870  ! localise  au point  ... V (i,j) ...
    69   !
     71
    7072  !  pbarxy(i,j)= Pext(i,j) *alpha2(i,j) + Pext(i+1,j) *alpha3(i+1,j) +
    7173  !           Pext(i,j+1)*alpha1(i,j+1)+ Pext(i+1,j+1)*alpha4(i+1,j+1)
    7274  ! localise  au point  ... Z (i,j) ...
    73   !
    74   !
    75   !
     75
     76
     77
    7678  !=======================================================================
    7779
    7880
    79   INCLUDE "dimensions.h"
    80   INCLUDE "paramet.h"
     81
     82
    8183
    8284  REAL :: ps( ip1jmp1 ), psexbarxy ( ip1jm ), pext( ip1jmp1 )
Note: See TracChangeset for help on using the changeset viewer.