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

Put dimensions.h and paramet.h into modules

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massdair_loc.f90

    r5136 r5159  
    33  USE lmdz_comgeom
    44
    5   !
     5
    66  ! *********************************************************************
    77  !   ....  Calcule la masse d'air  dans chaque maille   ....
    88  ! *********************************************************************
    9   !
     9
    1010  !    Auteurs : P. Le Van , Fr. Hourdin  .
    1111  !   ..........
    12   !
     12
    1313  !  ..    p                      est  un argum. d'entree pour le s-pg ...
    1414  !  ..  masse                    est un  argum.de sortie pour le s-pg ...
    15   !
     15
    1616  !  ....  p est defini aux interfaces des llm couches   .....
    17   !
     17
     18USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     19  USE lmdz_paramet
    1820  IMPLICIT NONE
    1921  !
    20   INCLUDE "dimensions.h"
    21   INCLUDE "paramet.h"
    22   !
     22
     23
     24
    2325  !  .....   arguments  ....
    24   !
     26
    2527  REAL :: p(ijb_u:ije_u,llmp1), masse(ijb_u:ije_u,llm)
    2628
     
    3133  REAL :: massemoyn, massemoys
    3234
    33   !
    34   !
     35
     36
    3537  !   Methode pour calculer massebx et masseby .
    3638  !   ----------------------------------------
    37   !
     39
    3840  !    A chaque point scalaire P (i,j) est affecte 4 coefficients d'aires
    3941  !   alpha1(i,j)  calcule  au point ( i+1/4,j-1/4 )
     
    4143  !   alpha3(i,j)  calcule  au point ( i-1/4,j+1/4 )
    4244  !   alpha4(i,j)  calcule  au point ( i-1/4,j-1/4 )
    43   !
     45
    4446  !    Avec  alpha1(i,j) = aire(i+1/4,j-1/4)/ aire(i,j)
    45   !
     47
    4648  !    N.B .  Pour plus de details, voir s-pg  ...  iniconst ...
    47   !
    48   !
    49   !
     49
     50
     51
    5052  !   alpha4 .         . alpha1    . alpha4
    5153  !    (i,j)             (i,j)       (i+1,j)
    52   !
     54
    5355  !         P .        U .          . P
    5456  !       (i,j)       (i,j)         (i+1,j)
    55   !
     57
    5658  !   alpha3 .         . alpha2    .alpha3
    5759  !    (i,j)              (i,j)     (i+1,j)
    58   !
     60
    5961  !         V .        Z .          . V
    6062  !       (i,j)
    61   !
     63
    6264  !   alpha4 .         . alpha1    .alpha4
    6365  !   (i,j+1)            (i,j+1)   (i+1,j+1)
    64   !
     66
    6567  !         P .        U .          . P
    6668  !      (i,j+1)                    (i+1,j+1)
    67   !
    68   !
    69   !
     69
     70
     71
    7072  !                   On  a :
    71   !
     73
    7274  !    massebx(i,j) = masse(i  ,j) * ( alpha1(i  ,j) + alpha2(i,j))   +
    7375  !               masse(i+1,j) * ( alpha3(i+1,j) + alpha4(i+1,j) )
    7476  ! localise  au point  ... U (i,j) ...
    75   !
     77
    7678  !    masseby(i,j) = masse(i,j  ) * ( alpha2(i,j  ) + alpha3(i,j  )  +
    7779  !               masse(i,j+1) * ( alpha1(i,j+1) + alpha4(i,j+1)
    7880  ! localise  au point  ... V (i,j) ...
    79   !
    80   !
     81
     82
    8183  !=======================================================================
    8284
     
    9294!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    9395  DO   l = 1 , llm
    94   !
     96
    9597    DO    ij     = ijb, ije
    9698     masse(ij,l) = airesurg(ij) * ( p(ij,l) - p(ij,l+1) )
    9799    ENDDO
    98   !
     100
    99101    DO   ij = ijb, ije,iip1
    100102     masse(ij+ iim,l) = masse(ij,l)
    101103    ENDDO
    102   !
     104
    103105  !   DO    ij     = 1,  iim
    104106  !    masse(   ij   ,l) = masse(   ij   ,l) * aire(  ij    )
Note: See TracChangeset for help on using the changeset viewer.