Ignore:
Timestamp:
Oct 28, 2024, 11:17:48 AM (7 weeks ago)
Author:
abarral
Message:

Turn comgeom.h comgeom2.h into modules

Location:
LMDZ6/trunk/libf/dyn3dmem
Files:
58 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3dmem/addfi_loc.f90

    r5272 r5281  
    1111  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    1212          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     13  USE comgeom_mod_h
    1314  IMPLICIT NONE
    1415  !
     
    4647  !-----------------------------------------------------------------------
    4748  !
    48   !    0.  Declarations :
    49   !    ------------------
    50   include "comgeom.h"
    51   !
    5249  !    Arguments :
    5350  !    -----------
  • LMDZ6/trunk/libf/dyn3dmem/advect_new_loc.f90

    r5272 r5281  
    44SUBROUTINE advect_new_loc(ucov,vcov,teta,w,massebx,masseby, &
    55        du,dv,dteta)
     6  USE comgeom_mod_h
    67  USE parallel_lmdz
    78  USE write_field_loc
     
    3233  !   Declarations:
    3334  !   -------------
    34   include "comgeom.h"
    3535
    3636  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/advtrac_loc.f90

    r5280 r5281  
    88   !            M.A Filiberti (04/2002)
    99   !
     10   USE comgeom2_mod_h
    1011   USE comdissip_mod_h
    1112   USE infotrac,     ONLY: nqtot, tracers
     
    2930
    3031
    31    include "comgeom2.h"
    3232   include "description.h"
    3333!   include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/bilan_dyn_loc.f90

    r5272 r5281  
    1010  !             vQ..A=Cp T + L * ...
    1111
     12  USE comgeom2_mod_h
    1213  USE IOIPSL
    1314  USE parallel_lmdz
     
    2627
    2728
    28   include "comgeom2.h"
    2929  include "iniprint.h"
    3030
  • LMDZ6/trunk/libf/dyn3dmem/caldyn_loc.f90

    r5272 r5281  
    22        (itau,ucov,vcov,teta,ps,masse,pk,pkf,phis , &
    33        phi,conser,du,dv,dteta,dp,w,pbaru,pbarv,time )
     4  USE comgeom_mod_h
    45  USE parallel_lmdz
    56  USE Write_Field_loc
     
    3132
    3233
    33   include "comgeom.h"
    3434
    3535  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/call_dissip_mod.f90

    r5272 r5281  
    4747    CALL allocate_u(dtetadis,llm,d)
    4848    CALL allocate_u(dtetaecdt,llm,d)
    49    
    50    
     49
     50
    5151    CALL dissip_allocate
    52    
     52
    5353  END SUBROUTINE call_dissip_allocate
    54  
     54
    5555  SUBROUTINE call_dissip_switch_dissip(dist)
    5656  USE allocate_field_mod
     
    7676
    7777    CALL dissip_switch_dissip(dist)
    78    
    79   END SUBROUTINE call_dissip_switch_dissip 
    80  
    81 
    82  
     78
     79  END SUBROUTINE call_dissip_switch_dissip
     80
     81
     82
    8383  SUBROUTINE call_dissip(ucov_dyn,vcov_dyn,teta_dyn,p_dyn,pk_dyn,ps_dyn)
    8484  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    9292  USE write_field_loc
    9393  USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_DEBUGIO
     94  USE comgeom_mod_h
    9495  IMPLICIT NONE
    95     INCLUDE 'comgeom.h'
    9696    REAL,INTENT(INOUT) :: ucov_dyn(ijb_u:ije_u,llm) ! covariant zonal wind
    9797    REAL,INTENT(INOUT) :: vcov_dyn(ijb_v:ije_v,llm) ! covariant meridional wind
  • LMDZ6/trunk/libf/dyn3dmem/convflu_loc.f90

    r5272 r5281  
    1515  ! nbniv   est le nombre de niveaux vert. de  xflu et de yflu .
    1616  !
     17  USE comgeom_mod_h
    1718  USE parallel_lmdz
    1819  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    3334  !
    3435  !
    35   INCLUDE "comgeom.h"
    3636  !
    3737
  • LMDZ6/trunk/libf/dyn3dmem/convmas1_loc.f90

    r5272 r5281  
    66! Purpose: Compute mass flux convergence at p levels.
    77!          Equivalent to convmas_loc if convmas2_loc is called after.
     8  USE comgeom_mod_h
    89  USE parallel_lmdz
    910  USE mod_filtreg_p
     
    1415
    1516
    16   include "comgeom.h"
    1717!===============================================================================
    1818! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/convmas2_loc.f90

    r5272 r5281  
    66! Purpose: Compute mass flux convergence at p levels.
    77!          Equivalent to convmas_loc if convmas1_loc is called before.
     8  USE comgeom_mod_h
    89  USE parallel_lmdz
    910  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1314
    1415
    15   include "comgeom.h"
    1616!===============================================================================
    1717! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/convmas_loc.f90

    r5272 r5281  
    55!-------------------------------------------------------------------------------
    66! Purpose: Compute mass flux convergence at p levels.
     7  USE comgeom_mod_h
    78  USE parallel_lmdz
    89  USE mod_filtreg_p
     
    1314
    1415
    15   include "comgeom.h"
    1616!===============================================================================
    1717! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/covcont_loc.f90

    r5272 r5281  
    11SUBROUTINE covcont_loc (klevel,ucov, vcov, ucont, vcont )
     2  USE comgeom_mod_h
    23  USE parallel_lmdz
    34  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1920  !
    2021  !=======================================================================
    21   INCLUDE "comgeom.h"
    2222
    2323  INTEGER :: klevel
  • LMDZ6/trunk/libf/dyn3dmem/covnat_loc.f90

    r5272 r5281  
    33!
    44SUBROUTINE covnat_loc(klevel,ucov, vcov, unat, vnat )
     5  USE comgeom_mod_h
    56  USE parallel_lmdz
    67  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    2223  !
    2324  !=======================================================================
    24   INCLUDE "comgeom.h"
    2525
    2626  INTEGER :: klevel
  • LMDZ6/trunk/libf/dyn3dmem/dissip_loc.f90

    r5280 r5281  
    44SUBROUTINE dissip_loc( vcov,ucov,teta,p, dv,du,dh )
    55  !
     6  USE comgeom_mod_h
    67  USE comdissipn_mod_h
    78  USE comdissnew_mod_h
     
    3738
    3839
    39   include "comgeom.h"
    4040
    4141  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/diverg_gam_loc.f90

    r5272 r5281  
    99  !          x et y  etant des composantes covariantes   ...
    1010  !  *********************************************************************
     11  USE comgeom_mod_h
    1112  USE parallel_lmdz
    1213  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    2627
    2728
    28   INCLUDE "comgeom.h"
    2929  !
    3030  !    ..........          variables en arguments    ...................
  • LMDZ6/trunk/libf/dyn3dmem/diverg_p.f90

    r5272 r5281  
    88  !          x et y  etant des composantes covariantes   ...
    99  !  *********************************************************************
     10  USE comgeom_mod_h
    1011  USE parallel_lmdz
    1112  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    2526
    2627
    27   INCLUDE "comgeom.h"
    2828  !
    2929  !    ..........          variables en arguments    ...................
  • LMDZ6/trunk/libf/dyn3dmem/divergf_loc.f90

    r5272 r5281  
    88  !          x et y  etant des composantes covariantes   ...
    99  !  *********************************************************************
     10  USE comgeom_mod_h
    1011  USE parallel_lmdz
    1112  USE mod_filtreg_p
     
    2627
    2728
    28   INCLUDE "comgeom.h"
    2929  !
    3030  !    ..........          variables en arguments    ...................
  • LMDZ6/trunk/libf/dyn3dmem/divgrad2_loc.f90

    r5280 r5281  
    1010  !     divgra     est  un argument  de sortie pour le s-prg
    1111  !
     12  USE comgeom2_mod_h
    1213  USE comdissipn_mod_h
    1314  USE parallel_lmdz
     
    2223
    2324
    24   INCLUDE "comgeom2.h"
    2525
    2626  !    .......    variables en arguments   .......
  • LMDZ6/trunk/libf/dyn3dmem/dynetat0_loc.f90

    r5272 r5281  
    66! Purpose: Initial state reading.
    77!-------------------------------------------------------------------------------
     8  USE comgeom_mod_h
    89  USE parallel_lmdz
    910  USE infotrac,    ONLY: nqtot, tracers, niso, iqIsoPha, iH2O, isoName, &
     
    3031
    3132
    32   include "comgeom.h"
    3333  include "description.h"
    3434  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/dynredem_loc.f90

    r5272 r5281  
    44! Write the NetCDF restart file (initialization).
    55!-------------------------------------------------------------------------------
     6  USE comgeom_mod_h
    67  USE IOIPSL
    78  USE parallel_lmdz
     
    2324
    2425  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    25 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     26  USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    2627          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    27 IMPLICIT NONE
    28 
    29 
    30   include "comgeom.h"
     28  USE comgeom_mod_h
     29  IMPLICIT NONE
     30
    3131  include "description.h"
    3232  include "iniprint.h"
     
    3434! Arguments:
    3535  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
    36   INTEGER,          INTENT(IN) :: iday_end         !--- 
     36  INTEGER,          INTENT(IN) :: iday_end         !---
    3737  REAL,             INTENT(IN) :: phis(ijb_u:ije_u)!--- GROUND GEOPOTENTIAL
    3838!===============================================================================
     
    7979  tab_cntrl(19) = preff
    8080
    81 !    .....    parameters for zoom    ......   
     81!    .....    parameters for zoom    ......
    8282  tab_cntrl(20) = clon
    8383  tab_cntrl(21) = clat
     
    178178                          err, modname, fil, msg
    179179  USE temps_mod, ONLY: itau_dyn, itaufin
    180  
     180
    181181  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    182182USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     
    186186
    187187  include "description.h"
    188   include "comgeom.h"
    189188  include "iniprint.h"
    190189!===============================================================================
  • LMDZ6/trunk/libf/dyn3dmem/enercin_loc.f90

    r5272 r5281  
    55!-------------------------------------------------------------------------------
    66! Purpose: Compute kinetic energy at sigma levels.
     7  USE comgeom_mod_h
    78  USE parallel_lmdz
    89  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1213
    1314
    14   include "comgeom.h"
    1515!===============================================================================
    1616! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/exner_hyb_loc_m.f90

    r5272 r5281  
    11module exner_hyb_loc_m
    22
    3   IMPLICIT NONE
     3  USE comgeom_mod_h
     4    IMPLICIT NONE
    45
    56contains
     
    1415    !
    1516    !   ************************************************************************
    16     !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des 
     17    !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
    1718    !    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
    1819    !    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
     
    2627    !    ( voir note de Fr.Hourdin )  ,
    2728    !
    28     !    on determine successivement , du haut vers le bas des couches, les 
    29     !    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2), 
    30     !    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches, 
     29    !    on determine successivement , du haut vers le bas des couches, les
     30    !    coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
     31    !    puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches,
    3132    !     pk(ij,l)  donne  par la relation (2),  pour l = 2 a l = llm .
    3233    !
     
    4546
    4647
    47     include "comgeom.h"
    4848
    4949    INTEGER  ngrid
  • LMDZ6/trunk/libf/dyn3dmem/exner_milieu_loc_m.f90

    r5272 r5281  
    11module exner_milieu_loc_m
    22
    3   IMPLICIT NONE
     3  USE comgeom_mod_h
     4    IMPLICIT NONE
    45
    56contains
     
    1516    !
    1617    !   ************************************************************************
    17     !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des 
     18    !    Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
    1819    !    couches .   Pk(l) sera calcule aux milieux  des couches l ,entre les
    1920    !    pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
     
    2324    !
    2425    !     WARNING : CECI est une version speciale de exner_hyb originale
    25     !               Utilise dans la version martienne pour pouvoir 
     26    !               Utilise dans la version martienne pour pouvoir
    2627    !               tourner avec des coordonnees verticales complexe
    27     !              => Il ne verifie PAS la condition la proportionalite en 
     28    !              => Il ne verifie PAS la condition la proportionalite en
    2829    !              energie totale/ interne / potentielle (F.Forget 2001)
    2930    !    ( voir note de Fr.Hourdin )  ,
     
    3334    USE comconst_mod, ONLY: cpp, kappa, r, jmp1
    3435    USE comvert_mod, ONLY: preff
    35    
     36
    3637    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    3738USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     
    4142
    4243
    43     include "comgeom.h"
    4444
    4545    INTEGER  ngrid
  • LMDZ6/trunk/libf/dyn3dmem/flumass_loc.f90

    r5272 r5281  
    55!-------------------------------------------------------------------------------
    66! Purpose: Compute mass flux at s levels.
     7  USE comgeom_mod_h
    78  USE parallel_lmdz
    89  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1213
    1314
    14   include "comgeom.h"
    1515!===============================================================================
    1616! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/friction_loc.f90

    r5272 r5281  
    44!=======================================================================
    55SUBROUTINE friction_loc(ucov,vcov,pdt)
     6  USE comgeom2_mod_h
    67  USE parallel_lmdz
    78  USE control_mod
     
    2627
    2728
    28   include "comgeom2.h"
    2929  include "iniprint.h"
    3030  include "academic.h"
  • LMDZ6/trunk/libf/dyn3dmem/gcm.F90

    r5280 r5281  
    1313!  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
    1414!#endif
     15  USE comgeom_mod_h
    1516  USE comdissnew_mod_h
    1617  USE mod_hallo
     
    6162  !   Declarations:
    6263  !   -------------
    63   include "comgeom.h"
    6464  include "description.h"
    6565  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/gr_u_scal_loc.f90

    r5272 r5281  
    2525  !
    2626  !=======================================================================
     27  USE comgeom_mod_h
    2728  USE parallel_lmdz
    2829  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    3637
    3738
    38   INCLUDE "comgeom.h"
    3939
    4040  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/gr_v_scal_loc.f90

    r5272 r5281  
    2525  !
    2626  !=======================================================================
     27  USE comgeom_mod_h
    2728  USE parallel_lmdz
    2829  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    3637
    3738
    38   INCLUDE "comgeom.h"
    3939
    4040  !   Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/gradiv2_loc.f90

    r5280 r5281  
    1313  !
    1414  !
     15  USE comgeom_mod_h
    1516  USE comdissipn_mod_h
    1617  USE parallel_lmdz
     
    2728
    2829
    29   INCLUDE "comgeom.h"
    3030  !
    3131  ! ........    variables en arguments      ........
  • LMDZ6/trunk/libf/dyn3dmem/groupe_loc.f90

    r5272 r5281  
    11subroutine groupe_loc(pext,pbaru,pbarv,pbarum,pbarvm,wm)
     2  USE comgeom2_mod_h
    23  USE parallel_lmdz
    34  USE Write_field_loc
     
    2324
    2425
    25   include "comgeom2.h"
    2626
    2727  ! integer ngroup
  • LMDZ6/trunk/libf/dyn3dmem/groupeun_loc.f90

    r5272 r5281  
    11SUBROUTINE groupeun_loc(jjmax,llmax,sb,se,jjb,jje,q)
     2  USE comgeom2_mod_h
    23  USE parallel_lmdz
    34  USE Write_Field_p
     
    1011
    1112
    12   include "comgeom2.h"
    1313
    1414  INTEGER :: jjmax,llmax,sb,se,jjb,jje
     
    138138SUBROUTINE init_groupeun_loc(airen_tab, aires_tab)
    139139
     140  USE comgeom2_mod_h
    140141  USE parallel_lmdz
    141142  USE comconst_mod, ONLY: ngroup
     
    147148
    148149
    149   include "comgeom2.h"
    150150
    151151  ! INTEGER ngroup
  • LMDZ6/trunk/libf/dyn3dmem/guide_loc_mod.f90

    r5279 r5281  
    787787  SUBROUTINE guide_zonave_u(typ,vsize,field)
    788788
     789    USE comgeom_mod_h
    789790    USE comconst_mod, ONLY: pi
    790791
    791792    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    792 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     793    USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    793794          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    794795IMPLICIT NONE
     
    796797
    797798
    798     INCLUDE "comgeom.h"
    799799
    800800    ! input/output variables
     
    862862  SUBROUTINE guide_zonave_v(typ,hsize,vsize,field)
    863863
     864    USE comgeom_mod_h
    864865    USE comconst_mod, ONLY: pi
    865866
     
    871872
    872873
    873     INCLUDE "comgeom.h"
    874874
    875875    ! input/output variables
     
    932932!=======================================================================
    933933  SUBROUTINE guide_interp(psi,teta)
    934     use exner_hyb_loc_m, only: exner_hyb_loc
     934    USE comgeom2_mod_h
     935  use exner_hyb_loc_m, only: exner_hyb_loc
    935936    use exner_milieu_loc_m, only: exner_milieu_loc
    936937  USE parallel_lmdz
     
    946947
    947948
    948   include "comgeom2.h"
    949949
    950950  REAL, DIMENSION (iip1,jjb_u:jje_u),     INTENT(IN) :: psi ! Psol gcm
     
    14311431
    14321432    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    1433 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     1433    USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    14341434          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
    1435 implicit none
    1436 
    1437 
    1438 
    1439     include "comgeom2.h"
     1435    USE comgeom2_mod_h
     1436    implicit none
     1437
    14401438
    14411439! input arguments :
     
    22022200
    22032201    USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    2204 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     2202    USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    22052203          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     2204    USE comgeom2_mod_h
    22062205IMPLICIT NONE
    22072206
    22082207
    22092208
    2210     INCLUDE "comgeom2.h"
    22112209
    22122210    ! Variables entree
     
    24242422
    24252423subroutine dump2du(var,varname)
    2426 use parallel_lmdz
     2424     use parallel_lmdz
    24272425use mod_hallo
    24282426USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    24602458subroutine dumpall
    24612459     USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    2462 USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     2460     USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
    24632461          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
     2462     USE comgeom_mod_h
    24642463implicit none
    24652464
    24662465
    2467      include "comgeom.h"
    24682466     call barrier
    24692467     call dump2du(alpha_u(ijb_u:ije_u),'  alpha_u couche 1')
  • LMDZ6/trunk/libf/dyn3dmem/iniacademic_loc.f90

    r5272 r5281  
    44SUBROUTINE iniacademic_loc(vcov,ucov,teta,q,masse,ps,phis,time_0)
    55
     6  USE comgeom_mod_h
    67  USE filtreg_mod, ONLY: inifilr
    78  USE infotrac,    ONLY: nqtot, niso, iqIsoPha, tracers, isoName, addPhase
     
    3738
    3839
    39   include "comgeom.h"
    4040  include "academic.h"
    4141  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/initdynav_loc.f90

    r5272 r5281  
    55
    66  ! This routine needs IOIPSL
    7    USE IOIPSL
     7   USE comgeom_mod_h
     8  USE IOIPSL
    89
    910   USE parallel_lmdz
     
    4950
    5051
    51   include "comgeom.h"
    5252  include "description.h"
    5353  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/initfluxsto_p.f90

    r5272 r5281  
    77
    88  ! This routine needs IOIPSL
    9    USE IOIPSL
     9   USE comgeom_mod_h
     10  USE IOIPSL
    1011
    1112   USE parallel_lmdz
     
    5051
    5152
    52   include "comgeom.h"
    5353  include "description.h"
    5454  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/inithist_loc.f90

    r5272 r5281  
    55
    66  ! This routine needs IOIPSL
    7    USE IOIPSL
     7   USE comgeom_mod_h
     8  USE IOIPSL
    89
    910   USE parallel_lmdz
     
    4748
    4849
    49   include "comgeom.h"
    5050  include "description.h"
    5151  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/integrd_loc.f90

    r5272 r5281  
    55        (  nq,vcovm1,ucovm1,tetam1,psm1,massem1, &
    66        dv,du,dteta,dq,dp,vcov,ucov,teta,q,ps0,masse,phis) !,finvmaold)
     7  USE comgeom_mod_h
    78  USE parallel_lmdz
    89  USE control_mod
     
    3940
    4041
    41   include "comgeom.h"
    4242  include "iniprint.h"
    4343
  • LMDZ6/trunk/libf/dyn3dmem/laplacien_gam_loc.f90

    r5272 r5281  
    1111  !  divgra     est  un argument  de sortie pour le s-prog
    1212  !
     13  USE comgeom_mod_h
    1314  USE parallel_lmdz
    1415  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1920
    2021
    21   INCLUDE "comgeom.h"
    2222
    2323  !
  • LMDZ6/trunk/libf/dyn3dmem/laplacien_loc.f90

    r5272 r5281  
    99  !  divgra     est  un argument  de sortie pour le s-prog
    1010  !
     11  USE comgeom_mod_h
    1112  USE parallel_lmdz
    1213  USE mod_filtreg_p
     
    1819
    1920
    20   INCLUDE "comgeom.h"
    2121
    2222  !
  • LMDZ6/trunk/libf/dyn3dmem/laplacien_rot_loc.f90

    r5272 r5281  
    1010  !  rotout           est  un argument  de sortie pour le s-prog
    1111  !
     12  USE comgeom_mod_h
    1213  USE parallel_lmdz
    1314  USE mod_filtreg_p
     
    1920
    2021
    21   INCLUDE "comgeom.h"
    2222
    2323  !
  • LMDZ6/trunk/libf/dyn3dmem/laplacien_rotgam_loc.f90

    r5272 r5281  
    99  !  divgra     est  un argument  de sortie pour le s-prog
    1010  !
     11  USE comgeom_mod_h
    1112  USE parallel_lmdz
    1213  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1718
    1819
    19   INCLUDE "comgeom.h"
    2020
    2121  !
  • LMDZ6/trunk/libf/dyn3dmem/leapfrog_loc.f90

    r5280 r5281  
    22        masse0,phis0,q0,time_0)
    33
    4    USE comdissnew_mod_h
     4   USE comgeom_mod_h
     5  USE comdissnew_mod_h
    56   USE misc_mod
    67   USE parallel_lmdz
     
    7677  !   Declarations:
    7778  !   -------------
    78   include "comgeom.h"
    7979  include "description.h"
    8080  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/massbar_loc.f90

    r5272 r5281  
    66! Purpose: Compute air mass mean along X and Y in each cell.
    77! See iniconst for more details.
     8  USE comgeom_mod_h
    89  USE parallel_lmdz
    910  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1314
    1415
    15   include "comgeom.h"
    1616!===============================================================================
    1717! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/massbarxy_loc.f90

    r5277 r5281  
    66! Purpose: Compute air mass mean along X and Y in each cell.
    77! See iniconst for more details.
     8  USE comgeom_mod_h
    89  USE parallel_lmdz
    910  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1314
    1415
    15   include "comgeom.h"
    1616!===============================================================================
    1717! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/massdair_loc.f90

    r5272 r5281  
    11SUBROUTINE massdair_loc( p, masse )
     2  USE comgeom_mod_h
    23  USE parallel_lmdz
    34  !
     
    2122
    2223
    23   include "comgeom.h"
    2424  !
    2525  !  .....   arguments  ....
  • LMDZ6/trunk/libf/dyn3dmem/mod_xios_dyn3dmem.f90

    r5272 r5281  
    3737
    3838
     39     USE comgeom_mod_h
    3940     USE comvert_mod, ONLY: presnivs
    4041     USE parallel_lmdz
     
    4748
    4849
    49      INCLUDE 'comgeom.h'
    5050
    5151     TYPE(xios_duration) :: tstep_xios
  • LMDZ6/trunk/libf/dyn3dmem/nxgrad_gam_loc.f90

    r5272 r5281  
    99  !   x  et y    sont des arguments de sortie pour le s-prog
    1010  !
     11  USE comgeom_mod_h
    1112  USE parallel_lmdz
    1213
     
    1819
    1920
    20   INCLUDE "comgeom.h"
    2121  INTEGER :: klevel
    2222  REAL :: rot( ijb_v:ije_v,klevel )
  • LMDZ6/trunk/libf/dyn3dmem/nxgrad_loc.f90

    r5272 r5281  
    99  !   x  et y    sont des arguments de sortie pour le s-prog
    1010  !
     11  USE comgeom_mod_h
    1112  USE parallel_lmdz
    1213  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1718
    1819
    19   INCLUDE "comgeom.h"
    2020  INTEGER :: klevel
    2121  REAL :: rot( ijb_v:ije_v,klevel ),x( ijb_u:ije_u,klevel )
  • LMDZ6/trunk/libf/dyn3dmem/rotat_nfil_loc.f90

    r5272 r5281  
    1010  !        rot          est  un argument  de sortie pour le s-prog
    1111  !
     12  USE comgeom_mod_h
    1213  USE parallel_lmdz
    1314  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1819
    1920
    20   INCLUDE "comgeom.h"
    2121  !
    2222  !   .....  variables en arguments  ......
  • LMDZ6/trunk/libf/dyn3dmem/rotat_p.f90

    r5272 r5281  
    1010  !        rot          est  un argument  de sortie pour le s-prog
    1111  !
     12  USE comgeom_mod_h
    1213  USE parallel_lmdz
    1314  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
     
    1819
    1920
    20   INCLUDE "comgeom.h"
    2121  !
    2222  !   .....  variables en arguments  ......
  • LMDZ6/trunk/libf/dyn3dmem/rotatf_loc.f90

    r5272 r5281  
    1010  !        rot          est  un argument  de sortie pour le s-prog
    1111  !
     12  USE comgeom_mod_h
    1213  USE parallel_lmdz
    1314  USE mod_filtreg_p
     
    1920
    2021
    21   INCLUDE "comgeom.h"
    2222  !
    2323  !   .....  variables en arguments  ......
  • LMDZ6/trunk/libf/dyn3dmem/sw_case_williamson91_6_loc.f90

    r5272 r5281  
    2626  !
    2727  !=======================================================================
     28  USE comgeom_mod_h
    2829  USE parallel_lmdz
    2930  USE comconst_mod, ONLY: cpp, omeg, rad
     
    4041
    4142
    42   include "comgeom.h"
    4343  include "iniprint.h"
    4444
  • LMDZ6/trunk/libf/dyn3dmem/top_bound_loc.f90

    r5280 r5281  
    33!
    44SUBROUTINE top_bound_loc(vcov,ucov,teta,masse,dt)
     5  USE comgeom2_mod_h
    56  USE comdissipn_mod_h
    67  USE parallel_lmdz
     
    1617
    1718
    18   include "comgeom2.h"
    1919
    2020
  • LMDZ6/trunk/libf/dyn3dmem/tourpot_loc.f90

    r5272 r5281  
    55!-------------------------------------------------------------------------------
    66! Purpose: Compute potential vorticity.
     7  USE comgeom_mod_h
    78  USE parallel_lmdz
    89  USE mod_filtreg_p
     
    1314
    1415
    15   include "comgeom.h"
    1616!===============================================================================
    1717! Arguments:
  • LMDZ6/trunk/libf/dyn3dmem/vlsplt_loc.F90

    r5272 r5281  
    417417  !
    418418  !   --------------------------------------------------------------------
     419  USE comgeom_mod_h
    419420  USE parallel_lmdz
    420421  USE infotrac, ONLY : nqtot,tracers, & ! CRisi                 &
     
    428429
    429430
    430   include "comgeom.h"
    431431  !
    432432  !
  • LMDZ6/trunk/libf/dyn3dmem/vlspltqs_loc.F90

    r5272 r5281  
    422422  !
    423423  !   --------------------------------------------------------------------
     424  USE comgeom_mod_h
    424425  USE parallel_lmdz
    425426  USE infotrac, ONLY : nqtot,tracers, & ! CRisi                 &
     
    433434
    434435
    435   include "comgeom.h"
    436436  include "iniprint.h"
    437437  !
  • LMDZ6/trunk/libf/dyn3dmem/writedyn_xios.f90

    r5272 r5281  
    55     &                           masse,ps,phis)
    66
     7      USE comgeom_mod_h
    78      USE lmdz_xios
    89      USE parallel_lmdz
     
    1314      USE temps_mod, ONLY: itau_dyn
    1415      USE mod_xios_dyn3dmem, ONLY : writefield_dyn_u, writefield_dyn_v
    15      
     16
    1617      USE dimensions_mod, ONLY: iim, jjm, llm, ndm
    1718USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
     
    3940
    4041
    41       include "comgeom.h"
    4242      include "description.h"
    4343      include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/writedynav_loc.f90

    r5272 r5281  
    66
    77  ! This routine needs IOIPSL
     8  USE comgeom_mod_h
    89  USE ioipsl
    910
     
    4849
    4950
    50   include "comgeom.h"
    5151  include "description.h"
    5252  include "iniprint.h"
  • LMDZ6/trunk/libf/dyn3dmem/writehist_loc.f90

    r5272 r5281  
    66
    77  ! This routine needs IOIPSL
     8  USE comgeom_mod_h
    89  USE ioipsl
    910
     
    4849
    4950
    50   include "comgeom.h"
    5151  include "description.h"
    5252  include "iniprint.h"
Note: See TracChangeset for help on using the changeset viewer.