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/phylmdiso/climb_hq_mod.F90

    r5087 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#ifdef ISO
     
    4242
    4343CONTAINS
    44 !
    45 !****************************************************************************************
    46 !
     44
     45!****************************************************************************************
     46
    4747  SUBROUTINE climb_hq_down(knon, coefhq, paprs, pplay, &
    4848       delp, temp, q, dtime, &
     
    6767! for the quantity X=[Q,H] in equation X(k) = C(k) + D(k)*X(k-1), where k is
    6868! the index of the vertical layer.
    69 !
     69
    7070! Input arguments
    7171!****************************************************************************************
     
    147147! 1)
    148148! Allocation at first time step only
    149 !   
     149
    150150!****************************************************************************************
    151151
     
    203203! 2)
    204204! Definition of the coeficient K
    205 !
     205
    206206!****************************************************************************************
    207207    Kcoefhq(:,:) = 0.0
     
    217217! 3)
    218218! Calculation of gama for "Q" and "H"
    219 !
     219
    220220!****************************************************************************************
    221221!   surface pressure is used as reference
     
    278278! 4)
    279279! Calculte the coefficients C and D for specific humidity, q
    280 !
     280
    281281!****************************************************************************************
    282282   
     
    340340! 5)
    341341! Calculte the coefficients C and D for potentiel entalpie, H
    342 !
     342
    343343!****************************************************************************************
    344344    h_old(:,:) = 0.0
     
    358358! 6)
    359359! Return the first layer in output variables
    360 !
     360
    361361!****************************************************************************************
    362362    Acoef_H_out = Acoef_H
     
    372372! 7)
    373373! If Pbl is split, return also the other layers in output variables
    374 !
     374
    375375!****************************************************************************************
    376376!!! jyg le 07/02/2012
     
    415415
    416416  END SUBROUTINE climb_hq_down
    417 !
    418 !****************************************************************************************
    419 !
     417
     418!****************************************************************************************
     419
    420420  SUBROUTINE calc_coef(knon, Kcoef, gama, delp, X, Ccoef, Dcoef, Acoef, Bcoef)
    421 !
     421
    422422! Calculate the coefficients C and D in : X(k) = C(k) + D(k)*X(k-1)
    423423! where X is H or Q, and k the vertical level k=1,klev
    424 !
     424
    425425    INCLUDE "YOMCST.h"
    426426! Input arguments
     
    443443!****************************************************************************************
    444444! Niveau au sommet, k=klev
    445 !
     445
    446446!****************************************************************************************
    447447    Ccoef(:,:) = 0.0
     
    458458!****************************************************************************************
    459459! Niveau  (klev-1) <= k <= 2
    460 !
     460
    461461!****************************************************************************************
    462462
     
    472472!****************************************************************************************
    473473! Niveau k=1
    474 !
     474
    475475!****************************************************************************************
    476476
     
    482482
    483483  END SUBROUTINE calc_coef
    484 !
    485 !****************************************************************************************
    486 !
     484
     485!****************************************************************************************
     486
    487487  SUBROUTINE climb_hq_up(knon, dtime, t_old, q_old, &
    488488       flx_q1, flx_h1, paprs, pplay, &
     
    505505USE isotopes_verif_mod
    506506#endif
    507 !
     507
    508508! This routine calculates the flux and tendency of the specific humidity q and
    509509! the potential engergi H.
     
    511511! X(k) = C(k) + D(k)*X(k-1) for X=[q,H], where the coefficients
    512512! C and D are known from before and k is index of the vertical layer.
    513 !   
    514513
    515514! Input arguments
     
    564563! Definition of some variables
    565564    REAL, DIMENSION(klon,klev)               :: d_h, zairm
    566 !
     565
    567566!****************************************************************************************
    568567
     
    645644! 2)
    646645! Calculation of Q and H
    647 !
     646
    648647!****************************************************************************************
    649648
     
    715714! 3)
    716715! Calculation of the flux for Q and H
    717 !
     716
    718717!****************************************************************************************
    719718
     
    748747! 4)
    749748! Calculation of tendency for Q and H
    750 !
     749
    751750!****************************************************************************************
    752751    d_h_col_vdf(:) = 0.0
     
    798797!****************************************************************************************
    799798! Some deallocations
    800 !
     799
    801800!****************************************************************************************
    802801    IF (last) THEN
     
    822821    END IF
    823822  END SUBROUTINE climb_hq_up
    824 !
    825 !****************************************************************************************
    826 !
     823
     824!****************************************************************************************
     825
    827826END MODULE climb_hq_mod
    828827
Note: See TracChangeset for help on using the changeset viewer.