Changeset 5134 for LMDZ6


Ignore:
Timestamp:
Jul 26, 2024, 5:56:37 PM (7 weeks 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
Files:
4 deleted
213 edited
6 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/addfi.F90

    r5123 r5134  
    4646  !    ------------------
    4747  !
    48   include "dimensions.h"
    49   include "paramet.h"
    50   include "comgeom.h"
     48  INCLUDE "dimensions.h"
     49  INCLUDE "paramet.h"
     50  INCLUDE "comgeom.h"
    5151  !
    5252  !    Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/advect.F90

    r5123 r5134  
    2828  !   -------------
    2929
    30   include "dimensions.h"
    31   include "paramet.h"
    32   include "comgeom.h"
     30  INCLUDE "dimensions.h"
     31  INCLUDE "paramet.h"
     32  INCLUDE "comgeom.h"
    3333
    3434  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/advtrac.f90

    r5119 r5134  
    1818  USE lmdz_iniprint, ONLY: lunout, prt_level
    1919  USE lmdz_ssum_scopy, ONLY: scopy
     20  USE lmdz_comdissip, ONLY: coefdis, tetavel, tetatemp, gamdissip, niterdis
    2021
    2122  IMPLICIT NONE
    2223
    23   include "dimensions.h"
    24   include "paramet.h"
    25   include "comdissip.h"
    26   include "comgeom2.h"
     24  INCLUDE "dimensions.h"
     25  INCLUDE "paramet.h"
     26  INCLUDE "comgeom2.h"
    2727
    2828  !---------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/bilan_dyn.F90

    r5128 r5134  
    1818  IMPLICIT NONE
    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  !====================================================================
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/caladvtrac.F90

    r5119 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/dyn3d/caldyn.F90

    r5113 r5134  
    2525  !   ----------------
    2626
    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:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/check_isotopes.F90

    r5128 r5134  
    55
    66   IMPLICIT NONE
    7    include "dimensions.h"
     7   INCLUDE "dimensions.h"
    88   REAL,             INTENT(INOUT) :: q(ip1jmp1,llm,nqtot)
    99   INTEGER,          INTENT(IN)    :: ip1jmp1
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/conf_gcm.f90

    r5128 r5134  
    1717  USE temps_mod, ONLY: calend, year_len
    1818  USE lmdz_iniprint, ONLY: lunout, prt_level
    19 
     19  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     20          tetagrot, tetatemp, coefdis, vert_prof_dissip
    2021
    2122  IMPLICIT NONE
     
    3435  !   Declarations :
    3536  !   --------------
    36   include "dimensions.h"
    37   include "paramet.h"
    38   include "comdissnew.h"
     37  INCLUDE "dimensions.h"
     38  INCLUDE "paramet.h"
    3939
    4040  !   local:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/covnat.F90

    r5106 r5134  
    1818  !=======================================================================
    1919
    20  include "dimensions.h"
    21  include "paramet.h"
    22  include "comgeom.h"
     20 INCLUDE "dimensions.h"
     21 INCLUDE "paramet.h"
     22 INCLUDE "comgeom.h"
    2323
    2424  INTEGER :: klevel
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dissip.F90

    r5123 r5134  
    22
    33SUBROUTINE dissip(vcov, ucov, teta, p, dv, du, dh)
    4   !
    54  USE comconst_mod, ONLY: dtdiss
     5  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
     6  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     7          tetagrot, tetatemp, coefdis, vert_prof_dissip
    68
    79  IMPLICIT NONE
     
    2628  !   -------------
    2729
    28   include "dimensions.h"
    29   include "paramet.h"
    30   include "comgeom.h"
    31   include "comdissnew.h"
    32   include "comdissipn.h"
     30  INCLUDE "dimensions.h"
     31  INCLUDE "paramet.h"
     32  INCLUDE "comgeom.h"
    3333
    3434  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dteta1.F90

    r5106 r5134  
    2020  !=======================================================================
    2121
    22   include "dimensions.h"
    23   include "paramet.h"
     22  INCLUDE "dimensions.h"
     23  INCLUDE "paramet.h"
    2424
    2525  REAL :: teta(ip1jmp1, llm), pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dudv1.F90

    r5106 r5134  
    1818  !-----------------------------------------------------------------------
    1919
    20   include "dimensions.h"
    21   include "paramet.h"
     20  INCLUDE "dimensions.h"
     21  INCLUDE "paramet.h"
    2222
    2323  REAL :: vorpot(ip1jm, llm), pbaru(ip1jmp1, llm), &
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dudv2.F90

    r5106 r5134  
    2525  !=======================================================================
    2626  !
    27   include "dimensions.h"
    28   include "paramet.h"
     27  INCLUDE "dimensions.h"
     28  INCLUDE "paramet.h"
    2929
    3030  REAL :: teta(ip1jmp1, llm), pkf(ip1jmp1, llm), bern(ip1jmp1, llm), &
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dynetat0.F90

    r5128 r5134  
    2525
    2626  IMPLICIT NONE
    27   include "dimensions.h"
    28   include "paramet.h"
    29   include "comgeom2.h"
     27  INCLUDE "dimensions.h"
     28  INCLUDE "paramet.h"
     29  INCLUDE "comgeom2.h"
    3030!===============================================================================
    3131! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dynredem.F90

    r5118 r5134  
    2222
    2323  IMPLICIT NONE
    24   include "dimensions.h"
    25   include "paramet.h"
    26   include "comgeom2.h"
     24  INCLUDE "dimensions.h"
     25  INCLUDE "paramet.h"
     26  INCLUDE "comgeom2.h"
    2727  !===============================================================================
    2828  ! Arguments:
     
    169169
    170170  IMPLICIT NONE
    171   include "dimensions.h"
    172   include "paramet.h"
    173   include "comgeom.h"
     171  INCLUDE "dimensions.h"
     172  INCLUDE "paramet.h"
     173  INCLUDE "comgeom.h"
    174174  !===============================================================================
    175175  ! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/dynredem_mod.F90

    r5128 r5134  
    77  PUBLIC :: dynredem_write_u, dynredem_write_v, dynredem_read_u, err
    88  PUBLIC :: cre_var, put_var1, put_var2, fil, modname, msg
    9   include "dimensions.h"
    10   include "paramet.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
    1111  CHARACTER(LEN = 256), SAVE :: fil, modname
    1212  INTEGER, SAVE :: nvarid
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/fluxstokenc.F90

    r5119 r5134  
    1616  IMPLICIT NONE
    1717  !
    18   include "dimensions.h"
    19   include "paramet.h"
    20   include "comgeom.h"
    21   include "tracstoke.h"
     18  INCLUDE "dimensions.h"
     19  INCLUDE "paramet.h"
     20  INCLUDE "comgeom.h"
     21  INCLUDE "tracstoke.h"
    2222
    2323  REAL :: time_step, t_wrt, t_ops
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/friction.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/dyn3d/gcm.F90

    r5128 r5134  
    2828  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    2929  USE lmdz_iniprint, ONLY: lunout, prt_level
    30 
     30  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     31          tetagrot, tetatemp, coefdis, vert_prof_dissip
    3132
    3233  IMPLICIT NONE
     
    6263  !   -------------
    6364
    64   include "dimensions.h"
    65   include "paramet.h"
    66   include "comdissnew.h"
    67   include "comgeom.h"
    68   include "tracstoke.h"
     65  INCLUDE "dimensions.h"
     66  INCLUDE "paramet.h"
     67  INCLUDE "comgeom.h"
     68  INCLUDE "tracstoke.h"
    6969
    7070  REAL zdtvr
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/groupe.F90

    r5128 r5134  
    2020  !   pas besoin de w en entree.
    2121
    22   include "dimensions.h"
    23   include "paramet.h"
    24   include "comgeom2.h"
     22  INCLUDE "dimensions.h"
     23  INCLUDE "paramet.h"
     24  INCLUDE "comgeom2.h"
    2525
    2626  ! integer ngroup
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/groupeun.F90

    r5105 r5134  
    77  IMPLICIT NONE
    88
    9   include "dimensions.h"
    10   include "paramet.h"
    11   include "comgeom2.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
     11  INCLUDE "comgeom2.h"
    1212
    1313  INTEGER :: jjmax, llmax
     
    137137  IMPLICIT NONE
    138138
    139   include "dimensions.h"
    140   include "paramet.h"
    141   include "comgeom2.h"
     139  INCLUDE "dimensions.h"
     140  INCLUDE "paramet.h"
     141  INCLUDE "comgeom2.h"
    142142
    143143  ! INTEGER ngroup
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/guide_mod.F90

    r5128 r5134  
    678678    IMPLICIT NONE
    679679
    680     include "dimensions.h"
    681     include "paramet.h"
    682     include "comgeom2.h"
     680    INCLUDE "dimensions.h"
     681    INCLUDE "paramet.h"
     682    INCLUDE "comgeom2.h"
    683683
    684684    REAL, DIMENSION (iip1, jjp1), INTENT(IN) :: psi ! Psol gcm
     
    928928    IMPLICIT NONE
    929929
    930     include "dimensions.h"
    931     include "paramet.h"
    932     include "comgeom2.h"
     930    INCLUDE "dimensions.h"
     931    INCLUDE "paramet.h"
     932    INCLUDE "comgeom2.h"
    933933
    934934    ! input arguments :
     
    10941094    IMPLICIT NONE
    10951095
    1096     include "dimensions.h"
    1097     include "paramet.h"
     1096    INCLUDE "dimensions.h"
     1097    INCLUDE "paramet.h"
    10981098
    10991099    INTEGER, INTENT(IN) :: timestep
     
    13901390    IMPLICIT NONE
    13911391
    1392     include "dimensions.h"
    1393     include "paramet.h"
     1392    INCLUDE "dimensions.h"
     1393    INCLUDE "paramet.h"
    13941394
    13951395    INTEGER, INTENT(IN) :: timestep
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/iniacademic.F90

    r5128 r5134  
    1919  USE lmdz_ran1, ONLY: ran1
    2020  USE lmdz_iniprint, ONLY: lunout, prt_level
    21 
     21  USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4
    2222
    2323  !   Author:    Frederic Hourdin      original: 15/01/93
     
    3030  !   ---------------
    3131
    32   include "dimensions.h"
    33   include "paramet.h"
    34   include "comgeom.h"
    35   include "academic.h"
     32  INCLUDE "dimensions.h"
     33  INCLUDE "paramet.h"
     34  INCLUDE "comgeom.h"
    3635
    3736  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/integrd.F90

    r5128 r5134  
    3333  !   -------------
    3434
    35   include "dimensions.h"
    36   include "paramet.h"
    37   include "comgeom.h"
     35  INCLUDE "dimensions.h"
     36  INCLUDE "paramet.h"
     37  INCLUDE "comgeom.h"
    3838
    3939  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/leapfrog.F90

    r5128 r5134  
    2828  USE lmdz_iniprint, ONLY: lunout, prt_level
    2929  USE lmdz_ssum_scopy, ONLY: scopy, ssum
    30 
     30  USE lmdz_academic, ONLY: tetarappel, knewt_t, kfrict, knewt_g, clat4
     31  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     32          tetagrot, tetatemp, coefdis, vert_prof_dissip
    3133
    3234  IMPLICIT NONE
     
    6365  !   -------------
    6466
    65   include "dimensions.h"
    66   include "paramet.h"
    67   include "comdissnew.h"
    68   include "comgeom.h"
    69   include "academic.h"
     67  INCLUDE "dimensions.h"
     68  INCLUDE "paramet.h"
     69  INCLUDE "comgeom.h"
    7070
    7171  REAL, INTENT(IN) :: time_0 ! not used
     
    686686        ! For some Grads outputs of fields
    687687        IF (output_grads_dyn) THEN
    688           include "write_grads_dyn.h"
     688          INCLUDE "write_grads_dyn.h"
    689689        endif
    690690      endif ! of if (leapf.OR.(.NOT.leapf.AND.(.NOT.forward)))
     
    806806        ! For some Grads outputs
    807807        IF (output_grads_dyn) THEN
    808           include "write_grads_dyn.h"
     808          INCLUDE "write_grads_dyn.h"
    809809        endif
    810810
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/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/dyn3d/qminimum.F90

    r5123 r5134  
    88  USE lmdz_ssum_scopy, ONLY: ssum
    99
    10   IMPLICIT none
     10  IMPLICIT NONE
    1111  !
    1212  !  -- Objet : Traiter les valeurs trop petites (meme negatives)
    1313  !         pour l'eau vapeur et l'eau liquide
    1414  !
    15   include "dimensions.h"
    16   include "paramet.h"
     15  INCLUDE "dimensions.h"
     16  INCLUDE "paramet.h"
    1717  !
    1818  INTEGER :: nqtot
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/replay3d.F90

    r5128 r5134  
    2121        grossismx, grossismy, dzoomx, dzoomy,taux,tauy
    2222  USE mod_const_mpi, ONLY: comm_lmdz
    23 
     23  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     24          tetagrot, tetatemp, coefdis, vert_prof_dissip
    2425
    2526  IMPLICIT NONE
     
    5556  !   -------------
    5657
    57   include "dimensions.h"
    58   include "paramet.h"
    59   include "comdissnew.h"
    60   include "comgeom2.h"
     58  INCLUDE "dimensions.h"
     59  INCLUDE "paramet.h"
     60  INCLUDE "comgeom2.h"
    6161
    6262  REAL zdtvr
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/sw_case_williamson91_6.F90

    r5118 r5134  
    3434  !   ---------------
    3535
    36   include "dimensions.h"
    37   include "paramet.h"
    38   include "comgeom.h"
     36  INCLUDE "dimensions.h"
     37  INCLUDE "paramet.h"
     38  INCLUDE "comgeom.h"
    3939
    4040  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/tetaleveli1j.F90

    r5117 r5134  
    66
    77  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    8   IMPLICIT none
     8  IMPLICIT NONE
    99
    10   include "dimensions.h"
     10  INCLUDE "dimensions.h"
    1111
    1212  !================================================================
     
    4343  ! REAL ptop, pbot, aist(klon), aisb(klon)
    4444  !
    45   include "paramet.h"
     45  INCLUDE "paramet.h"
    4646  !
    4747  INTEGER :: lt(ip1jm), lb(ip1jm)
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/tetaleveli1j1.F90

    r5117 r5134  
    66
    77  ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    8   IMPLICIT none
     8  IMPLICIT NONE
    99
    10   include "dimensions.h"
     10  INCLUDE "dimensions.h"
    1111
    1212  !================================================================
     
    4343  ! REAL ptop, pbot, aist(klon), aisb(klon)
    4444  !
    45   include "paramet.h"
     45  INCLUDE "paramet.h"
    4646  !
    4747  INTEGER :: lt(ip1jmp1), lb(ip1jmp1)
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/top_bound.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/dyn3d/vlsplt.F90

    r5123 r5134  
    2222  IMPLICIT NONE
    2323  !
    24   include "dimensions.h"
    25   include "paramet.h"
     24  INCLUDE "dimensions.h"
     25  INCLUDE "paramet.h"
    2626
    2727  !
     
    120120  IMPLICIT NONE
    121121  !
    122   include "dimensions.h"
    123   include "paramet.h"
     122  INCLUDE "dimensions.h"
     123  INCLUDE "paramet.h"
    124124  !
    125125  !
     
    437437  IMPLICIT NONE
    438438  !
    439   include "dimensions.h"
    440   include "paramet.h"
    441   include "comgeom.h"
     439  INCLUDE "dimensions.h"
     440  INCLUDE "paramet.h"
     441  INCLUDE "comgeom.h"
    442442  !
    443443  !
     
    756756  IMPLICIT NONE
    757757  !
    758   include "dimensions.h"
    759   include "paramet.h"
     758  INCLUDE "dimensions.h"
     759  INCLUDE "paramet.h"
    760760  !
    761761  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/vlspltqs.F90

    r5128 r5134  
    2929  IMPLICIT NONE
    3030  !
    31   include "dimensions.h"
    32   include "paramet.h"
     31  INCLUDE "dimensions.h"
     32  INCLUDE "paramet.h"
    3333
    3434  !
     
    188188  IMPLICIT NONE
    189189  !
    190   include "dimensions.h"
    191   include "paramet.h"
     190  INCLUDE "dimensions.h"
     191  INCLUDE "paramet.h"
    192192  !
    193193  !
     
    525525  IMPLICIT NONE
    526526  !
    527   include "dimensions.h"
    528   include "paramet.h"
    529   include "comgeom.h"
     527  INCLUDE "dimensions.h"
     528  INCLUDE "paramet.h"
     529  INCLUDE "comgeom.h"
    530530  !
    531531  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d/wrgrads.f90

    r5128 r5134  
    1414  !    titlevar   Titre
    1515
    16   include "gradsdef.h"
     16  INCLUDE "gradsdef.h"
    1717
    1818  !   arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/adaptdt.f90

    r5117 r5134  
    77  USE comconst_mod, ONLY: dtvr
    88  USE lmdz_description, ONLY: descript
     9  USE lmdz_comdissip, ONLY: coefdis, tetavel, tetatemp, gamdissip, niterdis
     10
    911  IMPLICIT NONE
    1012
    11   include "dimensions.h"
    12   include "paramet.h"
    13   include "comdissip.h"
    14   include "comgeom2.h"
     13  INCLUDE "dimensions.h"
     14  INCLUDE "paramet.h"
     15  INCLUDE "comgeom2.h"
    1516
    1617  !----------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advn.f90

    r5123 r5134  
    1919  IMPLICIT NONE
    2020  !
    21   include "dimensions.h"
    22   include "paramet.h"
    23   include "comgeom.h"
     21  INCLUDE "dimensions.h"
     22  INCLUDE "paramet.h"
     23  INCLUDE "comgeom.h"
    2424
    2525  !
     
    469469  IMPLICIT NONE
    470470  !
    471   include "dimensions.h"
    472   include "paramet.h"
     471  INCLUDE "dimensions.h"
     472  INCLUDE "paramet.h"
    473473  !
    474474  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advx.f90

    r5105 r5134  
    2323  !  parametres principaux du modele
    2424  !
    25   include "dimensions.h"
    26   include "paramet.h"
     25  INCLUDE "dimensions.h"
     26  INCLUDE "paramet.h"
    2727
    2828  !  Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advxp.f90

    r5105 r5134  
    1313  !  parametres principaux du modele
    1414  !
    15   include "dimensions.h"
    16   include "paramet.h"
     15  INCLUDE "dimensions.h"
     16  INCLUDE "paramet.h"
    1717
    1818   INTEGER :: ntra
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advy.f90

    r5123 r5134  
    2626  !
    2727  !
    28   include "dimensions.h"
    29   include "paramet.h"
    30   include "comgeom2.h"
     28  INCLUDE "dimensions.h"
     29  INCLUDE "paramet.h"
     30  INCLUDE "comgeom2.h"
    3131
    3232  !  Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advyp.f90

    r5123 r5134  
    2828  !
    2929  !
    30   include "dimensions.h"
    31   include "paramet.h"
    32   include "comgeom.h"
     30  INCLUDE "dimensions.h"
     31  INCLUDE "paramet.h"
     32  INCLUDE "comgeom.h"
    3333
    3434  !  Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advz.f90

    r5105 r5134  
    2121  !  parametres principaux du modele
    2222  !
    23   include "dimensions.h"
    24   include "paramet.h"
     23  INCLUDE "dimensions.h"
     24  INCLUDE "paramet.h"
    2525
    2626  ! INCLUDE "traceur.h"
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/advzp.f90

    r5105 r5134  
    3131  !  parametres principaux du modele
    3232  !
    33   include "dimensions.h"
    34   include "paramet.h"
    35   include "comgeom.h"
     33  INCLUDE "dimensions.h"
     34  INCLUDE "paramet.h"
     35  INCLUDE "comgeom.h"
    3636  !
    3737  !  Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/bernoui.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/dyn3d_common/caldyn0.F90

    r5103 r5134  
    99  USE comvert_mod, ONLY: ap, bp
    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/dyn3d_common/convmas.F90

    r5106 r5134  
    77  USE lmdz_filtreg, ONLY: filtreg
    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/dyn3d_common/coordij.f90

    r5116 r5134  
    1818  INTEGER :: i,j
    1919
    20   include "dimensions.h"
    21   include "paramet.h"
    22   include "comgeom.h"
     20  INCLUDE "dimensions.h"
     21  INCLUDE "paramet.h"
     22  INCLUDE "comgeom.h"
    2323
    2424  REAL :: zlon,zlat
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/covcont.F90

    r5106 r5134  
    77!-------------------------------------------------------------------------------
    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/dyn3d_common/disvert.F90

    r5128 r5134  
    1414  IMPLICIT NONE
    1515
    16   include "dimensions.h"
    17   include "paramet.h"
     16  INCLUDE "dimensions.h"
     17  INCLUDE "paramet.h"
    1818
    1919!-------------------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/disvert_noterre.f90

    r5123 r5134  
    1515  IMPLICIT NONE
    1616
    17   include "dimensions.h"
    18   include "paramet.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
    1919  !
    2020  !=======================================================================
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/divgrad.f90

    r5119 r5134  
    44  USE lmdz_filtreg, ONLY: filtreg
    55  USE lmdz_ssum_scopy, ONLY: scopy
     6  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
     7
    68  IMPLICIT NONE
    79  !
     
    2123  !   -------------
    2224  !
    23   include "dimensions.h"
    24   include "paramet.h"
    25   include "comgeom.h"
    26   include "comdissipn.h"
     25  INCLUDE "dimensions.h"
     26  INCLUDE "paramet.h"
     27  INCLUDE "comgeom.h"
    2728  !
    2829  INTEGER :: klevel
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/divgrad2.f90

    r5119 r5134  
    1313  !
    1414  USE lmdz_ssum_scopy, ONLY: scopy
     15  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    1516
    1617  IMPLICIT NONE
     
    1920  INCLUDE "paramet.h"
    2021  INCLUDE "comgeom2.h"
    21   INCLUDE "comdissipn.h"
    2222
    2323  !    .......    variables en arguments   .......
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/ener_mod.F90

    r5099 r5134  
    66IMPLICIT NONE 
    77
    8 include "dimensions.h"
    9 include "paramet.h"
     8INCLUDE "dimensions.h"
     9INCLUDE "paramet.h"
    1010
    1111      REAL ang0,etot0,ptot0,ztot0,stot0,                        &
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/enercin.F90

    r5106 r5134  
    66! Purpose: Compute kinetic energy at sigma levels.
    77  IMPLICIT NONE
    8   include "dimensions.h"
    9   include "paramet.h"
    10   include "comgeom.h"
     8  INCLUDE "dimensions.h"
     9  INCLUDE "paramet.h"
     10  INCLUDE "comgeom.h"
    1111!===============================================================================
    1212! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/exner_hyb_m.F90

    r5133 r5134  
    3939    IMPLICIT NONE
    4040   
    41     include "dimensions.h"
    42     include "paramet.h"
    43     include "comgeom.h"
     41    INCLUDE "dimensions.h"
     42    INCLUDE "paramet.h"
     43    INCLUDE "comgeom.h"
    4444
    4545    INTEGER  ngrid
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/exner_milieu_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/dyn3d_common/extrapol.f90

    r5106 r5134  
    66SUBROUTINE extrapol(pfild, kxlon, kylat, pmask, &
    77        norsud, ldper, knbor, pwork)
    8   IMPLICIT none
     8  IMPLICIT NONE
    99  !
    1010  ! OASIS routine (Adaptation: Laurent Li, le 14 mars 1997)
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/flumass.F90

    r5106 r5134  
    66! Purpose: Compute mass flux at s levels.
    77  IMPLICIT NONE
    8   include "dimensions.h"
    9   include "paramet.h"
    10   include "comgeom.h"
     8  INCLUDE "dimensions.h"
     9  INCLUDE "paramet.h"
     10  INCLUDE "comgeom.h"
    1111!===============================================================================
    1212! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/fxhyp_m.F90

    r5119 r5134  
    2424    USE serre_mod, ONLY: clon, grossismx, dzoomx, taux
    2525
    26     include "dimensions.h"
     26    INCLUDE "dimensions.h"
    2727    ! for iim
    2828
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/fxy.f90

    r5122 r5134  
    1515  !
    1616  !
    17   include "dimensions.h"
    18   include "paramet.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
    1919
    2020  INTEGER :: i, j
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/fyhyp_m.F90

    r5119 r5134  
    2020    USE serre_mod, ONLY: clat, grossismy, dzoomy, tauy
    2121
    22     include "dimensions.h"
     22    INCLUDE "dimensions.h"
    2323    ! for jjm
    2424
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/geopot.f90

    r5106 r5134  
    2727  !   -------------
    2828
    29   include "dimensions.h"
    30   include "paramet.h"
     29  INCLUDE "dimensions.h"
     30  INCLUDE "paramet.h"
    3131
    3232  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gr_ecrit_fi.f90

    r5105 r5134  
    44  SUBROUTINE gr_ecrit_fi(nfield,nlon,iim,jjmp1,ecrit,fi)
    55
    6     IMPLICIT none
     6    IMPLICIT NONE
    77
    88  ! Transformer une variable de la grille d'ecriture a la grille physique
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gradiv.f90

    r5119 r5134  
    1818  USE lmdz_filtreg, ONLY: filtreg
    1919  USE lmdz_ssum_scopy, ONLY: scopy
     20  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    2021
    2122  IMPLICIT NONE
    2223  !
    23   include "dimensions.h"
    24   include "paramet.h"
    25   include "comdissipn.h"
     24  INCLUDE "dimensions.h"
     25  INCLUDE "paramet.h"
    2626
    2727  INTEGER :: klevel
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gradiv2.f90

    r5119 r5134  
    1717  USE lmdz_filtreg, ONLY: filtreg
    1818  USE lmdz_ssum_scopy, ONLY: scopy
     19  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    1920
    2021  IMPLICIT NONE
     
    2324  INCLUDE "paramet.h"
    2425  INCLUDE "comgeom.h"
    25   INCLUDE "comdissipn.h"
    2626  !
    2727  ! ........    variables en arguments      ........
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/iniconst.F90

    r5128 r5134  
    1818  !   -------------
    1919
    20   include "dimensions.h"
    21   include "paramet.h"
     20  INCLUDE "dimensions.h"
     21  INCLUDE "paramet.h"
    2222
    2323  CHARACTER(LEN = *), parameter :: modname = "iniconst"
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inidissip.F90

    r5128 r5134  
    1818  USE lmdz_ran1, ONLY: ran1
    1919  USE lmdz_iniprint, ONLY: lunout, prt_level
    20 
     20  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    2121
    2222  IMPLICIT NONE
    23   include "dimensions.h"
    24   include "paramet.h"
    25   include "comdissipn.h"
     23  INCLUDE "dimensions.h"
     24  INCLUDE "paramet.h"
    2625
    2726  LOGICAL, INTENT(IN) :: lstardis
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inigeom.f90

    r5123 r5134  
    2323        alphax,alphay,taux,tauy,transx,transy,pxo,pyo
    2424  USE lmdz_ssum_scopy, ONLY: ssum
     25  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     26          tetagrot, tetatemp, coefdis, vert_prof_dissip
     27
    2528  IMPLICIT NONE
    2629  !
    27   include "dimensions.h"
    28   include "paramet.h"
    29   include "comgeom2.h"
    30   include "comdissnew.h"
     30  INCLUDE "dimensions.h"
     31  INCLUDE "paramet.h"
     32  INCLUDE "comgeom2.h"
    3133
    3234  !-----------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/initdynav.F90

    r5118 r5134  
    3636  !   L. Fairhead, LMD, 03/99
    3737
    38   include "dimensions.h"
    39   include "paramet.h"
    40   include "comgeom.h"
     38  INCLUDE "dimensions.h"
     39  INCLUDE "paramet.h"
     40  INCLUDE "comgeom.h"
    4141
    4242  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/initfluxsto.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/dyn3d_common/inithist.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  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/inter_barxy_m.F90

    r5119 r5134  
    1717    USE lmdz_assert, ONLY: assert
    1818
    19     include "dimensions.h"
     19    INCLUDE "dimensions.h"
    2020    ! (for "iim", "jjm")
    2121
    22     include "paramet.h"
     22    INCLUDE "paramet.h"
    2323    ! (for other included files)
    2424
    25     include "comgeom2.h"
     25    INCLUDE "comgeom2.h"
    2626    ! (for "aire", "apoln", "apols")
    2727
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/interpost.f90

    r5116 r5134  
    77
    88
    9   include "dimensions.h"
    10   include "paramet.h"
    11   include "comgeom2.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
     11  INCLUDE "comgeom2.h"
    1212
    1313  ! Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/interpre.f90

    r5116 r5134  
    88  USE comvert_mod, ONLY: ap, bp
    99  USE lmdz_description, ONLY: descript
     10  USE lmdz_comdissip, ONLY: coefdis, tetavel, tetatemp, gamdissip, niterdis
    1011
    1112  IMPLICIT NONE
    1213
    13   include "dimensions.h"
    14   include "paramet.h"
    15   include "comdissip.h"
    16   include "comgeom2.h"
     14  INCLUDE "dimensions.h"
     15  INCLUDE "paramet.h"
     16  INCLUDE "comgeom2.h"
    1717
    1818  !---------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/invert_zoom_x_m.F90

    r5119 r5134  
    1313    USE serre_mod, ONLY: clon
    1414
    15     include "dimensions.h"
     15    INCLUDE "dimensions.h"
    1616    ! for iim
    1717
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/limx.f90

    r5123 r5134  
    1515  IMPLICIT NONE
    1616  !
    17   include "dimensions.h"
    18   include "paramet.h"
    19   include "comgeom.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
     19  INCLUDE "comgeom.h"
    2020  !
    2121  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/limy.f90

    r5123 r5134  
    2020  IMPLICIT NONE
    2121  !
    22   include "dimensions.h"
    23   include "paramet.h"
    24   include "comgeom.h"
     22  INCLUDE "dimensions.h"
     23  INCLUDE "paramet.h"
     24  INCLUDE "comgeom.h"
    2525  !
    2626  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/limz.f90

    r5123 r5134  
    1515  IMPLICIT NONE
    1616  !
    17   include "dimensions.h"
    18   include "paramet.h"
    19   include "comgeom.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
     19  INCLUDE "comgeom.h"
    2020  !
    2121  !
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_academic.f90

    r5131 r5134  
    1 
     1! Replaces academic.h
    22! $Id$
    33
    4       common/academic/tetarappel,knewt_t,kfrict,knewt_g,clat4
    5       REAL :: tetarappel(ip1jmp1,llm)
    6       REAL :: knewt_t(llm)
    7       REAL :: kfrict(llm)
    8       REAL :: knewt_g
    9       REAL :: clat4(ip1jmp1)
     4MODULE lmdz_academic
     5  IMPLICIT NONE; PRIVATE
     6  INCLUDE "dimensions.h"
     7  INCLUDE "paramet.h"
     8
     9  PUBLIC tetarappel, knewt_t, kfrict, knewt_g, clat4
     10
     11  REAL :: tetarappel(ip1jmp1, llm)
     12  REAL :: knewt_t(llm)
     13  REAL :: kfrict(llm)
     14  REAL :: knewt_g
     15  REAL :: clat4(ip1jmp1)
     16
     17END MODULE lmdz_academic
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_comdissip.f90

    r5131 r5134  
     1! Replaces comdissip.h
     2MODULE lmdz_comdissip
     3  IMPLICIT NONE; PRIVATE
     4  PUBLIC coefdis, tetavel, tetatemp, gamdissip, niterdis
    15
    2 ! $Header$
    3 
    4 !-----------------------------------------------------------------------
    5 ! INCLUDE comdissip.h
    6 
    7       COMMON/comdissip/                                                 &
    8           coefdis,tetavel,tetatemp,gamdissip,niterdis
    9 
    10 
    11       INTEGER niterdis
    12 
    13       REAL tetavel,tetatemp,coefdis,gamdissip
    14 
    15 !-----------------------------------------------------------------------
     6  INTEGER niterdis
     7  REAL tetavel, tetatemp, coefdis, gamdissip
     8END MODULE lmdz_comdissip
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_comdissipn.f90

    r5131 r5134  
     1! Replaces comdissipn.h
     2MODULE lmdz_comdissipn
     3  IMPLICIT NONE; PRIVATE
     4  PUBLIC tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    15
    2 ! $Header$
     6  INCLUDE "dimensions.h"
    37
    4 !  Attention : ce fichier include est compatible format fixe/format libre
    5 !                 veillez à n'utiliser que des ! pour les commentaires
    6 !                 et à bien positionner les & des lignes de continuation
    7 !                 (les placer en colonne 6 et en colonne 73)
    8 !-----------------------------------------------------------------------
    9 ! INCLUDE comdissipn.h
    10 
    11       REAL  tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    12 
    13       COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,     &
    14                               cdivu,      crot,         cdivh
    15 
    16 !    Les parametres de ce common proviennent des calculs effectues dans
    17 !             Inidissip  .
    18 
    19 !-----------------------------------------------------------------------
     8  REAL tetaudiv(llm), tetaurot(llm), tetah(llm), cdivu, crot, cdivh
     9END MODULE lmdz_comdissipn
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/lmdz_comdissnew.f90

    r5131 r5134  
     1! Replaces comdissnew.h
    12
    2 ! $Id$
     3MODULE lmdz_comdissnew
     4  IMPLICIT NONE; PRIVATE
     5  PUBLIC lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     6          tetagrot, tetatemp, coefdis, vert_prof_dissip
    37
     8  LOGICAL lstardis
     9  INTEGER nitergdiv, nitergrot, niterh
    410
    5 !  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
    6 !                 veillez à n'utiliser que des ! pour les commentaires
    7 !                 et à bien positionner les & des lignes de continuation
    8 !                 (les placer en colonne 6 et en colonne 73)
     11  INTEGER vert_prof_dissip ! vertical profile of horizontal dissipation
     12  !     Allowed values:
     13  !     0: rational fraction, function of pressure
     14  !     1: tanh of altitude
    915
    10 !-----------------------------------------------------------------------
    11 ! INCLUDE 'comdissnew.h'
    12 
    13       COMMON/comdissnew/ lstardis,nitergdiv,nitergrot,niterh,tetagdiv,  &
    14                          tetagrot,tetatemp,coefdis, vert_prof_dissip
    15 
    16       LOGICAL lstardis
    17       INTEGER nitergdiv, nitergrot, niterh
    18 
    19       INTEGER vert_prof_dissip ! vertical profile of horizontal dissipation
    20 !     Allowed values:
    21 !     0: rational fraction, function of pressure
    22 !     1: tanh of altitude
    23 
    24       REAL     tetagdiv, tetagrot,  tetatemp, coefdis
    25 
    26 ! ... Les parametres de ce common comdissnew sont  lues par defrun_new
    27 !              sur le fichier  run.def    ....
    28 
    29 !-----------------------------------------------------------------------
     16  REAL     tetagdiv, tetagrot, tetatemp, coefdis
     17  ! ... Les parametres de ce common comdissnew sont  lues par defrun_new
     18  !              sur le fichier  run.def    ....
     19END MODULE lmdz_comdissnew
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/massbar.F90

    r5099 r5134  
    77! See iniconst for more details.
    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/dyn3d_common/massbarxy.F90

    r5099 r5134  
    77! See iniconst for more details.
    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/dyn3d_common/massdair.f90

    r5123 r5134  
    1818  IMPLICIT NONE
    1919  !
    20   include "dimensions.h"
    21   include "paramet.h"
    22   include "comgeom.h"
     20  INCLUDE "dimensions.h"
     21  INCLUDE "paramet.h"
     22  INCLUDE "comgeom.h"
    2323  !
    2424  !  .....   arguments  ....
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/nxgraro2.f90

    r5119 r5134  
    1616  USE lmdz_filtreg, ONLY: filtreg
    1717  USE lmdz_ssum_scopy, ONLY: scopy
     18  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    1819
    1920  IMPLICIT NONE
     
    2122  INCLUDE "dimensions.h"
    2223  INCLUDE "paramet.h"
    23   INCLUDE "comdissipn.h"
    2424  !
    2525  !    ......  variables en arguments  .......
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/nxgrarot.f90

    r5119 r5134  
    1717  USE lmdz_filtreg, ONLY: filtreg
    1818  USE lmdz_ssum_scopy, ONLY: scopy
     19  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    1920
    2021  IMPLICIT NONE
    2122  !
    2223  !
    23   include "dimensions.h"
    24   include "paramet.h"
    25   include "comdissipn.h"
     24  INCLUDE "dimensions.h"
     25  INCLUDE "paramet.h"
    2626  !
    2727  INTEGER :: klevel
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/pentes_ini.f90

    r5123 r5134  
    2626
    2727
    28   include "dimensions.h"
    29   include "paramet.h"
    30   include "comgeom2.h"
     28  INCLUDE "dimensions.h"
     29  INCLUDE "paramet.h"
     30  INCLUDE "comgeom2.h"
    3131
    3232  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/prather.f90

    r5123 r5134  
    2323
    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  !   Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/pression.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/dyn3d_common/principal_cshift_m.F90

    r5119 r5134  
    1414    USE serre_mod, ONLY: clon
    1515
    16     include "dimensions.h"
     16    INCLUDE "dimensions.h"
    1717    ! for iim
    1818
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/tourpot.F90

    r5106 r5134  
    77  USE lmdz_filtreg, ONLY: filtreg
    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/dyn3d_common/traceurpole.f90

    r5116 r5134  
    33SUBROUTINE traceurpole(q, masse)
    44  USE lmdz_description, ONLY: descript
     5  USE lmdz_comdissip, ONLY: coefdis, tetavel, tetatemp, gamdissip, niterdis
     6
    57  IMPLICIT NONE
    68
    7   include "dimensions.h"
    8   include "paramet.h"
    9   include "comdissip.h"
    10   include "comgeom2.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
     11  INCLUDE "comgeom2.h"
    1112
    1213
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/ugeostr.F90

    r5117 r5134  
    1515  IMPLICIT NONE
    1616
    17   include "dimensions.h"
    18   include "paramet.h"
    19   include "comgeom2.h"
     17  INCLUDE "dimensions.h"
     18  INCLUDE "paramet.h"
     19  INCLUDE "comgeom2.h"
    2020
    2121  REAL ucov(iip1,jjp1,llm),phi(iip1,jjp1,llm)
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/vitvert.F90

    r5106 r5134  
    77  USE comvert_mod, ONLY: bp
    88  IMPLICIT NONE
    9   include "dimensions.h"
    10   include "paramet.h"
     9  INCLUDE "dimensions.h"
     10  INCLUDE "paramet.h"
    1111!===============================================================================
    1212! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/writedynav.F90

    r5118 r5134  
    3131
    3232  !   Declarations
    33   include "dimensions.h"
    34   include "paramet.h"
    35   include "comgeom.h"
     33  INCLUDE "dimensions.h"
     34  INCLUDE "paramet.h"
     35  INCLUDE "comgeom.h"
    3636
    3737  !   Arguments
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/writehist.f90

    r5118 r5134  
    3434  !
    3535  !   Declarations
    36   include "dimensions.h"
    37   include "paramet.h"
    38   include "comgeom.h"
     36  INCLUDE "dimensions.h"
     37  INCLUDE "paramet.h"
     38  INCLUDE "comgeom.h"
    3939
    4040  !
  • 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  !
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/calfis.f90

    r5128 r5134  
    9292  !    ------------------
    9393
    94   include "dimensions.h"
    95   include "paramet.h"
     94  INCLUDE "dimensions.h"
     95  INCLUDE "paramet.h"
    9696
    9797  INTEGER :: ngridmx
    9898  PARAMETER(ngridmx = 2 + (jjm - 1) * iim - 1 / jjm)
    9999
    100   include "comgeom2.h"
     100  INCLUDE "comgeom2.h"
    101101
    102102  !    Arguments :
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/lmdz_calfis_loc.F90

    r5128 r5134  
    109109    !    ------------------
    110110
    111     include "dimensions.h"
    112     include "paramet.h"
     111    INCLUDE "dimensions.h"
     112    INCLUDE "paramet.h"
    113113
    114114    INTEGER :: ngridmx
    115115    PARAMETER(ngridmx = 2 + (jjm - 1) * iim - 1 / jjm)
    116116
    117     include "comgeom2.h"
     117    INCLUDE "comgeom2.h"
    118118    !    Arguments :
    119119    !    -----------
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/mod_interface_dyn_phys.F90

    r5117 r5134  
    1414    USE lmdz_phys_mpi_data
    1515    IMPLICIT NONE
    16     include 'dimensions.h'   
     16    INCLUDE 'dimensions.h'
    1717   
    1818    INTEGER :: i,j,k
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/ce0l.F90

    r5128 r5134  
    5252  !-------------------------------------------------------------------------------
    5353  ! Local variables:
    54   include "dimensions.h"
    55   include "paramet.h"
    56   include "comgeom2.h"
     54  INCLUDE "dimensions.h"
     55  INCLUDE "paramet.h"
     56  INCLUDE "comgeom2.h"
    5757
    5858  REAL :: masque(iip1, jjp1)             !--- CONTINENTAL MASK
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90

    r5128 r5134  
    4141  USE lmdz_strings, ONLY: strLower
    4242  USE lmdz_iniprint, ONLY: lunout, prt_level
     43  USE lmdz_comdissnew, ONLY: lstardis, nitergdiv, nitergrot, niterh, tetagdiv, &
     44          tetagrot, tetatemp, coefdis, vert_prof_dissip
    4345
    4446  IMPLICIT NONE
     
    4749  PUBLIC :: etat0dyn_netcdf
    4850
    49   include "dimensions.h"
    50   include "paramet.h"
    51   include "comgeom2.h"
    52   include "comdissnew.h"
     51  INCLUDE "dimensions.h"
     52  INCLUDE "paramet.h"
     53  INCLUDE "comgeom2.h"
    5354  REAL, SAVE :: deg2rad
    5455  INTEGER, SAVE :: iml_dyn, jml_dyn, llm_dyn, ttm_dyn, fid_dyn
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r5132 r5134  
    5656  PUBLIC :: etat0phys_netcdf
    5757
    58   include "dimensions.h"
    59   include "paramet.h"
    60   include "comgeom2.h"
    61   include "dimsoil.h"
    62   include "clesphys.h"
     58  INCLUDE "dimensions.h"
     59  INCLUDE "paramet.h"
     60  INCLUDE "comgeom2.h"
     61  INCLUDE "dimsoil.h"
     62  INCLUDE "clesphys.h"
    6363  REAL, SAVE :: deg2rad
    6464  REAL, SAVE, ALLOCATABLE :: tsol(:)
     
    9494    USE phys_state_var_mod, ONLY: beta_aridity, delta_tsurf, awake_dens, cv_gen, &
    9595            ratqs_inter_, rneb_ancien
     96    USE lmdz_alpale
     97
    9698    IMPLICIT NONE
    9799    !-------------------------------------------------------------------------------
     
    128130
    129131    INCLUDE "compbl.h"
    130     INCLUDE "alpale.h"
    131132
    132133    deg2rad = pi / 180.0
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r5118 r5134  
    4949    ! =======================================================================
    5050
    51     include "dimensions.h"
    52     include "paramet.h"
    53     include "tracstoke.h"
    54     include "comgeom.h"
     51    INCLUDE "dimensions.h"
     52    INCLUDE "paramet.h"
     53    INCLUDE "tracstoke.h"
     54    INCLUDE "comgeom.h"
    5555
    5656    REAL, INTENT (IN) :: prad ! radius of the planet (m)
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/init_ssrf_m.F90

    r5118 r5134  
    1717  PRIVATE
    1818  PUBLIC :: start_init_subsurf
    19   include "dimensions.h"
    20   include "paramet.h"
    21   include "comgeom2.h"
     19  INCLUDE "dimensions.h"
     20  INCLUDE "paramet.h"
     21  INCLUDE "comgeom2.h"
    2222
    2323CONTAINS
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/limit_netcdf.f90

    r5128 r5134  
    8585    !-------------------------------------------------------------------------------
    8686    ! Arguments:
    87     include "dimensions.h"
    88     include "paramet.h"
     87    INCLUDE "dimensions.h"
     88    INCLUDE "paramet.h"
    8989    REAL, DIMENSION(iip1, jjp1), INTENT(INOUT) :: masque ! land mask
    9090    REAL, DIMENSION(iip1, jjp1), INTENT(INOUT) :: phis   ! ground geopotential
     
    9292    !-------------------------------------------------------------------------------
    9393    ! Local variables:
    94     include "comgeom2.h"
     94    INCLUDE "comgeom2.h"
    9595
    9696    !--- INPUT NETCDF FILES AND VARIABLES NAMES ------------------------------------
     
    334334
    335335      IMPLICIT NONE
    336       include "dimensions.h"
    337       include "paramet.h"
    338       include "comgeom2.h"
     336      INCLUDE "dimensions.h"
     337      INCLUDE "paramet.h"
     338      INCLUDE "comgeom2.h"
    339339      !-----------------------------------------------------------------------------
    340340      ! Arguments:
  • LMDZ6/branches/Amaury_dev/libf/dynphy_lonlat/phylmd/test_disvert_m.F90

    r5119 r5134  
    1919
    2020    ! For llm:
    21     include "dimensions.h"
     21    INCLUDE "dimensions.h"
    2222
    2323    ! Local:
  • LMDZ6/branches/Amaury_dev/libf/filtrez/lmdz_fft_fftw.F90

    r5107 r5134  
    1717  SUBROUTINE Init_fft(iim,nvectmax)
    1818  IMPLICIT NONE
    19 #include <fftw3.f>
     19#INCLUDE <fftw3.f>
    2020    INTEGER :: iim
    2121    INTEGER :: nvectmax
     
    8585  SUBROUTINE fft_forward(vect,TF_vect,nb_vect)
    8686    IMPLICIT NONE
    87 #include <fftw3.f>
     87#INCLUDE <fftw3.f>
    8888    INTEGER,INTENT(IN)     :: nb_vect
    8989    REAL,INTENT(IN)        :: vect(vsize+inc,nb_vect)
     
    9898  SUBROUTINE fft_backward(TF_vect,vect,nb_vect)
    9999    IMPLICIT NONE
    100 #include <fftw3.f>
     100#INCLUDE <fftw3.f>
    101101    INTEGER,INTENT(IN)     :: nb_vect
    102102    REAL,INTENT(OUT)       :: vect(vsize+inc,nb_vect)
  • LMDZ6/branches/Amaury_dev/libf/filtrez/lmdz_filtre_fft.F90

    r5120 r5134  
    1717    USE lmdz_fft
    1818    IMPLICIT NONE
    19     include 'dimensions.h'
     19    INCLUDE 'dimensions.h'
    2020    REAL,   INTENT(IN) :: coeffu(iim,jjm)
    2121    INTEGER,INTENT(IN) :: modfrstu(jjm)
     
    123123#endif
    124124    IMPLICIT NONE
    125     include 'dimensions.h'
     125    INCLUDE 'dimensions.h'
    126126    INTEGER,INTENT(IN) :: nlat
    127127    INTEGER,INTENT(IN) :: jj_begin
  • LMDZ6/branches/Amaury_dev/libf/filtrez/lmdz_filtre_fft_loc.F90

    r5128 r5134  
    1414    USE lmdz_fft
    1515    IMPLICIT NONE
    16     include 'dimensions.h'
     16    INCLUDE 'dimensions.h'
    1717    REAL, INTENT(IN) :: coeffu(iim, jjm)
    1818    INTEGER, INTENT(IN) :: modfrstu(jjm)
     
    111111#endif
    112112    IMPLICIT NONE
    113     include 'dimensions.h'
     113    INCLUDE 'dimensions.h'
    114114    INTEGER, INTENT(IN) :: jjb
    115115    INTEGER, INTENT(IN) :: jje
  • LMDZ6/branches/Amaury_dev/libf/filtrez/lmdz_filtreg.F90

    r5123 r5134  
    333333    IMPLICIT NONE
    334334    !
    335     include "dimensions.h"
    336     include "paramet.h"
    337     include "comgeom.h"
     335    INCLUDE "dimensions.h"
     336    INCLUDE "paramet.h"
     337    INCLUDE "comgeom.h"
    338338    !
    339339    REAL :: vec(iim, iim), vec1(iim, iim)
     
    593593    !     Correction  le 28/10/97    P. Le Van .
    594594    !  -------------------------------------------------------------------
    595     include "dimensions.h"
    596     include "paramet.h"
    597     include "comgeom.h"
     595    INCLUDE "dimensions.h"
     596    INCLUDE "paramet.h"
     597    INCLUDE "comgeom.h"
    598598
    599599    REAL  dlonu(iim), dlatu(jjm)
  • LMDZ6/branches/Amaury_dev/libf/misc/lmdz_vampir.F90

    r5119 r5134  
    1919
    2020#ifdef USE_VT
    21     include 'VT.inc'
     21    INCLUDE 'VT.inc'
    2222    INTEGER :: ierr
    2323   
     
    3232
    3333#ifdef USE_MPE
    34     include 'mpe_logf.h'
     34    INCLUDE 'mpe_logf.h'
    3535    INTEGER :: ierr,i
    3636   
     
    5353    INTEGER :: number
    5454#ifdef USE_VT   
    55     include 'VT.inc'
     55    INCLUDE 'VT.inc'
    5656    INTEGER :: ierr
    5757   
     
    5959#endif
    6060#ifdef USE_MPE
    61     include 'mpe_logf.h'
     61    INCLUDE 'mpe_logf.h'
    6262    INTEGER :: ierr,i
    6363    ierr = MPE_Log_event( MPE_begin(number), 0, '' )
     
    7070    INTEGER :: Number
    7171#ifdef USE_VT   
    72     include 'VT.inc'
     72    INCLUDE 'VT.inc'
    7373    INTEGER :: ierr
    7474   
     
    7777
    7878#ifdef USE_MPE
    79     include 'mpe_logf.h'
     79    INCLUDE 'mpe_logf.h'
    8080    INTEGER :: ierr,i
    8181    ierr = MPE_Log_event( MPE_end(number), 0, '' )
  • LMDZ6/branches/Amaury_dev/libf/misc/lmdz_xer.f90

    r5123 r5134  
    10451045    !   891214  Prologue converted to Version 4.0 format.  (BAB)
    10461046    !   900206  Routine changed from user-callable to subsidiary.  (WRB)
    1047     !   900510  Changed calling sequence to include LIBRARY and SUBROUTINE
     1047    !   900510  Changed calling sequence to INCLUDE LIBRARY and SUBROUTINE
    10481048    !       names, changed routine name from XERCTL to XERCNT.  (RWC)
    10491049    !   920501  Reformatted the REFERENCES section.  (WRB)
  • LMDZ6/branches/Amaury_dev/libf/phydev/physiq_mod.F90

    r5117 r5134  
    2727      USE iophy, ONLY: histwrite_phy
    2828
    29       IMPLICIT none
     29      IMPLICIT NONE
    3030
    3131! Routine argument:
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/aeropt_spl.f90

    r5105 r5134  
    1010  USE dimphy
    1111  USE infotrac
    12   IMPLICIT none
     12  IMPLICIT NONE
    1313  !
    1414  INCLUDE "chem.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/cltrac_spl.f90

    r5105 r5134  
    33
    44  USE dimphy
    5   IMPLICIT none
     5  IMPLICIT NONE
    66  !======================================================================
    77  ! Auteur(s): O. Boucher (LOA/LMD) date: 19961127
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfc.f90

    r5117 r5134  
    55  USE dimphy
    66  USE netcdf, ONLY: nf90_close, nf90_noerr, nf90_inq_varid, nf90_open, nf90_nowrite, nf90_get_var
    7   IMPLICIT none
     7  IMPLICIT NONE
    88
    99  ! Lire les conditions aux limites du modele pour la chimie.
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfc_new.f90

    r5117 r5134  
    77  USE dimphy
    88  USE netcdf, ONLY: nf90_get_var, nf90_close, nf90_noerr, nf90_inq_varid, nf90_open, nf90_nowrite
    9   IMPLICIT none
     9  IMPLICIT NONE
    1010
    1111  ! Lire les conditions aux limites du modele pour la chimie.
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfs.f90

    r5117 r5134  
    66  USE netcdf, ONLY: nf90_close, nf90_noerr, nf90_inq_varid, nf90_open, &
    77          nf90_nowrite, nf90_get_var
    8   IMPLICIT none
     8  IMPLICIT NONE
    99
    1010  ! Lire les conditions aux limites du modele pour la chimie.
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/condsurfs_new.f90

    r5117 r5134  
    1010  USE dimphy
    1111  USE netcdf, ONLY: nf90_get_var, nf90_inq_varid, nf90_close, nf90_noerr, nf90_open, nf90_nowrite
    12   IMPLICIT none
     12  IMPLICIT NONE
    1313
    1414  ! Lire les conditions aux limites du modele pour la chimie.
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/lsc_scav_orig.F90

    r5117 r5134  
    2121!=====================================================================
    2222
    23   include "dimensions.h"
    24   include "chem.h"
    25   include "YOECUMF.h"
     23  INCLUDE "dimensions.h"
     24  INCLUDE "chem.h"
     25  INCLUDE "YOECUMF.h"
    2626
    2727  REAL,INTENT(IN)                        :: pdtime ! time step (s)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/lsc_scav_spl.F90

    r5117 r5134  
    2323! SPLA version taken from trunk revision 2041
    2424
    25   include "dimensions.h"
    26   include "chem.h"
    27   include "YOECUMF.h"
     25  INCLUDE "dimensions.h"
     26  INCLUDE "chem.h"
     27  INCLUDE "YOECUMF.h"
    2828
    2929  REAL,INTENT(IN)                        :: pdtime ! time step (s)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r5123 r5134  
    7575  !JE20150620>>
    7676
    77   ! Author: Abderrahmane IDELKADI (original include file)
     77  ! Author: Abderrahmane IDELKADI (original INCLUDE file)
    7878  ! Author: Laurent FAIRHEAD (transformation to module/subroutine)
    7979  ! Author: Ulysse GERARD (effective implementation)
     
    396396    USE lmdz_yomcst
    397397    USE lmdz_iniprint, ONLY: lunout, prt_level
     398    USE lmdz_alpale
    398399
    399400    IMPLICIT NONE
     
    401402    !   INCLUDE "temps.h"
    402403    INCLUDE "clesphys.h"
    403     INCLUDE "alpale.h"
    404404    INCLUDE "compbl.h"
    405405    INCLUDE "dimensions.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/phytracr_spl_mod.F90

    r5133 r5134  
    798798
    799799    USE lmdz_yomcst
    800 
    801     IMPLICIT none
     800    USE lmdz_alpale
     801
     802    IMPLICIT NONE
    802803
    803804    !======================================================================
     
    817818    INCLUDE "YOETHF.h"
    818819    INCLUDE "paramet.h"
    819     INCLUDE "alpale.h"
    820820
    821821    !======================================================================
     
    11611161    ! JE for updating in  cltrac
    11621162    REAL, DIMENSION(klon, klev) :: delp     ! epaisseur de couche (Pa)
    1163     !! JE for include gas to particle conversion in output
     1163    !! JE for INCLUDE gas to particle conversion in output
    11641164    !      REAL his_g2pgas(klon)      ! gastoparticle in gas units (check!)
    11651165    !      REAL his_g2paer(klon)      ! gastoparticle in aerosol units (check!)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/tiedqneg.f90

    r5106 r5134  
    22
    33  USE dimphy
    4   IMPLICIT none
     4  IMPLICIT NONE
    55  !======================================================================
    66  ! Auteur(s): CG (LGGE/CNRS) date: 19950201
  • LMDZ6/branches/Amaury_dev/libf/phylmd/add_phys_tend_mod.F90

    r5117 r5134  
    108108USE phys_output_var_mod, ONLY: d_qw_col, d_ql_col, d_qs_col, d_qbs_col, d_qt_col, d_ek_col, d_h_dair_col &
    109109             , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_qbs_col, d_h_col
    110 IMPLICIT none
     110IMPLICIT NONE
    111111INCLUDE "YOMCST.h"
    112112INCLUDE "clesphys.h"
     
    507507USE phys_output_var_mod, ONLY: d_qw_col, d_ql_col, d_qs_col, d_qbs_col, d_qt_col, d_ek_col, d_h_dair_col &
    508508             , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_qbs_col, d_h_col
    509 IMPLICIT none
     509IMPLICIT NONE
    510510  include "YOMCST.h"
    511511  include "clesphys.h"
     
    656656                    zh_qw_col, zh_ql_col, zh_qs_col, zh_qbs_col, zh_col)
    657657
    658 IMPLICIT none
     658IMPLICIT NONE
    659659INCLUDE "YOMCST.h"
    660660
     
    736736    , rain_lsc, snow_lsc
    737737USE climb_hq_mod, ONLY: d_h_col_vdf, f_h_bnd
    738 IMPLICIT none
     738IMPLICIT NONE
    739739INCLUDE "YOMCST.h"
    740740
  • LMDZ6/branches/Amaury_dev/libf/phylmd/add_wake_tend.F90

    r5116 r5134  
    1313
    1414USE lmdz_print_control, ONLY: prt_level
    15 IMPLICIT none
     15IMPLICIT NONE
    1616
    1717! Arguments :
  • LMDZ6/branches/Amaury_dev/libf/phylmd/alpale_th.F90

    r5117 r5134  
    2121  USE lmdz_print_control, ONLY: mydebug=>debug , lunout, prt_level
    2222  USE lmdz_abort_physic, ONLY: abort_physic
     23  USE lmdz_alpale
    2324
    2425  IMPLICIT NONE
     
    4748
    4849  REAL, DIMENSION(klon), INTENT(OUT)                         :: birth_rate
    49 
    50   include "alpale.h"
    5150
    5251! Local variables
  • LMDZ6/branches/Amaury_dev/libf/phylmd/calbeta.F90

    r5099 r5134  
    88  USE indice_sol_mod
    99
    10   IMPLICIT none
     10  IMPLICIT NONE
    1111
    1212  INCLUDE "flux_arp.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/cfmip_point_locations.F90

    r5116 r5134  
    55
    66 SUBROUTINE read_CFMIP_point_locations(npCFMIP, tab, lonCFMIP, latCFMIP)
    7   IMPLICIT none
     7  IMPLICIT NONE
    88  INTEGER :: npCFMIP
    99  REAL, DIMENSION(npCFMIP) :: lonCFMIP, latCFMIP
     
    3535  USE lmdz_grid_phy, ONLY: nbp_lon, nbp_lat, klon_glo
    3636
    37   IMPLICIT none
     37  IMPLICIT NONE
    3838  INTEGER :: npCFMIP
    3939  REAL, DIMENSION(npCFMIP) :: lonCFMIP, latCFMIP
  • LMDZ6/branches/Amaury_dev/libf/phylmd/cmp_seri_mod.F90

    r5117 r5134  
    2626         t_seri
    2727
    28     IMPLICIT none
     28    IMPLICIT NONE
    2929    ! Local :
    3030    !--------
     
    6262         t_seri
    6363    USE lmdz_print_control, ONLY: prt_level
    64     IMPLICIT none
     64    IMPLICIT NONE
    6565    ! Arguments :
    6666    !------------
  • LMDZ6/branches/Amaury_dev/libf/phylmd/coefcdrag.F90

    r5117 r5134  
    1010      USE lmdz_abort_physic, ONLY: abort_physic
    1111
    12       IMPLICIT none
     12      IMPLICIT NONE
    1313!-------------------------------------------------------------------------
    1414! Objet : calcul des cdrags pour le moment (cdram) et les flux de chaleur
  • LMDZ6/branches/Amaury_dev/libf/phylmd/conf_phys_m.F90

    r5117 r5134  
    3737    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_STRATAER
    3838    USE lmdz_abort_physic, ONLY: abort_physic
     39    USE lmdz_alpale
    3940
    4041    INCLUDE "conema3.h"
     
    4243    INCLUDE "YOMCST.h"
    4344    INCLUDE "YOMCST2.h"
    44     INCLUDE "alpale.h"
    4545
    4646    !IM : on inclut/initialise les taux de CH4, N2O, CFC11 et CFC12
  • LMDZ6/branches/Amaury_dev/libf/phylmd/create_etat0_unstruct_mod.F90

    r5116 r5134  
    9292  USE lmdz_geometry
    9393  USE lmdz_ioipsl_getin_p, ONLY: getin_p
     94  USE lmdz_alpale
    9495
    9596  IMPLICIT NONE
     
    114115
    115116    INCLUDE "compbl.h"
    116     INCLUDE "alpale.h"
    117    
     117
    118118    INTEGER :: ji,j,i
    119119 
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/lmdz_1dutils.f90

    r5133 r5134  
    66CONTAINS
    77  REAL FUNCTION fq_sat(kelvin, millibar)
    8     IMPLICIT none
     8    IMPLICIT NONE
    99    !======================================================================
    1010    ! Autheur(s): Z.X. Li (LMD/CNRS)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/dyn1d/lmdz_old_1dconv.f90

    r5128 r5134  
    632632  SUBROUTINE rdgrads(itape, icount, nl, z, ht, hq, hw, hu, hv, hthtur, hqtur, &
    633633          &  ts_fcg, ts, imp_fcg, Turb_fcg)
    634     IMPLICIT none
     634    IMPLICIT NONE
    635635    INTEGER itape, icount, icomp, nl
    636636    REAL z(nl), ht(nl), hq(nl), hw(nl), hu(nl), hv(nl)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/ener_conserv.F90

    r5117 r5134  
    3131USE lmdz_abort_physic, ONLY: abort_physic
    3232
    33 IMPLICIT none
     33IMPLICIT NONE
    3434INCLUDE "YOMCST.h"
    3535INCLUDE "YOETHF.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/gr_fi_ecrit.F90

    r5099 r5134  
    11SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)
    2   IMPLICIT none
     2  IMPLICIT NONE
    33
    44  ! Tranformer une variable de la grille physique a
  • LMDZ6/branches/Amaury_dev/libf/phylmd/inlandsis/surf_inlandsis_mod.F90

    r5128 r5134  
    10421042        USE indice_sol_mod
    10431043
    1044         IMPLICIT none
     1044        IMPLICIT NONE
    10451045        !======================================================================
    10461046        ! Auteur(s) HJ PUNGE (LSCE) date: 07/2009
     
    12781278        USE dimphy
    12791279
    1280         IMPLICIT none
     1280        IMPLICIT NONE
    12811281
    12821282        include "clesphys.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/iophys.F90

    r5119 r5134  
    187187#ifdef und
    188188      SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)
    189       IMPLICIT none
     189      IMPLICIT NONE
    190190
    191191!=======================================================================
  • LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_alpale.f90

    r5133 r5134  
    1 SUBROUTINE alpale( debut, itap, dtime, paprs, omega, t_seri,   &
    2                     alp_offset, it_wape_prescr,  wape_prescr, fip_prescr, &
    3                     ale_bl_prescr, alp_bl_prescr, &
    4                     wake_pe, wake_fip,  &
    5                     Ale_bl, Ale_bl_trig, Alp_bl, &
    6                     Ale, Alp, Ale_wake, Alp_wake )
    7 
    8 ! **************************************************************
    9 ! *
    10 ! ALPALE                                                       *
    11 ! *
    12 ! *
    13 ! written by   : Jean-Yves Grandpeix, 12/05/2016              *
    14 ! modified by :                                               *
    15 ! **************************************************************
    16 
    17   USE dimphy
    18   USE lmdz_ioipsl_getin_p, ONLY: getin_p
    19   USE lmdz_print_control, ONLY: mydebug=>debug , lunout, prt_level
    20   USE phys_local_var_mod, ONLY: zw2       ! Variables internes non sauvegardees de la physique
    21   USE lmdz_abort_physic, ONLY: abort_physic
    22 
    23   IMPLICIT NONE
    24 
    25 !================================================================
    26 ! Auteur(s)   : Jean-Yves Grandpeix, 12/05/2016
    27 ! Objet : Sums up all contributions to Ale and Alp
    28 !================================================================
    29 
    30 ! Input arguments
    31 !----------------
    32   LOGICAL, INTENT(IN)                                        :: debut
    33   INTEGER, INTENT(IN)                                        :: itap
    34   REAL, INTENT(IN)                                           :: dtime
    35   INTEGER, INTENT(IN)                                        :: it_wape_prescr
    36   REAL, INTENT(IN)                                           :: wape_prescr, fip_prescr
    37   REAL, INTENT(IN)                                           :: Ale_bl_prescr, Alp_bl_prescr
    38   REAL, INTENT(IN)                                           :: alp_offset
    39   REAL, DIMENSION(klon,klev+1), INTENT(IN)                   :: paprs
    40   REAL, DIMENSION(klon,klev), INTENT(IN)                     :: t_seri
    41   REAL, DIMENSION(klon,klev), INTENT(IN)                     :: omega
    42   REAL, DIMENSION(klon), INTENT(IN)                          :: wake_pe, wake_fip
    43   REAL, DIMENSION(klon), INTENT(IN)                          :: Ale_bl, Ale_bl_trig, Alp_bl
    44 
    45 
    46 ! Output arguments
    47 !----------------
    48   REAL, DIMENSION(klon), INTENT(OUT)                         :: Ale, Alp
    49   REAL, DIMENSION(klon), INTENT(OUT)                         :: Ale_wake, Alp_wake
    50 
    51   include "alpale.h"
    52   include "YOMCST.h"
    53   include "YOETHF.h"
    54 
    55 ! Local variables
    56 !----------------
    57   INTEGER                                                    :: i, k
    58   REAL, DIMENSION(klon)                                      :: www
    59   REAL, SAVE                                                 :: ale_max=1000.
    60   REAL, SAVE                                                 :: alp_max=2.
    61   CHARACTER*20 modname
    62   CHARACTER*80 abort_message
     1! Contains the alpale subroutine, as well as the old content from alpale.h
     2
     3MODULE lmdz_alpale
     4  IMPLICIT NONE; PRIVATE
     5  PUBLIC alpale
     6
     7  !=====================================================================
     8  ! Specifique de Ale/Alp :
     9  !=====================================================================
     10  PUBLIC iflag_trig_bl, iflag_clos_bl, tau_trig_shallow, tau_trig_deep, iflag_strig, &
     11          alp_bl_k, s_trig, h_trig, iflag_coupl, iflag_clos, iflag_wake
     12  ! dans alealp_th, thermcell_alp, physiq_mod, conf_phys
     13  INTEGER :: iflag_trig_bl, iflag_clos_bl, iflag_strig
     14  INTEGER :: tau_trig_shallow, tau_trig_deep
     15  REAL :: s_trig, h_trig
     16  ! thermcell_alp et convection ...
     17  INTEGER :: iflag_coupl, iflag_clos, iflag_wake
     18  ! thermcell_alp
     19  REAL :: alp_bl_k
     20  !$OMP THREADPRIVATE(iflag_trig_bl, iflag_clos_bl, tau_trig_shallow, tau_trig_deep, iflag_strig)
     21  !$OMP THREADPRIVATE(alp_bl_k, s_trig, h_trig, iflag_coupl, iflag_clos, iflag_wake)
     22
     23CONTAINS
     24
     25  SUBROUTINE alpale(debut, itap, dtime, paprs, omega, t_seri, &
     26          alp_offset, it_wape_prescr, wape_prescr, fip_prescr, &
     27          ale_bl_prescr, alp_bl_prescr, &
     28          wake_pe, wake_fip, &
     29          Ale_bl, Ale_bl_trig, Alp_bl, &
     30          Ale, Alp, Ale_wake, Alp_wake)
     31
     32    ! **************************************************************
     33    ! *
     34    ! ALPALE                                                       *
     35    ! *
     36    ! *
     37    ! written by   : Jean-Yves Grandpeix, 12/05/2016              *
     38    ! modified by :                                               *
     39    ! **************************************************************
     40
     41    USE dimphy
     42    USE lmdz_ioipsl_getin_p, ONLY: getin_p
     43    USE lmdz_print_control, ONLY: mydebug => debug, lunout, prt_level
     44    USE phys_local_var_mod, ONLY: zw2       ! Variables internes non sauvegardees de la physique
     45    USE lmdz_abort_physic, ONLY: abort_physic
     46
     47    IMPLICIT NONE
     48
     49    !================================================================
     50    ! Auteur(s)   : Jean-Yves Grandpeix, 12/05/2016
     51    ! Objet : Sums up all contributions to Ale and Alp
     52    !================================================================
     53
     54    ! Input arguments
     55    !----------------
     56    LOGICAL, INTENT(IN) :: debut
     57    INTEGER, INTENT(IN) :: itap
     58    REAL, INTENT(IN) :: dtime
     59    INTEGER, INTENT(IN) :: it_wape_prescr
     60    REAL, INTENT(IN) :: wape_prescr, fip_prescr
     61    REAL, INTENT(IN) :: Ale_bl_prescr, Alp_bl_prescr
     62    REAL, INTENT(IN) :: alp_offset
     63    REAL, DIMENSION(klon, klev + 1), INTENT(IN) :: paprs
     64    REAL, DIMENSION(klon, klev), INTENT(IN) :: t_seri
     65    REAL, DIMENSION(klon, klev), INTENT(IN) :: omega
     66    REAL, DIMENSION(klon), INTENT(IN) :: wake_pe, wake_fip
     67    REAL, DIMENSION(klon), INTENT(IN) :: Ale_bl, Ale_bl_trig, Alp_bl
     68
     69
     70    ! Output arguments
     71    !----------------
     72    REAL, DIMENSION(klon), INTENT(OUT) :: Ale, Alp
     73    REAL, DIMENSION(klon), INTENT(OUT) :: Ale_wake, Alp_wake
     74
     75    include "YOMCST.h"
     76    include "YOETHF.h"
     77
     78    ! Local variables
     79    !----------------
     80    INTEGER :: i, k
     81    REAL, DIMENSION(klon) :: www
     82    REAL, SAVE :: ale_max = 1000.
     83    REAL, SAVE :: alp_max = 2.
     84    CHARACTER*20 modname
     85    CHARACTER*80 abort_message
    6386
    6487
    6588    !$OMP THREADPRIVATE(ale_max,alp_max)
    6689
    67        ! Calcul de l'energie disponible ALE (J/kg) et de la puissance
    68        ! disponible ALP (W/m2) pour le soulevement des particules dans
    69        ! le modele convectif
    70 
    71        do i = 1,klon
    72           ALE(i) = 0.
    73           ALP(i) = 0.
    74        enddo
    75 
    76        !calcul de ale_wake et alp_wake
    77        IF (iflag_wake>=1) THEN
    78           IF (itap <= it_wape_prescr) THEN
    79              do i = 1,klon
    80                 ale_wake(i) = wape_prescr
    81                 alp_wake(i) = fip_prescr
    82              enddo
    83           else
    84              do i = 1,klon
    85                 !jyg  ALE=WAPE au lieu de ALE = 1/2 Cstar**2
    86                 !cc           ale_wake(i) = 0.5*wake_cstar(i)**2
    87                 ale_wake(i) = wake_pe(i)
    88                 alp_wake(i) = wake_fip(i)
    89              enddo
    90           endif
    91        else
    92           do i = 1,klon
    93              ale_wake(i) = 0.
    94              alp_wake(i) = 0.
     90    ! Calcul de l'energie disponible ALE (J/kg) et de la puissance
     91    ! disponible ALP (W/m2) pour le soulevement des particules dans
     92    ! le modele convectif
     93
     94    do i = 1, klon
     95      ALE(i) = 0.
     96      ALP(i) = 0.
     97    enddo
     98
     99    !calcul de ale_wake et alp_wake
     100    IF (iflag_wake>=1) THEN
     101      IF (itap <= it_wape_prescr) THEN
     102        do i = 1, klon
     103          ale_wake(i) = wape_prescr
     104          alp_wake(i) = fip_prescr
     105        enddo
     106      else
     107        do i = 1, klon
     108          !jyg  ALE=WAPE au lieu de ALE = 1/2 Cstar**2
     109          !cc           ale_wake(i) = 0.5*wake_cstar(i)**2
     110          ale_wake(i) = wake_pe(i)
     111          alp_wake(i) = wake_fip(i)
     112        enddo
     113      endif
     114    else
     115      do i = 1, klon
     116        ale_wake(i) = 0.
     117        alp_wake(i) = 0.
     118      enddo
     119    endif
     120    !combinaison avec ale et alp de couche limite: constantes si pas
     121    !de couplage, valeurs calculees dans le thermique sinon
     122    IF (iflag_coupl==0) THEN
     123      IF (debut.AND.prt_level>9) &
     124              WRITE(lunout, *)'ALE et ALP imposes'
     125      do i = 1, klon
     126        !on ne couple que ale
     127        !           ALE(i) = max(ale_wake(i),Ale_bl(i))
     128        ALE(i) = max(ale_wake(i), ale_bl_prescr)
     129        !on ne couple que alp
     130        !           ALP(i) = alp_wake(i) + Alp_bl(i)
     131        ALP(i) = alp_wake(i) + alp_bl_prescr
     132      enddo
     133    else
     134      IF(prt_level>9)WRITE(lunout, *)'ALE et ALP couples au thermique'
     135      !         do i = 1,klon
     136      !             ALE(i) = max(ale_wake(i),Ale_bl(i))
     137      ! avant        ALP(i) = alp_wake(i) + Alp_bl(i)
     138      !             ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb
     139      !         WRITE(20,*)'ALE',ALE(i),Ale_bl(i),ale_wake(i)
     140      !         WRITE(21,*)'ALP',ALP(i),Alp_bl(i),alp_wake(i)
     141      !         enddo
     142
     143      ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     144      ! Modif FH 2010/04/27. Sans doute temporaire.
     145      ! Deux options pour le alp_offset : constant si >?? 0 ou
     146      ! proportionnel ??a w si <0
     147      ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     148      ! Estimation d'une vitesse verticale effective pour ALP
     149      IF (1==0) THEN
     150        www(1:klon) = 0.
     151        do k = 2, klev - 1
     152          do i = 1, klon
     153            www(i) = max(www(i), -omega(i, k) * RD * t_seri(i, k) &
     154                    / (RG * paprs(i, k)) * zw2(i, k) * zw2(i, k))
     155            ! if (paprs(i,k)>pbase(i)) THEN
     156            ! calcul approche de la vitesse verticale en m/s
     157            !  www(i)=max(www(i),-omega(i,k)*RD*temp(i,k)/(RG*paprs(i,k))
     158            !             endif
     159            !   Le 0.1 est en gros H / ps = 1e4 / 1e5
    95160          enddo
    96        endif
    97        !combinaison avec ale et alp de couche limite: constantes si pas
    98        !de couplage, valeurs calculees dans le thermique sinon
    99        IF (iflag_coupl==0) THEN
    100           IF (debut.AND.prt_level>9) &
    101                WRITE(lunout,*)'ALE et ALP imposes'
    102           do i = 1,klon
    103              !on ne couple que ale
    104              !           ALE(i) = max(ale_wake(i),Ale_bl(i))
    105              ALE(i) = max(ale_wake(i),ale_bl_prescr)
    106              !on ne couple que alp
    107              !           ALP(i) = alp_wake(i) + Alp_bl(i)
    108              ALP(i) = alp_wake(i) + alp_bl_prescr
    109           enddo
    110        else
    111           IF(prt_level>9)WRITE(lunout,*)'ALE et ALP couples au thermique'
    112           !         do i = 1,klon
    113           !             ALE(i) = max(ale_wake(i),Ale_bl(i))
    114           ! avant        ALP(i) = alp_wake(i) + Alp_bl(i)
    115           !             ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb
    116           !         WRITE(20,*)'ALE',ALE(i),Ale_bl(i),ale_wake(i)
    117           !         WRITE(21,*)'ALP',ALP(i),Alp_bl(i),alp_wake(i)
    118           !         enddo
    119 
    120           ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    121           ! Modif FH 2010/04/27. Sans doute temporaire.
    122           ! Deux options pour le alp_offset : constant si >?? 0 ou
    123           ! proportionnel ??a w si <0
    124           ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    125           ! Estimation d'une vitesse verticale effective pour ALP
    126           IF (1==0) THEN
    127              www(1:klon)=0.
    128              do k=2,klev-1
    129                 do i=1,klon
    130                    www(i)=max(www(i),-omega(i,k)*RD*t_seri(i,k) &
    131                         /(RG*paprs(i,k)) *zw2(i,k)*zw2(i,k))
    132                    ! if (paprs(i,k)>pbase(i)) THEN
    133                    ! calcul approche de la vitesse verticale en m/s
    134                    !  www(i)=max(www(i),-omega(i,k)*RD*temp(i,k)/(RG*paprs(i,k))
    135                    !             endif
    136                    !   Le 0.1 est en gros H / ps = 1e4 / 1e5
    137                 enddo
    138              enddo
    139              do i=1,klon
    140                 IF (www(i)>0. .AND. ale_bl(i)>0. ) www(i)=www(i)/ale_bl(i)
    141              enddo
    142           ENDIF
    143 
    144 
    145           do i = 1,klon
    146              ALE(i) = max(ale_wake(i),Ale_bl(i))
    147              !cc nrlmd le 10/04/2012----------Stochastic triggering------------
    148              IF (iflag_trig_bl>=1) THEN
    149                 ALE(i) = max(ale_wake(i),Ale_bl_trig(i))
    150              endif
    151              !cc fin nrlmd le 10/04/2012
    152              IF (alp_offset>=0.) THEN
    153                 ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb
    154              else
    155                 abort_message ='Ne pas passer la car www non calcule'
    156                 CALL abort_physic (modname,abort_message,1)
    157 
    158                 ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    159                 !                                _                  _
    160                 ! Ajout d'une composante 3 * A * w w'2 a w'3 avec
    161                 ! w=www : w max sous pbase ou A est la fraction
    162                 ! couverte par les ascendances w' on utilise le fait
    163                 ! que A * w'3 = ALP et donc A * w'2 ~ ALP / sqrt(ALE)
    164                 ! (on ajoute 0.1 pour les singularites)
    165                 ALP(i)=alp_wake(i)*(1.+3.*www(i)/( sqrt(ale_wake(i))+0.1) ) &
    166                      +alp_bl(i)  *(1.+3.*www(i)/( sqrt(ale_bl(i))  +0.1) )
    167                 !    ALP(i)=alp_wake(i)+Alp_bl(i)+alp_offset*min(omega(i,6),0.)
    168                 !             if (alp(i)<0.) THEN
    169                 !                PRINT*,'ALP ',alp(i),alp_wake(i) &
    170                 !                     ,Alp_bl(i),alp_offset*min(omega(i,6),0.)
    171                 !             endif
    172              endif
    173           enddo
    174           ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    175 
    176        endif
    177        do i=1,klon
    178           IF (alp(i)>alp_max) THEN
    179              IF(prt_level>9)WRITE(lunout,*)                             &
    180                   'WARNING SUPER ALP (seuil=',alp_max, &
    181                   '): i, alp, alp_wake,ale',i,alp(i),alp_wake(i),ale(i)
    182              alp(i)=alp_max
    183           endif
    184           IF (ale(i)>ale_max) THEN
    185              IF(prt_level>9)WRITE(lunout,*)                             &
    186                   'WARNING SUPER ALE (seuil=',ale_max, &
    187                   '): i, alp, alp_wake,ale',i,ale(i),ale_wake(i),alp(i)
    188              ale(i)=ale_max
    189           endif
    190        enddo
    191 
    192        !fin calcul ale et alp
    193        !=======================================================================
    194 
    195 
    196   RETURN
     161        enddo
     162        do i = 1, klon
     163          IF (www(i)>0. .AND. ale_bl(i)>0.) www(i) = www(i) / ale_bl(i)
     164        enddo
     165      ENDIF
     166
     167      do i = 1, klon
     168        ALE(i) = max(ale_wake(i), Ale_bl(i))
     169        !cc nrlmd le 10/04/2012----------Stochastic triggering------------
     170        IF (iflag_trig_bl>=1) THEN
     171          ALE(i) = max(ale_wake(i), Ale_bl_trig(i))
     172        endif
     173        !cc fin nrlmd le 10/04/2012
     174        IF (alp_offset>=0.) THEN
     175          ALP(i) = alp_wake(i) + Alp_bl(i) + alp_offset ! modif sb
     176        else
     177          abort_message = 'Ne pas passer la car www non calcule'
     178          CALL abort_physic (modname, abort_message, 1)
     179
     180          ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     181          !                                _                  _
     182          ! Ajout d'une composante 3 * A * w w'2 a w'3 avec
     183          ! w=www : w max sous pbase ou A est la fraction
     184          ! couverte par les ascendances w' on utilise le fait
     185          ! que A * w'3 = ALP et donc A * w'2 ~ ALP / sqrt(ALE)
     186          ! (on ajoute 0.1 pour les singularites)
     187          ALP(i) = alp_wake(i) * (1. + 3. * www(i) / (sqrt(ale_wake(i)) + 0.1)) &
     188                  + alp_bl(i) * (1. + 3. * www(i) / (sqrt(ale_bl(i)) + 0.1))
     189          !    ALP(i)=alp_wake(i)+Alp_bl(i)+alp_offset*min(omega(i,6),0.)
     190          !             if (alp(i)<0.) THEN
     191          !                PRINT*,'ALP ',alp(i),alp_wake(i) &
     192          !                     ,Alp_bl(i),alp_offset*min(omega(i,6),0.)
     193          !             endif
     194        endif
     195      enddo
     196      ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     197
     198    endif
     199    do i = 1, klon
     200      IF (alp(i)>alp_max) THEN
     201        IF(prt_level>9)WRITE(lunout, *)                             &
     202                'WARNING SUPER ALP (seuil=', alp_max, &
     203                '): i, alp, alp_wake,ale', i, alp(i), alp_wake(i), ale(i)
     204        alp(i) = alp_max
     205      endif
     206      IF (ale(i)>ale_max) THEN
     207        IF(prt_level>9)WRITE(lunout, *)                             &
     208                'WARNING SUPER ALE (seuil=', ale_max, &
     209                '): i, alp, alp_wake,ale', i, ale(i), ale_wake(i), alp(i)
     210        ale(i) = ale_max
     211      endif
     212    enddo
     213
     214    !fin calcul ale et alp
     215    !=======================================================================
     216
     217    RETURN
    197218  END
    198219
     220END MODULE lmdz_alpale
  • LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_cloudth.F90

    r5117 r5134  
    21222122    USE phys_state_var_mod, ONLY: fm_therm, detr_therm, entr_therm
    21232123
    2124     IMPLICIT none
     2124    IMPLICIT NONE
    21252125
    21262126    INCLUDE "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_lscp_old.F90

    r5117 r5134  
    2727
    2828
    29   IMPLICIT none
     29  IMPLICIT NONE
    3030  !======================================================================
    3131  ! Auteur(s): Z.X. Li (LMD/CNRS)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/lmdz_thermcell_alp.F90

    r5119 r5134  
    2121      USE indice_sol_mod
    2222      USE lmdz_thermcell_main, ONLY: thermcell_tke_transport
     23      USE lmdz_alpale
     24
    2325      IMPLICIT NONE
    2426
     
    4042      INCLUDE "YOETHF.h"
    4143      INCLUDE "FCTTRE.h"
    42       INCLUDE "alpale.h"
    4344
    4445!   arguments:
  • LMDZ6/branches/Amaury_dev/libf/phylmd/o3_chem_m.F90

    r5119 r5134  
    22module o3_chem_m
    33
    4   IMPLICIT none
     4  IMPLICIT NONE
    55
    66  PRIVATE o3_prod
  • LMDZ6/branches/Amaury_dev/libf/phylmd/perturb_radlwsw.F90

    r5117 r5134  
    44
    55      USE dimphy
    6       IMPLICIT none
     6      IMPLICIT NONE
    77      INCLUDE "flux_arp.h"     
    88
  • LMDZ6/branches/Amaury_dev/libf/phylmd/phyetat0_mod.F90

    r5117 r5134  
    4242    USE netcdf, ONLY: missing_val_netcdf => nf90_fill_real
    4343    USE config_ocean_skin_m, ONLY: activate_ocean_skin
    44 
    45     IMPLICIT none
     44    USE lmdz_alpale
     45
     46    IMPLICIT NONE
    4647    !======================================================================
    4748    ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
     
    5051    include "dimsoil.h"
    5152    include "clesphys.h"
    52     include "alpale.h"
    5353    include "compbl.h"
    5454    include "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/phyredem.F90

    r5117 r5134  
    4242  USE config_ocean_skin_m, ONLY: activate_ocean_skin
    4343  USE lmdz_abort_physic, ONLY: abort_physic
    44 
    45   IMPLICIT none
     44  USE lmdz_alpale
     45
     46  IMPLICIT NONE
    4647
    4748  include "dimsoil.h"
    4849  include "clesphys.h"
    49   include "alpale.h"
    5050  include "compbl.h"
    5151  !======================================================================
  • LMDZ6/branches/Amaury_dev/libf/phylmd/phys_output_write_mod.F90

    r5132 r5134  
    467467    USE tracinca_mod, ONLY: config_inca
    468468    USE config_ocean_skin_m, ONLY: activate_ocean_skin
    469 
    470469    USE lmdz_vertical_layers, ONLY: presnivs
     470    USE lmdz_alpale
    471471
    472472    IMPLICIT NONE
    473473
    474474    INCLUDE "clesphys.h"
    475     INCLUDE "alpale.h"
    476475    INCLUDE "compbl.h"
    477476    INCLUDE "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmd/physiq_mod.F90

    r5133 r5134  
    350350    USE output_physiqex_mod, ONLY: output_physiqex
    351351    USE lmdz_simu_airs, ONLY: simu_airs
     352    USE lmdz_alpale
    352353
    353354    IMPLICIT NONE
     
    405406    include "dimsoil.h"
    406407    include "clesphys.h"
    407     include "alpale.h"
    408408    include "dimpft.h"
    409409    !======================================================================
  • LMDZ6/branches/Amaury_dev/libf/phylmd/physiqex_mod.F90

    r5117 r5134  
    2222      USE output_physiqex_mod, ONLY: output_physiqex
    2323
    24       IMPLICIT none
     24      IMPLICIT NONE
    2525
    2626! Routine argument:
  • LMDZ6/branches/Amaury_dev/libf/phylmd/qcheck.F90

    r5099 r5134  
    11FUNCTION qcheck(klon,klev,paprs,q,ql,aire)
    2   IMPLICIT none
     2  IMPLICIT NONE
    33
    44  ! Calculer et imprimer l'eau totale. A utiliser pour verifier
  • LMDZ6/branches/Amaury_dev/libf/phylmd/reevap.F90

    r5117 r5134  
    55    USE add_phys_tend_mod, ONLY: fl_cor_ebil
    66   
    7     IMPLICIT none
     7    IMPLICIT NONE
    88    !>======================================================================
    99
  • LMDZ6/branches/Amaury_dev/libf/phylmd/screenp_mod.F90

    r5117 r5134  
    1919                     ustar, testar, qstar, zref, &
    2020                     delu, delte, delq)
    21       IMPLICIT none
     21      IMPLICIT NONE
    2222!-------------------------------------------------------------------------
    2323
     
    126126                     zref, &
    127127                     delu, delte, delq)
    128       IMPLICIT none
     128      IMPLICIT NONE
    129129!-------------------------------------------------------------------------
    130130
  • LMDZ6/branches/Amaury_dev/libf/phylmd/water_int.F90

    r5103 r5134  
    66!=============================================================
    77
    8 IMPLICIT none
     8IMPLICIT NONE
    99
    1010! Arguments
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/add_phys_tend_mod.F90

    r5117 r5134  
    160160#endif 
    161161#endif
    162 IMPLICIT none
     162IMPLICIT NONE
    163163  include "YOMCST.h"
    164164  include "clesphys.h"
     
    684684USE phys_output_var_mod, ONLY: d_qw_col, d_ql_col, d_qs_col, d_qbs_col, d_qt_col, d_ek_col, d_h_dair_col &
    685685              , d_h_qw_col, d_h_ql_col, d_h_qs_col, d_h_qbs_col, d_h_col
    686 IMPLICIT none
     686IMPLICIT NONE
    687687  include "YOMCST.h"
    688688  include "clesphys.h"
     
    834834                    zh_qw_col, zh_ql_col, zh_qs_col, zh_qbs_col, zh_col)
    835835
    836 IMPLICIT none
     836IMPLICIT NONE
    837837  include "YOMCST.h"
    838838
     
    915915      , rain_lsc, snow_lsc
    916916USE climb_hq_mod, ONLY: d_h_col_vdf, f_h_bnd
    917 IMPLICIT none
     917IMPLICIT NONE
    918918include "YOMCST.h"
    919919
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/add_wake_tend.F90

    r5116 r5134  
    2121    USE phys_state_var_mod, ONLY:  wake_deltaxt   
    2222#endif
    23 IMPLICIT none
     23IMPLICIT NONE
    2424
    2525! Arguments :
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/lmdz_alpale.f90

    r5133 r5134  
    1 link ../phylmd/alpale.F90
     1link ../phylmd/lmdz_alpale.f90
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/lmdz_lscp_old.F90

    r5132 r5134  
    6868#endif
    6969
    70   IMPLICIT none
     70  IMPLICIT NONE
    7171  !======================================================================
    7272  ! Auteur(s): Z.X. Li (LMD/CNRS)
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/phyetat0_mod.F90

    r5132 r5134  
    5151  USE netcdf, ONLY: missing_val_netcdf => nf90_fill_real
    5252  USE config_ocean_skin_m, ONLY: activate_ocean_skin
     53  USE lmdz_alpale
    5354#ifdef ISO
    5455  USE infotrac_phy, ONLY: niso
     
    6061#endif
    6162
    62   IMPLICIT none
     63  IMPLICIT NONE
    6364  !======================================================================
    6465  ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
     
    6768  include "dimsoil.h"
    6869  include "clesphys.h"
    69   include "alpale.h"
    7070  include "compbl.h"
    7171  include "YOMCST.h"
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/phyredem.F90

    r5132 r5134  
    5252  USE config_ocean_skin_m, ONLY: activate_ocean_skin
    5353  USE lmdz_abort_physic, ONLY: abort_physic
    54 
    55   IMPLICIT none
     54  USE lmdz_alpale
     55
     56  IMPLICIT NONE
    5657
    5758  include "dimsoil.h"
    5859  include "clesphys.h"
    59   include "alpale.h"
    6060  include "compbl.h"
    6161  !======================================================================
     
    509509#endif
    510510      !USE phyredem, ONLY: put_field_srf1
     511      USE lmdz_alpale
    511512
    512513        IMPLICIT NONE
     
    516517 include "dimsoil.h"
    517518 include "clesphys.h"
    518  include "alpale.h"
    519519 include "compbl.h"
    520520      ! inputs
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/physiq_mod.F90

    r5133 r5134  
    418418       USE output_physiqex_mod, ONLY: output_physiqex
    419419       USE lmdz_simu_airs, ONLY: simu_airs
     420       USE lmdz_alpale
    420421
    421422
     
    474475    include "dimsoil.h"
    475476    include "clesphys.h"
    476     include "alpale.h"
    477477    include "dimpft.h"
    478478    !======================================================================
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/reevap.F90

    r5117 r5134  
    1515#endif
    1616#endif
    17     IMPLICIT none
     17    IMPLICIT NONE
    1818    !>======================================================================
    1919
Note: See TracChangeset for help on using the changeset viewer.