Ignore:
Timestamp:
Jul 26, 2024, 5:56:37 PM (8 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/dyn3d
Files:
35 edited

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
Note: See TracChangeset for help on using the changeset viewer.