Ignore:
Timestamp:
Oct 19, 2023, 4:02:57 PM (9 months ago)
Author:
idelkadi
Message:

Merged trunk changes -r4488:4726 LMDZ_ECRad branch

Location:
LMDZ6/branches/LMDZ_ECRad
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ_ECRad

  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/1DUTILS.h

    r4482 r4727  
    266266!Config  Def  = 0.
    267267!Config  Help =
    268        tsurf = 0.
     268       time_ini = 0.
    269269       CALL getin('time_ini',time_ini)
    270270
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/1D_decl_cases.h

    r4104 r4727  
    1 #include "netcdf.inc"
     1        INCLUDE "netcdf.inc"
    22
    33! Declarations specifiques au cas Toga
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/1D_read_forc_cases.h

    r4482 r4727  
    7373
    7474! initial and boundary conditions :
     75      ! initial pressure
    7576      psurf = ps_prof_cas
    76       if (tskin_prof_cas .NE. 0.) THEN
     77
     78      !initial surface temperature
     79      if (tskin_prof_cas .NE. 0.) then
     80      ! we take the first value of the prescribed ts
    7781          tsurf=tskin_prof_cas
     82      else if (ts_prof_cas .NE. 0) then
     83      ! if an initial ts value is present, we take it
     84          tsurf=ts_prof_cas
    7885      endif
    7986
     87      ! ts forcing during the run (if any)
    8088      tg = ts_prof_cas
    8189      if ((tg .eq. 0.) .and. (tskin_prof_cas .NE. 0.)) THEN
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/1Dconv.h

    r2310 r4727  
    1313!cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
    1414
    15 #include "YOMCST.h"
     15      INCLUDE "YOMCST.h"
    1616
    1717      INTEGER klev
     
    461461      implicit none
    462462
    463 #include "dimensions.h"
    464 !cccc#include "dimphy.h"
     463      INCLUDE "dimensions.h"
     464!cccc      INCLUDE "dimphy.h"
    465465
    466466      integer k
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/mod_1D_amma_read.F90

    r2373 r4727  
    5959      implicit none
    6060
    61 #include "netcdf.inc"
     61      INCLUDE "netcdf.inc"
    6262
    6363      INTEGER nid,rid,ierr
     
    180180!program reading forcings of the AMMA case study
    181181      implicit none
    182 #include "netcdf.inc"
     182      INCLUDE "netcdf.inc"
    183183
    184184      integer ntime,nlevel
     
    407407!---------------------------------------------------------------------------------------
    408408
    409 #include "compar1d.h"
     409        INCLUDE "compar1d.h"
    410410
    411411! inputs:
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/mod_1D_cases_read.F90

    r2373 r4727  
    9090      implicit none
    9191
    92 #include "netcdf.inc"
     92      INCLUDE "netcdf.inc"
    9393
    9494      INTEGER nid,rid,ierr
     
    267267!program reading forcing of the case study
    268268      implicit none
    269 #include "netcdf.inc"
     269      INCLUDE "netcdf.inc"
    270270
    271271      integer ntime,nlevel
     
    994994!---------------------------------------------------------------------------------------
    995995
    996 #include "compar1d.h"
    997 #include "date_cas.h"
     996        INCLUDE "compar1d.h"
     997        INCLUDE "date_cas.h"
    998998
    999999! inputs:
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/mod_1D_cases_read2.F90

    r4482 r4727  
    8181    implicit none
    8282
    83 #include "netcdf.inc"
     83    INCLUDE "netcdf.inc"
    8484
    8585    INTEGER nid,rid,ierr
     
    192192    implicit none
    193193
    194 #include "netcdf.inc"
     194    INCLUDE "netcdf.inc"
    195195
    196196    INTEGER nid,rid,ierr
     
    240240    allocate(plev_cas(nlev_cas,nt_cas),plevh_cas(nlev_cas+1))       
    241241    allocate(z_cas(nlev_cas,nt_cas),zh_cas(nlev_cas+1))
    242     allocate(ap_cas(nlev_cas+1),bp_cas(nt_cas+1))
     242    allocate(ap_cas(nlev_cas+1),bp_cas(nlev_cas+1))
    243243    allocate(t_cas(nlev_cas,nt_cas),q_cas(nlev_cas,nt_cas),qv_cas(nlev_cas,nt_cas),ql_cas(nlev_cas,nt_cas), &
    244244         qi_cas(nlev_cas,nt_cas),rh_cas(nlev_cas,nt_cas))
     
    320320    implicit none
    321321
    322 #include "netcdf.inc"
    323 #include "date_cas.h"
     322    INCLUDE "netcdf.inc"
     323    INCLUDE "date_cas.h"
    324324
    325325    INTEGER nid,rid,ierr
     
    393393    allocate(plev_cas(nlev_cas,nt_cas),plevh_cas(nlev_cas+1))       
    394394    allocate(z_cas(nlev_cas,nt_cas),zh_cas(nlev_cas+1))
    395     allocate(ap_cas(nlev_cas+1),bp_cas(nt_cas+1))
     395    allocate(ap_cas(nlev_cas+1),bp_cas(nlev_cas+1))
    396396    allocate(t_cas(nlev_cas,nt_cas),q_cas(nlev_cas,nt_cas),qv_cas(nlev_cas,nt_cas),ql_cas(nlev_cas,nt_cas), &
    397397         qi_cas(nlev_cas,nt_cas),rh_cas(nlev_cas,nt_cas))
     
    543543  use netcdf, only: nf90_get_var
    544544  implicit none
    545 #include "netcdf.inc"
     545  INCLUDE "netcdf.inc"
    546546
    547547  integer ntime,nlevel
     
    660660  use netcdf, only: nf90_get_var
    661661  implicit none
    662 #include "netcdf.inc"
     662  INCLUDE "netcdf.inc"
    663663
    664664  integer ntime,nlevel
     
    831831  use netcdf, only: nf90_get_var
    832832  implicit none
    833 #include "netcdf.inc"
     833  INCLUDE "netcdf.inc"
    834834
    835835  integer ntime,nlevel,k,t
     
    10611061  !---------------------------------------------------------------------------------------
    10621062
    1063 #include "compar1d.h"
    1064 #include "date_cas.h"
     1063  INCLUDE "compar1d.h"
     1064  INCLUDE "date_cas.h"
    10651065
    10661066  ! inputs:
     
    11351135  !       endif
    11361136  timeit=(day-day_ju_ini_cas)*86400
    1137   print *,'day=',day
    1138   print *,'day_ju_ini_cas=',day_ju_ini_cas
    1139   print *,'pdt_cas=',pdt_cas
    1140   print *,'timeit=',timeit
    1141   print *,'nt_cas=',nt_cas
     1137  !print *,'day=',day
     1138  !print *,'day_ju_ini_cas=',day_ju_ini_cas
     1139  !print *,'pdt_cas=',pdt_cas
     1140  !print *,'timeit=',timeit
     1141  !print *,'nt_cas=',nt_cas
    11421142
    11431143  ! Determine the closest observation times:
     
    11551155  time_cas1=(it_cas1-1)*pdt_cas
    11561156  time_cas2=(it_cas2-1)*pdt_cas
    1157   print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
     1157  !print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
    11581158
    11591159  if (it_cas1 .gt. nt_cas) then
     
    12701270  !---------------------------------------------------------------------------------------
    12711271
    1272 #include "compar1d.h"
    1273 #include "date_cas.h"
     1272  INCLUDE "compar1d.h"
     1273  INCLUDE "date_cas.h"
    12741274
    12751275  ! inputs:
     
    13501350  !       endif
    13511351  timeit=(day-day_ju_ini_cas)*86400
    1352   print *,'day=',day
    1353   print *,'day_ju_ini_cas=',day_ju_ini_cas
    1354   print *,'pdt_cas=',pdt_cas
    1355   print *,'timeit=',timeit
    1356   print *,'nt_cas=',nt_cas
     1352  !print *,'day=',day
     1353  !print *,'day_ju_ini_cas=',day_ju_ini_cas
     1354  !print *,'pdt_cas=',pdt_cas
     1355  !print *,'timeit=',timeit
     1356  !print *,'nt_cas=',nt_cas
    13571357
    13581358  ! Determine the closest observation times:
     
    13701370  time_cas1=(it_cas1-1)*pdt_cas
    13711371  time_cas2=(it_cas2-1)*pdt_cas
    1372   print *,'timeit,pdt_cas,nt_cas=',timeit,pdt_cas,nt_cas
    1373   print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
     1372  !print *,'timeit,pdt_cas,nt_cas=',timeit,pdt_cas,nt_cas
     1373  !print *,'it_cas1,it_cas2,time_cas1,time_cas2=',it_cas1,it_cas2,time_cas1,time_cas2
    13741374
    13751375  if (it_cas1 .gt. nt_cas) then
     
    14031403     t_prof_cas(k) = t_cas(k,it_cas2)                                 &       
    14041404          -frac*(t_cas(k,it_cas2)-t_cas(k,it_cas1))
    1405      print *,'k,frac,plev_cas1,plev_cas2=',k,frac,plev_cas(k,it_cas1),plev_cas(k,it_cas2)
     1405     !print *,'k,frac,plev_cas1,plev_cas2=',k,frac,plev_cas(k,it_cas1),plev_cas(k,it_cas2)
    14061406     theta_prof_cas(k) = theta_cas(k,it_cas2)                         &                     
    14071407          -frac*(theta_cas(k,it_cas2)-theta_cas(k,it_cas1))
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/mod_1D_cases_read_std.F90

    r4482 r4727  
    9090    implicit none
    9191
    92 #include "netcdf.inc"
    93 #include "date_cas.h"
     92    INCLUDE "netcdf.inc"
     93    INCLUDE "date_cas.h"
    9494
    9595    INTEGER nid,rid,ierr
     
    163163    allocate(plev_cas(nlev_cas,nt_cas),plevh_cas(nlev_cas+1))       
    164164    allocate(z_cas(nlev_cas,nt_cas),zh_cas(nlev_cas+1))
    165     allocate(ap_cas(nlev_cas+1),bp_cas(nt_cas+1))
     165    allocate(ap_cas(nlev_cas+1),bp_cas(nlev_cas+1))
    166166    allocate(t_cas(nlev_cas,nt_cas),q_cas(nlev_cas,nt_cas),qv_cas(nlev_cas,nt_cas),ql_cas(nlev_cas,nt_cas), &
    167167         qi_cas(nlev_cas,nt_cas),rh_cas(nlev_cas,nt_cas))
     
    331331    use netcdf, only: nf90_get_var
    332332    implicit none
    333 #include "netcdf.inc"
    334 #include "compar1d.h"
     333    INCLUDE "netcdf.inc"
     334    INCLUDE "compar1d.h"
    335335
    336336    integer ntime,nlevel,k,t
     
    671671    !---------------------------------------------------------------------------------------
    672672
    673 #include "compar1d.h"
    674 #include "date_cas.h"
     673    INCLUDE "compar1d.h"
     674    INCLUDE "date_cas.h"
    675675
    676676    ! inputs:
     
    934934    implicit none
    935935
    936 #include "YOMCST.h"
    937 #include "dimensions.h"
     936    INCLUDE "YOMCST.h"
     937    INCLUDE "dimensions.h"
    938938
    939939    !-------------------------------------------------------------------------
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/old_1DUTILS_read_interp.h

    r4482 r4727  
    150150      implicit none
    151151
    152 #include "netcdf.inc"
     152      INCLUDE "netcdf.inc"
    153153
    154154      integer ntime,nlevel
     
    495495
    496496         implicit none
    497 #include "netcdf.inc"
     497         INCLUDE "netcdf.inc"
    498498         integer nid,ttm,llm
    499499         real*8 time(ttm)
     
    545545       implicit none
    546546
    547 #include "dimensions.h"
     547      INCLUDE "dimensions.h"
    548548
    549549!-------------------------------------------------------------------------
     
    659659       implicit none
    660660
    661 #include "dimensions.h"
     661      INCLUDE "dimensions.h"
    662662
    663663!-------------------------------------------------------------------------
     
    781781! Read RICO forcing data
    782782!-------------------------------------------------------------------------
    783 #include "dimensions.h"
     783      INCLUDE "dimensions.h"
    784784
    785785
     
    10571057       implicit none
    10581058 
    1059 #include "dimensions.h"
     1059      INCLUDE "dimensions.h"
    10601060
    10611061!-------------------------------------------------------------------------
     
    11791179       implicit none
    11801180 
    1181 #include "dimensions.h"
     1181       INCLUDE "dimensions.h"
    11821182
    11831183!-------------------------------------------------------------------------
     
    13381338       implicit none
    13391339 
    1340 #include "dimensions.h"
     1340       INCLUDE "dimensions.h"
    13411341
    13421342!-------------------------------------------------------------------------
     
    15611561!---------------------------------------------------------------------------------------
    15621562
    1563 #include "compar1d.h"
     1563        INCLUDE "compar1d.h"
    15641564
    15651565! inputs:
     
    17031703!---------------------------------------------------------------------------------------
    17041704
    1705 #include "compar1d.h"
     1705        INCLUDE "compar1d.h"
    17061706
    17071707! inputs:
     
    18161816!---------------------------------------------------------------------------------------
    18171817
    1818 #include "compar1d.h"
     1818        INCLUDE "compar1d.h"
    18191819
    18201820! inputs:
     
    21732173      implicit none
    21742174
    2175 #include "netcdf.inc"
     2175      INCLUDE "netcdf.inc"
    21762176
    21772177      integer ntime,nlevel
     
    23852385      implicit none
    23862386
    2387 #include "netcdf.inc"
    2388 #include "YOMCST.h"
     2387      INCLUDE "netcdf.inc"
     2388      INCLUDE "YOMCST.h"
    23892389
    23902390      integer ntime,nlevel
     
    27192719      implicit none
    27202720
    2721 #include "netcdf.inc"
     2721      INCLUDE "netcdf.inc"
    27222722
    27232723      integer ntime,nlevel,nsol
     
    29602960     
    29612961      parameter (ncm_1=49180)
    2962 #include "YOMCST.h"
     2962      INCLUDE "YOMCST.h"
    29632963
    29642964      real albsfc(ncm_1), albsfc_w(ncm_1)
     
    30643064      SUBROUTINE read_rtmip(nlev_rtmip,play,plev,t,h2o,o3)
    30653065     
    3066 #include "YOMCST.h"
     3066      INCLUDE "YOMCST.h"
    30673067
    30683068      real t(nlev_rtmip), pt(nlev_rtmip),pb(nlev_rtmip),h2o(nlev_rtmip), o3(nlev_rtmip)
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/old_1D_decl_cases.h

    r3780 r4727  
    1 #include "netcdf.inc"
     1         INCLUDE "netcdf.inc"
    22
    33! Declarations specifiques au cas Toga
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/old_lmdz1d.F90

    r4482 r4727  
    1313       ftsol, beta_aridity, pbl_tke, pctsrf, radsol, rain_fall, snow_fall, ratqs, &
    1414       rnebcon, rugoro, sig1, w01, solaire_etat0, sollw, sollwdown, &
    15        solsw, solswfdiff, t_ancien, q_ancien, u_ancien, v_ancien, &
     15       solsw, solswfdiff, t_ancien, q_ancien, u_ancien, v_ancien, rneb_ancien, &
    1616       wake_delta_pbl_TKE, delta_tsurf, wake_fip, wake_pe, &
    1717       wake_deltaq, wake_deltat, wake_s, wake_dens, &
     
    4747
    4848      implicit none
    49 #include "dimensions.h"
    50 #include "YOMCST.h"
    51 !!#include "control.h"
    52 #include "clesphys.h"
    53 #include "dimsoil.h"
    54 !#include "indicesol.h"
    55 
    56 #include "compar1d.h"
    57 #include "flux_arp.h"
    58 #include "date_cas.h"
    59 #include "tsoilnudge.h"
    60 #include "fcg_gcssold.h"
    61 !!!#include "fbforcing.h"
    62 #include "compbl.h"
     49      INCLUDE "dimensions.h"
     50      INCLUDE "YOMCST.h"
     51!!      INCLUDE "control.h"
     52      INCLUDE "clesphys.h"
     53      INCLUDE "dimsoil.h"
     54!      INCLUDE "indicesol.h"
     55
     56      INCLUDE "compar1d.h"
     57      INCLUDE "flux_arp.h"
     58      INCLUDE "date_cas.h"
     59      INCLUDE "tsoilnudge.h"
     60      INCLUDE "fcg_gcssold.h"
     61!!!      INCLUDE "fbforcing.h"
     62      INCLUDE "compbl.h"
    6363
    6464!=====================================================================
     
    163163!=====================================================================
    164164!
    165 #include "old_1D_decl_cases.h"
     165      INCLUDE "old_1D_decl_cases.h"
    166166!
    167167!---------------------------------------------------------------------
     
    721721!=====================================================================
    722722
    723 #include "old_1D_read_forc_cases.h"
     723      INCLUDE "old_1D_read_forc_cases.h"
    724724
    725725      if (forcing_GCM2SCM) then
     
    920920        u_ancien(1,:)=u(:)
    921921        v_ancien(1,:)=v(:)
     922        rneb_ancien(1,:)=0.
    922923
    923924        u10m=0.
     
    945946!------------------------------------------------------------------------
    946947!Al1 =============== restart option ==========================
     948        iflag_physiq=0
     949        call getin('iflag_physiq',iflag_physiq)
     950
    947951        if (.not.restart) then
    948952          iflag_pbl = 5
     
    10651069!---------------------------------------------------------------------
    10661070
    1067 #include "old_1D_interp_cases.h"
     1071      INCLUDE "old_1D_interp_cases.h"
    10681072
    10691073      if (forcing_GCM2SCM) then
     
    12481252!! Increment state variables
    12491253!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    1250 print*,'OLDLMDZ1D AANT'
    12511254    IF (flag_inhib_forcing == 0) then ! if tendency of forcings should be added
    1252 print*,'OLDLMDZ1D ARES' , forcing_sandu
    12531255
    12541256! pour les cas sandu et astex, on reclacule u,v,q,temp et teta dans 1D_nudge_sandu_astex.h
    12551257! au dessus de 700hpa, on relaxe vers les profils initiaux
    12561258      if (forcing_sandu .OR. forcing_astex) then
    1257 #include "1D_nudge_sandu_astex.h"
     1259      INCLUDE "1D_nudge_sandu_astex.h"
    12581260      else
    12591261        u(1:mxcalc)=u(1:mxcalc) + timestep*(                                &
     
    13601362        END SUBROUTINE old_lmdz1d
    13611363
    1362 #include "old_1DUTILS_read_interp.h"
     1364        INCLUDE "old_1DUTILS_read_interp.h"
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/replay1d.F90

    r4482 r4727  
    1111
    1212      implicit none
    13 #include "dimensions.h"
     13      INCLUDE "dimensions.h"
    1414
    1515real :: airefi
     
    7575! Initialisation de la parametrisation
    7676!---------------------------------------------------------------------
    77 call get_ini_module
     77call call_ini_replay
    7878
    7979!---------------------------------------------------------------------
  • LMDZ6/branches/LMDZ_ECRad/libf/phylmd/dyn1d/scm.F90

    r4482 r4727  
    99       ftsol, beta_aridity, pbl_tke, pctsrf, radsol, rain_fall, snow_fall, ratqs, &
    1010       rnebcon, rugoro, sig1, w01, solaire_etat0, sollw, sollwdown, &
    11        solsw, solswfdiff, t_ancien, q_ancien, u_ancien, v_ancien, &
     11       solsw, solswfdiff, t_ancien, q_ancien, u_ancien, v_ancien, rneb_ancien, &
    1212       wake_delta_pbl_TKE, delta_tsurf, wake_fip, wake_pe, &
    1313       wake_deltaq, wake_deltat, wake_s, wake_dens, &
     
    4343
    4444      implicit none
    45 #include "dimensions.h"
    46 #include "YOMCST.h"
    47 !!#include "control.h"
    48 #include "clesphys.h"
    49 #include "dimsoil.h"
    50 !#include "indicesol.h"
    51 
    52 #include "compar1d.h"
    53 #include "flux_arp.h"
    54 #include "date_cas.h"
    55 #include "tsoilnudge.h"
    56 #include "fcg_gcssold.h"
    57 #include "compbl.h"
     45      INCLUDE "dimensions.h"
     46      INCLUDE "YOMCST.h"
     47!!      INCLUDE "control.h"
     48      INCLUDE "clesphys.h"
     49      INCLUDE "dimsoil.h"
     50!      INCLUDE "indicesol.h"
     51
     52      INCLUDE "compar1d.h"
     53      INCLUDE "flux_arp.h"
     54      INCLUDE "date_cas.h"
     55      INCLUDE "tsoilnudge.h"
     56      INCLUDE "fcg_gcssold.h"
     57      INCLUDE "compbl.h"
    5858
    5959!=====================================================================
     
    129129!=====================================================================
    130130!
    131 #include "1D_decl_cases.h"
     131      INCLUDE "1D_decl_cases.h"
    132132!
    133133!---------------------------------------------------------------------
     
    489489!=====================================================================
    490490
    491 #include "1D_read_forc_cases.h"
     491      INCLUDE "1D_read_forc_cases.h"
    492492   print*,'A d_t_adv ',d_t_adv(1:20)*86400
    493493
     
    678678        u_ancien(1,:)=u(:)
    679679        v_ancien(1,:)=v(:)
     680        rneb_ancien(1,:)=0.
    680681 
    681682        u10m=0.
     
    703704!------------------------------------------------------------------------
    704705!Al1 =============== restart option ======================================
     706        iflag_physiq=0
     707        call getin('iflag_physiq',iflag_physiq)
     708
    705709        if (.not.restart) then
    706710          iflag_pbl = 5
     
    803807!---------------------------------------------------------------------
    804808
    805 #include "1D_interp_cases.h"
     809      INCLUDE "1D_interp_cases.h"
    806810
    807811!---------------------------------------------------------------------
Note: See TracChangeset for help on using the changeset viewer.