Changeset 2597


Ignore:
Timestamp:
Jul 22, 2016, 8:44:47 AM (8 years ago)
Author:
Ehouarn Millour
Message:

Cleanup in the dynamics: get rid of comconst.h, make it a module comconst_mod.
EM

Location:
LMDZ5/trunk/libf
Files:
1 added
1 deleted
142 edited
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/addfi.F

    r1987 r2597  
    4646c    ------------------
    4747c
    48 #include "dimensions.h"
    49 #include "paramet.h"
    50 #include "comconst.h"
    51 #include "comgeom.h"
    52 #include "serre.h"
     48      include "dimensions.h"
     49      include "paramet.h"
     50      include "comgeom.h"
     51      include "serre.h"
    5352c
    5453c    Arguments :
  • LMDZ5/trunk/libf/dyn3d/advect.F

    r1907 r2597  
    44      SUBROUTINE advect(ucov,vcov,teta,w,massebx,masseby,du,dv,dteta)
    55
     6      USE comconst_mod, ONLY: daysec
     7     
    68      IMPLICIT NONE
    79c=======================================================================
     
    2426c   -------------
    2527
    26 #include "dimensions.h"
    27 #include "paramet.h"
    28 #include "comconst.h"
    29 #include "comvert.h"
    30 #include "comgeom.h"
    31 #include "logic.h"
    32 #include "ener.h"
     28      include "dimensions.h"
     29      include "paramet.h"
     30      include "comvert.h"
     31      include "comgeom.h"
     32      include "logic.h"
     33      include "ener.h"
    3334
    3435c   Arguments:
  • LMDZ5/trunk/libf/dyn3d/advtrac.F90

    r2286 r2597  
    1111  USE infotrac, ONLY: nqtot, iadv,nqperes,ok_iso_verif
    1212  USE control_mod, ONLY: iapp_tracvl, day_step
    13 
     13  USE comconst_mod, ONLY: dtvr
    1414
    1515  IMPLICIT NONE
     
    1717  include "dimensions.h"
    1818  include "paramet.h"
    19   include "comconst.h"
    2019  include "comvert.h"
    2120  include "comdissip.h"
  • LMDZ5/trunk/libf/dyn3d/bilan_dyn.F

    r1907 r2597  
    1313      USE IOIPSL
    1414#endif
     15      USE comconst_mod, ONLY: pi, cpp
    1516
    1617      IMPLICIT NONE
    1718
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comconst.h"
    21 #include "comvert.h"
    22 #include "comgeom2.h"
    23 #include "temps.h"
    24 #include "iniprint.h"
     19      include "dimensions.h"
     20      include "paramet.h"
     21      include "comvert.h"
     22      include "comgeom2.h"
     23      include "temps.h"
     24      include "iniprint.h"
    2525
    2626c====================================================================
  • LMDZ5/trunk/libf/dyn3d/caladvtrac.F

    r2286 r2597  
    1010      USE infotrac, ONLY : nqtot
    1111      USE control_mod, ONLY : iapp_tracvl,planet_type
     12      USE comconst_mod, ONLY: dtvr
    1213 
    1314      IMPLICIT NONE
     
    2324
    2425
    25 #include "dimensions.h"
    26 #include "paramet.h"
    27 #include "comconst.h"
     26      include "dimensions.h"
     27      include "paramet.h"
    2828
    2929c   Arguments:
  • LMDZ5/trunk/libf/dyn3d/caldyn.F

    r1987 r2597  
    2424!   ----------------
    2525
    26 #include "dimensions.h"
    27 #include "paramet.h"
    28 #include "comconst.h"
    29 #include "comvert.h"
    30 #include "comgeom.h"
     26      include "dimensions.h"
     27      include "paramet.h"
     28      include "comvert.h"
     29      include "comgeom.h"
    3130
    3231!   Arguments:
  • LMDZ5/trunk/libf/dyn3d/conf_gcm.F90

    r2442 r2597  
    1313  USE infotrac, ONLY : type_trac
    1414  use assert_m, only: assert
     15  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
     16                          iflag_top_bound, mode_top_bound, tau_top_bound, &
     17                          ngroup
    1518
    1619  IMPLICIT NONE
     
    3538  include "comdissnew.h"
    3639  include "temps.h"
    37   include "comconst.h"
    3840  include "iniprint.h"
    3941
  • LMDZ5/trunk/libf/dyn3d/dissip.F

    r1987 r2597  
    44      SUBROUTINE dissip( vcov,ucov,teta,p, dv,du,dh )
    55c
     6      USE comconst_mod, ONLY: dtdiss
     7     
    68      IMPLICIT NONE
    79
     
    2527c   -------------
    2628
    27 #include "dimensions.h"
    28 #include "paramet.h"
    29 #include "comconst.h"
    30 #include "comgeom.h"
    31 #include "comdissnew.h"
    32 #include "comdissipn.h"
     29      include "dimensions.h"
     30      include "paramet.h"
     31      include "comgeom.h"
     32      include "comdissnew.h"
     33      include "comdissipn.h"
    3334
    3435c   Arguments:
  • LMDZ5/trunk/libf/dyn3d/dynetat0.f90

    r2299 r2597  
    1111  USE control_mod, ONLY: planet_type
    1212  USE assert_eq_m, ONLY: assert_eq
     13  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa, lllm, omeg, rad
    1314  IMPLICIT NONE
    1415  include "dimensions.h"
    1516  include "paramet.h"
    1617  include "temps.h"
    17   include "comconst.h"
    1818  include "comvert.h"
    1919  include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3d/dynredem.F90

    r2299 r2597  
    1111                    NF90_CLOSE,  NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER
    1212  USE dynredem_mod, ONLY: cre_var, put_var1, put_var2, err, modname, fil
     13  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    1314  IMPLICIT NONE
    1415  include "dimensions.h"
    1516  include "paramet.h"
    16   include "comconst.h"
    1717  include "comvert.h"
    1818  include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3d/fluxstokenc.F

    r2239 r2597  
    1616      IMPLICIT NONE
    1717c
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comconst.h"
    21 #include "comvert.h"
    22 #include "comgeom.h"
    23 #include "tracstoke.h"
    24 #include "temps.h"
    25 #include "iniprint.h"
     18      include "dimensions.h"
     19      include "paramet.h"
     20      include "comvert.h"
     21      include "comgeom.h"
     22      include "tracstoke.h"
     23      include "temps.h"
     24      include "iniprint.h"
    2625
    2726      REAL time_step,t_wrt, t_ops
  • LMDZ5/trunk/libf/dyn3d/friction.F

    r1907 r2597  
    1212      USE ioipsl_getincom
    1313#endif
    14      
     14      USE comconst_mod, ONLY: pi
    1515      IMPLICIT NONE
    1616
     
    2727!=======================================================================
    2828
    29 #include "dimensions.h"
    30 #include "paramet.h"
    31 #include "comgeom2.h"
    32 #include "comconst.h"
    33 #include "iniprint.h"
    34 #include "academic.h"
     29      include "dimensions.h"
     30      include "paramet.h"
     31      include "comgeom2.h"
     32      include "iniprint.h"
     33      include "academic.h"
    3534
    3635! arguments:
  • LMDZ5/trunk/libf/dyn3d/gcm.F90

    r2438 r2597  
    2323  USE control_mod
    2424  USE mod_const_mpi, ONLY: COMM_LMDZ
    25 
     25  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
    2626
    2727!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    6868  include "dimensions.h"
    6969  include "paramet.h"
    70   include "comconst.h"
    7170  include "comdissnew.h"
    7271  include "comvert.h"
     
    7473  include "logic.h"
    7574  include "temps.h"
    76 !!!!!!!!!!!include "control.h"
    7775  include "ener.h"
    7876  include "description.h"
     
    8987  REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
    9088  REAL ps(ip1jmp1)                       ! pression  au sol
    91   REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
     89!  REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
    9290  REAL masse(ip1jmp1,llm)                ! masse d'air
    9391  REAL phis(ip1jmp1)                     ! geopotentiel au sol
    94   REAL phi(ip1jmp1,llm)                  ! geopotentiel
    95   REAL w(ip1jmp1,llm)                    ! vitesse verticale
     92!  REAL phi(ip1jmp1,llm)                  ! geopotentiel
     93!  REAL w(ip1jmp1,llm)                    ! vitesse verticale
    9694
    9795  ! variables dynamiques intermediaire pour le transport
     
    103101
    104102  LOGICAL lafin
    105   INTEGER ij,iq,l,i,j
    106103
    107104
    108105  real time_step, t_wrt, t_ops
    109 
    110   LOGICAL first
    111106
    112107  !      LOGICAL call_iniphys
     
    118113  !     tansformation d'energie cinetique en energie thermique
    119114  !     cree par la dissipation
    120   REAL dhecdt(ip1jmp1,llm)
     115!  REAL dhecdt(ip1jmp1,llm)
    121116  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
    122117  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
    123   CHARACTER (len=15) :: ztit
     118!  CHARACTER (len=15) :: ztit
    124119  !-jld
    125120
  • LMDZ5/trunk/libf/dyn3d/groupe.F

    r2442 r2597  
    33!
    44      subroutine groupe(pext,pbaru,pbarv,pbarum,pbarvm,wm)
     5     
     6      use comconst_mod, only: ngroup
     7     
    58      implicit none
    69
     
    1619c   pas besoin de w en entree.
    1720
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comconst.h"
    21 #include "comgeom2.h"
    22 #include "comvert.h"
     21      include "dimensions.h"
     22      include "paramet.h"
     23      include "comgeom2.h"
     24      include "comvert.h"
    2325
    2426!     integer ngroup
  • LMDZ5/trunk/libf/dyn3d/groupeun.F

    r2442 r2597  
    33!
    44      SUBROUTINE groupeun(jjmax,llmax,q)
     5     
     6      USE comconst_mod, ONLY: ngroup
     7     
    58      IMPLICIT NONE
    69
    7 #include "dimensions.h"
    8 #include "paramet.h"
    9 #include "comconst.h"
    10 #include "comgeom2.h"
     10      include "dimensions.h"
     11      include "paramet.h"
     12      include "comgeom2.h"
    1113
    1214      INTEGER jjmax,llmax
     
    135137     
    136138      SUBROUTINE INIT_GROUPEUN(airen_tab, aires_tab)
     139     
     140      USE comconst_mod, ONLY: ngroup
     141     
    137142      IMPLICIT NONE
    138143
    139 #include "dimensions.h"
    140 #include "paramet.h"
    141 #include "comconst.h"
    142 #include "comgeom2.h"
     144      include "dimensions.h"
     145      include "paramet.h"
     146      include "comgeom2.h"
    143147
    144148!     INTEGER ngroup
  • LMDZ5/trunk/libf/dyn3d/guide_mod.F90

    r2263 r2597  
    314314  SUBROUTINE guide_main(itau,ucov,vcov,teta,q,masse,ps)
    315315
    316     USE control_mod
     316    USE control_mod, ONLY: day_step, iperiod
     317    USE comconst_mod, ONLY: dtvr, daysec
    317318 
    318319    IMPLICIT NONE
     
    320321    INCLUDE "dimensions.h"
    321322    INCLUDE "paramet.h"
    322     INCLUDE "comconst.h"
    323323    INCLUDE "comvert.h"
    324324
     
    542542  SUBROUTINE guide_zonave(typ,hsize,vsize,field)
    543543
     544    USE comconst_mod, ONLY: pi
     545   
    544546    IMPLICIT NONE
    545547
     
    547549    INCLUDE "paramet.h"
    548550    INCLUDE "comgeom.h"
    549     INCLUDE "comconst.h"
    550551   
    551552    ! input/output variables
     
    607608  use exner_hyb_m, only: exner_hyb
    608609  use exner_milieu_m, only: exner_milieu
     610  use comconst_mod, only: kappa, cpp
    609611  IMPLICIT NONE
    610612
     
    613615  include "comvert.h"
    614616  include "comgeom2.h"
    615   include "comconst.h"
    616617
    617618  REAL, DIMENSION (iip1,jjp1),     INTENT(IN) :: psi ! Psol gcm
     
    777778            do j=1,jjp1
    778779                IF (guide_teta) THEN
    779                     do i=1,iim
    780                         ij=(j-1)*iip1+i
    781                         tgui1(ij,l)=zu1(i,j,l)
    782                         tgui2(ij,l)=zu2(i,j,l)
    783                     enddo
     780                    do i=1,iim
     781                        ij=(j-1)*iip1+i
     782                        tgui1(ij,l)=zu1(i,j,l)
     783                        tgui2(ij,l)=zu2(i,j,l)
     784                    enddo
    784785                ELSE
    785                     do i=1,iim
    786                         ij=(j-1)*iip1+i
    787                         tgui1(ij,l)=zu1(i,j,l)*cpp/pk(i,j,l)
    788                         tgui2(ij,l)=zu2(i,j,l)*cpp/pk(i,j,l)
    789                     enddo
     786                    do i=1,iim
     787                        ij=(j-1)*iip1+i
     788                        tgui1(ij,l)=zu1(i,j,l)*cpp/pk(i,j,l)
     789                        tgui2(ij,l)=zu2(i,j,l)*cpp/pk(i,j,l)
     790                    enddo
    790791                ENDIF
    791792                tgui1(j*iip1,l)=tgui1((j-1)*iip1+1,l)   
     
    855856! Calcul des constantes de rappel alpha (=1/tau)
    856857
     858    use comconst_mod, only: pi
     859   
    857860    implicit none
    858861
    859862    include "dimensions.h"
    860863    include "paramet.h"
    861     include "comconst.h"
    862864    include "comgeom2.h"
    863865    include "serre.h"
     
    15161518  SUBROUTINE guide_out(varname,hsize,vsize,field)
    15171519
     1520    USE comconst_mod, ONLY: pi
     1521   
    15181522    IMPLICIT NONE
    15191523
     
    15221526    INCLUDE "netcdf.inc"
    15231527    INCLUDE "comgeom2.h"
    1524     INCLUDE "comconst.h"
    15251528    INCLUDE "comvert.h"
    15261529   
  • LMDZ5/trunk/libf/dyn3d/iniacademic.F90

    r2270 r2597  
    1616  use exner_hyb_m, only: exner_hyb
    1717  use exner_milieu_m, only: exner_milieu
     18  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    1819
    1920  !   Author:    Frederic Hourdin      original: 15/01/93
     
    2930  include "paramet.h"
    3031  include "comvert.h"
    31   include "comconst.h"
    3232  include "comgeom.h"
    3333  include "academic.h"
  • LMDZ5/trunk/libf/dyn3d/integrd.F

    r2094 r2597  
    88
    99      use control_mod, only : planet_type
     10      use comconst_mod, only: pi
    1011
    1112      IMPLICIT NONE
     
    2728c   -------------
    2829
    29 #include "dimensions.h"
    30 #include "paramet.h"
    31 #include "comconst.h"
    32 #include "comgeom.h"
    33 #include "comvert.h"
    34 #include "logic.h"
    35 #include "temps.h"
    36 #include "serre.h"
    37 #include "iniprint.h"
     30      include "dimensions.h"
     31      include "paramet.h"
     32      include "comgeom.h"
     33      include "comvert.h"
     34      include "logic.h"
     35      include "temps.h"
     36      include "serre.h"
     37      include "iniprint.h"
    3838
    3939c   Arguments:
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r2475 r2597  
    2020      use exner_hyb_m, only: exner_hyb
    2121      use exner_milieu_m, only: exner_milieu
     22      USE comconst_mod, ONLY: cpp, dtphys, dtvr, pi, ihf
    2223
    2324      IMPLICIT NONE
     
    5455c   -------------
    5556
    56 #include "dimensions.h"
    57 #include "paramet.h"
    58 #include "comconst.h"
    59 #include "comdissnew.h"
    60 #include "comvert.h"
    61 #include "comgeom.h"
    62 #include "logic.h"
    63 #include "temps.h"
    64 #include "ener.h"
    65 #include "description.h"
    66 #include "serre.h"
    67 !#include "com_io_dyn.h"
    68 #include "iniprint.h"
    69 #include "academic.h"
     57      include "dimensions.h"
     58      include "paramet.h"
     59      include "comdissnew.h"
     60      include "comvert.h"
     61      include "comgeom.h"
     62      include "logic.h"
     63      include "temps.h"
     64      include "ener.h"
     65      include "description.h"
     66      include "serre.h"
     67      include "iniprint.h"
     68      include "academic.h"
    7069
    7170      REAL,INTENT(IN) :: time_0 ! not used
  • LMDZ5/trunk/libf/dyn3d/sw_case_williamson91_6.F

    r1907 r2597  
    2626c
    2727c=======================================================================
     28      USE comconst_mod, ONLY: cpp, omeg, rad
     29     
    2830      IMPLICIT NONE
    2931c-----------------------------------------------------------------------
     
    3133c   ---------------
    3234
    33 #include "dimensions.h"
    34 #include "paramet.h"
    35 #include "comvert.h"
    36 #include "comconst.h"
    37 #include "comgeom.h"
    38 #include "iniprint.h"
     35      include "dimensions.h"
     36      include "paramet.h"
     37      include "comvert.h"
     38      include "comgeom.h"
     39      include "iniprint.h"
    3940
    4041c   Arguments:
  • LMDZ5/trunk/libf/dyn3d/top_bound.F

    r1907 r2597  
    33!
    44      SUBROUTINE top_bound(vcov,ucov,teta,masse,dt)
     5     
     6      USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound,
     7     &                        tau_top_bound
     8     
    59      IMPLICIT NONE
    610c
    7 #include "dimensions.h"
    8 #include "paramet.h"
    9 #include "comconst.h"
    10 #include "comvert.h"
    11 #include "comgeom2.h"
     11      include "dimensions.h"
     12      include "paramet.h"
     13      include "comvert.h"
     14      include "comgeom2.h"
    1215
    1316
     
    3942! NB: top_bound sponge is only called from leapfrog if ok_strato=.true.
    4043
    41 ! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst.h)
     44! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst_mod)
    4245!    iflag_top_bound=0 for no sponge
    4346!    iflag_top_bound=1 for sponge over 4 topmost layers
  • LMDZ5/trunk/libf/dyn3d/vlsplt.F

    r2286 r2597  
    2121      IMPLICIT NONE
    2222c
    23 #include "dimensions.h"
    24 #include "paramet.h"
    25 #include "logic.h"
    26 #include "comvert.h"
    27 #include "comconst.h"
     23      include "dimensions.h"
     24      include "paramet.h"
     25      include "logic.h"
     26      include "comvert.h"
    2827
    2928c
     
    159158      include "logic.h"
    160159      include "comvert.h"
    161       include "comconst.h"
    162160      include "iniprint.h"
    163161c
     
    528526c
    529527c   --------------------------------------------------------------------
     528      USE comconst_mod, ONLY: pi
    530529      IMPLICIT NONE
    531530c
    532 #include "dimensions.h"
    533 #include "paramet.h"
    534 #include "logic.h"
    535 #include "comvert.h"
    536 #include "comconst.h"
    537 #include "comgeom.h"
     531      include "dimensions.h"
     532      include "paramet.h"
     533      include "logic.h"
     534      include "comvert.h"
     535      include "comgeom.h"
    538536c
    539537c
     
    893891      IMPLICIT NONE
    894892c
    895 #include "dimensions.h"
    896 #include "paramet.h"
    897 #include "logic.h"
    898 #include "comvert.h"
    899 #include "comconst.h"
     893      include "dimensions.h"
     894      include "paramet.h"
     895      include "logic.h"
     896      include "comvert.h"
    900897c
    901898c
  • LMDZ5/trunk/libf/dyn3d/vlspltqs.F

    r2286 r2597  
    2323c     pk exner au milieu des couches necessaire pour calculer Qsat
    2424c   --------------------------------------------------------------------
     25     
     26      USE comconst_mod, ONLY: cpp
     27     
    2528      IMPLICIT NONE
    2629c
    27 #include "dimensions.h"
    28 #include "paramet.h"
    29 #include "logic.h"
    30 #include "comvert.h"
    31 #include "comconst.h"
     30      include "dimensions.h"
     31      include "paramet.h"
     32      include "logic.h"
     33      include "comvert.h"
    3234
    3335c
     
    192194      IMPLICIT NONE
    193195c
    194 #include "dimensions.h"
    195 #include "paramet.h"
    196 #include "logic.h"
    197 #include "comvert.h"
    198 #include "comconst.h"
     196      include "dimensions.h"
     197      include "paramet.h"
     198      include "logic.h"
     199      include "comvert.h"
    199200c
    200201c
     
    559560c
    560561c   --------------------------------------------------------------------
     562     
     563      USE comconst_mod, ONLY: pi
     564     
    561565      IMPLICIT NONE
    562566c
    563 #include "dimensions.h"
    564 #include "paramet.h"
    565 #include "logic.h"
    566 #include "comvert.h"
    567 #include "comconst.h"
    568 #include "comgeom.h"
     567      include "dimensions.h"
     568      include "paramet.h"
     569      include "logic.h"
     570      include "comvert.h"
     571      include "comgeom.h"
    569572c
    570573c
  • LMDZ5/trunk/libf/dyn3d_common/adaptdt.F

    r1952 r2597  
    55     c                   masse)
    66
    7       USE control_mod
     7!      USE control_mod
     8      USE comconst_mod, ONLY: dtvr
    89      IMPLICIT NONE
    910
     
    1112c#include "paramr2.h"
    1213#include "paramet.h"
    13 #include "comconst.h"
    1414#include "comdissip.h"
    1515#include "comvert.h"
  • LMDZ5/trunk/libf/dyn3d_common/advn.F

    r1945 r2597  
    2121#include "logic.h"
    2222#include "comvert.h"
    23 #include "comconst.h"
    2423#include "comgeom.h"
    2524#include "iniprint.h"
     
    488487#include "logic.h"
    489488#include "comvert.h"
    490 #include "comconst.h"
    491489#include "iniprint.h"
    492490c
  • LMDZ5/trunk/libf/dyn3d_common/advx.F

    r1952 r2597  
    2525#include "dimensions.h"
    2626#include "paramet.h"
    27 #include "comconst.h"
    2827#include "comvert.h"
    2928
  • LMDZ5/trunk/libf/dyn3d_common/advxp.F

    r1945 r2597  
    1515#include "dimensions.h"
    1616#include "paramet.h"
    17 #include "comconst.h"
    1817#include "comvert.h"
    1918
  • LMDZ5/trunk/libf/dyn3d_common/advy.F

    r1945 r2597  
    2828#include "dimensions.h"
    2929#include "paramet.h"
    30 #include "comconst.h"
    3130#include "comvert.h"
    3231#include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3d_common/advyp.F

    r1945 r2597  
    3030#include "dimensions.h"
    3131#include "paramet.h"
    32 #include "comconst.h"
    3332#include "comvert.h"
    3433#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3d_common/advz.F

    r1952 r2597  
    2323#include "dimensions.h"
    2424#include "paramet.h"
    25 #include "comconst.h"
    2625#include "comvert.h"
    2726
  • LMDZ5/trunk/libf/dyn3d_common/advzp.F

    r1945 r2597  
    3333#include "dimensions.h"
    3434#include "paramet.h"
    35 #include "comconst.h"
    3635#include "comvert.h"
    3736#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3d_common/caldyn0.F90

    r2336 r2597  
    1010  include "dimensions.h"
    1111  include "paramet.h"
    12   include "comconst.h"
    1312  include "comvert.h"
    1413  include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3d_common/comconst_mod.F90

    r2595 r2597  
    22! $Id$
    33!
    4 !-----------------------------------------------------------------------
    5 ! INCLUDE comconst.h
    64
    7       COMMON/comconsti/im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl,          &
    8      &                 iflag_top_bound,mode_top_bound,ngroup
    9       COMMON/comconstr/dtvr,daysec,                                     &
    10      & pi,dtphys,dtdiss,rad,r,cpp,kappa,cotot,unsim,g,omeg              &
    11      &                   ,dissip_factz,dissip_deltaz,dissip_zref        &
    12      &                   ,tau_top_bound,                                &
    13      & daylen,year_day,molmass, ihf
     5MODULE comconst_mod
    146
     7IMPLICIT NONE 
    158
    169      INTEGER im,jm,lllm,imp1,jmp1,lllmm1,lllmp1,lcl
     
    3225! top_bound sponge:
    3326      INTEGER iflag_top_bound ! sponge type
    34       INTEGER ngroup
     27      INTEGER ngroup ! parameter to group points (along longitude) near poles
    3528      INTEGER mode_top_bound  ! sponge mode
    3629      REAL tau_top_bound ! inverse of sponge characteristic time scale (Hz)
     
    4134      REAL ihf ! (W/m2) Intrinsic heat flux (for giant planets)
    4235
    43 !-----------------------------------------------------------------------
     36
     37END MODULE comconst_mod
  • LMDZ5/trunk/libf/dyn3d_common/conf_planete.F90

    r1945 r2597  
    1010USE ioipsl_getincom
    1111#endif
     12USE comconst_mod, ONLY: pi, g, molmass, kappa, cpp, omeg, rad, &
     13                        year_day, daylen, daysec, ihf
    1214IMPLICIT NONE
    1315!
     
    1618!   --------------
    1719#include "dimensions.h"
    18 #include "comconst.h"
    1920#include "comvert.h"
    2021!
  • LMDZ5/trunk/libf/dyn3d_common/coordij.F

    r1945 r2597  
    1111c=======================================================================
    1212
     13      USE comconst_mod, ONLY: pi
     14     
    1315      IMPLICIT NONE
    1416      REAL lon,lat
     
    1820#include "dimensions.h"
    1921#include "paramet.h"
    20 #include "comconst.h"
    2122#include "comgeom.h"
    2223#include "serre.h"
  • LMDZ5/trunk/libf/dyn3d_common/disvert.F90

    r2153 r2597  
    1616  include "paramet.h"
    1717  include "comvert.h"
    18   include "comconst.h"
    1918  include "iniprint.h"
    2019  include "logic.h"
  • LMDZ5/trunk/libf/dyn3d_common/disvert_noterre.F

    r1952 r2597  
    1212      use ioipsl_getincom
    1313#endif
     14      USE comconst_mod, ONLY: kappa
    1415
    1516      IMPLICIT NONE
     
    1819#include "paramet.h"
    1920#include "comvert.h"
    20 #include "comconst.h"
    2121#include "logic.h"
    2222#include "iniprint.h"
  • LMDZ5/trunk/libf/dyn3d_common/exner_hyb_m.F90

    r2021 r2597  
    3333    !
    3434    !
     35    USE comconst_mod, ONLY: jmp1, cpp, kappa, r
     36    IMPLICIT NONE
     37   
    3538    include "dimensions.h"
    3639    include "paramet.h"
    37     include "comconst.h"
    3840    include "comgeom.h"
    3941    include "comvert.h"
  • LMDZ5/trunk/libf/dyn3d_common/exner_milieu_m.F90

    r2021 r2597  
    3030    !
    3131    !
     32    USE comconst_mod, ONLY: jmp1, cpp, kappa, r
     33    IMPLICIT NONE
     34   
    3235    include "dimensions.h"
    3336    include "paramet.h"
    34     include "comconst.h"
    3537    include "comgeom.h"
    3638    include "comvert.h"
  • LMDZ5/trunk/libf/dyn3d_common/fxy.F

    r1952 r2597  
    66     , rlonu,xprimu,rlonv,xprimv,rlonm025,xprimm025,rlonp025,xprimp025)
    77
     8      USE comconst_mod, ONLY: pi
    89      IMPLICIT NONE
    910
     
    1718#include "paramet.h"
    1819#include "serre.h"
    19 #include "comconst.h"
    2020
    2121       INTEGER i,j
  • LMDZ5/trunk/libf/dyn3d_common/fxysinus.F

    r1952 r2597  
    77
    88
     9      USE comconst_mod, ONLY: pi
    910      IMPLICIT NONE
    1011c
     
    1718#include "dimensions.h"
    1819#include "paramet.h"
    19 #include "comconst.h"
    2020
    2121       INTEGER i,j
  • LMDZ5/trunk/libf/dyn3d_common/grilles_gcm_netcdf_sub.F90

    r2221 r2597  
    99SUBROUTINE grilles_gcm_netcdf_sub(masque,phis)
    1010
     11  USE comconst_mod, ONLY: cpp, kappa, g, omeg, daysec, rad, pi
    1112  IMPLICIT NONE
    1213
    1314  INCLUDE "dimensions.h"
    1415  INCLUDE "paramet.h"
    15   INCLUDE "comconst.h"
    1616  INCLUDE "comgeom.h"
    1717  INCLUDE "comvert.h"
  • LMDZ5/trunk/libf/dyn3d_common/iniconst.F90

    r2040 r2597  
    1111  use ioipsl_getincom
    1212#endif
    13 
     13  USE comconst_mod, ONLY: im, imp1, jm, jmp1, lllm, lllmm1, lllmp1, &
     14                          unsim, pi, r, kappa, cpp, dtvr, dtphys
     15 
    1416  IMPLICIT NONE
    1517  !
     
    2123  include "dimensions.h"
    2224  include "paramet.h"
    23   include "comconst.h"
    2425  include "temps.h"
    2526  include "comvert.h"
  • LMDZ5/trunk/libf/dyn3d_common/inidissip.F90

    r1952 r2597  
    1212
    1313  USE control_mod, only : dissip_period,iperiod
     14  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
     15                          dtdiss, dtvr, rad
    1416
    1517  IMPLICIT NONE
     
    1719  include "paramet.h"
    1820  include "comdissipn.h"
    19   include "comconst.h"
    2021  include "comvert.h"
    2122  include "logic.h"
  • LMDZ5/trunk/libf/dyn3d_common/inigeom.F

    r2218 r2597  
    1818      use fxhyp_m, only: fxhyp
    1919      use fyhyp_m, only: fyhyp
     20      USE comconst_mod, ONLY: pi, g, omeg, rad
    2021      IMPLICIT NONE
    2122c
    22 #include "dimensions.h"
    23 #include "paramet.h"
    24 #include "comconst.h"
    25 #include "comgeom2.h"
    26 #include "serre.h"
    27 #include "logic.h"
    28 #include "comdissnew.h"
     23      include "dimensions.h"
     24      include "paramet.h"
     25      include "comgeom2.h"
     26      include "serre.h"
     27      include "logic.h"
     28      include "comdissnew.h"
    2929
    3030c-----------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3d_common/initdynav.F90

    r2239 r2597  
    99  use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid, &
    1010       dynhistave_file,dynhistvave_file,dynhistuave_file
     11  USE comconst_mod, ONLY: pi
    1112  implicit none
    1213
     
    3435  include "dimensions.h"
    3536  include "paramet.h"
    36   include "comconst.h"
    3737  include "comvert.h"
    3838  include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3d_common/initfluxsto.F

    r2239 r2597  
    99       USE IOIPSL
    1010#endif
     11      USE comconst_mod, ONLY: pi
    1112      implicit none
    1213
     
    3839C
    3940C   Declarations
    40 #include "dimensions.h"
    41 #include "paramet.h"
    42 #include "comconst.h"
    43 #include "comvert.h"
    44 #include "comgeom.h"
    45 #include "temps.h"
    46 #include "ener.h"
    47 #include "logic.h"
    48 #include "description.h"
    49 #include "serre.h"
    50 #include "iniprint.h"
     41      include "dimensions.h"
     42      include "paramet.h"
     43      include "comvert.h"
     44      include "comgeom.h"
     45      include "temps.h"
     46      include "ener.h"
     47      include "logic.h"
     48      include "description.h"
     49      include "serre.h"
     50      include "iniprint.h"
    5151
    5252C   Arguments
     
    114114     .             tau0, zjulian, tstep, vhoriid, filevid)
    115115       
    116         rl(1,1) = 1.   
     116        rl(1,1) = 1.
    117117      call histbeg('defstoke.nc', 1, rl, 1, rl,
    118118     .             1, 1, 1, 1,
  • LMDZ5/trunk/libf/dyn3d_common/inithist.F

    r2239 r2597  
    1010       use com_io_dyn_mod, only : histid,histvid,histuid,               &
    1111     &                        dynhist_file,dynhistv_file,dynhistu_file
    12 
     12       USE comconst_mod, ONLY: pi
    1313      implicit none
    1414
     
    3838C
    3939C   Declarations
    40 #include "dimensions.h"
    41 #include "paramet.h"
    42 #include "comconst.h"
    43 #include "comvert.h"
    44 #include "comgeom.h"
    45 #include "temps.h"
    46 #include "ener.h"
    47 #include "logic.h"
    48 #include "description.h"
    49 #include "serre.h"
    50 #include "iniprint.h"
     40      include "dimensions.h"
     41      include "paramet.h"
     42      include "comvert.h"
     43      include "comgeom.h"
     44      include "temps.h"
     45      include "ener.h"
     46      include "logic.h"
     47      include "description.h"
     48      include "serre.h"
     49      include "iniprint.h"
    5150
    5251C   Arguments
  • LMDZ5/trunk/libf/dyn3d_common/inter_barxy_m.F90

    r1952 r2597  
    374374
    375375    use assert_eq_m, only: assert_eq
     376    use comconst_mod, only: pi
    376377
    377378    IMPLICIT NONE
    378 
    379     include "comconst.h"
    380     ! (for "pi")
    381379
    382380    REAL, intent(in):: xi(:)
     
    431429    ! order.
    432430
     431    use comconst_mod, only: pi
     432
    433433    IMPLICIT NONE
    434 
    435     include "comconst.h"
    436     ! (for "pi")
    437434
    438435    REAL, intent(in):: xi(:) ! angle, in rad or degrees
  • LMDZ5/trunk/libf/dyn3d_common/interpost.F

    r1945 r2597  
    77
    88
    9 #include "dimensions.h"
    10 #include "paramet.h"
    11 #include "comconst.h"
    12 #include "comvert.h"
    13 #include "comgeom2.h"
     9      include "dimensions.h"
     10      include "paramet.h"
     11      include "comvert.h"
     12      include "comgeom2.h"
    1413
    1514c Arguments   
  • LMDZ5/trunk/libf/dyn3d_common/interpre.F

    r2121 r2597  
    66     s            unatppm,vnatppm,psppm)
    77
    8       USE control_mod
     8      USE comconst_mod, ONLY: g
    99
    1010       implicit none
    1111
    12 #include "dimensions.h"
    13 c#include "paramr2.h"
    14 #include "paramet.h"
    15 #include "comconst.h"
    16 #include "comdissip.h"
    17 #include "comvert.h"
    18 #include "comgeom2.h"
    19 #include "logic.h"
    20 #include "temps.h"
    21 #include "ener.h"
    22 #include "description.h"
     12      include "dimensions.h"
     13      include "paramet.h"
     14      include "comdissip.h"
     15      include "comvert.h"
     16      include "comgeom2.h"
     17      include "logic.h"
     18      include "temps.h"
     19      include "ener.h"
     20      include "description.h"
    2321
    2422c---------------------------------------------------
     
    7775          do j=1,jjm
    7876              do i=1,iip1
    79                   vnat(i,j,l)=-pbarv(i,j,l)/masseby(i,j,l)*cv(i,j)             
     77                  vnat(i,j,l)=-pbarv(i,j,l)/masseby(i,j,l)*cv(i,j)
    8078              enddo
    8179          enddo
     
    119117                 vnatppm(i,j,l)=vnat(i,j,llm-l+1)
    120118                 fluxwppm(i,j,l)=fluxw(i,j,llm-l+1)
    121                  qppm(i,j,l)=q(i,j,llm-l+1)                             
     119                 qppm(i,j,l)=q(i,j,llm-l+1)
    122120             enddo
    123121          enddo                               
  • LMDZ5/trunk/libf/dyn3d_common/limx.F

    r1952 r2597  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "logic.h"
    20 #include "comvert.h"
    21 #include "comconst.h"
    22 #include "comgeom.h"
     17      include "dimensions.h"
     18      include "paramet.h"
     19      include "logic.h"
     20      include "comvert.h"
     21      include "comgeom.h"
    2322c
    2423c
  • LMDZ5/trunk/libf/dyn3d_common/limy.F

    r1952 r2597  
    1414c
    1515c   --------------------------------------------------------------------
     16      USE comconst_mod, ONLY: pi
    1617      IMPLICIT NONE
    1718c
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "logic.h"
    21 #include "comvert.h"
    22 #include "comconst.h"
    23 #include "comgeom.h"
     19      include "dimensions.h"
     20      include "paramet.h"
     21      include "logic.h"
     22      include "comvert.h"
     23      include "comgeom.h"
    2424c
    2525c
  • LMDZ5/trunk/libf/dyn3d_common/limz.F

    r1952 r2597  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "logic.h"
    20 #include "comvert.h"
    21 #include "comconst.h"
    22 #include "comgeom.h"
     17      include "dimensions.h"
     18      include "paramet.h"
     19      include "logic.h"
     20      include "comvert.h"
     21      include "comgeom.h"
    2322c
    2423c
  • LMDZ5/trunk/libf/dyn3d_common/massbarxy.F90

    r2336 r2597  
    99  include "dimensions.h"
    1010  include "paramet.h"
    11   include "comconst.h"
    1211  include "comgeom.h"
    1312!===============================================================================
  • LMDZ5/trunk/libf/dyn3d_common/massdair.F

    r1945 r2597  
    1818      IMPLICIT NONE
    1919c
    20 #include "dimensions.h"
    21 #include "paramet.h"
    22 #include "comconst.h"
    23 #include "comgeom.h"
     20      include "dimensions.h"
     21      include "paramet.h"
     22      include "comgeom.h"
    2423c
    2524c  .....   arguments  ....
  • LMDZ5/trunk/libf/dyn3d_common/pentes_ini.F

    r1952 r2597  
    33!
    44      SUBROUTINE pentes_ini (q,w,masse,pbaru,pbarv,mode)
     5     
     6      USE comconst_mod, ONLY: pi, dtvr
     7     
    58      IMPLICIT NONE
    69
     
    2225
    2326
    24 #include "dimensions.h"
    25 #include "paramet.h"
    26 #include "comconst.h"
    27 #include "comvert.h"
    28 #include "comgeom2.h"
     27      include "dimensions.h"
     28      include "paramet.h"
     29      include "comvert.h"
     30      include "comgeom2.h"
    2931
    3032c   Arguments:
  • LMDZ5/trunk/libf/dyn3d_common/prather.F

    r1952 r2597  
    33!
    44      SUBROUTINE prather (q,w,masse,pbaru,pbarv,nt,dt)
     5     
     6      USE comconst_mod, ONLY: pi
     7     
    58      IMPLICIT NONE
    69
     
    1922
    2023
    21 #include "dimensions.h"
    22 #include "paramet.h"
    23 #include "comconst.h"
    24 #include "comvert.h"
    25 #include "comgeom2.h"
     24      include "dimensions.h"
     25      include "paramet.h"
     26      include "comvert.h"
     27      include "comgeom2.h"
    2628
    2729c   Arguments:
  • LMDZ5/trunk/libf/dyn3d_common/sortvarc.F

    r2083 r2597  
    77
    88      USE control_mod, ONLY: resetvarc
     9      USE comconst_mod, ONLY: dtvr, daysec, g, rad, omeg
    910      IMPLICIT NONE
    1011
     
    2728      INCLUDE "dimensions.h"
    2829      INCLUDE "paramet.h"
    29       INCLUDE "comconst.h"
    3030      INCLUDE "comvert.h"
    3131      INCLUDE "comgeom.h"
  • LMDZ5/trunk/libf/dyn3d_common/traceurpole.F

    r1952 r2597  
    44          subroutine traceurpole(q,masse)
    55
    6       USE control_mod
    7 
    86          implicit none
    97     
    10 #include "dimensions.h"
    11 c#include "paramr2.h"
    12 #include "paramet.h"
    13 #include "comconst.h"
    14 #include "comdissip.h"
    15 #include "comvert.h"
    16 #include "comgeom2.h"
    17 #include "logic.h"
    18 #include "temps.h"
    19 #include "ener.h"
    20 #include "description.h"
     8      include "dimensions.h"
     9      include "paramet.h"
     10      include "comdissip.h"
     11      include "comvert.h"
     12      include "comgeom2.h"
     13      include "logic.h"
     14      include "temps.h"
     15      include "ener.h"
     16      include "description.h"
    2117
    2218
  • LMDZ5/trunk/libf/dyn3d_common/ugeostr.F90

    r1952 r2597  
    1111  ! levels are pressure levels.
    1212
     13  use comconst_mod, only: omeg, rad
     14 
    1315  implicit none
    1416
    1517  include "dimensions.h"
    1618  include "paramet.h"
    17   include "comconst.h"
    1819  include "comgeom2.h"
    1920
  • LMDZ5/trunk/libf/dyn3d_common/writedynav.F90

    r2239 r2597  
    88  USE infotrac, ONLY : nqtot, ttext
    99  use com_io_dyn_mod, only : histaveid, histvaveid, histuaveid
     10  USE comconst_mod, ONLY: cpp
    1011
    1112  implicit none
     
    3132  include "dimensions.h"
    3233  include "paramet.h"
    33   include "comconst.h"
    3434  include "comvert.h"
    3535  include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3d_common/writehist.F

    r2239 r2597  
    3333C
    3434C   Declarations
    35 #include "dimensions.h"
    36 #include "paramet.h"
    37 #include "comconst.h"
    38 #include "comvert.h"
    39 #include "comgeom.h"
    40 #include "temps.h"
    41 #include "ener.h"
    42 #include "logic.h"
    43 #include "description.h"
    44 #include "serre.h"
    45 #include "iniprint.h"
     35      include "dimensions.h"
     36      include "paramet.h"
     37      include "comvert.h"
     38      include "comgeom.h"
     39      include "temps.h"
     40      include "ener.h"
     41      include "logic.h"
     42      include "description.h"
     43      include "serre.h"
     44      include "iniprint.h"
    4645
    4746C
  • LMDZ5/trunk/libf/dyn3dmem/addfi_loc.F

    r1987 r2597  
    4646c    ------------------
    4747c
    48 #include "dimensions.h"
    49 #include "paramet.h"
    50 #include "comconst.h"
    51 #include "comgeom.h"
    52 #include "serre.h"
     48      include "dimensions.h"
     49      include "paramet.h"
     50      include "comgeom.h"
     51      include "serre.h"
    5352c
    5453c    Arguments :
  • LMDZ5/trunk/libf/dyn3dmem/advect_new_loc.F

    r1907 r2597  
    77      USE write_field_loc
    88      USE advect_new_mod
     9      USE comconst_mod, ONLY: daysec
    910      IMPLICIT NONE
    1011c=======================================================================
     
    2728c   -------------
    2829
    29 #include "dimensions.h"
    30 #include "paramet.h"
    31 #include "comconst.h"
    32 #include "comvert.h"
    33 #include "comgeom.h"
    34 #include "logic.h"
    35 #include "ener.h"
     30      include "dimensions.h"
     31      include "paramet.h"
     32      include "comvert.h"
     33      include "comgeom.h"
     34      include "logic.h"
     35      include "ener.h"
    3636
    3737c   Arguments:
     
    122122                 
    123123           uav(ij,l)=0.25*(ucov(ij,l)+ucov(ij-iip1,l))
    124      .               +0.25*(ucov(ij+iip1,l)+ucov(ij,l))
     124     .               +0.25*(ucov(ij+iip1,l)+ucov(ij,l))
    125125         ENDDO
    126126         
  • LMDZ5/trunk/libf/dyn3dmem/advtrac_loc.F

    r2286 r2597  
    2727      USE control_mod, ONLY: iapp_tracvl, day_step, planet_type
    2828      USE advtrac_mod, ONLY: finmasse
     29      USE comconst_mod, ONLY: dtvr
    2930      IMPLICIT NONE
    3031c
    31 #include "dimensions.h"
    32 #include "paramet.h"
    33 #include "comconst.h"
    34 #include "comvert.h"
    35 #include "comdissip.h"
    36 #include "comgeom2.h"
    37 #include "logic.h"
    38 #include "temps.h"
    39 #include "ener.h"
    40 #include "description.h"
     32      include "dimensions.h"
     33      include "paramet.h"
     34      include "comvert.h"
     35      include "comdissip.h"
     36      include "comgeom2.h"
     37      include "logic.h"
     38      include "temps.h"
     39      include "ener.h"
     40      include "description.h"
    4141
    4242c-------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3dmem/bilan_dyn_loc.F

    r2475 r2597  
    1717      use misc_mod
    1818      USE write_field_loc
     19      USE comconst_mod, ONLY: cpp, pi
    1920      IMPLICIT NONE
    2021
    21 #include "dimensions.h"
    22 #include "paramet.h"
    23 #include "comconst.h"
    24 #include "comvert.h"
    25 #include "comgeom2.h"
    26 #include "temps.h"
    27 #include "iniprint.h"
     22      include "dimensions.h"
     23      include "paramet.h"
     24      include "comvert.h"
     25      include "comgeom2.h"
     26      include "temps.h"
     27      include "iniprint.h"
    2828
    2929c====================================================================
  • LMDZ5/trunk/libf/dyn3dmem/caladvtrac_loc.F

    r2286 r2597  
    2929
    3030
    31 #include "dimensions.h"
    32 #include "paramet.h"
    33 #include "comconst.h"
     31      include "dimensions.h"
     32      include "paramet.h"
    3433
    3534c   Arguments:
     
    210209        call resume_timer(timer_caldyn)
    211210c$OMP END MASTER
    212 c$OMP BARRIER   
     211c$OMP BARRIER
    213212          iadvtr=0
    214213       ENDIF ! if iadvtr.EQ.iapp_tracvl
  • LMDZ5/trunk/libf/dyn3dmem/caldyn_loc.F

    r1987 r2597  
    3131!   ----------------
    3232
    33 #include "dimensions.h"
    34 #include "paramet.h"
    35 #include "comconst.h"
    36 #include "comvert.h"
    37 #include "comgeom.h"
     33      include "dimensions.h"
     34      include "paramet.h"
     35      include "comvert.h"
     36      include "comgeom.h"
    3837
    3938!   Arguments:
  • LMDZ5/trunk/libf/dyn3dmem/call_calfis_mod.F90

    r2375 r2597  
    8282  USE write_field_loc
    8383  USE write_field
     84  USE comconst_mod, ONLY: dtphys
    8485  IMPLICIT NONE
    85     INCLUDE "comconst.h"
    8686    INCLUDE "comvert.h"
    8787    INCLUDE "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/conf_gcm.F90

    r2444 r2597  
    1717  USE infotrac, ONLY : type_trac
    1818  use assert_m, only: assert
     19  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
     20                          iflag_top_bound, mode_top_bound, tau_top_bound, &
     21                          ngroup
    1922
    2023  IMPLICIT NONE
     
    3942  include "comdissnew.h"
    4043  include "temps.h"
    41   include "comconst.h"
    4244  include "iniprint.h"
    4345
  • LMDZ5/trunk/libf/dyn3dmem/dissip_loc.F

    r1987 r2597  
    77      USE write_field_loc
    88      USE dissip_mod, ONLY: dissip_allocate
     9      USE comconst_mod, ONLY: dtdiss
    910      IMPLICIT NONE
    1011
     
    2829c   -------------
    2930
    30 #include "dimensions.h"
    31 #include "paramet.h"
    32 #include "comconst.h"
    33 #include "comgeom.h"
    34 #include "comdissnew.h"
    35 #include "comdissipn.h"
     31      include "dimensions.h"
     32      include "paramet.h"
     33      include "comgeom.h"
     34      include "comdissnew.h"
     35      include "comdissipn.h"
    3636
    3737c   Arguments:
  • LMDZ5/trunk/libf/dyn3dmem/dynetat0_loc.f90

    r2299 r2597  
    1212  USE control_mod, ONLY: planet_type
    1313  USE assert_eq_m, ONLY: assert_eq
     14  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa, lllm, &
     15                          omeg, rad
    1416  IMPLICIT NONE
    1517  include "dimensions.h"
    1618  include "paramet.h"
    1719  include "temps.h"
    18   include "comconst.h"
    1920  include "comvert.h"
    2021  include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dmem/dynredem_loc.F90

    r2584 r2597  
    1313                    NF90_CLOSE,  NF90_PUT_ATT, NF90_UNLIMITED, NF90_CLOBBER
    1414  USE dynredem_mod, ONLY: cre_var, put_var, err, modname, fil
     15  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    1516  IMPLICIT NONE
    1617  include "dimensions.h"
    1718  include "paramet.h"
    18   include "comconst.h"
    1919  include "comvert.h"
    2020  include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dmem/exner_hyb_loc_m.F90

    r2021 r2597  
    3535    USE mod_filtreg_p
    3636    USE write_field_loc
     37    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
     38    IMPLICIT NONE
    3739    !
    3840    include "dimensions.h"
    3941    include "paramet.h"
    40     include "comconst.h"
    4142    include "comgeom.h"
    4243    include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dmem/exner_milieu_loc_m.F90

    r2021 r2597  
    3131    USE parallel_lmdz
    3232    USE mod_filtreg_p
     33    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
     34    IMPLICIT NONE
    3335    !
    3436    include "dimensions.h"
    3537    include "paramet.h"
    36     include "comconst.h"
    3738    include "comgeom.h"
    3839    include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dmem/friction_loc.F

    r1907 r2597  
    1212      USE ioipsl_getincom
    1313#endif
     14      USE comconst_mod, ONLY: pi
    1415      IMPLICIT NONE
    1516
     
    2627!=======================================================================
    2728
    28 #include "dimensions.h"
    29 #include "paramet.h"
    30 #include "comgeom2.h"
    31 #include "comconst.h"
    32 #include "iniprint.h"
    33 #include "academic.h"
     29      include "dimensions.h"
     30      include "paramet.h"
     31      include "comgeom2.h"
     32      include "iniprint.h"
     33      include "academic.h"
    3434
    3535! arguments:
  • LMDZ5/trunk/libf/dyn3dmem/gcm.F90

    r2475 r2597  
    2121  USE iniphysiq_mod, ONLY: iniphysiq
    2222#endif
     23  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
    2324  IMPLICIT NONE
    2425
     
    5455  include "dimensions.h"
    5556  include "paramet.h"
    56   include "comconst.h"
    5757  include "comdissnew.h"
    5858  include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dmem/groupe_loc.F

    r2442 r2597  
    33      USE Write_field_loc
    44      USE groupe_mod
     5      USE comconst_mod, ONLY: ngroup
    56      implicit none
    67
     
    1617c   pas besoin de w en entree.
    1718
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comconst.h"
    21 #include "comgeom2.h"
    22 #include "comvert.h"
     19      include "dimensions.h"
     20      include "paramet.h"
     21      include "comgeom2.h"
     22      include "comvert.h"
    2323
    2424!     integer ngroup
  • LMDZ5/trunk/libf/dyn3dmem/groupeun_loc.F

    r2442 r2597  
    22      USE parallel_lmdz
    33      USE Write_Field_p
     4      USE comconst_mod, ONLY: ngroup
    45      IMPLICIT NONE
    56
    6 #include "dimensions.h"
    7 #include "paramet.h"
    8 #include "comconst.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
     
    136136
    137137      USE parallel_lmdz
     138      USE comconst_mod, ONLY: ngroup
    138139      IMPLICIT NONE
    139140
    140 #include "dimensions.h"
    141 #include "paramet.h"
    142 #include "comconst.h"
    143 #include "comgeom2.h"
     141      include "dimensions.h"
     142      include "paramet.h"
     143      include "comgeom2.h"
    144144
    145145!     INTEGER ngroup
  • LMDZ5/trunk/libf/dyn3dmem/guide_loc_mod.F90

    r2263 r2597  
    346346    USE control_mod
    347347    USE write_field_loc
     348    USE comconst_mod, ONLY: cpp, daysec, dtvr, kappa
    348349   
    349350    IMPLICIT NONE
     
    351352    INCLUDE "dimensions.h"
    352353    INCLUDE "paramet.h"
    353     INCLUDE "comconst.h"
    354354    INCLUDE "comvert.h"
    355355
     
    748748  SUBROUTINE guide_zonave_u(typ,vsize,field)
    749749
     750    USE comconst_mod, ONLY: pi
     751   
    750752    IMPLICIT NONE
    751753
     
    753755    INCLUDE "paramet.h"
    754756    INCLUDE "comgeom.h"
    755     INCLUDE "comconst.h"
    756757   
    757758    ! input/output variables
     
    819820  SUBROUTINE guide_zonave_v(typ,hsize,vsize,field)
    820821
     822    USE comconst_mod, ONLY: pi
     823   
    821824    IMPLICIT NONE
    822825
     
    824827    INCLUDE "paramet.h"
    825828    INCLUDE "comgeom.h"
    826     INCLUDE "comconst.h"
    827829   
    828830    ! input/output variables
     
    890892  USE mod_hallo
    891893  USE Bands
     894  USE comconst_mod, ONLY: cpp, kappa
    892895  IMPLICIT NONE
    893896
     
    896899  include "comvert.h"
    897900  include "comgeom2.h"
    898   include "comconst.h"
    899901
    900902  REAL, DIMENSION (iip1,jjb_u:jje_u),     INTENT(IN) :: psi ! Psol gcm
     
    10121014!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    10131015        DO l=1,llm
    1014             DO j=jjbu,jjeu
    1015                 DO i =1, iip1
     1016            DO j=jjbu,jjeu
     1017                DO i =1, iip1
    10161018                    pls(i,j,l)=(ap(l)+ap(l+1))/2.+psi(i,j)*(bp(l)+bp(l+1))/2.
    10171019                ENDDO
     
    10301032   DO l = 1, llm
    10311033       DO j=jjbu,jjeu
    1032         DO i =1, iip1
    1033             pls(i,j,l) = preff * ( pk(i,j,l)/cpp) ** unskap
    1034         ENDDO
     1034           DO i =1, iip1
     1035               pls(i,j,l) = preff * ( pk(i,j,l)/cpp) ** unskap
     1036           ENDDO
    10351037       ENDDO
    10361038   ENDDO
     
    13021304        ! Calcul des nouvelles valeurs des niveaux de pression du guidage
    13031305        IF (guide_plevs.EQ.1) THEN
    1304         CALL Register_Hallo_u(psnat1,1,1,2,2,1,Req)
    1305         CALL Register_Hallo_u(psnat2,1,1,2,2,1,Req)
    1306         CALL SendRequest(Req)
    1307 !$OMP BARRIER
    1308         CALL WaitRequest(Req)
     1306        CALL Register_Hallo_u(psnat1,1,1,2,2,1,Req)
     1307        CALL Register_Hallo_u(psnat2,1,1,2,2,1,Req)
     1308        CALL SendRequest(Req)
     1309!$OMP BARRIER
     1310        CALL WaitRequest(Req)
    13091311!$OMP BARRIER
    13101312!$OMP DO
     
    13201322            ENDDO
    13211323        ELSE IF (guide_plevs.EQ.2) THEN
    1322         CALL Register_Hallo_u(pnat1,llm,1,2,2,1,Req)
    1323         CALL Register_Hallo_u(pnat2,llm,1,2,2,1,Req)
    1324         CALL SendRequest(Req)
    1325 !$OMP BARRIER
    1326         CALL WaitRequest(Req)
     1324        CALL Register_Hallo_u(pnat1,llm,1,2,2,1,Req)
     1325        CALL Register_Hallo_u(pnat2,llm,1,2,2,1,Req)
     1326        CALL SendRequest(Req)
     1327!$OMP BARRIER
     1328        CALL WaitRequest(Req)
    13271329!$OMP BARRIER
    13281330!$OMP DO
     
    13701372! Calcul des constantes de rappel alpha (=1/tau)
    13711373
     1374    use comconst_mod, only: pi
     1375   
    13721376    implicit none
    13731377
    13741378    include "dimensions.h"
    13751379    include "paramet.h"
    1376     include "comconst.h"
    13771380    include "comgeom2.h"
    13781381    include "serre.h"
     
    21272130    USE parallel_lmdz
    21282131    USE mod_hallo, ONLY : gather_field_u, gather_field_v
     2132    USE comconst_mod, ONLY: pi
    21292133    IMPLICIT NONE
    21302134
     
    21332137    INCLUDE "netcdf.inc"
    21342138    INCLUDE "comgeom2.h"
    2135     INCLUDE "comconst.h"
    21362139    INCLUDE "comvert.h"
    21372140   
  • LMDZ5/trunk/libf/dyn3dmem/iniacademic_loc.F90

    r2270 r2597  
    1818#endif
    1919  USE Write_Field
     20  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    2021
    2122  !   Author:    Frederic Hourdin      original: 15/01/93
     
    3132  include "paramet.h"
    3233  include "comvert.h"
    33   include "comconst.h"
    3434  include "comgeom.h"
    3535  include "academic.h"
  • LMDZ5/trunk/libf/dyn3dmem/initdynav_loc.F

    r2475 r2597  
    1414       use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid,       &
    1515     &        dynhistave_file,dynhistvave_file,dynhistuave_file
     16       USE comconst_mod, ONLY: pi
    1617       implicit none
    1718
     
    4142C
    4243C   Declarations
    43 #include "dimensions.h"
    44 #include "paramet.h"
    45 #include "comconst.h"
    46 #include "comvert.h"
    47 #include "comgeom.h"
    48 #include "temps.h"
    49 #include "ener.h"
    50 #include "logic.h"
    51 #include "description.h"
    52 #include "serre.h"
    53 #include "iniprint.h"
     44      include "dimensions.h"
     45      include "paramet.h"
     46      include "comvert.h"
     47      include "comgeom.h"
     48      include "temps.h"
     49      include "ener.h"
     50      include "logic.h"
     51      include "description.h"
     52      include "serre.h"
     53      include "iniprint.h"
    5454
    5555C   Arguments
  • LMDZ5/trunk/libf/dyn3dmem/initfluxsto_p.F

    r1907 r2597  
    1313       use Write_field
    1414       use misc_mod
     15       USE comconst_mod, ONLY: pi
    1516       
    1617      implicit none
     
    4344C
    4445C   Declarations
    45 #include "dimensions.h"
    46 #include "paramet.h"
    47 #include "comconst.h"
    48 #include "comvert.h"
    49 #include "comgeom.h"
    50 #include "temps.h"
    51 #include "ener.h"
    52 #include "logic.h"
    53 #include "description.h"
    54 #include "serre.h"
    55 #include "iniprint.h"
     46      include "dimensions.h"
     47      include "paramet.h"
     48      include "comvert.h"
     49      include "comgeom.h"
     50      include "temps.h"
     51      include "ener.h"
     52      include "logic.h"
     53      include "description.h"
     54      include "serre.h"
     55      include "iniprint.h"
    5656
    5757C   Arguments
     
    166166     .             filevid,dynv_domain_id)
    167167       
    168       rl(1,1) = 1.     
     168      rl(1,1) = 1.
    169169     
    170170      if (mpi_rank==0) then
  • LMDZ5/trunk/libf/dyn3dmem/inithist_loc.F

    r2475 r2597  
    1414       use com_io_dyn_mod, only : histid,histvid,histuid,               &
    1515     &                        dynhist_file,dynhistv_file,dynhistu_file
     16       USE comconst_mod, ONLY: pi
    1617       implicit none
    1718
     
    4041C
    4142C   Declarations
    42 #include "dimensions.h"
    43 #include "paramet.h"
    44 #include "comconst.h"
    45 #include "comvert.h"
    46 #include "comgeom.h"
    47 #include "temps.h"
    48 #include "ener.h"
    49 #include "logic.h"
    50 #include "description.h"
    51 #include "serre.h"
    52 #include "iniprint.h"
     43      include "dimensions.h"
     44      include "paramet.h"
     45      include "comvert.h"
     46      include "comgeom.h"
     47      include "temps.h"
     48      include "ener.h"
     49      include "logic.h"
     50      include "description.h"
     51      include "serre.h"
     52      include "iniprint.h"
    5353
    5454C   Arguments
  • LMDZ5/trunk/libf/dyn3dmem/integrd_loc.F

    r2461 r2597  
    1212      USE integrd_mod
    1313      USE infotrac, ONLY: ok_iso_verif ! ajout CRisi
     14      USE comconst_mod, ONLY: pi
    1415      IMPLICIT NONE
    1516
     
    3031c   -------------
    3132
    32 #include "dimensions.h"
    33 #include "paramet.h"
    34 #include "comconst.h"
    35 #include "comgeom.h"
    36 #include "comvert.h"
    37 #include "logic.h"
    38 #include "temps.h"
    39 #include "serre.h"
    40 #include "iniprint.h"
    41 !      include 'mpif.h'
     33      include "dimensions.h"
     34      include "paramet.h"
     35      include "comgeom.h"
     36      include "comvert.h"
     37      include "logic.h"
     38      include "temps.h"
     39      include "serre.h"
     40      include "iniprint.h"
    4241
    4342c   Arguments:
     
    335334      ije=ij_end
    336335
    337         if (planet_type.eq."earth") then
     336        if (planet_type.eq."earth") then
    338337! Earth-specific treatment of first 2 tracers (water)
    339338c$OMP BARRIER
     
    452451          DO l = 1, llm
    453452            massem1(ijb:ije,l)=massescr(ijb:ije,l)
    454           ENDDO
    455 c$OMP END DO NOWAIT      
     453          ENDDO
     454c$OMP END DO NOWAIT         
    456455      END IF
    457456c$OMP BARRIER
  • LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F

    r2475 r2597  
    3232       use exner_hyb_loc_m, only: exner_hyb_loc
    3333       use exner_milieu_loc_m, only: exner_milieu_loc
     34       USE comconst_mod, ONLY: cpp, dtvr, ihf
    3435      IMPLICIT NONE
    3536
     
    6566c   -------------
    6667
    67 #include "dimensions.h"
    68 #include "paramet.h"
    69 #include "comconst.h"
    70 #include "comdissnew.h"
    71 #include "comvert.h"
    72 #include "comgeom.h"
    73 #include "logic.h"
    74 #include "temps.h"
    75 #include "ener.h"
    76 #include "description.h"
    77 #include "serre.h"
    78 !#include "com_io_dyn.h"
    79 #include "iniprint.h"
    80 #include "academic.h"
    81 !      include "mpif.h"
     68      include "dimensions.h"
     69      include "paramet.h"
     70      include "comdissnew.h"
     71      include "comvert.h"
     72      include "comgeom.h"
     73      include "logic.h"
     74      include "temps.h"
     75      include "ener.h"
     76      include "description.h"
     77      include "serre.h"
     78      include "iniprint.h"
     79      include "academic.h"
    8280     
    8381      REAL,INTENT(IN) :: time_0 ! not used
  • LMDZ5/trunk/libf/dyn3dmem/massbarxy_loc.F90

    r2336 r2597  
    1010  include "dimensions.h"
    1111  include "paramet.h"
    12   include "comconst.h"
    1312  include "comgeom.h"
    1413!===============================================================================
  • LMDZ5/trunk/libf/dyn3dmem/massdair_loc.F

    r1907 r2597  
    1616      IMPLICIT NONE
    1717c
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comconst.h"
    21 #include "comgeom.h"
     18      include "dimensions.h"
     19      include "paramet.h"
     20      include "comgeom.h"
    2221c
    2322c  .....   arguments  ....
  • LMDZ5/trunk/libf/dyn3dmem/sw_case_williamson91_6_loc.F

    r1907 r2597  
    2727c=======================================================================
    2828      USE parallel_lmdz
     29      USE comconst_mod, ONLY: cpp, omeg, rad
    2930
    3031      IMPLICIT NONE
     
    3334c   ---------------
    3435
    35 #include "dimensions.h"
    36 #include "paramet.h"
    37 #include "comvert.h"
    38 #include "comconst.h"
    39 #include "comgeom.h"
    40 #include "iniprint.h"
     36      include "dimensions.h"
     37      include "paramet.h"
     38      include "comvert.h"
     39      include "comgeom.h"
     40      include "iniprint.h"
    4141
    4242c   Arguments:
  • LMDZ5/trunk/libf/dyn3dmem/top_bound_loc.F

    r1907 r2597  
    44      SUBROUTINE top_bound_loc(vcov,ucov,teta,masse,dt)
    55      USE parallel_lmdz
     6      USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound,
     7     &                        tau_top_bound
    68      IMPLICIT NONE
    79c
    8 #include "dimensions.h"
    9 #include "paramet.h"
    10 #include "comconst.h"
    11 #include "comvert.h"
    12 #include "comgeom2.h"
     10      include "dimensions.h"
     11      include "paramet.h"
     12      include "comvert.h"
     13      include "comgeom2.h"
    1314
    1415
     
    4041! NB: top_bound sponge is only called from leapfrog if ok_strato=.true.
    4142
    42 ! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst.h)
     43! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst_mod)
    4344!    iflag_top_bound=0 for no sponge
    4445!    iflag_top_bound=1 for sponge over 4 topmost layers
     
    7475      REAL tzon(jjb_u:jje_u,llm)
    7576     
    76       integer i 
     77      integer i
    7778      REAL,SAVE :: rdamp(llm)
    7879      real,save :: lambda(llm) ! inverse or quenching time scale (Hz)
  • LMDZ5/trunk/libf/dyn3dmem/vlsplt_loc.F

    r2286 r2597  
    1717      IMPLICIT NONE
    1818c
    19 #include "dimensions.h"
    20 #include "paramet.h"
    21 #include "logic.h"
    22 #include "comvert.h"
    23 #include "comconst.h"
     19      include "dimensions.h"
     20      include "paramet.h"
     21      include "logic.h"
     22      include "comvert.h"
    2423c
    2524c
     
    417416      USE parallel_lmdz
    418417      USE infotrac, ONLY : nqtot,nqfils,nqdesc,iqfils ! CRisi
     418      USE comconst_mod, ONLY: pi
    419419      IMPLICIT NONE
    420420c
    421 #include "dimensions.h"
    422 #include "paramet.h"
    423 #include "logic.h"
    424 #include "comvert.h"
    425 #include "comconst.h"
    426 #include "comgeom.h"
     421      include "dimensions.h"
     422      include "paramet.h"
     423      include "logic.h"
     424      include "comvert.h"
     425      include "comgeom.h"
    427426c
    428427c
     
    875874      IMPLICIT NONE
    876875c
    877 #include "dimensions.h"
    878 #include "paramet.h"
    879 #include "logic.h"
    880 #include "comvert.h"
    881 #include "comconst.h"
     876      include "dimensions.h"
     877      include "paramet.h"
     878      include "logic.h"
     879      include "comvert.h"
    882880c
    883881c
  • LMDZ5/trunk/libf/dyn3dmem/vlspltgen_loc.F

    r2286 r2597  
    3131     &    ok_iso_verif
    3232      USE vlspltgen_mod
     33      USE comconst_mod, ONLY: cpp
    3334      IMPLICIT NONE
    3435
    3536c
    36 #include "dimensions.h"
    37 #include "paramet.h"
    38 #include "logic.h"
    39 #include "comvert.h"
    40 #include "comconst.h"
     37      include "dimensions.h"
     38      include "paramet.h"
     39      include "logic.h"
     40      include "comvert.h"
    4141
    4242c
     
    100100
    101101       
    102         ijb=ij_begin-iip1
    103         ije=ij_end+iip1
    104         if (pole_nord) ijb=ij_begin
    105         if (pole_sud) ije=ij_end
    106        
     102        ijb=ij_begin-iip1
     103        ije=ij_end+iip1
     104        if (pole_nord) ijb=ij_begin
     105        if (pole_sud) ije=ij_end
     106       
    107107c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    108         DO l = 1, llm
     108        DO l = 1, llm
    109109         DO ij = ijb, ije
    110110          tempe(ij) = teta(ij,l) * pk(ij,l) /cpp
     
    208208#endif
    209209        if(iadv(iq) == 0) then
    210        
    211           cycle
    212        
    213         else if (iadv(iq)==10) then
     210       
     211          cycle
     212       
     213        else if (iadv(iq)==10) then
    214214
    215215#ifdef _ADV_HALO       
    216216! CRisi: on ajoute les nombres de fils et tableaux des fils
    217217! On suppose qu'on ne peut advecter les fils que par le schéma 10. 
    218           call vlx_loc(zq,pente_max,zm,mu,
    219      &               ij_begin,ij_begin+2*iip1-1,iq)
     218          call vlx_loc(zq,pente_max,zm,mu,
     219     &                     ij_begin,ij_begin+2*iip1-1,iq)
    220220          call vlx_loc(zq,pente_max,zm,mu,
    221221     &               ij_end-2*iip1+1,ij_end,iq)
    222222#else
    223           call vlx_loc(zq,pente_max,zm,mu,
    224      &               ij_begin,ij_end,iq)
     223          call vlx_loc(zq,pente_max,zm,mu,
     224     &                     ij_begin,ij_end,iq)
    225225#endif
    226226
     
    240240          call VTe(VTHallo)
    241241c$OMP END MASTER
    242         else if (iadv(iq)==14) then
     242        else if (iadv(iq)==14) then
    243243
    244244#ifdef _ADV_HALO           
     
    268268c$OMP END MASTER
    269269        else
    270        
    271           stop 'vlspltgen_p : schema non parallelise'
     270       
     271          stop 'vlspltgen_p : schema non parallelise'
    272272     
    273273        endif
     
    301301
    302302        if(iadv(iq) == 0) then
    303        
    304           cycle
    305        
    306         else if (iadv(iq)==10) then
     303       
     304          cycle
     305       
     306        else if (iadv(iq)==10) then
    307307
    308308#ifdef _ADV_HALLO
     
    310310     &                 ij_begin+2*iip1,ij_end-2*iip1,iq)
    311311#endif       
    312         else if (iadv(iq)==14) then
     312        else if (iadv(iq)==14) then
    313313#ifdef _ADV_HALLO
    314314          call vlxqs_loc(zq,pente_max,zm,mu,
     
    316316#endif   
    317317        else
    318        
    319           stop 'vlspltgen_p : schema non parallelise'
     318       
     319          stop 'vlspltgen_p : schema non parallelise'
    320320     
    321321        endif
     
    358358
    359359        if(iadv(iq) == 0) then
    360        
    361           cycle
    362        
    363         else if (iadv(iq)==10) then
     360       
     361          cycle
     362       
     363        else if (iadv(iq)==10) then
    364364       
    365365          call vly_loc(zq,pente_max,zm,mv,iq)
    366366 
    367         else if (iadv(iq)==14) then
     367        else if (iadv(iq)==14) then
    368368     
    369369          call vlyqs_loc(zq,pente_max,zm,mv,
     
    371371 
    372372        else
    373        
    374           stop 'vlspltgen_p : schema non parallelise'
     373       
     374          stop 'vlspltgen_p : schema non parallelise'
    375375     
    376376        endif
     
    389389#endif
    390390        if(iadv(iq) == 0) then
    391          
    392           cycle
    393        
    394         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     391         
     392          cycle
     393       
     394        else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    395395
    396396c$OMP BARRIER       
     
    420420c$OMP MASTER
    421421          call VTe(VTHallo)
    422 c$OMP END MASTER       
     422c$OMP END MASTER       
    423423c$OMP BARRIER
    424424        else
    425        
    426           stop 'vlspltgen_p : schema non parallelise'
     425       
     426          stop 'vlspltgen_p : schema non parallelise'
    427427     
    428428        endif
     
    439439c$OMP MASTER
    440440      call VTe(VTHallo)
    441 c$OMP END MASTER       
     441c$OMP END MASTER       
    442442
    443443
     
    451451
    452452        if(iadv(iq) == 0) then
    453          
    454           cycle
    455        
    456         else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
     453         
     454          cycle
     455       
     456        else if (iadv(iq)==10 .or. iadv(iq)==14 ) then
    457457c$OMP BARRIER       
    458458
     
    464464c$OMP BARRIER       
    465465        else
    466        
    467           stop 'vlspltgen_p : schema non parallelise'
     466       
     467          stop 'vlspltgen_p : schema non parallelise'
    468468     
    469469        endif
     
    501501#endif
    502502        if(iadv(iq) == 0) then
    503        
    504           cycle
    505        
    506         else if (iadv(iq)==10) then
     503       
     504          cycle
     505       
     506        else if (iadv(iq)==10) then
    507507       
    508508          call vly_loc(zq,pente_max,zm,mv,iq)
    509509 
    510         else if (iadv(iq)==14) then
     510        else if (iadv(iq)==14) then
    511511     
    512512          call vlyqs_loc(zq,pente_max,zm,mv,
     
    514514 
    515515        else
    516        
    517           stop 'vlspltgen_p : schema non parallelise'
     516       
     517          stop 'vlspltgen_p : schema non parallelise'
    518518     
    519519        endif
     
    532532#endif
    533533        if(iadv(iq) == 0) then
    534          
    535           cycle
    536        
    537         else if (iadv(iq)==10) then
     534         
     535          cycle
     536       
     537        else if (iadv(iq)==10) then
    538538       
    539539          call vlx_loc(zq,pente_max,zm,mu,
    540540     &               ij_begin,ij_end,iq)
    541541 
    542         else if (iadv(iq)==14) then
     542        else if (iadv(iq)==14) then
    543543     
    544544          call vlxqs_loc(zq,pente_max,zm,mu,
     
    546546 
    547547        else
    548        
     548       
    549549          stop 'vlspltgen_p : schema non parallelise'
    550550     
     
    574574           DO ij=ijb,ije
    575575c             print *,'zq-->',ij,l,iq,zq(ij,l,iq)
    576 c            print *,'q-->',ij,l,iq,q(ij,l,iq)
    577              q(ij,l,iq)=zq(ij,l,iq)
     576c             print *,'q-->',ij,l,iq,q(ij,l,iq)
     577             q(ij,l,iq)=zq(ij,l,iq)
    578578           ENDDO
    579579        ENDDO
  • LMDZ5/trunk/libf/dyn3dmem/vlspltqs_loc.F

    r2286 r2597  
    1212      IMPLICIT NONE
    1313c
    14 #include "dimensions.h"
    15 #include "paramet.h"
    16 #include "logic.h"
    17 #include "comvert.h"
    18 #include "comconst.h"
     14      include "dimensions.h"
     15      include "paramet.h"
     16      include "logic.h"
     17      include "comvert.h"
    1918c
    2019c
     
    420419      USE parallel_lmdz
    421420      USE infotrac, ONLY : nqtot,nqfils,nqdesc,iqfils ! CRisi 
     421      USE comconst_mod, ONLY: pi
    422422      IMPLICIT NONE
    423423c
    424 #include "dimensions.h"
    425 #include "paramet.h"
    426 #include "logic.h"
    427 #include "comvert.h"
    428 #include "comconst.h"
    429 #include "comgeom.h"
     424      include "dimensions.h"
     425      include "paramet.h"
     426      include "logic.h"
     427      include "comvert.h"
     428      include "comgeom.h"
    430429c
    431430c
  • LMDZ5/trunk/libf/dyn3dmem/writedynav_loc.F

    r2475 r2597  
    1313      USE infotrac, ONLY : nqtot, ttext
    1414      use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid
     15      USE comconst_mod, ONLY: cpp
    1516      implicit none
    1617
     
    4142C
    4243C   Declarations
    43 #include "dimensions.h"
    44 #include "paramet.h"
    45 #include "comconst.h"
    46 #include "comvert.h"
    47 #include "comgeom.h"
    48 #include "temps.h"
    49 #include "ener.h"
    50 #include "logic.h"
    51 #include "description.h"
    52 #include "serre.h"
    53 #include "iniprint.h"
     44      include "dimensions.h"
     45      include "paramet.h"
     46      include "comvert.h"
     47      include "comgeom.h"
     48      include "temps.h"
     49      include "ener.h"
     50      include "logic.h"
     51      include "description.h"
     52      include "serre.h"
     53      include "iniprint.h"
    5454
    5555C
  • LMDZ5/trunk/libf/dyn3dmem/writehist_loc.F

    r2475 r2597  
    1313      USE infotrac, ONLY : nqtot, ttext
    1414      use com_io_dyn_mod, only : histid,histvid,histuid
     15      USE comconst_mod, ONLY: cpp
    1516      implicit none
    1617
     
    4142C
    4243C   Declarations
    43 #include "dimensions.h"
    44 #include "paramet.h"
    45 #include "comconst.h"
    46 #include "comvert.h"
    47 #include "comgeom.h"
    48 #include "temps.h"
    49 #include "ener.h"
    50 #include "logic.h"
    51 #include "description.h"
    52 #include "serre.h"
    53 #include "iniprint.h"
     44      include "dimensions.h"
     45      include "paramet.h"
     46      include "comvert.h"
     47      include "comgeom.h"
     48      include "temps.h"
     49      include "ener.h"
     50      include "logic.h"
     51      include "description.h"
     52      include "serre.h"
     53      include "iniprint.h"
    5454
    5555C
  • LMDZ5/trunk/libf/dyn3dpar/addfi_p.F

    r1987 r2597  
    4848#include "dimensions.h"
    4949#include "paramet.h"
    50 #include "comconst.h"
    5150#include "comgeom.h"
    5251#include "serre.h"
  • LMDZ5/trunk/libf/dyn3dpar/advect_new_p.F

    r1907 r2597  
    66      USE parallel_lmdz
    77      USE write_field_p
     8      USE comconst_mod, ONLY: daysec
    89      IMPLICIT NONE
    910c=======================================================================
     
    2829#include "dimensions.h"
    2930#include "paramet.h"
    30 #include "comconst.h"
    3131#include "comvert.h"
    3232#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/advect_p.F

    r1907 r2597  
    55      USE parallel_lmdz
    66      USE write_field_p
     7      USE comconst_mod, ONLY: daysec
    78      IMPLICIT NONE
    89c=======================================================================
     
    2728#include "dimensions.h"
    2829#include "paramet.h"
    29 #include "comconst.h"
    3030#include "comvert.h"
    3131#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/advtrac_p.F90

    r2239 r2597  
    1919  USE infotrac, ONLY: nqtot, iadv
    2020  USE control_mod, ONLY: iapp_tracvl, day_step, planet_type
     21  USE comconst_mod, ONLY: dtvr
    2122  IMPLICIT NONE
    2223  !
    2324  include "dimensions.h"
    2425  include "paramet.h"
    25   include "comconst.h"
    2626  include "comvert.h"
    2727  include "comdissip.h"
  • LMDZ5/trunk/libf/dyn3dpar/bilan_dyn_p.F

    r1907 r2597  
    1717      use misc_mod
    1818      use write_field_p
     19      USE comconst_mod, ONLY: cpp, pi
    1920      IMPLICIT NONE
    2021
    2122#include "dimensions.h"
    2223#include "paramet.h"
    23 #include "comconst.h"
    2424#include "comvert.h"
    2525#include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3dpar/caladvtrac_p.F

    r1907 r2597  
    1010      USE infotrac, ONLY : nqtot
    1111      USE control_mod, ONLY : iapp_tracvl,planet_type
     12      USE comconst_mod, ONLY: dtvr
    1213c
    1314      IMPLICIT NONE
     
    2526#include "dimensions.h"
    2627#include "paramet.h"
    27 #include "comconst.h"
    2828
    2929c   Arguments:
  • LMDZ5/trunk/libf/dyn3dpar/caldyn_p.F

    r1987 r2597  
    3131#include "dimensions.h"
    3232#include "paramet.h"
    33 #include "comconst.h"
    3433#include "comvert.h"
    3534#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F90

    r2442 r2597  
    1616  USE infotrac, ONLY : type_trac
    1717  use assert_m, only: assert
     18  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
     19                          iflag_top_bound, mode_top_bound, tau_top_bound, &
     20                          ngroup
    1821
    1922  IMPLICIT NONE
     
    3841  include "comdissnew.h"
    3942  include "temps.h"
    40   include "comconst.h"
    4143  include "iniprint.h"
    4244
  • LMDZ5/trunk/libf/dyn3dpar/dissip_p.F

    r1987 r2597  
    66      USE parallel_lmdz
    77      USE write_field_p
     8      USE comconst_mod, ONLY: dtdiss
    89      IMPLICIT NONE
    910
     
    2930#include "dimensions.h"
    3031#include "paramet.h"
    31 #include "comconst.h"
    3232#include "comgeom.h"
    3333#include "comdissnew.h"
  • LMDZ5/trunk/libf/dyn3dpar/dynetat0.F

    r1930 r2597  
    99
    1010      use control_mod, only : planet_type
     11      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa,
     12     &                        lllm, omeg, rad
    1113
    1214      IMPLICIT NONE
     
    3032#include "paramet.h"
    3133#include "temps.h"
    32 #include "comconst.h"
    3334#include "comvert.h"
    3435#include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3dpar/dynredem.F

    r1930 r2597  
    99      USE infotrac
    1010      use netcdf95, only: NF95_PUT_VAR
     11      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    1112 
    1213      IMPLICIT NONE
     
    1819#include "dimensions.h"
    1920#include "paramet.h"
    20 #include "comconst.h"
    2121#include "comvert.h"
    2222#include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3dpar/dynredem_p.F

    r1907 r2597  
    1010      USE infotrac
    1111      use netcdf95, only: NF95_PUT_VAR
     12      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    1213 
    1314      IMPLICIT NONE
     
    1920#include "dimensions.h"
    2021#include "paramet.h"
    21 #include "comconst.h"
    2222#include "comvert.h"
    2323#include "comgeom2.h"
  • LMDZ5/trunk/libf/dyn3dpar/exner_hyb_p_m.F90

    r2021 r2597  
    3333    !
    3434    USE parallel_lmdz
     35    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
    3536    !
    3637    include "dimensions.h"
    3738    include "paramet.h"
    38     include "comconst.h"
    3939    include "comgeom.h"
    4040    include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dpar/exner_milieu_p_m.F90

    r2026 r2597  
    3030    !
    3131    USE parallel_lmdz
     32    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
    3233    !
    3334    include "dimensions.h"
    3435    include "paramet.h"
    35     include "comconst.h"
    3636    include "comgeom.h"
    3737    include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dpar/fluxstokenc_p.F

    r1907 r2597  
    2121#include "dimensions.h"
    2222#include "paramet.h"
    23 #include "comconst.h"
    2423#include "comvert.h"
    2524#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/friction_p.F

    r1907 r2597  
    1212      USE ioipsl_getincom
    1313#endif
     14      USE comconst_mod, ONLY: pi
    1415      IMPLICIT NONE
    1516
     
    2930#include "paramet.h"
    3031#include "comgeom2.h"
    31 #include "comconst.h"
    3232#include "iniprint.h"
    3333#include "academic.h"
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r2418 r2597  
    3232      USE iniphysiq_mod, ONLY: iniphysiq
    3333#endif
     34      USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
     35
    3436      IMPLICIT NONE
    3537
     
    6567#include "dimensions.h"
    6668#include "paramet.h"
    67 #include "comconst.h"
    6869#include "comdissnew.h"
    6970#include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dpar/groupe_p.F

    r2442 r2597  
    11      subroutine groupe_p(pext,pbaru,pbarv,pbarum,pbarvm,wm)
    22      USE parallel_lmdz
     3      USE comconst_mod, ONLY: ngroup
    34      implicit none
    45
     
    1617#include "dimensions.h"
    1718#include "paramet.h"
    18 #include "comconst.h"
    1919#include "comgeom2.h"
    2020#include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dpar/groupeun_p.F

    r2442 r2597  
    22      USE parallel_lmdz
    33      USE Write_Field_p
     4      USE comconst_mod, ONLY: ngroup
    45      IMPLICIT NONE
    56
    67#include "dimensions.h"
    78#include "paramet.h"
    8 #include "comconst.h"
    99#include "comgeom2.h"
    1010
     
    136136
    137137      USE parallel_lmdz
     138      USE comconst_mod, ONLY: ngroup
    138139      IMPLICIT NONE
    139140
    140141#include "dimensions.h"
    141142#include "paramet.h"
    142 #include "comconst.h"
    143143#include "comgeom2.h"
    144144
  • LMDZ5/trunk/libf/dyn3dpar/guide_p_mod.F90

    r2134 r2597  
    341341    USE parallel_lmdz
    342342    USE control_mod
     343    USE comconst_mod, ONLY: daysec, dtvr, cpp, kappa
    343344   
    344345    IMPLICIT NONE
     
    346347    INCLUDE "dimensions.h"
    347348    INCLUDE "paramet.h"
    348     INCLUDE "comconst.h"
    349349    INCLUDE "comvert.h"
    350350
     
    619619  SUBROUTINE guide_zonave(typ,hsize,vsize,field)
    620620
     621    USE comconst_mod, ONLY: pi
     622   
    621623    IMPLICIT NONE
    622624
     
    624626    INCLUDE "paramet.h"
    625627    INCLUDE "comgeom.h"
    626     INCLUDE "comconst.h"
    627628   
    628629    ! input/output variables
     
    707708  USE mod_hallo
    708709  USE Bands
     710  USE comconst_mod, ONLY: cpp, kappa
    709711  IMPLICIT NONE
    710712
     
    713715  include "comvert.h"
    714716  include "comgeom2.h"
    715   include "comconst.h"
    716717
    717718  REAL, DIMENSION (iip1,jjp1),     INTENT(IN) :: psi ! Psol gcm
     
    10991100! Calcul des constantes de rappel alpha (=1/tau)
    11001101
     1102    use comconst_mod, only: pi
     1103   
    11011104    implicit none
    11021105
    11031106    include "dimensions.h"
    11041107    include "paramet.h"
    1105     include "comconst.h"
    11061108    include "comgeom2.h"
    11071109    include "serre.h"
     
    18131815  SUBROUTINE guide_out(varname,hsize,vsize,field,factt)
    18141816    USE parallel_lmdz
     1817    USE comconst_mod, ONLY: pi
    18151818    IMPLICIT NONE
    18161819
     
    18191822    INCLUDE "netcdf.inc"
    18201823    INCLUDE "comgeom2.h"
    1821     INCLUDE "comconst.h"
    18221824    INCLUDE "comvert.h"
    18231825   
  • LMDZ5/trunk/libf/dyn3dpar/iniacademic.F90

    r2087 r2597  
    1616  use exner_hyb_m, only: exner_hyb
    1717  use exner_milieu_m, only: exner_milieu
     18  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    1819
    1920  !   Author:    Frederic Hourdin      original: 15/01/93
     
    2930  include "paramet.h"
    3031  include "comvert.h"
    31   include "comconst.h"
    3232  include "comgeom.h"
    3333  include "academic.h"
  • LMDZ5/trunk/libf/dyn3dpar/initdynav_p.F

    r1907 r2597  
    1212       use misc_mod
    1313       USE infotrac
     14       USE comconst_mod, ONLY: pi
    1415
    1516      implicit none
     
    4344#include "dimensions.h"
    4445#include "paramet.h"
    45 #include "comconst.h"
    4646#include "comvert.h"
    4747#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/initfluxsto_p.F

    r1907 r2597  
    1313       use Write_field
    1414       use misc_mod
     15       USE comconst_mod, ONLY: pi
    1516       
    1617      implicit none
     
    4546#include "dimensions.h"
    4647#include "paramet.h"
    47 #include "comconst.h"
    4848#include "comvert.h"
    4949#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/inithist_p.F

    r1907 r2597  
    1313       use misc_mod
    1414       USE infotrac
     15       USE comconst_mod, ONLY: pi
    1516
    1617      implicit none
     
    4546#include "dimensions.h"
    4647#include "paramet.h"
    47 #include "comconst.h"
    4848#include "comvert.h"
    4949#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/integrd_p.F

    r2110 r2597  
    77      USE parallel_lmdz
    88      USE control_mod, only : planet_type
     9      USE comconst_mod, ONLY: pi
    910      IMPLICIT NONE
    1011
     
    2728#include "dimensions.h"
    2829#include "paramet.h"
    29 #include "comconst.h"
    3030#include "comgeom.h"
    3131#include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r2375 r2597  
    2828     &                       periodav, ok_dyn_ave, output_grads_dyn,
    2929     &                       iapp_tracvl
     30       USE comconst_mod, ONLY: cpp, dtvr, ihf, dtphys, pi, jmp1
    3031      IMPLICIT NONE
    3132
     
    6364#include "dimensions.h"
    6465#include "paramet.h"
    65 #include "comconst.h"
    6666#include "comdissnew.h"
    6767#include "comvert.h"
  • LMDZ5/trunk/libf/dyn3dpar/massbar_p.F

    r1907 r2597  
    1818#include "dimensions.h"
    1919#include "paramet.h"
    20 #include "comconst.h"
    2120#include "comgeom.h"
    2221c
  • LMDZ5/trunk/libf/dyn3dpar/massbarxy_p.F

    r1907 r2597  
    1717#include "dimensions.h"
    1818#include "paramet.h"
    19 #include "comconst.h"
    2019#include "comgeom.h"
    2120c
  • LMDZ5/trunk/libf/dyn3dpar/massdair_p.F

    r1907 r2597  
    1818#include "dimensions.h"
    1919#include "paramet.h"
    20 #include "comconst.h"
    2120#include "comgeom.h"
    2221c
  • LMDZ5/trunk/libf/dyn3dpar/sw_case_williamson91_6.F

    r1907 r2597  
    2626c
    2727c=======================================================================
     28      USE comconst_mod, ONLY: cpp, omeg, rad
    2829      IMPLICIT NONE
    2930c-----------------------------------------------------------------------
     
    3435#include "paramet.h"
    3536#include "comvert.h"
    36 #include "comconst.h"
    3737#include "comgeom.h"
    3838#include "iniprint.h"
  • LMDZ5/trunk/libf/dyn3dpar/top_bound_p.F

    r1907 r2597  
    44      SUBROUTINE top_bound_p(vcov,ucov,teta,masse,dt)
    55      USE parallel_lmdz
     6      USE comconst_mod, ONLY: iflag_top_bound, mode_top_bound,
     7     &                        tau_top_bound
    68      IMPLICIT NONE
    79c
    810#include "dimensions.h"
    911#include "paramet.h"
    10 #include "comconst.h"
    1112#include "comvert.h"
    1213#include "comgeom2.h"
     
    4041! NB: top_bound sponge is only called from leapfrog if ok_strato=.true.
    4142
    42 ! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst.h)
     43! sponge parameters: (loaded/set in conf_gcm.F ; stored in comconst_mod)
    4344!    iflag_top_bound=0 for no sponge
    4445!    iflag_top_bound=1 for sponge over 4 topmost layers
  • LMDZ5/trunk/libf/dyn3dpar/vlsplt_p.F

    r1907 r2597  
    2727#include "logic.h"
    2828#include "comvert.h"
    29 #include "comconst.h"
    3029
    3130c
     
    210209#include "logic.h"
    211210#include "comvert.h"
    212 #include "comconst.h"
    213211c
    214212c
     
    539537c   --------------------------------------------------------------------
    540538      USE parallel_lmdz
     539      USE comconst_mod, ONLY: pi
    541540      IMPLICIT NONE
    542541c
     
    545544#include "logic.h"
    546545#include "comvert.h"
    547 #include "comconst.h"
    548546#include "comgeom.h"
    549547c
     
    934932#include "logic.h"
    935933#include "comvert.h"
    936 #include "comconst.h"
    937934c
    938935c
  • LMDZ5/trunk/libf/dyn3dpar/vlspltgen_p.F

    r1907 r2597  
    2727      USE VAMPIR
    2828      USE infotrac, ONLY : nqtot
     29      USE comconst_mod, ONLY: cpp
    2930      IMPLICIT NONE
    3031
     
    3435#include "logic.h"
    3536#include "comvert.h"
    36 #include "comconst.h"
    3737
    3838c
  • LMDZ5/trunk/libf/dyn3dpar/vlspltqs_p.F

    r1907 r2597  
    2525      USE mod_hallo
    2626      USE VAMPIR
     27      USE comconst_mod, ONLY: cpp
    2728      IMPLICIT NONE
    2829
     
    3233#include "logic.h"
    3334#include "comvert.h"
    34 #include "comconst.h"
    3535
    3636c
     
    238238#include "logic.h"
    239239#include "comvert.h"
    240 #include "comconst.h"
    241240c
    242241c
     
    584583c   --------------------------------------------------------------------
    585584      USE parallel_lmdz
     585      USE comconst_mod, ONLY: pi
    586586      IMPLICIT NONE
    587587c
     
    590590#include "logic.h"
    591591#include "comvert.h"
    592 #include "comconst.h"
    593592#include "comgeom.h"
    594593c
  • LMDZ5/trunk/libf/dyn3dpar/writedynav_p.F

    r1907 r2597  
    1212      USE misc_mod
    1313      USE infotrac
     14      USE comconst_mod, ONLY: cpp
    1415      implicit none
    1516
     
    4243#include "dimensions.h"
    4344#include "paramet.h"
    44 #include "comconst.h"
    4545#include "comvert.h"
    4646#include "comgeom.h"
  • LMDZ5/trunk/libf/dyn3dpar/writehist_p.F

    r1907 r2597  
    4343#include "dimensions.h"
    4444#include "paramet.h"
    45 #include "comconst.h"
    4645#include "comvert.h"
    4746#include "comgeom.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/calfis.F

    r2418 r2597  
    3434      USE callphysiq_mod, ONLY: call_physiq
    3535#endif
    36 
     36      USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, kappa, pi
     37     
    3738      IMPLICIT NONE
    3839c=======================================================================
     
    9697      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    9798
    98 #include "comconst.h"
    9999#include "comvert.h"
    100100#include "comgeom2.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/calfis_loc.F

    r2429 r2597  
    5050      USE callphysiq_mod, ONLY: call_physiq
    5151#endif
     52      USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, kappa, pi
    5253
    5354#ifdef CPP_PARA
     
    107108c    ------------------
    108109
    109 #include "dimensions.h"
    110 #include "paramet.h"
    111 #include "temps.h"
     110      include "dimensions.h"
     111      include "paramet.h"
     112      include "temps.h"
    112113
    113114      INTEGER ngridmx
    114115      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    115116
    116 #include "comconst.h"
    117 #include "comvert.h"
    118 #include "comgeom2.h"
    119 #include "iniprint.h"
     117      include "comvert.h"
     118      include "comgeom2.h"
     119      include "iniprint.h"
    120120#ifdef CPP_MPI
    121121      include 'mpif.h'
  • LMDZ5/trunk/libf/dynphy_lonlat/calfis_p.F

    r2429 r2597  
    4747      USE callphysiq_mod, ONLY: call_physiq
    4848#endif
     49      USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, kappa, pi
    4950
    5051      IMPLICIT NONE
     
    110111      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    111112
    112 #include "comconst.h"
    113113#include "comvert.h"
    114114#include "comgeom2.h"
     
    159159      REAL,ALLOCATABLE,SAVE :: zphi(:,:),zphis(:)
    160160c
    161       REAL zrot(iip1,jjb_v:jje_v,llm) ! AdlC May 2014
     161!      REAL zrot(iip1,jjb_v:jje_v,llm) ! AdlC May 2014
     162      REAL :: zrot(iip1,jjm,llm)
    162163      REAL,ALLOCATABLE,SAVE :: zufi(:,:), zvfi(:,:), zrfi(:,:)
    163164      REAL,ALLOCATABLE,SAVE :: ztfi(:,:),zqfi(:,:,:)
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r2457 r2597  
    3434  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
    3535#endif
     36  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, kappa, omeg, r, rad, &
     37                          pi, jmp1
    3638
    3739  IMPLICIT NONE
     
    4244  include "paramet.h"
    4345  include "comgeom2.h"
    44   include "comconst.h"
    4546  include "comvert.h"
    4647  include "iniprint.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90

    r2361 r2597  
    3636  USE ioipsl,         ONLY: flininfo, flinopen, flinget, flinclo, histclo
    3737  USE assert_eq_m,    ONLY: assert_eq
     38  USE comconst_mod, ONLY: pi, cpp, kappa
    3839  IMPLICIT NONE
    3940
     
    4647  include "comgeom2.h"
    4748  include "comvert.h"
    48   include "comconst.h"
    4949  include "temps.h"
    5050  include "comdissnew.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r2531 r2597  
    4444    zmax0,fevap, rnebcon,falb_dir, wake_fip,    agesno,  detr_therm, pbl_tke,  &
    4545    phys_state_var_init
     46  USE comconst_mod, ONLY: pi, dtvr
    4647
    4748  PRIVATE
     
    5253  include "paramet.h"
    5354  include "comgeom2.h"
    54   include "comconst.h"
    5555  include "dimsoil.h"
    5656  include "temps.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r2588 r2597  
    5151  include "dimensions.h"
    5252  include "comvert.h"
    53   include "comconst.h"
    5453  include "iniprint.h"
    5554  include "temps.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/init_ssrf_m.F90

    r2399 r2597  
    99  USE grid_atob_m,        ONLY: grille_m
    1010  USE ioipsl,             ONLY: flininfo, flinopen, flinget, flinclo
     11  USE comconst_mod, ONLY: im, pi
    1112
    1213  CHARACTER(LEN=256), PARAMETER :: icefname="landiceref.nc", icevar="landice"
     
    1718  include "paramet.h"
    1819  include "comgeom2.h"
    19   include "comconst.h"
    2020
    2121CONTAINS
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/limit_netcdf.F90

    r2576 r2597  
    7070  USE inter_barxy_m,      ONLY: inter_barxy
    7171  USE netcdf95,           ONLY: nf95_def_var, nf95_put_att, nf95_put_var
     72  USE comconst_mod, ONLY: pi
    7273  IMPLICIT NONE
    7374!-------------------------------------------------------------------------------
     
    8384  include "logic.h"
    8485  include "comgeom2.h"
    85   include "comconst.h"
    8686
    8787!--- INPUT NETCDF FILES NAMES --------------------------------------------------
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/test_disvert_m.F90

    r2345 r2597  
    1515    use exner_hyb_m, only: exner_hyb
    1616    use vertical_layers_mod, only: ap,bp,preff
     17    use comconst_mod, only: kappa, cpp
    1718
    1819    ! For llm:
    1920    include "dimensions.h"
    20 
    21     ! For kappa, cpp:
    22     include "comconst.h"
    2321
    2422    ! Local:
  • LMDZ5/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r2565 r2597  
    435435      USE infotrac
    436436      use control_mod
     437      USE comconst_mod, ONLY: im, jm, lllm
    437438
    438439      IMPLICIT NONE
     
    443444!   -------------
    444445      include "dimensions.h"
    445       include "comconst.h"
    446446      include "temps.h"
    447447!!#include "control.h"
     
    579579      USE infotrac
    580580      use control_mod
     581      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
    581582
    582583      IMPLICIT NONE
     
    587588!   -------------
    588589      include "dimensions.h"
    589       include "comconst.h"
    590590      include "temps.h"
    591591!!#include "control.h"
Note: See TracChangeset for help on using the changeset viewer.