Ignore:
Timestamp:
Jul 22, 2014, 6:33:56 PM (10 years ago)
Author:
lguez
Message:

Removed "on rentre dans guide_main" from guide_main in dyn3dpar, was
already commented out in the dyn3dmem version.

Keeping length of lines under 80 characters in physiq (for
readability). Removed wrong comments "ajout des tendances de la
diffusion turbulente". Replaced "con" by "convection" as an argument
of add_phys_tend.

Location:
LMDZ5/trunk/libf/phylmd
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/hgardfou.F90

    r1992 r2100  
    1313  include "iniprint.h"
    1414  REAL t(klon, klev), tsol(klon, nbsrf)
    15   CHARACTER *(*) text
     15  CHARACTER(len=*), intent(in):: text
    1616  CHARACTER (LEN=20) :: modname = 'hgardfou'
    17   CHARACTER (LEN=80) :: abort_message
    1817
    1918  INTEGER i, k, nsrf
     
    129128  END DO
    130129
    131   IF (.NOT. ok) THEN
    132     abort_message = 'hgardfou s arrete ' // text
    133     CALL abort_gcm(modname, abort_message, 1)
    134   END IF
     130  IF (.NOT. ok) CALL abort_gcm(modname, text, 1)
    135131
    136   RETURN
    137132END SUBROUTINE hgardfou
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2098 r2100  
    19291929     ntra = 1
    19301930
    1931      !=====================================================================================
    1932      !ajout pour la parametrisation des poches froides:
    1933      !calcul de t_wake et t_undi: si pas de poches froides, t_wake=t_undi=t_seri
     1931     !=========================================================================
     1932     !ajout pour la parametrisation des poches froides: calcul de
     1933     !t_wake et t_undi: si pas de poches froides, t_wake=t_undi=t_seri
    19341934     do k=1,klev
    19351935        do i=1,klon
     
    19521952     enddo
    19531953
    1954      !c--   Calcul de l'energie disponible ALE (J/kg) et de la puissance disponible ALP (W/m2)
    1955      !c--    pour le soulevement des particules dans le modele convectif
     1954     ! Calcul de l'energie disponible ALE (J/kg) et de la puissance
     1955     ! disponible ALP (W/m2) pour le soulevement des particules dans
     1956     ! le modele convectif
    19561957     !
    19571958     do i = 1,klon
     
    19811982        enddo
    19821983     endif
    1983      !combinaison avec ale et alp de couche limite: constantes si pas de couplage, valeurs calculees
    1984      !dans le thermique sinon
     1984     !combinaison avec ale et alp de couche limite: constantes si pas
     1985     !de couplage, valeurs calculees dans le thermique sinon
    19851986     if (iflag_coupl.eq.0) then
    19861987        if (debut.and.prt_level.gt.9) &
     
    20042005        !         enddo
    20052006
    2006 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     2007        ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    20072008        ! Modif FH 2010/04/27. Sans doute temporaire.
    2008         ! Deux options pour le alp_offset : constant si >?? 0 ou proportionnel ??a
    2009         ! w si <0
    2010 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     2009        ! Deux options pour le alp_offset : constant si >?? 0 ou
     2010        ! proportionnel ??a w si <0
     2011        ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    20112012        do i = 1,klon
    20122013           ALE(i) = max(ale_wake(i),Ale_bl(i))
     
    20262027           endif
    20272028        enddo
    2028 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     2029        ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    20292030
    20302031
     
    20462047
    20472048     !fin calcul ale et alp
    2048      !=================================================================================================
     2049     !=======================================================================
    20492050
    20502051
     
    21742175  !    .              d_u_con, d_v_con)
    21752176
    2176   !-----------------------------------------------------------------------------------------
    2177   ! ajout des tendances de la diffusion turbulente
    2178   CALL add_phys_tend(d_u_con,d_v_con,d_t_con,d_q_con,dql0,dqi0,paprs,'con')
    2179   !-----------------------------------------------------------------------------------------
     2177  CALL add_phys_tend(d_u_con, d_v_con, d_t_con, d_q_con, dql0, dqi0, paprs, &
     2178       'convection')
     2179  !----------------------------------------------------------------------------
    21802180
    21812181  if (mydebug) then
     
    22872287          ,wake_ddeltat,wake_ddeltaq)
    22882288     !
    2289      !-----------------------------------------------------------------------------------------
     2289     !-------------------------------------------------------------------------
    22902290     ! ajout des tendances des poches froides
    22912291     ! Faire rapidement disparaitre l'ancien dt_wake pour garder un d_t_wake
     
    22942294     d_q_wake(:,:)=dq_wake(:,:)*dtime
    22952295     CALL add_phys_tend(du0,dv0,d_t_wake,d_q_wake,dql0,dqi0,paprs,'wake')
    2296      !-----------------------------------------------------------------------------------------
     2296     !------------------------------------------------------------------------
    22972297
    22982298  endif
     
    25512551        endif
    25522552
    2553         !-----------------------------------------------------------------------------------------
     2553        !-----------------------------------------------------------------------
    25542554        ! ajout des tendances de l'ajustement sec ou des thermiques
    25552555        CALL add_phys_tend(du0,dv0,d_t_ajsb,d_q_ajsb,dql0,dqi0,paprs,'ajsb')
     
    25572557        d_q_ajs(:,:)=d_q_ajs(:,:)+d_q_ajsb(:,:)
    25582558
    2559         !-----------------------------------------------------------------------------------------
     2559        !---------------------------------------------------------------------
    25602560
    25612561     endif
     
    26092609  WHERE (rain_lsc < 0) rain_lsc = 0.
    26102610  WHERE (snow_lsc < 0) snow_lsc = 0.
    2611   !-----------------------------------------------------------------------------------------
    2612   ! ajout des tendances de la diffusion turbulente
     2611
    26132612  CALL add_phys_tend(du0,dv0,d_t_lsc,d_q_lsc,d_ql_lsc,d_qi_lsc,paprs,'lsc')
    2614   !-----------------------------------------------------------------------------------------
     2613  !---------------------------------------------------------------------------
    26152614  DO k = 1, klev
    26162615     DO i = 1, klon
     
    27402739#else
    27412740
    2742               abort_message='You should compile with -rrtm if running with iflag_rrtm=1'
     2741              abort_message = 'You should compile with -rrtm if running ' &
     2742                   // 'with iflag_rrtm=1'
    27432743              call abort_gcm(modname,abort_message,1)
    27442744#endif
Note: See TracChangeset for help on using the changeset viewer.