Ignore:
Timestamp:
Oct 25, 2024, 4:16:13 PM (28 hours ago)
Author:
abarral
Message:

Turn cvflag.h into a module

Location:
LMDZ6/trunk/libf/phylmd
Files:
5 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/cv30_routines.f90

    r5268 r5275  
    18161816    mp, rp, up, vp, trap, wt, water, evap, b & ! RomP-jyg
    18171817    , wdtraina, wdtrainm) ! 26/08/10  RomP-jyg
     1818  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     1819          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    18181820  IMPLICIT NONE
    1819 
    1820 
    18211821  include "cvthermo.h"
    18221822  include "cv30param.h"
    1823   include "cvflag.h"
    18241823
    18251824  ! inputs:
     
    21822181    tvp, iflag, precip, vprecip, ft, fr, fu, fv, ftra, upwd, dnwd, dnwd0, ma, &
    21832182    mike, tls, tps, qcondc, wd)
     2183  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     2184          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    21842185  IMPLICIT NONE
    21852186
    21862187  include "cvthermo.h"
    21872188  include "cv30param.h"
    2188   include "cvflag.h"
    21892189  include "conema3.h"
    21902190
     
    30823082
    30833083  ! fraction deau condensee dans les melanges convertie en precip : epm
    3084   ! et eau condensée précipitée dans masse d'air saturé : l_m*dM_m/dzdz.dzdz
     3084  ! et eau condens�e pr�cipit�e dans masse d'air satur� : l_m*dM_m/dzdz.dzdz
    30853085  DO j = 1, nam1
    30863086    DO k = 1, j - 1
     
    32773277
    32783278        ! On fait varier epmax en fn de la cape
    3279         ! Il faut donc recalculer ep, et hp qui a déjà été calculé et
    3280         ! qui en dépend
    3281         ! Toutes les autres variables fn de ep sont calculées plus bas.
     3279        ! Il faut donc recalculer ep, et hp qui a d�j� �t� calcul� et
     3280        ! qui en dpend
     3281        ! Toutes les autres variables fn de ep sont calcules plus bas.
    32823282
    32833283        INCLUDE "cvthermo.h"
  • LMDZ6/trunk/libf/phylmd/cv3_routines.f90

    r5268 r5275  
    77SUBROUTINE cv3_param(nd, k_upper, delt)
    88
     9  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     10          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    911  USE ioipsl_getin_p_mod, ONLY : getin_p
    1012  use mod_phys_lmdz_para
     
    3537
    3638  include "cv3param.h"
    37   include "cvflag.h"
    3839  include "conema3.h"
    3940
     
    183184SUBROUTINE cv3_incrcount(len, nd, delt, sig)
    184185
    185 IMPLICIT NONE
     186USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     187          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
     188  IMPLICIT NONE
    186189
    187190! =====================================================================
     
    190193
    191194  include "cv3param.h"
    192   include "cvflag.h"
    193195
    194196!inputs:
     
    603605SUBROUTINE cv3_undilute1(len, nd, t, qs, gz, plcl, p, icb, tnk, qnk, gznk, &
    604606                         tp, tvp, clw, icbs)
     607  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     608          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    605609  IMPLICIT NONE
    606610
     
    11011105
    11021106!JAM--------------------------------------------------------------------
    1103 ! Calcul de la quantité d'eau sous forme de glace
     1107! Calcul de la quantit d'eau sous forme de glace
    11041108! --------------------------------------------------------------------
    11051109  INTEGER nl, len
     
    11351139                         frac_a, frac_s, qpreca, qta)
    11361140  USE print_control_mod, ONLY: prt_level
     1141  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     1142          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    11371143  IMPLICIT NONE
    11381144
     
    11581164  include "cv3param.h"
    11591165  include "conema3.h"
    1160   include "cvflag.h"
    11611166  include "YOMCST2.h"
    11621167
     
    20452050                       pbase, p, ph, tv, buoy, &
    20462051                       sig, w0, cape, m, iflag)
     2052  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     2053          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    20472054  IMPLICIT NONE
    20482055
     
    22872294                      unk, vnk, hp, tv, tvp, ep, clw, m, sig, &
    22882295                      ment, qent, uent, vent, nent, sij, elij, ments, qents, traent)
     2296  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     2297          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    22892298  IMPLICIT NONE
    22902299
     
    22962305  include "cvthermo.h"
    22972306  include "cv3param.h"
    2298   include "cvflag.h"
    22992307
    23002308!inputs:
     
    27092717                     faci, b, sigd, &
    27102718                     wdtrainA, wdtrainS, wdtrainM)                                      ! RomP
     2719  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     2720          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    27112721  USE print_control_mod, ONLY: prt_level, lunout
    27122722  IMPLICIT NONE
    27132723
    2714 
    27152724  include "cvthermo.h"
    27162725  include "cv3param.h"
    2717   include "cvflag.h"
    27182726  include "nuage.h"
    27192727
     
    27822790
    27832791! =============================
    2784 ! --- INITIALIZE OUTPUT ARRAYS 
     2792! --- INITIALIZE OUTPUT ARRAYS
    27852793! =============================
    27862794!  (loops up to nl+1)
     
    28562864
    28572865!
    2858 ! Get adiabatic ascent mass flux 
     2866! Get adiabatic ascent mass flux
    28592867!
    28602868!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    29152923
    29162924
    2917     DO il = 1, ncum                                                   
    2918       IF (i<=inb(il) .AND. lwork(il)) THEN                           
    2919         wdtrain(il) = grav*ep(il, i)*m(il, i)*clw(il, i)           
     2925    DO il = 1, ncum
     2926      IF (i<=inb(il) .AND. lwork(il)) THEN
     2927        wdtrain(il) = grav*ep(il, i)*m(il, i)*clw(il, i)
    29202928        wdtrainS(il, i) = wdtrain(il)/grav                                            !   Ps   jyg
    29212929!!        wdtrainA(il, i) = wdtrain(il)/grav                                          !   Ps   RomP
    2922       END IF                                                         
    2923     END DO                                                           
     2930      END IF
     2931    END DO
    29242932
    29252933    IF (i>1) THEN
     
    30723080!!---end jyg---
    30733081
    3074 ! --------retour à la formulation originale d'Emanuel.
     3082! --------retour la formulation originale d'Emanuel.
    30753083        IF (cvflag_ice) THEN
    30763084
     
    30823090
    30833091!JAM  Attention: evap=sigt*E
    3084 !    Modification: evap devient l'évaporation en milieu de couche
    3085 !    car nécessaire dans cv3_yield
    3086 !    Du coup, il faut modifier pas mal d'équations...
     3092!    Modification: evap devient l'vaporation en milieu de couche
     3093!    car ncessaire dans cv3_yield
     3094!    Du coup, il faut modifier pas mal d'quations...
    30873095!    et l'expression de afac qui devient afac1
    30883096!    revap=sqrt((prec(i+1)+prec(i))/2)
     
    31033111!JYG    Dans sa formulation originale, Emanuel calcule l'evaporation par:
    31043112! c             evap(il,i)=sigt*afac*revap
    3105 ! ce qui n'est pas correct. Dans cv_routines, la formulation a été modifiee.
     3113! ce qui n'est pas correct. Dans cv_routines, la formulation a �t� modifiee.
    31063114! Ici,l'evaporation evap est simplement calculee par l'equation de
    31073115! conservation.
     
    31623170!           water(il,i)=water(il,i)+fondue(il,i)
    31633171!           ice(il,i)=ice(il,i)-fondue(il,i)
    3164            
     3172
    31653173!           if((water(il,i)+ice(il,i)).lt.1.e-30)then
    31663174!             faci(il,i)=0.
     
    34563464    USE print_control_mod, ONLY: lunout, prt_level
    34573465    USE add_phys_tend_mod, only : fl_cor_ebil
     3466    USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     3467          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    34583468
    34593469  IMPLICIT NONE
     
    34613471  include "cvthermo.h"
    34623472  include "cv3param.h"
    3463   include "cvflag.h"
    34643473  include "conema3.h"
    34653474
     
    35153524      REAL, DIMENSION (nloc, nd), INTENT (OUT)           :: qcondc                      ! cld
    35163525      REAL, DIMENSION (nloc, nd), INTENT (OUT)           :: qtc, sigt                   ! cld
    3517       REAL, DIMENSION (nloc, nd), INTENT (OUT)           :: detrain                     ! Louis : pour le calcul de Klein du terme de variance qui détraine dans lenvironnement
     3526      REAL, DIMENSION (nloc, nd), INTENT (OUT)           :: detrain                     ! Louis : pour le calcul de Klein du terme de variance qui détraine dans lenvironnement
    35183527      REAL, DIMENSION (nloc), INTENT (OUT)               :: wd                          ! gust
    35193528      REAL, DIMENSION (nloc), INTENT (OUT)               :: cbmf
     
    48974906        IF  (k<=inb(il) .AND. i<=inb(il) .AND. iflag(il)<=1) THEN   ! cld
    48984907          sument(il) =sument(il) + abs(ment(il,k,i))
    4899           detrain(il,i) = detrain(il,i) + abs(ment(il,k,i))*(qdet(il,k,i) - rr(il,i))*(qdet(il,k,i) - rr(il,i)) ! Louis terme de détrainement dans le bilan de variance
     4908          detrain(il,i) = detrain(il,i) + abs(ment(il,k,i))*(qdet(il,k,i) - rr(il,i))*(qdet(il,k,i) - rr(il,i)) ! Louis terme de détrainement dans le bilan de variance
    49004909        ENDIF
    49014910      ENDDO     ! il
    49024911    ENDDO       ! k
    49034912
    4904 ! 14/01/15 AJ delta n'a rien à faire là...                                                 
     4913! 14/01/15 AJ delta n'a rien � faire l�...                                                 
    49054914    DO il = 1, ncum                                                  ! cld
    49064915!!      IF (wa(il,i)>0.0 .AND. iflag(il)<=1) &                         ! cld
     
    49184927
    49194928! IM cf. FH
    4920 ! 14/01/15 AJ ne correspond pas à ce qui a été codé par JYG et SB           
     4929! 14/01/15 AJ ne correspond pas � ce qui a �t� cod� par JYG et SB           
    49214930                                                         
    49224931      IF (iflag_clw==0) THEN                                         ! cld
     
    49524961                      ep, Vprecip, elij, clw, epmlmMm, eplaMm, &
    49534962                      icb, inb)
     4963  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     4964          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    49544965  IMPLICIT NONE
    49554966
     
    49915002
    49925003! fraction deau condensee dans les melanges convertie en precip : epm
    4993 ! et eau condensée précipitée dans masse d'air saturé : l_m*dM_m/dzdz.dzdz
     5004! et eau condens�e pr�cipit�e dans masse d'air satur� : l_m*dM_m/dzdz.dzdz
    49945005  DO j = 1, nl
    49955006    DO k = 1, nl
    49965007      DO i = 1, ncum
    4997         IF (k>=icb(i) .AND. k<=inb(i) .AND. & 
     5008        IF (k>=icb(i) .AND. k<=inb(i) .AND. &
    49985009!!jyg              j.ge.k.and.j.le.inb(i)) then
    49995010!!jyg             epm(i,j,k)=1.-(1.-ep(i,j))*clw(i,j)/elij(i,k,j)
     
    51385149                 , pbase, p, ph, tv, buoy, sig, w0,iflag &
    51395150                 , epmax_diag)
     5151          USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     5152          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    51405153        implicit none
    51415154
    51425155        ! On fait varier epmax en fn de la cape
    5143         ! Il faut donc recalculer ep, et hp qui a déjà été calculé et
    5144         ! qui en dépend
    5145         ! Toutes les autres variables fn de ep sont calculées plus bas.
     5156        ! Il faut donc recalculer ep, et hp qui a d�j� �t� calcul� et
     5157        ! qui en dpend
     5158        ! Toutes les autres variables fn de ep sont calcules plus bas.
    51465159
    51475160  include "cvthermo.h"
    5148   include "cv3param.h" 
     5161  include "cv3param.h"
    51495162  include "conema3.h"
    5150   include "cvflag.h"
    51515163
    51525164! inputs:
     
    51785190
    51795191        ! il faut calculer la cape: on fait un calcule simple car tant qu'on ne
    5180         ! connait pas ep, on ne connait pas les mélanges, ddfts etc... qui sont
     5192        ! connait pas ep, on ne connait pas les mlanges, ddfts etc... qui sont
    51815193        ! necessaires au calcul de la cape dans la nouvelle physique
    51825194       
  • LMDZ6/trunk/libf/phylmd/cv3p2_closure.f90

    r5274 r5275  
    1818  ! **************************************************************
    1919
     20  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     21          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    2022  USE print_control_mod, ONLY: prt_level, lunout
    2123  USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
     
    3537  include "cvthermo.h"
    3638  include "cv3param.h"
    37   include "cvflag.h"
    3839  include "YOMCST2.h"
    3940
  • LMDZ6/trunk/libf/phylmd/cv3p_mixing.f90

    r5268 r5275  
    1313! **************************************************************
    1414
     15  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     16          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    1517  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
    1618  USE ioipsl_getin_p_mod, ONLY: getin_p
     
    2224  include "cv3param.h"
    2325  include "YOMCST2.h"
    24   include "cvflag.h"
    2526
    2627!inputs:
  • LMDZ6/trunk/libf/phylmd/cv_driver.F90

    r5274 r5275  
    682682SUBROUTINE cv_flag(iflag_ice_thermo)
    683683
     684  USE cvflag_mod_h, ONLY: icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     685          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
    684686  USE ioipsl_getin_p_mod, ONLY : getin_p
    685687
     
    690692  INTEGER iflag_ice_thermo
    691693
    692   include "cvflag.h"
    693694
    694695  ! -- si .TRUE., on rend la gravite plus explicite et eventuellement
  • LMDZ6/trunk/libf/phylmd/cvflag_mod_h.f90

    r5274 r5275  
    1 !
    2 ! $Header$
    3 !
    4       logical cvflag_grav
    5       logical cvflag_ice
    6       logical ok_optim_yield
    7       logical ok_entrain
    8       logical ok_homo_tend
    9       logical ok_convstop
    10       logical ok_intermittent
    11       logical cvflag_prec_eject
    12       logical qsat_depends_on_qt
    13       logical adiab_ascent_mass_flux_depends_on_ejectliq
    14       logical keepbug_ice_frac
    15       integer icvflag_Tpa
     1! Replaces cvflag.h
    162
    17       COMMON /cvflag/ icvflag_Tpa, &
    18                       cvflag_grav, cvflag_ice, &
    19                       ok_optim_yield, &
    20                       ok_entrain, &
    21                       ok_homo_tend, &
    22                       ok_convstop, ok_intermittent, &
    23                       cvflag_prec_eject, &
    24                       qsat_depends_on_qt, &
    25                       adiab_ascent_mass_flux_depends_on_ejectliq, &
    26                       keepbug_ice_frac
    27 !$OMP THREADPRIVATE(/cvflag/)
     3MODULE cvflag_mod_h
     4  IMPLICIT NONE; PRIVATE
     5  PUBLIC  icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     6          ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac
     7
     8  LOGICAL cvflag_grav
     9  LOGICAL cvflag_ice
     10  LOGICAL ok_optim_yield
     11  LOGICAL ok_entrain
     12  LOGICAL ok_homo_tend
     13  LOGICAL ok_convstop
     14  LOGICAL ok_intermittent
     15  LOGICAL cvflag_prec_eject
     16  LOGICAL qsat_depends_on_qt
     17  LOGICAL adiab_ascent_mass_flux_depends_on_ejectliq
     18  LOGICAL keepbug_ice_frac
     19  INTEGER icvflag_Tpa
     20
     21  !$OMP THREADPRIVATE(icvflag_Tpa, cvflag_grav, cvflag_ice, ok_optim_yield, ok_entrain, ok_homo_tend, &
     22  !$OMP      ok_convstop, ok_intermittent, cvflag_prec_eject, qsat_depends_on_qt, adiab_ascent_mass_flux_depends_on_ejectliq, keepbug_ice_frac)
     23END MODULE cvflag_mod_h
Note: See TracChangeset for help on using the changeset viewer.