Ignore:
Timestamp:
Jul 26, 2024, 5:56:37 PM (17 months ago)
Author:
abarral
Message:

Replace academic.h, alpale.h, comdissip.h, comdissipn.h, comdissnew.h by modules
Remove unused clesph0.h

Location:
LMDZ6/branches/Amaury_dev/libf/dyn3dmem
Files:
56 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/addfi_loc.f90

    r5123 r5134  
    4747  !    ------------------
    4848  !
    49   include "dimensions.h"
    50   include "paramet.h"
    51   include "comgeom.h"
     49  INCLUDE "dimensions.h"
     50  INCLUDE "paramet.h"
     51  INCLUDE "comgeom.h"
    5252  !
    5353  !    Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/advect_new_loc.f90

    r5123 r5134  
    3030  !   -------------
    3131
    32   include "dimensions.h"
    33   include "paramet.h"
    34   include "comgeom.h"
     32  INCLUDE "dimensions.h"
     33  INCLUDE "paramet.h"
     34  INCLUDE "comgeom.h"
    3535
    3636  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/advtrac_loc.f90

    r5128 r5134  
    2121  USE lmdz_description, ONLY: descript
    2222  USE lmdz_libmath, ONLY: minmax
    23 
     23  USE lmdz_comdissip, ONLY: coefdis, tetavel, tetatemp, gamdissip, niterdis
    2424
    2525  IMPLICIT NONE
    2626
    27   include "dimensions.h"
    28   include "paramet.h"
    29   include "comdissip.h"
    30   include "comgeom2.h"
     27  INCLUDE "dimensions.h"
     28  INCLUDE "paramet.h"
     29  INCLUDE "comgeom2.h"
    3130
    3231  !---------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/bands.F90

    r5119 r5134  
    4444    IMPLICIT NONE
    4545
    46     include "dimensions.h"
     46    INCLUDE "dimensions.h"
    4747      INTEGER :: i,j
    4848      CHARACTER (LEN=4) :: siim,sjjm,sllm,sproc
     
    438438    USE parallel_lmdz
    439439    IMPLICIT NONE
    440     include "dimensions.h"
     440    INCLUDE "dimensions.h"
    441441
    442442      INTEGER :: i,j
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/bernoui_loc.f90

    r5117 r5134  
    2424  !   -------------
    2525  !
    26   include "dimensions.h"
    27   include "paramet.h"
     26  INCLUDE "dimensions.h"
     27  INCLUDE "paramet.h"
    2828  !
    2929  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/bilan_dyn_loc.f90

    r5128 r5134  
    2323  IMPLICIT NONE
    2424
    25   include "dimensions.h"
    26   include "paramet.h"
    27   include "comgeom2.h"
     25  INCLUDE "dimensions.h"
     26  INCLUDE "paramet.h"
     27  INCLUDE "comgeom2.h"
    2828
    2929  !====================================================================
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/caladvtrac_loc.f90

    r5117 r5134  
    2828  !=======================================================================
    2929
    30   include "dimensions.h"
    31   include "paramet.h"
     30  INCLUDE "dimensions.h"
     31  INCLUDE "paramet.h"
    3232
    3333  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/caldyn_loc.f90

    r5117 r5134  
    2929  !   ----------------
    3030
    31   include "dimensions.h"
    32   include "paramet.h"
    33   include "comgeom.h"
     31  INCLUDE "dimensions.h"
     32  INCLUDE "paramet.h"
     33  INCLUDE "comgeom.h"
    3434
    3535  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/check_isotopes_loc.F90

    r5128 r5134  
    77
    88   IMPLICIT NONE
    9    include "dimensions.h"
     9   INCLUDE "dimensions.h"
    1010   REAL,             INTENT(INOUT) :: q(ijb_u:ije_u,llm,nqtot)
    1111   INTEGER,          INTENT(IN)    :: ijb, ije   !--- Can be local and different from ijb_u,ije_u, for example in qminimum
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/conf_gcm.F90

    r5128 r5134  
    2222  USE temps_mod, ONLY: calend, year_len, offline_time
    2323  USE lmdz_iniprint, ONLY: lunout, prt_level
    24 
     24  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     25          tetagrot, tetatemp, coefdis, vert_prof_dissip
    2526
    2627  IMPLICIT NONE
     
    3940  !   Declarations :
    4041  !   --------------
    41   include "dimensions.h"
    42   include "paramet.h"
    43   include "comdissnew.h"
     42  INCLUDE "dimensions.h"
     43  INCLUDE "paramet.h"
    4444
    4545  !   local:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/convmas1_loc.F90

    r5106 r5134  
    99  USE lmdz_filtreg_p
    1010  IMPLICIT NONE
    11   include "dimensions.h"
    12   include "paramet.h"
    13   include "comgeom.h"
     11  INCLUDE "dimensions.h"
     12  INCLUDE "paramet.h"
     13  INCLUDE "comgeom.h"
    1414!===============================================================================
    1515! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/convmas2_loc.F90

    r5106 r5134  
    88  USE parallel_lmdz
    99  IMPLICIT NONE
    10   include "dimensions.h"
    11   include "paramet.h"
    12   include "comgeom.h"
     10  INCLUDE "dimensions.h"
     11  INCLUDE "paramet.h"
     12  INCLUDE "comgeom.h"
    1313!===============================================================================
    1414! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/convmas_loc.F90

    r5106 r5134  
    88  USE lmdz_filtreg_p
    99  IMPLICIT NONE
    10   include "dimensions.h"
    11   include "paramet.h"
    12   include "comgeom.h"
     10  INCLUDE "dimensions.h"
     11  INCLUDE "paramet.h"
     12  INCLUDE "comgeom.h"
    1313!===============================================================================
    1414! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dissip_loc.f90

    r5123 r5134  
    88  USE comconst_mod, ONLY: dtdiss
    99  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_DEBUGIO
     10  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
     11  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     12          tetagrot, tetatemp, coefdis, vert_prof_dissip
     13
    1014  IMPLICIT NONE
    1115
     
    2933  !   -------------
    3034
    31   include "dimensions.h"
    32   include "paramet.h"
    33   include "comgeom.h"
    34   include "comdissnew.h"
    35   include "comdissipn.h"
     35  INCLUDE "dimensions.h"
     36  INCLUDE "paramet.h"
     37  INCLUDE "comgeom.h"
    3638
    3739  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/divgrad2_loc.f90

    r5106 r5134  
    1414  USE mod_hallo
    1515  USE divgrad2_mod
     16  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
     17
    1618  IMPLICIT NONE
    1719  !
     
    1921  INCLUDE "paramet.h"
    2022  INCLUDE "comgeom2.h"
    21   INCLUDE "comdissipn.h"
    2223
    2324  !    .......    variables en arguments   .......
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dteta1_loc.f90

    r5117 r5134  
    2121
    2222
    23   include "dimensions.h"
    24   include "paramet.h"
     23  INCLUDE "dimensions.h"
     24  INCLUDE "paramet.h"
    2525
    2626  REAL :: teta( ijb_u:ije_u,llm )
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dudv2_loc.f90

    r5117 r5134  
    2323  !=======================================================================
    2424  !
    25   include "dimensions.h"
    26   include "paramet.h"
     25  INCLUDE "dimensions.h"
     26  INCLUDE "paramet.h"
    2727
    2828  REAL :: teta( ijb_u:ije_u,llm ),pkf( ijb_u:ije_u,llm )
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dynetat0_loc.F90

    r5128 r5134  
    2626
    2727  IMPLICIT NONE
    28   include "dimensions.h"
    29   include "paramet.h"
    30   include "comgeom.h"
     28  INCLUDE "dimensions.h"
     29  INCLUDE "paramet.h"
     30  INCLUDE "comgeom.h"
    3131!===============================================================================
    3232! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/dynredem_loc.F90

    r5118 r5134  
    2525
    2626  IMPLICIT NONE
    27   include "dimensions.h"
    28   include "paramet.h"
    29   include "comgeom.h"
     27  INCLUDE "dimensions.h"
     28  INCLUDE "paramet.h"
     29  INCLUDE "comgeom.h"
    3030  !===============================================================================
    3131  ! Arguments:
     
    178178
    179179  IMPLICIT NONE
    180   include "dimensions.h"
    181   include "paramet.h"
    182   include "comgeom.h"
     180  INCLUDE "dimensions.h"
     181  INCLUDE "paramet.h"
     182  INCLUDE "comgeom.h"
    183183  !===============================================================================
    184184  ! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/enercin_loc.F90

    r5106 r5134  
    77  USE parallel_lmdz
    88  IMPLICIT NONE
    9   include "dimensions.h"
    10   include "paramet.h"
    11   include "comgeom.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
     11  INCLUDE "comgeom.h"
    1212!===============================================================================
    1313! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/exner_hyb_loc_m.F90

    r5128 r5134  
    4141    IMPLICIT NONE
    4242
    43     include "dimensions.h"
    44     include "paramet.h"
    45     include "comgeom.h"
     43    INCLUDE "dimensions.h"
     44    INCLUDE "paramet.h"
     45    INCLUDE "comgeom.h"
    4646
    4747    INTEGER  ngrid
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/exner_milieu_loc_m.F90

    r5128 r5134  
    3737    IMPLICIT NONE
    3838
    39     include "dimensions.h"
    40     include "paramet.h"
    41     include "comgeom.h"
     39    INCLUDE "dimensions.h"
     40    INCLUDE "paramet.h"
     41    INCLUDE "comgeom.h"
    4242
    4343    INTEGER  ngrid
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/flumass_loc.F90

    r5099 r5134  
    77  USE parallel_lmdz
    88  IMPLICIT NONE
    9   include "dimensions.h"
    10   include "paramet.h"
    11   include "comgeom.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
     11  INCLUDE "comgeom.h"
    1212!===============================================================================
    1313! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/fluxstokenc_p.f90

    r5117 r5134  
    2424  !=======================================================================
    2525
    26   include "dimensions.h"
    27   include "paramet.h"
    28   include "tracstoke.h"
     26  INCLUDE "dimensions.h"
     27  INCLUDE "paramet.h"
     28  INCLUDE "tracstoke.h"
    2929
    3030  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/friction_loc.f90

    r5128 r5134  
    88  USE comconst_mod, ONLY: pi
    99  USE lmdz_iniprint, ONLY: lunout, prt_level
    10 
     10  USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4
    1111
    1212  IMPLICIT NONE
     
    2424  !=======================================================================
    2525
    26   include "dimensions.h"
    27   include "paramet.h"
    28   include "comgeom2.h"
    29   include "academic.h"
     26  INCLUDE "dimensions.h"
     27  INCLUDE "paramet.h"
     28  INCLUDE "comgeom2.h"
    3029
    3130  ! arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gcm.F90

    r5128 r5134  
    2727  USE lmdz_description, ONLY: descript
    2828  USE lmdz_iniprint, ONLY: lunout, prt_level
    29 
     29  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     30          tetagrot, tetatemp, coefdis, vert_prof_dissip
    3031
    3132  IMPLICIT NONE
     
    6061  !   Declarations:
    6162  !   -------------
    62   include "dimensions.h"
    63   include "paramet.h"
    64   include "comdissnew.h"
    65   include "comgeom.h"
    66   include "tracstoke.h"
     63  INCLUDE "dimensions.h"
     64  INCLUDE "paramet.h"
     65  INCLUDE "comgeom.h"
     66  INCLUDE "tracstoke.h"
    6767
    6868  REAL zdtvr
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/geopot_loc.f90

    r5106 r5134  
    2626  !   -------------
    2727
    28   include "dimensions.h"
    29   include "paramet.h"
     28  INCLUDE "dimensions.h"
     29  INCLUDE "paramet.h"
    3030
    3131  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/gradiv2_loc.f90

    r5117 r5134  
    1919  USE lmdz_filtreg_p
    2020  USE gradiv2_mod
     21  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
     22
    2123  IMPLICIT NONE
    2224  !
     
    2426  INCLUDE "paramet.h"
    2527  INCLUDE "comgeom.h"
    26   INCLUDE "comdissipn.h"
    2728  !
    2829  ! ........    variables en arguments      ........
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/groupe_loc.f90

    r5117 r5134  
    1818  !   pas besoin de w en entree.
    1919
    20   include "dimensions.h"
    21   include "paramet.h"
    22   include "comgeom2.h"
     20  INCLUDE "dimensions.h"
     21  INCLUDE "paramet.h"
     22  INCLUDE "comgeom2.h"
    2323
    2424  ! integer ngroup
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/groupeun_loc.f90

    r5105 r5134  
    55  IMPLICIT NONE
    66
    7   include "dimensions.h"
    8   include "paramet.h"
    9   include "comgeom2.h"
     7  INCLUDE "dimensions.h"
     8  INCLUDE "paramet.h"
     9  INCLUDE "comgeom2.h"
    1010
    1111  INTEGER :: jjmax,llmax,sb,se,jjb,jje
     
    139139  IMPLICIT NONE
    140140
    141   include "dimensions.h"
    142   include "paramet.h"
    143   include "comgeom2.h"
     141  INCLUDE "dimensions.h"
     142  INCLUDE "paramet.h"
     143  INCLUDE "comgeom2.h"
    144144
    145145  ! INTEGER ngroup
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/guide_loc_mod.F90

    r5128 r5134  
    916916    IMPLICIT NONE
    917917
    918     include "dimensions.h"
    919     include "paramet.h"
    920     include "comgeom2.h"
     918    INCLUDE "dimensions.h"
     919    INCLUDE "paramet.h"
     920    INCLUDE "comgeom2.h"
    921921
    922922    REAL, DIMENSION (iip1, jjb_u:jje_u), INTENT(IN) :: psi ! Psol gcm
     
    14001400    IMPLICIT NONE
    14011401
    1402     include "dimensions.h"
    1403     include "paramet.h"
    1404     include "comgeom2.h"
     1402    INCLUDE "dimensions.h"
     1403    INCLUDE "paramet.h"
     1404    INCLUDE "comgeom2.h"
    14051405
    14061406    ! input arguments :
     
    15661566    IMPLICIT NONE
    15671567
    1568     include "dimensions.h"
    1569     include "paramet.h"
     1568    INCLUDE "dimensions.h"
     1569    INCLUDE "paramet.h"
    15701570
    15711571    INTEGER, INTENT(IN) :: timestep
     
    18811881    IMPLICIT NONE
    18821882
    1883     include "dimensions.h"
    1884     include "paramet.h"
     1883    INCLUDE "dimensions.h"
     1884    INCLUDE "paramet.h"
    18851885
    18861886    INTEGER, INTENT(IN) :: timestep
     
    23802380    USE mod_hallo
    23812381    IMPLICIT NONE
    2382     include 'dimensions.h'
    2383     include 'paramet.h'
     2382    INCLUDE 'dimensions.h'
     2383    INCLUDE 'paramet.h'
    23842384
    23852385    CHARACTER (len = *) :: varname
     
    24082408  SUBROUTINE dumpall
    24092409    IMPLICIT NONE
    2410     include "dimensions.h"
    2411     include "paramet.h"
    2412     include "comgeom.h"
     2410    INCLUDE "dimensions.h"
     2411    INCLUDE "paramet.h"
     2412    INCLUDE "comgeom.h"
    24132413    CALL barrier
    24142414    CALL dump2du(alpha_u(ijb_u:ije_u), '  alpha_u couche 1')
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/iniacademic_loc.F90

    r5128 r5134  
    2020  USE lmdz_ran1, ONLY: ran1
    2121  USE lmdz_iniprint, ONLY: lunout, prt_level
    22 
     22  USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4
    2323
    2424  !   Author:    Frederic Hourdin      original: 15/01/93
     
    3131  !   ---------------
    3232
    33   include "dimensions.h"
    34   include "paramet.h"
    35   include "comgeom.h"
    36   include "academic.h"
     33  INCLUDE "dimensions.h"
     34  INCLUDE "paramet.h"
     35  INCLUDE "comgeom.h"
    3736
    3837  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/initdynav_loc.f90

    r5118 r5134  
    4444  !
    4545  !   Declarations
    46   include "dimensions.h"
    47   include "paramet.h"
    48   include "comgeom.h"
     46  INCLUDE "dimensions.h"
     47  INCLUDE "paramet.h"
     48  INCLUDE "comgeom.h"
    4949
    5050  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/initfluxsto_p.f90

    r5118 r5134  
    4141  !
    4242  !   Declarations
    43   include "dimensions.h"
    44   include "paramet.h"
    45   include "comgeom.h"
     43  INCLUDE "dimensions.h"
     44  INCLUDE "paramet.h"
     45  INCLUDE "comgeom.h"
    4646
    4747  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/inithist_loc.F90

    r5118 r5134  
    4242  !
    4343  !   Declarations
    44   include "dimensions.h"
    45   include "paramet.h"
    46   include "comgeom.h"
     44  INCLUDE "dimensions.h"
     45  INCLUDE "paramet.h"
     46  INCLUDE "comgeom.h"
    4747
    4848  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/integrd_loc.f90

    r5128 r5134  
    3838  !   -------------
    3939
    40   include "dimensions.h"
    41   include "paramet.h"
    42   include "comgeom.h"
     40  INCLUDE "dimensions.h"
     41  INCLUDE "paramet.h"
     42  INCLUDE "comgeom.h"
    4343
    4444  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/leapfrog_loc.F90

    r5128 r5134  
    4242  USE lmdz_description, ONLY: descript
    4343  USE lmdz_iniprint, ONLY: lunout, prt_level
    44 
     44  USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4
     45  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     46          tetagrot, tetatemp, coefdis, vert_prof_dissip
    4547
    4648  IMPLICIT NONE
     
    7779  !   -------------
    7880
    79   include "dimensions.h"
    80   include "paramet.h"
    81   include "comdissnew.h"
    82   include "comgeom.h"
    83   include "academic.h"
     81  INCLUDE "dimensions.h"
     82  INCLUDE "paramet.h"
     83  INCLUDE "comgeom.h"
    8484
    8585  REAL, INTENT(IN) :: time_0 ! not used
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massbar_loc.F90

    r5099 r5134  
    88  USE parallel_lmdz
    99  IMPLICIT NONE
    10   include "dimensions.h"
    11   include "paramet.h"
    12   include "comgeom.h"
     10  INCLUDE "dimensions.h"
     11  INCLUDE "paramet.h"
     12  INCLUDE "comgeom.h"
    1313!===============================================================================
    1414! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massbarxy_loc.F90

    r5099 r5134  
    88  USE parallel_lmdz
    99  IMPLICIT NONE
    10   include "dimensions.h"
    11   include "paramet.h"
    12   include "comgeom.h"
     10  INCLUDE "dimensions.h"
     11  INCLUDE "paramet.h"
     12  INCLUDE "comgeom.h"
    1313!===============================================================================
    1414! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/massdair_loc.f90

    r5123 r5134  
    1616  IMPLICIT NONE
    1717  !
    18   include "dimensions.h"
    19   include "paramet.h"
    20   include "comgeom.h"
     18  INCLUDE "dimensions.h"
     19  INCLUDE "paramet.h"
     20  INCLUDE "comgeom.h"
    2121  !
    2222  !  .....   arguments  ....
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/mod_xios_dyn3dmem.F90

    r5117 r5134  
    133133     USE parallel_lmdz
    134134     IMPLICIT NONE
    135      include 'dimensions.h'
    136      include 'paramet.h'
     135     INCLUDE 'dimensions.h'
     136     INCLUDE 'paramet.h'
    137137     CHARACTER(LEN=*)   :: name
    138138     REAL, DIMENSION(ij_begin:ij_end) :: Field
     
    154154     USE parallel_lmdz
    155155     IMPLICIT NONE
    156      include 'dimensions.h'
    157      include 'paramet.h'
     156     INCLUDE 'dimensions.h'
     157     INCLUDE 'paramet.h'
    158158     CHARACTER(LEN=*)   :: name
    159159     REAL, DIMENSION(ij_begin:ij_end,llm) :: Field
     
    187187     USE parallel_lmdz
    188188     IMPLICIT NONE
    189      include 'dimensions.h'
    190      include 'paramet.h'
     189     INCLUDE 'dimensions.h'
     190     INCLUDE 'paramet.h'
    191191     CHARACTER(LEN=*)   :: name
    192192     REAL, DIMENSION(ij_begin:ij_end) :: Field
     
    217217     USE parallel_lmdz
    218218     IMPLICIT NONE
    219      include 'dimensions.h'
    220      include 'paramet.h'
     219     INCLUDE 'dimensions.h'
     220     INCLUDE 'paramet.h'
    221221     CHARACTER(LEN=*)   :: name
    222222     REAL, DIMENSION(ij_begin:ij_end,llm) :: Field
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/nxgraro2_loc.f90

    r5117 r5134  
    1818  USE lmdz_filtreg_p
    1919  USE nxgraro2_mod
     20  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
     21
    2022  IMPLICIT NONE
    2123  !
    2224  INCLUDE "dimensions.h"
    2325  INCLUDE "paramet.h"
    24   INCLUDE "comdissipn.h"
    2526  !
    2627  !    ......  variables en arguments  .......
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/parallel_lmdz.F90

    r5128 r5134  
    392392#endif
    393393
    394     include "dimensions.h"
    395     include "paramet.h"
     394    INCLUDE "dimensions.h"
     395    INCLUDE "paramet.h"
    396396
    397397    INTEGER :: ierr
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/paramet.h

    r5128 r5134  
    33
    44
    5 !  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
     5!  ATTENTION!!!!: ce fichier INCLUDE est compatible format fixe/format libre
    66!                 veillez  n'utiliser que des ! pour les commentaires
    77!                 et  bien positionner les & des lignes de continuation
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/qminimum_loc.f90

    r5128 r5134  
    1010
    1111
    12   IMPLICIT none
     12  IMPLICIT NONE
    1313  !
    1414  !  -- Objet : Traiter les valeurs trop petites (meme negatives)
    1515  !         pour l'eau vapeur et l'eau liquide
    1616  !
    17   include "dimensions.h"
    18   include "paramet.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
    1919  !
    2020  INTEGER :: nqtot ! CRisi: on remplace nq par nqtot
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/sw_case_williamson91_6_loc.f90

    r5118 r5134  
    3535  !   ---------------
    3636
    37   include "dimensions.h"
    38   include "paramet.h"
    39   include "comgeom.h"
     37  INCLUDE "dimensions.h"
     38  INCLUDE "paramet.h"
     39  INCLUDE "comgeom.h"
    4040
    4141  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/top_bound_loc.f90

    r5118 r5134  
    77  USE comvert_mod, ONLY: presnivs, preff, scaleheight
    88  USE lmdz_iniprint, ONLY: lunout, prt_level
     9  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    910
    1011  IMPLICIT NONE
    1112  !
    12   include "dimensions.h"
    13   include "paramet.h"
    14   include "comgeom2.h"
     13  INCLUDE "dimensions.h"
     14  INCLUDE "paramet.h"
     15  INCLUDE "comgeom2.h"
    1516
    1617
     
    5253  !    tau_top_bound : inverse of charactericstic relaxation time scale at
    5354  !                   the topmost layer (Hz)
    54 
    55   INCLUDE "comdissipn.h"
    5655
    5756  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/tourpot_loc.F90

    r5106 r5134  
    88  USE lmdz_filtreg_p
    99  IMPLICIT NONE
    10   include "dimensions.h"
    11   include "paramet.h"
    12   include "comgeom.h"
     10  INCLUDE "dimensions.h"
     11  INCLUDE "paramet.h"
     12  INCLUDE "comgeom.h"
    1313!===============================================================================
    1414! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/vitvert_loc.F90

    r5099 r5134  
    99 
    1010  IMPLICIT NONE
    11   include "dimensions.h"
    12   include "paramet.h"
     11  INCLUDE "dimensions.h"
     12  INCLUDE "paramet.h"
    1313!===============================================================================
    1414! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/vlsplt_loc.f90

    r5128 r5134  
    1818  IMPLICIT NONE
    1919  !
    20   include "dimensions.h"
    21   include "paramet.h"
     20  INCLUDE "dimensions.h"
     21  INCLUDE "paramet.h"
    2222  !
    2323  !
     
    386386  IMPLICIT NONE
    387387  !
    388   include "dimensions.h"
    389   include "paramet.h"
    390   include "comgeom.h"
     388  INCLUDE "dimensions.h"
     389  INCLUDE "paramet.h"
     390  INCLUDE "comgeom.h"
    391391  !
    392392  !
     
    817817  IMPLICIT NONE
    818818  !
    819   include "dimensions.h"
    820   include "paramet.h"
     819  INCLUDE "dimensions.h"
     820  INCLUDE "paramet.h"
    821821  !
    822822  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/vlspltgen_loc.F90

    r5128 r5134  
    3636
    3737  !
    38   include "dimensions.h"
    39   include "paramet.h"
     38  INCLUDE "dimensions.h"
     39  INCLUDE "paramet.h"
    4040
    4141  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/vlspltqs_loc.f90

    r5128 r5134  
    1515  IMPLICIT NONE
    1616  !
    17   include "dimensions.h"
    18   include "paramet.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
    1919  !
    2020  !
     
    394394  IMPLICIT NONE
    395395  !
    396   include "dimensions.h"
    397   include "paramet.h"
    398   include "comgeom.h"
     396  INCLUDE "dimensions.h"
     397  INCLUDE "paramet.h"
     398  INCLUDE "comgeom.h"
    399399  !
    400400  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/write_field_loc.F90

    r5119 r5134  
    3838    USE mod_hallo
    3939    IMPLICIT NONE
    40     include 'dimensions.h'
    41     include 'paramet.h'
     40    INCLUDE 'dimensions.h'
     41    INCLUDE 'paramet.h'
    4242     
    4343    CHARACTER(LEN=*)   :: name
     
    103103    USE mod_hallo
    104104    IMPLICIT NONE
    105     include 'dimensions.h'
    106     include 'paramet.h'
     105    INCLUDE 'dimensions.h'
     106    INCLUDE 'paramet.h'
    107107     
    108108    CHARACTER(LEN=*)   :: name
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writedyn_xios.F90

    r5118 r5134  
    3535
    3636  !   Declarations
    37   include "dimensions.h"
    38   include "paramet.h"
    39   include "comgeom.h"
     37  INCLUDE "dimensions.h"
     38  INCLUDE "paramet.h"
     39  INCLUDE "comgeom.h"
    4040
    4141  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writedynav_loc.f90

    r5118 r5134  
    4343  !
    4444  !   Declarations
    45   include "dimensions.h"
    46   include "paramet.h"
    47   include "comgeom.h"
     45  INCLUDE "dimensions.h"
     46  INCLUDE "paramet.h"
     47  INCLUDE "comgeom.h"
    4848
    4949  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3dmem/writehist_loc.f90

    r5118 r5134  
    4040  !
    4141  !   Declarations
    42   include "dimensions.h"
    43   include "paramet.h"
    44   include "comgeom.h"
     42  INCLUDE "dimensions.h"
     43  INCLUDE "paramet.h"
     44  INCLUDE "comgeom.h"
    4545
    4646  !
Note: See TracChangeset for help on using the changeset viewer.