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

    r5158 r5159  
    66        , ucov    , vcov , ps, p ,pk , teta , q, ql)
    77  !======================================================================
    8   !
     8
    99  ! Purpose:
    1010  !    Calcul la difference d'enthalpie et de masse d'eau entre 2 appels,
     
    1414  !    Outil pour diagnostiquer la conservation de l'energie
    1515  !    et de la masse dans la dynamique.
    16   !
    17   !
     16
     17
    1818  !======================================================================
    1919  ! Arguments:
     
    3636  ! ql-------input-R- liquid watter (kg/kg)
    3737  ! aire-----input-R- mesh surafce (m2)
    38   !
     38
    3939  ! the following total value are computed by UNIT of earth surface
    40   !
     40
    4141  ! d_h_vcol--output-R- Heat flux (W/m2) define as the Enthalpy
    4242  !        change (J/m2) during one time step (dtime) for the whole
     
    4747  ! d_ql------output-R- same, for the liquid watter only (kg/m2/s)
    4848  ! d_ec------output-R- Cinetic Energy Budget (W/m2) for vertical air column
    49   !
    50   !
     49
     50
    5151  ! J.L. Dufresne, July 2002
    5252  !======================================================================
     
    5656  USE lmdz_comgeom
    5757
     58USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     59  USE lmdz_paramet
    5860  IMPLICIT NONE
    5961  !
    60   INCLUDE "dimensions.h"
    61   INCLUDE "paramet.h"
     62
     63
    6264
    6365  ! Ehouarn: for now set these parameters to what is in Earth physics...
     
    7375  REAL,PARAMETER :: RLVTT=2.5008E+6
    7476
    75   !
     77
    7678  INTEGER :: imjmp1
    7779  PARAMETER( imjmp1=iim*jjp1)
     
    9193  ! Output variables
    9294  REAL :: d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec
    93   !
     95
    9496  ! Local variables
    95   !
     97
    9698  REAL :: h_vcol_tot, h_dair_tot, h_qw_tot, h_ql_tot &
    9799        , h_qs_tot, qw_tot, ql_tot, qs_tot , ec_tot
     
    106108  ! qs_tot------  total mass of solid watter (kg/m2)
    107109  ! ec_tot------  total cinetic energy (kg/m2)
    108   !
     110
    109111  REAL :: masse(ip1jmp1,llm)                ! masse d'air
    110112  REAL :: vcont(ip1jm,llm),ucont(ip1jmp1,llm)
     
    129131  REAL :: zh_dair_col(imjmp1)
    130132  REAL :: zh_qw_col(imjmp1), zh_ql_col(imjmp1), zh_qs_col(imjmp1)
    131   !
     133
    132134  REAL :: d_h_dair, d_h_qw, d_h_ql, d_h_qs
    133   !
     135
    134136  REAL :: airetot, zcpvap, zcwat, zcice
    135   !
     137
    136138  INTEGER :: i, k, jj, ij , l ,ip1jjm1
    137   !
     139
    138140  INTEGER :: ndiag     ! max number of diagnostic in parallel
    139141  PARAMETER (ndiag=10)
     
    141143  save pas
    142144  data pas/ndiag*0/
    143   !
     145
    144146  REAL :: h_vcol_pre(ndiag), h_dair_pre(ndiag), h_qw_pre(ndiag) &
    145147        , h_ql_pre(ndiag), h_qs_pre(ndiag), qw_pre(ndiag) &
     
    157159  CALL massdair( p, masse )
    158160  !======================================================================
    159   !
    160   !
     161
     162
    161163  PRINT*,'MAIS POURQUOI DONC DIAGEDYN NE MARCHE PAS ?'
    162164  RETURN
     
    187189    ENDDO
    188190  ENDDO
    189   !
     191
    190192  ! Reset variables
    191193  DO i = 1, imjmp1
     
    199201    zh_qs_col(i) = 0.
    200202  ENDDO
    201   !
     203
    202204  zcpvap=RCPV
    203205  zcwat=RCW
    204206  zcice=RCS
    205   !
     207
    206208  ! Compute vertical sum for each atmospheric column
    207209  ! ================================================
     
    230232    END DO
    231233  ENDDO
    232   !
     234
    233235  ! Mean over the planete surface
    234236  ! =============================
     
    243245  h_qs_tot = 0.
    244246  airetot=0.
    245   !
     247
    246248  DO i=1,imjmp1
    247249    qw_tot = qw_tot + zqw_col(i)
     
    255257    airetot=airetot+zaire(i)
    256258  END DO
    257   !
     259
    258260  qw_tot = qw_tot/airetot
    259261  ql_tot = ql_tot/airetot
     
    264266  h_ql_tot = h_ql_tot/airetot
    265267  h_qs_tot = h_qs_tot/airetot
    266   !
     268
    267269  h_vcol_tot = h_dair_tot+h_qw_tot+h_ql_tot+h_qs_tot
    268   !
     270
    269271  ! Compute the change of the atmospheric state compare to the one
    270272  ! stored in "idiag2", and convert it in flux. THis computation
     
    272274  ! for "idiag"
    273275  ! ===================================
    274   !
     276
    275277  IF ( (idiag2>0) .AND. (pas(idiag2) /= 0) ) THEN
    276278    d_h_vcol  = (h_vcol_tot - h_vcol_pre(idiag2) )/dtime
     
    296298    d_qt     = 0.
    297299  ENDIF
    298   !
     300
    299301  IF (iprt>=2) THEN
    300302    WRITE(6,9000) tit,pas(idiag),d_qt,d_qw,d_ql,d_qs
     
    310312 9004   format('Dyn3d. Total Energy Budget (W/m2) ',A15,1i6,10(F8.2))
    311313  END IF
    312   !
     314
    313315  ! Store the new atmospheric state in "idiag"
    314   !
     316
    315317  pas(idiag)=pas(idiag)+1
    316318  h_vcol_pre(idiag)  = h_vcol_tot
     
    323325  qs_pre(idiag)     = qs_tot
    324326  ec_pre (idiag)    = ec_tot
    325   !
     327
    326328  ELSE
    327329    WRITE(lunout,*)'diagedyn: set to function with Earth parameters'
Note: See TracChangeset for help on using the changeset viewer.