Ignore:
Timestamp:
Oct 30, 2023, 5:37:00 PM (8 months ago)
Author:
Laurent Fairhead
Message:

Merge of ACC branch with 4740 revision from trunk

Location:
LMDZ6/branches/Portage_acc
Files:
36 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Portage_acc

  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/aeropt_spl.F

    r2630 r4743  
    1212      IMPLICIT none
    1313c
    14 #include "chem.h"
    15 #include "dimensions.h"
    16 c #include "dimphy.h"
    17 #include "YOMCST.h"
     14      INCLUDE "chem.h"
     15      INCLUDE "dimensions.h"
     16cINCLUDE "dimphy.h"
     17      INCLUDE "YOMCST.h"
    1818c
    1919c Arguments:
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/bcscav_spl.F

    r2630 r4743  
    99c=====================================================================
    1010c
    11 #include "dimensions.h"
    12 #include "chem.h"
    13 #include "YOMCST.h"
    14 #include "YOECUMF.h"
     11      INCLUDE "dimensions.h"
     12      INCLUDE "chem.h"
     13      INCLUDE "YOMCST.h"
     14      INCLUDE "YOECUMF.h"
    1515c
    1616      REAL pdtime, alpha_r, alpha_s, R_r, R_s
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/bl_for_dms.F

    r2630 r4743  
    1717c===================================================================
    1818c
    19 #include "dimensions.h"
    20 #include "YOMCST.h"
    21 #include "YOETHF.h"
    22 #include "FCTTRE.h"
     19      INCLUDE "dimensions.h"
     20      INCLUDE "YOMCST.h"
     21      INCLUDE "YOETHF.h"
     22      INCLUDE "FCTTRE.h"
    2323c
    2424c Arguments :
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/blcloud_scav.F

    r2630 r4743  
    1010      IMPLICIT NONE
    1111
    12 #include "dimensions.h"
    13 #include "chem.h"
    14 #include "YOMCST.h"
    15 #include "paramet.h"
     12      INCLUDE "dimensions.h"
     13      INCLUDE "chem.h"
     14      INCLUDE "YOMCST.h"
     15      INCLUDE "paramet.h"
    1616
    1717c============================= INPUT ===================================
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/blcloud_scav_lsc.F

    r2630 r4743  
    1010      IMPLICIT NONE
    1111
    12 #include "dimensions.h"
    13 #include "chem.h"
    14 #include "YOMCST.h"
    15 #include "paramet.h"
     12      INCLUDE "dimensions.h"
     13      INCLUDE "chem.h"
     14      INCLUDE "YOMCST.h"
     15      INCLUDE "paramet.h"
    1616
    1717c============================= INPUT ===================================
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/checkmass.F90

    r2630 r4743  
    44  IMPLICIT NONE
    55
    6 #include "YOMCST.h"
     6  INCLUDE "YOMCST.h"
    77
    88! Entrees
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/cltrac_spl.F

    r2630 r4743  
    2626c flux_tr--output-R- flux de tr
    2727c======================================================================
    28 #include "dimensions.h"
     28      INCLUDE "dimensions.h"
    2929      REAL dtime
    3030      REAL coef(klon,klev)
     
    3636c      REAL flux_tr(klon,klev)
    3737c======================================================================
    38 #include "YOMCST.h"
     38      INCLUDE "YOMCST.h"
    3939c======================================================================
    4040      INTEGER i, k
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/cm3_to_kg.F

    r2630 r4743  
    77      IMPLICIT NONE
    88c
    9 #include "dimensions.h"
    10 #include "YOMCST.h"
     9      INCLUDE "dimensions.h"
     10      INCLUDE "YOMCST.h"
    1111c     
    1212      REAL t_seri(klon,klev), pplay(klon,klev)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/coarsemission.F

    r2630 r4743  
    3333      IMPLICIT NONE
    3434
    35 #include "dimensions.h"
    36 #include "chem.h"
    37 #include "chem_spla.h"
    38 #include "YOMCST.h"
    39 #include "paramet.h"
     35      INCLUDE "dimensions.h"
     36      INCLUDE "chem.h"
     37      INCLUDE "chem_spla.h"
     38      INCLUDE "YOMCST.h"
     39      INCLUDE "paramet.h"
    4040     
    4141c============================== INPUT ==================================
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/condsurfc.F

    r2630 r4743  
    99! --------------------------------------------------------
    1010!
    11 #include "dimensions.h"
    12 #include "netcdf.inc"
     11      INCLUDE "dimensions.h"
     12      INCLUDE "netcdf.inc"
     13     
    1314      REAL lmt_bcff(klon), lmt_bcbb(klon),lmt_bc_penner(klon)
    1415      REAL lmt_omff(klon), lmt_ombb(klon)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/condsurfc_new.F

    r2630 r4743  
    1111c --------------------------------------------------------
    1212c
    13 #include "dimensions.h"
    14 #include "netcdf.inc"
     13      INCLUDE "dimensions.h"
     14      INCLUDE "netcdf.inc"
     15     
    1516      REAL lmt_bcff(klon), lmt_bcnff(klon), lmt_bcba(klon)
    1617      REAL lmt_omff(klon), lmt_omnff(klon), lmt_ombb(klon)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/condsurfs.F

    r2630 r4743  
    99c --------------------------------------------------------
    1010c
    11 #include "dimensions.h"
    12 #include "netcdf.inc"
     11      INCLUDE "dimensions.h"
     12      INCLUDE "netcdf.inc"
    1313c
    1414      REAL lmt_so2h(klon), lmt_so2b(klon), lmt_so2bb(klon)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/condsurfs_new.F

    r2630 r4743  
    1414c --------------------------------------------------------
    1515c
    16 #include "dimensions.h"
    17 #include "netcdf.inc"
     16      INCLUDE "dimensions.h"
     17      INCLUDE "netcdf.inc"
    1818c
    1919      REAL lmt_so2b(klon), lmt_so2h(klon), lmt_so2nff(klon)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/deposition.F

    r2630 r4743  
    1212      IMPLICIT NONE
    1313
    14 #include "dimensions.h"
    15 #include "chem.h"
    16 #include "YOMCST.h"
    17 #include "paramet.h"
     14      INCLUDE "dimensions.h"
     15      INCLUDE "chem.h"
     16      INCLUDE "YOMCST.h"
     17      INCLUDE "paramet.h"
    1818
    1919c----------------------------- INPUT -----------------------------------
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/finemission.F

    r2630 r4743  
    1717      IMPLICIT NONE
    1818
    19 #include "dimensions.h"
    20 #include "chem.h"
    21 #include "YOMCST.h"
    22 #include "paramet.h"
     19      INCLUDE "dimensions.h"
     20      INCLUDE "chem.h"
     21      INCLUDE "YOMCST.h"
     22      INCLUDE "paramet.h"
    2323
    2424      INTEGER i, k, kminbc, kmaxbc
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/gastoparticle.F

    r2630 r4743  
    1010      IMPLICIT NONE
    1111c
    12 #include "dimensions.h"
    13 #include "chem.h"
    14 #include "chem_spla.h"
    15 #include "YOMCST.h"
    16 #include "YOECUMF.h"
     12      INCLUDE "dimensions.h"
     13      INCLUDE "chem.h"
     14      INCLUDE "chem_spla.h"
     15      INCLUDE "YOMCST.h"
     16      INCLUDE "YOECUMF.h"
    1717c
    1818      REAL pdtphys
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/incloud_scav.F

    r2630 r4743  
    1111      IMPLICIT NONE
    1212
    13 #include "dimensions.h"
    14 #include "chem.h"
    15 #include "YOMCST.h"
    16 #include "paramet.h"
     13      INCLUDE "dimensions.h"
     14      INCLUDE "chem.h"
     15      INCLUDE "YOMCST.h"
     16      INCLUDE "paramet.h"
    1717
    1818c============================= INPUT ===================================
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/incloud_scav_lsc.F

    r2630 r4743  
    1111      IMPLICIT NONE
    1212
    13 #include "dimensions.h"
    14 #include "chem.h"
    15 #include "YOMCST.h"
    16 #include "paramet.h"
     13      INCLUDE "dimensions.h"
     14      INCLUDE "chem.h"
     15      INCLUDE "YOMCST.h"
     16      INCLUDE "paramet.h"
    1717
    1818c============================= INPUT ===================================
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/inscav_spl.F

    r2630 r4743  
    1010c=====================================================================
    1111c
    12 #include "dimensions.h"
    13 #include "chem.h"
    14 #include "YOMCST.h"
    15 #include "YOECUMF.h"
     12      INCLUDE "dimensions.h"
     13      INCLUDE "chem.h"
     14      INCLUDE "YOMCST.h"
     15      INCLUDE "YOECUMF.h"
    1616c
    1717      INTEGER it
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/kg_to_cm3.F

    r2630 r4743  
    55      IMPLICIT NONE
    66c
    7 #include "dimensions.h"
    8 #include "YOMCST.h"
     7      INCLUDE "dimensions.h"
     8      INCLUDE "YOMCST.h"
    99c     
    1010      REAL t_seri(klon,klev), pplay(klon,klev)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/minmaxqfi2.F

    r2630 r4743  
    33      USE dimphy
    44      USE infotrac
    5 #include "dimensions.h"
     5      INCLUDE "dimensions.h"
    66
    77!      character*20 comment
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/minmaxsource.F

    r2630 r4743  
    44      USE infotrac
    55
    6 #include "dimensions.h"
     6      INCLUDE "dimensions.h"
    77
    88!      character*20 comment
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/neutral.F

    r2630 r4743  
    2828c
    2929      USE dimphy
    30 #include "dimensions.h"
     30      INCLUDE "dimensions.h"
    3131c
    3232        real u10_mps(klon),ustar_mps(klon),obklen_m(klon)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/nightingale.F

    r2630 r4743  
    77      IMPLICIT NONE
    88c
    9 #include "dimensions.h"
    10 #include "YOMCST.h"
     9      INCLUDE "dimensions.h"
     10      INCLUDE "YOMCST.h"
    1111c
    1212      REAL u(klon,klev), v(klon,klev)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r4446 r4743  
    389389    USE iophy, ONLY: set_itau_iophy, histwrite_phy
    390390    USE netcdf, ONLY: nf90_fill_real
    391 
    392 #ifdef CPP_XIOS
    393391    ! ug Pour les sorties XIOS
    394     USE xios, ONLY: xios_update_calendar
    395     USE wxios, ONLY: wxios_closedef, missing_val
    396 #endif
     392    USE lmdz_xios, ONLY: xios_update_calendar, using_xios
     393    USE wxios, ONLY: wxios_closedef, missing_val_xios => missing_val
    397394    USE phys_cal_mod, ONLY : mth_len
    398395
     
    438435    INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d
    439436    REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2
    440 !   REAL, PARAMETER :: missing_val=nf90_fill_real
    441 #ifndef CPP_XIOS
    442437    REAL :: missing_val
    443 #endif
    444438    REAL, PARAMETER :: un_jour=86400.
     439
     440    IF (using_xios) THEN
     441      missing_val=missing_val_xios
     442    ELSE
     443      missing_val=nf90_fill_real
     444    ENDIF
    445445
    446446    ! On calcul le nouveau tau:
     
    460460    ! ug la boucle qui suit ne sert qu'une fois, pour l'initialisation, sinon il n'y a toujours qu'un seul passage:
    461461    DO iinit=1, iinitend
    462 #ifdef CPP_XIOS
    463        !$OMP MASTER
    464        IF (vars_defined) THEN
    465           IF (prt_level >= 10) THEN
    466              write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
    467           ENDIF
    468 !          CALL xios_update_calendar(itau_w)
    469           CALL xios_update_calendar(itap)
    470        ENDIF
    471        !$OMP END MASTER
    472        !$OMP BARRIER
    473 #endif
     462       IF (using_xios) THEN
     463         !$OMP MASTER
     464         IF (vars_defined) THEN
     465            IF (prt_level >= 10) THEN
     466               write(lunout,*)"phys_output_write: call xios_update_calendar, itau_w=",itau_w
     467            ENDIF
     468!           CALL xios_update_calendar(itau_w)
     469            CALL xios_update_calendar(itap)
     470         ENDIF
     471         !$OMP END MASTER
     472         !$OMP BARRIER
     473       ENDIF !using_xios
     474
    474475       ! On procède à l'écriture ou à la définition des nombreuses variables:
    475476!!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    489490!!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    490491! JE20141223 <<
    491 #include "spla_output_write.h"
     492       INCLUDE "spla_output_write.h"
    492493! JE20141223 >>
    493494
     
    828829
    829830#ifdef CPP_IOIPSL
    830 #ifndef CPP_XIOS
    831   IF (.NOT.ok_all_xml) THEN
    832        ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    833        ! Champs interpolles sur des niveaux de pression
    834        missing_val=missing_val_nf90
    835        DO iff=1, nfiles
    836           ll=0
    837           DO k=1, nlevSTD
    838              bb2=clevSTD(k)
    839              IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
    840                   bb2.EQ."500".OR.bb2.EQ."200".OR. &
    841                   bb2.EQ."100".OR. &
    842                   bb2.EQ."50".OR.bb2.EQ."10") THEN
    843 
    844                 ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    845                 ll=ll+1
    846                 CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
    847                 CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
    848                 CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
    849                 CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
    850                 CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
    851                 CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
    852 
    853              ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
    854           ENDDO
    855        ENDDO
    856   ENDIF
     831  IF (.NOT. using_xios) THEN
     832    IF (.NOT.ok_all_xml) THEN
     833         ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
     834         ! Champs interpolles sur des niveaux de pression
     835         DO iff=1, nfiles
     836           ll=0
     837            DO k=1, nlevSTD
     838               bb2=clevSTD(k)
     839               IF (bb2.EQ."850".OR.bb2.EQ."700".OR. &
     840                    bb2.EQ."500".OR.bb2.EQ."200".OR. &
     841                    bb2.EQ."100".OR. &
     842                    bb2.EQ."50".OR.bb2.EQ."10") THEN
     843
     844                  ! a refaire correctement !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     845                  ll=ll+1
     846                  CALL histwrite_phy(o_uSTDlevs(ll),uwriteSTD(:,k,iff), iff)
     847                  CALL histwrite_phy(o_vSTDlevs(ll),vwriteSTD(:,k,iff), iff)
     848                  CALL histwrite_phy(o_wSTDlevs(ll),wwriteSTD(:,k,iff), iff)
     849                  CALL histwrite_phy(o_zSTDlevs(ll),phiwriteSTD(:,k,iff), iff)
     850                  CALL histwrite_phy(o_qSTDlevs(ll),qwriteSTD(:,k,iff), iff)
     851                  CALL histwrite_phy(o_tSTDlevs(ll),twriteSTD(:,k,iff), iff)
     852
     853               ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
     854            ENDDO
     855         ENDDO
     856    ENDIF
     857  ENDIF !.NOT.using_xios
    857858#endif
    858 #endif
    859 
    860 #ifdef CPP_XIOS
    861   IF (ok_all_xml) THEN
    862 !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
    863 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     859
     860  IF (using_xios) THEN
     861    IF (ok_all_xml) THEN
     862  !XIOS  CALL xios_get_field_attr("u850",default_value=missing_val)
     863  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    864864          ll=0
    865865          DO k=1, nlevSTD
     
    878878             ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR.
    879879          ENDDO
    880   ENDIF
    881 #endif
     880    ENDIF
     881  ENDIF !using_xios
    882882       IF (vars_defined) THEN
    883883          DO i=1, klon
     
    14711471!!!!!!!!!!!! Sorties niveaux de pression NMC !!!!!!!!!!!!!!!!!!!!
    14721472#ifdef CPP_IOIPSL
    1473 #ifndef CPP_XIOS
    1474   IF (.NOT.ok_all_xml) THEN
    1475        ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
    1476        ! Champs interpolles sur des niveaux de pression
    1477        missing_val=missing_val_nf90
     1473
     1474  IF (.NOT. using_xios) THEN
     1475    IF (.NOT.ok_all_xml) THEN
     1476         ! ATTENTION, LES ANCIENS HISTWRITE ONT ETES CONSERVES EN ATTENDANT MIEUX:
     1477         ! Champs interpolles sur des niveaux de pression
    14781478       DO iff=7, nfiles-1 !--here we deal with files 7,8 and 9
    14791479
     
    15391539          CALL histwrite_phy(o_TxT,T2sumSTD(:,:,iff-6),iff)
    15401540       ENDDO !nfiles
     1541    ENDIF
    15411542  ENDIF
    15421543#endif
    1543 #endif
    1544 #ifdef CPP_XIOS
     1544
     1545IF (using_xios) THEN
    15451546  IF (ok_all_xml) THEN
    15461547!      DO iff=7, nfiles
     
    16071608          CALL histwrite_phy(o_TxT,T2STD(:,:))
    16081609!      ENDDO !nfiles
    1609   ENDIF
    1610 #endif
     1610    ENDIF
     1611  ENDIF !using_xios
    16111612!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    16121613           itr = 0
     
    16511652          ENDDO !  iff
    16521653#endif
    1653 #ifdef CPP_XIOS
    16541654          !On finalise l'initialisation:
    1655           CALL wxios_closedef()
    1656 #endif
     1655          IF (using_xios) CALL wxios_closedef()
    16571656
    16581657          !$OMP END MASTER
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/phytracr_spl_mod.F90

    r4446 r4743  
    804804
    805805      USE mod_phys_lmdz_transfert_para
    806 
    807   USE phys_cal_mod, only: jD_1jan,year_len, mth_len, days_elapsed, jh_1jan, year_cur, &
    808        mth_cur, phys_cal_update
     806      USE lmdz_thermcell_dq,  ONLY : thermcell_dq
     807      USE phys_cal_mod, only: jD_1jan,year_len, mth_len, days_elapsed, jh_1jan, year_cur, &
     808                              mth_cur, phys_cal_update
    809809
    810810!
     
    823823!!   et c'est encore different avec le parser de DC ?
    824824!======================================================================
    825 #include "dimensions.h"
    826 #include "chem.h"
    827 #include "chem_spla.h"
    828 #include "YOMCST.h"
    829 #include "YOETHF.h"
    830 #include "paramet.h"
    831 #include "alpale.h"
     825      INCLUDE "dimensions.h"
     826      INCLUDE "chem.h"
     827      INCLUDE "chem_spla.h"
     828      INCLUDE "YOMCST.h"
     829      INCLUDE "YOETHF.h"
     830      INCLUDE "paramet.h"
     831      INCLUDE "alpale.h"
    832832
    833833!======================================================================
     
    10701070!----------
    10711071      REAL,DIMENSION(klon,klev+1),INTENT(IN)   :: fm_therm
    1072       REAL,DIMENSION(klon,klev),INTENT(IN)     :: entr_therm
     1072      REAL,DIMENSION(klon,klev),INTENT(INOUT)     :: entr_therm
    10731073
    10741074
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/precuremission.F

    r2630 r4743  
    2222      IMPLICIT NONE
    2323
    24 #include "dimensions.h"
    25 #include "chem.h"
    26 #include "chem_spla.h"
    27 #include "YOMCST.h"
    28 #include "paramet.h"
     24      INCLUDE "dimensions.h"
     25      INCLUDE "chem.h"
     26      INCLUDE "chem_spla.h"
     27      INCLUDE "YOMCST.h"
     28      INCLUDE "paramet.h"
    2929
    3030c============================= INPUT ===================================
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/read_dust.F

    r3786 r4743  
    55      IMPLICIT NONE
    66c
    7 #include "dimensions.h"
    8 #include "paramet.h"
    9 #include "netcdf.inc"
     7      INCLUDE "dimensions.h"
     8      INCLUDE "paramet.h"
     9      INCLUDE "netcdf.inc"
    1010c
    1111      INTEGER step, nbjour
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/read_newemissions.F

    r3786 r4743  
    2626
    2727
    28 #include "dimensions.h"
     28      INCLUDE "dimensions.h"
    2929c      INCLUDE 'dimphy.h'     
    3030      INCLUDE 'paramet.h'     
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/read_surface.F90

    r2630 r4743  
    1313       IMPLICIT NONE
    1414
    15        include "netcdf.inc"
    16 #include "dimensions.h"
    17 #include "paramet.h"
     15       INCLUDE "netcdf.inc"
     16       INCLUDE "dimensions.h"
     17       INCLUDE "paramet.h"
    1818
    1919       character*10 name
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/read_vent.F

    r3806 r4743  
    55!      USE write_field_phy
    66      IMPLICIT NONE
    7 #include "dimensions.h"
    8 c #include "dimphy.h"
    9 #include "paramet.h"
    10 #include "netcdf.inc"
     7      INCLUDE "dimensions.h"
     8c       INCLUDE "dimphy.h"
     9      INCLUDE "paramet.h"
     10      INCLUDE "netcdf.inc"
    1111c
    1212      INTEGER step, nbjour
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/seasalt.F

    r2630 r4743  
    77      IMPLICIT NONE
    88c
    9 #include "dimensions.h"
    10 #include "chem.h"
    11 #include "chem_spla.h"
    12 #include "YOMCST.h"
    13 #include "YOECUMF.h"
     9      INCLUDE "dimensions.h"
     10      INCLUDE "chem.h"
     11      INCLUDE "chem_spla.h"
     12      INCLUDE "YOMCST.h"
     13      INCLUDE "YOECUMF.h"
    1414c
    1515      INTEGER i, bin                 !local variables
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/sediment_mod.F

    r2630 r4743  
    1212      IMPLICIT NONE
    1313c
    14 #include "dimensions.h"
    15 #include "chem.h"
    16 c #include "dimphy.h"
    17 #include "YOMCST.h"
    18 #include "YOECUMF.h"
     14      INCLUDE "dimensions.h"
     15      INCLUDE "chem.h"
     16c       INCLUDE "dimphy.h"
     17      INCLUDE "YOMCST.h"
     18      INCLUDE "YOECUMF.h"
    1919c
    2020       REAL RHcl(klon,klev)     ! humidite relative ciel clair
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/tiedqneg.F

    r2630 r4743  
    1515c======================================================================
    1616c
    17 #include "dimensions.h"
    18 c #include "dimphy.h"
     17      INCLUDE "dimensions.h"
     18c       INCLUDE "dimphy.h"
    1919      REAL pres_h(klon,klev+1)
    2020      REAL q(klon,klev)
  • LMDZ6/branches/Portage_acc/libf/phylmd/Dust/trconvect.F

    r2630 r4743  
    1010      IMPLICIT NONE
    1111
    12 #include "dimensions.h"
    13 #include "chem.h"
    14 #include "YOMCST.h"
    15 #include "paramet.h"
     12      INCLUDE "dimensions.h"
     13      INCLUDE "chem.h"
     14      INCLUDE "YOMCST.h"
     15      INCLUDE "paramet.h"
    1616
    1717c============================= INPUT ===================================
Note: See TracChangeset for help on using the changeset viewer.