Ignore:
Timestamp:
Jul 22, 2024, 9:29:09 PM (4 months ago)
Author:
abarral
Message:

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/climb_hq_mod.F90

    r5081 r5099  
    11MODULE climb_hq_mod
    2 !
     2
    33! Module to solve the verctical diffusion of "q" and "H";
    44! specific humidity and potential energi.
    5 !
     5
    66  USE dimphy
    77
     
    3030
    3131CONTAINS
    32 !
    33 !****************************************************************************************
    34 !
     32
     33!****************************************************************************************
     34
    3535  SUBROUTINE climb_hq_down(knon, coefhq, paprs, pplay, &
    3636       delp, temp, q, dtime, &
     
    4444! for the quantity X=[Q,H] in equation X(k) = C(k) + D(k)*X(k-1), where k is
    4545! the index of the vertical layer.
    46 !
     46
    4747! Input arguments
    4848!****************************************************************************************
     
    9090! 1)
    9191! Allocation at first time step only
    92 !   
     92
    9393!****************************************************************************************
    9494
     
    132132! 2)
    133133! Definition of the coeficient K
    134 !
     134
    135135!****************************************************************************************
    136136    Kcoefhq(:,:) = 0.0
     
    146146! 3)
    147147! Calculation of gama for "Q" and "H"
    148 !
     148
    149149!****************************************************************************************
    150150!   surface pressure is used as reference
     
    180180! 4)
    181181! Calculte the coefficients C and D for specific humidity, q
    182 !
     182
    183183!****************************************************************************************
    184184   
     
    189189! 5)
    190190! Calculte the coefficients C and D for potentiel entalpie, H
    191 !
     191
    192192!****************************************************************************************
    193193    h_old(:,:) = 0.0
     
    207207! 6)
    208208! Return the first layer in output variables
    209 !
     209
    210210!****************************************************************************************
    211211    Acoef_H_out = Acoef_H
     
    217217! 7)
    218218! If Pbl is split, return also the other layers in output variables
    219 !
     219
    220220!****************************************************************************************
    221221!!! jyg le 07/02/2012
     
    244244
    245245  END SUBROUTINE climb_hq_down
    246 !
    247 !****************************************************************************************
    248 !
     246
     247!****************************************************************************************
     248
    249249  SUBROUTINE calc_coef(knon, Kcoef, gama, delp, X, Ccoef, Dcoef, Acoef, Bcoef)
    250 !
     250
    251251! Calculate the coefficients C and D in : X(k) = C(k) + D(k)*X(k-1)
    252252! where X is H or Q, and k the vertical level k=1,klev
    253 !
     253
    254254    INCLUDE "YOMCST.h"
    255255! Input arguments
     
    272272!****************************************************************************************
    273273! Niveau au sommet, k=klev
    274 !
     274
    275275!****************************************************************************************
    276276    Ccoef(:,:) = 0.0
     
    287287!****************************************************************************************
    288288! Niveau  (klev-1) <= k <= 2
    289 !
     289
    290290!****************************************************************************************
    291291
     
    301301!****************************************************************************************
    302302! Niveau k=1
    303 !
     303
    304304!****************************************************************************************
    305305
     
    311311
    312312  END SUBROUTINE calc_coef
    313 !
    314 !****************************************************************************************
    315 !
     313
     314!****************************************************************************************
     315
    316316  SUBROUTINE climb_hq_up(knon, dtime, t_old, q_old, &
    317317       flx_q1, flx_h1, paprs, pplay, &
     
    322322!!!
    323323       flux_q, flux_h, d_q, d_t)
    324 !
     324
    325325! This routine calculates the flux and tendency of the specific humidity q and
    326326! the potential engergi H.
     
    328328! X(k) = C(k) + D(k)*X(k-1) for X=[q,H], where the coefficients
    329329! C and D are known from before and k is index of the vertical layer.
    330 !   
    331330
    332331! Input arguments
     
    365364! Definition of some variables
    366365    REAL, DIMENSION(klon,klev)               :: d_h, zairm
    367 !
     366
    368367!****************************************************************************************
    369368    flux_q(:,:) = 0.0
     
    406405! 2)
    407406! Calculation of Q and H
    408 !
     407
    409408!****************************************************************************************
    410409
     
    423422! 3)
    424423! Calculation of the flux for Q and H
    425 !
     424
    426425!****************************************************************************************
    427426
     
    444443! 4)
    445444! Calculation of tendency for Q and H
    446 !
     445
    447446!****************************************************************************************
    448447    d_h_col_vdf(:) = 0.0
     
    461460!****************************************************************************************
    462461! Some deallocations
    463 !
     462
    464463!****************************************************************************************
    465464    IF (last) THEN
     
    476475    END IF
    477476  END SUBROUTINE climb_hq_up
    478 !
    479 !****************************************************************************************
    480 !
     477
     478!****************************************************************************************
     479
    481480END MODULE climb_hq_mod
    482481
Note: See TracChangeset for help on using the changeset viewer.