Changeset 5294 for LMDZ6/trunk/libf


Ignore:
Timestamp:
Oct 29, 2024, 7:35:00 PM (3 days ago)
Author:
Laurent Fairhead
Message:

Keeping clesphys.h was not the right solution
LF

Location:
LMDZ6/trunk/libf/phylmd/rrtm
Files:
1 deleted
28 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/rrtm/aeropt_6bands_rrtm.F90

    r4165 r5294  
    1111  USE aero_mod
    1212  USE YOMCST, ONLY: RG
    13 
     13! Temporary fix waiting for cleaner interface (or not)
     14  USE clesphys_mod_h, ONLY: NSW
     15 
    1416  !    Yves Balkanski le 12 avril 2006
    1517  !    Celine Deandreis
     
    2123  IMPLICIT NONE
    2224  !
    23   INCLUDE "clesphys.h"
     25!!  INCLUDE "clesphys.h"
    2426  !
    2527  ! Input arguments:
  • LMDZ6/trunk/libf/phylmd/rrtm/aeropt_lw_rrtm.F90

    r3288 r5294  
    1515  USE YOERAD, ONLY: NLW
    1616  USE YOMCST, ONLY: RG
    17 
     17! Temporary fix waiting for cleaner interface (or not)
     18  USE clesphys_mod_h, ONLY: NSW
     19 
    1820  IMPLICIT NONE
    1921
    20   INCLUDE "clesphys.h"
     22!!  INCLUDE "clesphys.h"
    2123  !
    2224  ! Input arguments:
  • LMDZ6/trunk/libf/phylmd/rrtm/lwu.F90

    r5252 r5294  
    7777USE infotrac_phy, ONLY : type_trac
    7878USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_REPROBUS
     79! Temporary fix waiting for cleaner interface (or not)
     80USE clesphys_mod_h, ONLY: NSW, RCFC11, RCFC12,  RCH4, RN2O
    7981
    8082IMPLICIT NONE
     
    9496REAL(KIND=JPRB)   ,INTENT(OUT)   :: PABCU(KLON,NUA,3*KLEV+1)
    9597
    96 #include "clesphys.h"
     98!!include "clesphys.h"
    9799!-----------------------------------------------------------------------
    98100
  • LMDZ6/trunk/libf/phylmd/rrtm/radlsw.F90

    r3539 r5294  
    1616
    1717use write_field_phy
     18! Temporary fix waiting for cleaner interface (or not)
     19USE clesphys_mod_h, ONLY: NSW
    1820
    1921!**** *RADLSW* - INTERFACE TO ECMWF LW AND SW RADIATION SCHEMES
     
    155157IMPLICIT NONE
    156158
    157 include "clesphys.h"
     159!!include "clesphys.h"
    158160!!include "clesrrtm.h"
    159161include "YOETHF.h"
  • LMDZ6/trunk/libf/phylmd/rrtm/radlsw.intfb.h

    r2146 r5294  
    2121 & RCCNLND, RCCNSEA, RLWINHF, RSWINHF, RRe2De ,&
    2222 & LEDBUG
    23 include "clesphys.h"
     23! Temporary fix waiting for cleaner interface (or not)
     24USE clesphys_mod_h, ONLY: NSW
     25!!include "clesphys.h"
    2426INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    2527INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/read_rsun_rrtm.F90

    r5084 r5294  
    1717
    1818  USE YOESW, ONLY : RSUN
    19 
     19! Temporary fix waiting for cleaner interface (or not)
     20  USE clesphys_mod_h, ONLY: NSW, solaire
     21 
    2022  IMPLICIT NONE
    2123
    22   INCLUDE "clesphys.h"
     24!!  INCLUDE "clesphys.h"
    2325
    2426  ! Input arguments
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosol_optic_rrtm.F90

    r4124 r5294  
    2222  USE infotrac_phy, ONLY: tracers, nqtot, nbtr
    2323  USE YOMCST
    24 
     24! Temporary fix waiting for cleaner interface (or not)
     25  USE clesphys_mod_h, ONLY: NSW
     26 
    2527  IMPLICIT NONE
    2628
    27   include "clesphys.h"
     29!!  include "clesphys.h"
    2830
    2931  ! Input arguments
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosolstrato2_rrtm.F90

    r5084 r5294  
    2020    USE YOMCST
    2121    USE lmdz_xios
    22 
     22! Temporary fix waiting for cleaner interface (or not)
     23    USE clesphys_mod_h, ONLY: NSW
     24   
    2325    IMPLICIT NONE
    2426
    25     INCLUDE "clesphys.h"
     27!!    INCLUDE "clesphys.h"
    2628
    2729    CHARACTER (len = 80) :: abort_message
  • LMDZ6/trunk/libf/phylmd/rrtm/recmwf_aero.F90

    r4875 r5294  
    164164  USE YOMARPHY , ONLY : LRDUST
    165165  USE phys_output_mod, ONLY : swaerofree_diag, swaero_diag
    166 
     166! Temporary fix waiting for cleaner interface (or not)
     167  USE clesphys_mod_h, ONLY: NSW
     168 
    167169  !-----------------------------------------------------------------------
    168170
     
    171173
    172174  IMPLICIT NONE
    173   INCLUDE "clesphys.h"
     175!!  INCLUDE "clesphys.h"
    174176
    175177  INTEGER(KIND=JPIM),INTENT(IN)    :: KPROMA
  • LMDZ6/trunk/libf/phylmd/rrtm/rrtm_ecrt_140gp.F90

    r2626 r5294  
    3333!MPL/IM 20160915 on prend GES de phylmd USE YOERDI   , ONLY :    RCH4     ,RN2O    ,RCFC11  ,RCFC12
    3434USE YOESW    , ONLY : RAER
     35! Temporary fix waiting for cleaner interface (or not)
     36USE clesphys_mod_h, ONLY: NSW, rcfc11, rcfc12, rch4, rn2o
    3537
    3638!------------------------------Arguments--------------------------------
     
    114116
    115117!MPL/IM 20160915 on prend GES de phylmd
    116 #include "clesphys.h"
     118!!#include "clesphys.h"
    117119! ***
    118120
  • LMDZ6/trunk/libf/phylmd/rrtm/rrtm_rrtm_140gp.intfb.h

    r2146 r5294  
    1414 & JPINPX 
    1515!-NLW in clesphys now OB
    16 include "clesphys.h"
     16! Temporary fix waiting for cleaner interface (or not)
     17USE clesphys_mod_h, ONLY: NSW
     18!!include "clesphys.h"
    1719INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1820INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/srtm_srtm_224gp.F90

    r2027 r5294  
    2323USE YOMPHY3  , ONLY : RII0
    2424USE YOMCST   , ONLY : RI0
    25 
     25! Temporary fix waiting for cleaner interface (or not)
     26USE clesphys_mod_h, ONLY: NSW, rch4, rn2o
    2627
    2728
    2829IMPLICIT NONE
    2930
    30 #include "clesphys.h"
     31!!#include "clesphys.h"
    3132
    3233!-- Input arguments
  • LMDZ6/trunk/libf/phylmd/rrtm/srtm_srtm_224gp_mcica.F90

    r2626 r5294  
    2121USE YOMPHY3  , ONLY : RII0
    2222USE YOMCST   , ONLY : RI0
     23! Temporary fix waiting for cleaner interface (or not)
     24USE clesphys_mod_h, ONLY: NSW, rch4, rn2o
    2325
    2426IMPLICIT NONE
     
    134136#include "srtm_spcvrt_mcica.intfb.h"
    135137!MPL/IM 20160915 on prend GES de phylmd
    136 #include "clesphys.h"
     138!!#include "clesphys.h"
    137139
    138140!-----------------------------------------------------------------------
  • LMDZ6/trunk/libf/phylmd/rrtm/suecrad.F90

    r4251 r5294  
    155155USE YOMDYN   , ONLY : NDLNPR
    156156
     157! Temporary fix waiting for cleaner interface (or not)
     158USE clesphys_mod_h, ONLY: NSW, CFC11_ppt, CFC12_ppt, CH4_ppb, CO2_ppm, iflag_rrtm, N2O_ppb, overlap
     159
    157160IMPLICIT NONE
    158161
     
    243246!      ----------------------------------------------------------------
    244247
    245 #include "clesphys.h"
     248!#include "clesphys.h"
    246249#include "naerad.h"
    247250#include "namrgri.h"
  • LMDZ6/trunk/libf/phylmd/rrtm/suecrad15.F90

    r1990 r5294  
    7878USE YOMPRAD  , ONLY : LODBGRADI,LODBGRADL
    7979USE YOMRADF  , ONLY : EMTD     ,EMTU      ,TRSW    ,RMOON
     80! Temporary fix waiting for cleaner interface (or not)
     81USE clesphys_mod_h, ONLY: NSW
    8082
    8183IMPLICIT NONE
    8284
    83 include "clesphys.h"
     85!!include "clesphys.h"
    8486
    8587INTEGER(KIND=JPIM),INTENT(IN)    :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/suphec.F90

    r2799 r5294  
    8888USE YOMCT0  , ONLY  : LSCMEC   ,LROUGH   ,REXTZ0M  ,REXTZ0H
    8989USE vertical_layers_mod, ONLY: ap,bp
     90! Temporary fix waiting for cleaner interface (or not)
     91USE clesphys_mod_h, ONLY: NSW
    9092
    9193IMPLICIT NONE
    9294include "YOETHF.h"
    93 include "clesphys.h"
     95!!include "clesphys.h"
    9496
    9597INTEGER(KIND=JPIM),INTENT(IN)    :: KULOUT
  • LMDZ6/trunk/libf/phylmd/rrtm/sw.F90

    r2010 r5294  
    7474! NSW mis dans .def MPL 20140211
    7575USE write_field_phy
     76! Temporary fix waiting for cleaner interface (or not)
     77USE clesphys_mod_h, ONLY: NSW
    7678
    7779IMPLICIT NONE
    7880
    79 include "clesphys.h"
     81!!include "clesphys.h"
    8082
    8183integer, save :: icount=0
  • LMDZ6/trunk/libf/phylmd/rrtm/sw.intfb.h

    r1990 r5294  
    1313 & )
    1414USE PARKIND1 ,ONLY : JPIM ,JPRB
    15 include "clesphys.h"   
     15! Temporary fix waiting for cleaner interface (or not)
     16USE clesphys_mod_h, ONLY: NSW
     17!!include "clesphys.h"   
    1618INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1719INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/sw1s.F90

    r2192 r5294  
    7373! NSW mis dans .def MPL 20140211
    7474USE write_field_phy
     75! Temporary fix waiting for cleaner interface (or not)
     76USE clesphys_mod_h, ONLY: NSW
    7577
    7678IMPLICIT NONE
    7779
    78 include "clesphys.h"
     80!!include "clesphys.h"
    7981
    8082INTEGER(KIND=JPIM),INTENT(IN)    :: KLON
  • LMDZ6/trunk/libf/phylmd/rrtm/sw1s.intfb.h

    r1990 r5294  
    88 & )
    99USE PARKIND1 ,ONLY : JPIM ,JPRB
    10 include "clesphys.h"
     10! Temporary fix waiting for cleaner interface (or not)
     11USE clesphys_mod_h, ONLY: NSW
     12!!include "clesphys.h"
    1113INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1214INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/swclr.F90

    r2044 r5294  
    7070USE YOERDI   , ONLY : REPCLC
    7171USE YOERDU   , ONLY : REPSCT
     72! Temporary fix waiting for cleaner interface (or not)
     73USE clesphys_mod_h, ONLY: NSW
    7274
    7375IMPLICIT NONE
    74 INCLUDE "clesphys.h"
     76!!INCLUDE "clesphys.h"
    7577
    7678INTEGER(KIND=JPIM),INTENT(IN)    :: KLON
  • LMDZ6/trunk/libf/phylmd/rrtm/swclr.intfb.h

    r1990 r5294  
    88USE PARKIND1 ,ONLY : JPIM ,JPRB
    99USE YOERAD , ONLY : NOVLP
    10 include "clesphys.h"
     10! Temporary fix waiting for cleaner interface (or not)
     11USE clesphys_mod_h, ONLY: NSW
     12!!include "clesphys.h"
    1113INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1214INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/swni.F90

    r2401 r5294  
    8181USE YOERDU   , ONLY : REPLOG   ,REPSCQ   ,REPSC
    8282USE write_field_phy
     83! Temporary fix waiting for cleaner interface (or not)
     84USE clesphys_mod_h, ONLY: NSW
    8385
    8486IMPLICIT NONE
    8587
    86 include "clesphys.h"
     88!!include "clesphys.h"
    8789
    8890character*1 str1
  • LMDZ6/trunk/libf/phylmd/rrtm/swni.intfb.h

    r1990 r5294  
    99USE PARKIND1 ,ONLY : JPIM ,JPRB
    1010USE YOERAD , ONLY : NOVLP
    11 include "clesphys.h"
     11! Temporary fix waiting for cleaner interface (or not)
     12USE clesphys_mod_h, ONLY: NSW
     13!!include "clesphys.h"
    1214INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1315INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/swr.F90

    r2596 r5294  
    6666USE YOEOVLP  , ONLY : RA1OVLP
    6767USE write_field_phy
     68! Temporary fix waiting for cleaner interface (or not)
     69USE clesphys_mod_h, ONLY: NSW
    6870
    6971IMPLICIT NONE
    7072
    71 include "clesphys.h"
     73!!include "clesphys.h"
    7274INTEGER(KIND=JPIM),INTENT(IN)    :: KLON
    7375INTEGER(KIND=JPIM),INTENT(IN)    :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/swr.intfb.h

    r1990 r5294  
    88USE PARKIND1 ,ONLY : JPIM ,JPRB
    99USE YOERAD , ONLY : NOVLP
    10 include "clesphys.h"
     10! Temporary fix waiting for cleaner interface (or not)
     11USE clesphys_mod_h, ONLY: NSW
     12!!include "clesphys.h"
    1113INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1214INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/swu.F90

    r1990 r5294  
    6464 & RTDH2O   ,RTDUMG   ,RTH2O    ,RTUMG 
    6565USE YOEOVLP  , ONLY : RA1OVLP
     66! Temporary fix waiting for cleaner interface (or not)
     67USE clesphys_mod_h, ONLY: NSW
    6668
    6769IMPLICIT NONE
    6870
    69 include "clesphys.h"
     71!!include "clesphys.h"
    7072INTEGER(KIND=JPIM),INTENT(IN)    :: KLON
    7173INTEGER(KIND=JPIM),INTENT(IN)    :: KLEV
  • LMDZ6/trunk/libf/phylmd/rrtm/swu.intfb.h

    r1990 r5294  
    77USE PARKIND1 ,ONLY : JPIM ,JPRB
    88USE YOERAD , ONLY : NOVLP
    9 include "clesphys.h"
     9! Temporary fix waiting for cleaner interface (or not)
     10USE clesphys_mod_h, ONLY: NSW
     11!!include "clesphys.h"
    1012INTEGER(KIND=JPIM),INTENT(IN) :: KLON
    1113INTEGER(KIND=JPIM),INTENT(IN) :: KLEV
Note: See TracChangeset for help on using the changeset viewer.