Ignore:
Timestamp:
Sep 29, 2016, 11:26:46 PM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2593:2640 into testing branch

Location:
LMDZ5/branches/testing
Files:
4 deleted
52 edited
4 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3d_common/adaptdt.F

    r1999 r2641  
    55     c                   masse)
    66
    7       USE control_mod
     7      USE comconst_mod, ONLY: dtvr
    88      IMPLICIT NONE
    99
    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"
     10      include "dimensions.h"
     11      include "paramet.h"
     12      include "comdissip.h"
     13      include "comgeom2.h"
     14      include "description.h"
    2115
    2216c----------------------------------------------------------
  • LMDZ5/branches/testing/libf/dyn3d_common/advn.F

    r1999 r2641  
    1717      IMPLICIT NONE
    1818c
    19 #include "dimensions.h"
    20 #include "paramet.h"
    21 #include "logic.h"
    22 #include "comvert.h"
    23 #include "comconst.h"
    24 #include "comgeom.h"
    25 #include "iniprint.h"
     19      include "dimensions.h"
     20      include "paramet.h"
     21      include "comgeom.h"
     22      include "iniprint.h"
    2623
    2724c
     
    484481      IMPLICIT NONE
    485482c
    486 #include "dimensions.h"
    487 #include "paramet.h"
    488 #include "logic.h"
    489 #include "comvert.h"
    490 #include "comconst.h"
    491 #include "iniprint.h"
     483      include "dimensions.h"
     484      include "paramet.h"
     485      include "iniprint.h"
    492486c
    493487c
  • LMDZ5/branches/testing/libf/dyn3d_common/advx.F

    r1999 r2641  
    1818C  sm,s0,sx,sy,sz                                                C
    1919C  sont les arguments de sortie pour le s-pg                     C
    20 C                                                                C
     20C                                                                C
    2121CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    2222C
    2323C  parametres principaux du modele
    2424C
    25 #include "dimensions.h"
    26 #include "paramet.h"
    27 #include "comconst.h"
    28 #include "comvert.h"
     25      include "dimensions.h"
     26      include "paramet.h"
    2927
    3028C  Arguments :
  • LMDZ5/branches/testing/libf/dyn3d_common/advxp.F

    r1999 r2641  
    1313C  parametres principaux du modele
    1414C
    15 #include "dimensions.h"
    16 #include "paramet.h"
    17 #include "comconst.h"
    18 #include "comvert.h"
     15      include "dimensions.h"
     16      include "paramet.h"
    1917
    2018       INTEGER ntra
     
    103101c         IF (S0(i,j,l,ntra) .lt. 0. ) THEN
    104102c         PRINT*,'S0(',i,j,l,')=',S0(i,j,l,ntra)
    105 c            print*, 'SSX(',i,j,l,')=',SSX(i,j,l,ntra)
     103c             print*, 'SSX(',i,j,l,')=',SSX(i,j,l,ntra)
    106104c         print*, 'SY(',i,j,l,')=',SY(i,j,l,ntra)
    107105c         print*, 'SZ(',i,j,l,')=',SZ(i,j,l,ntra)
     
    120118      DO j = 1, jjp1
    121119      DO i = 1, iim
    122         sqi = sqi + S0(i,j,l,ntra)
     120        sqi = sqi + S0(i,j,l,ntra)
    123121      END DO
    124122      END DO
     
    612610c      DO 9999 j = 1, jjp1
    613611c      DO 9999 i = 1, iip1
    614 c          IF (S0(i,j,l,ntra).lt.0..and.LIMIT) THEN
     612c           IF (S0(i,j,l,ntra).lt.0..and.LIMIT) THEN
    615613c           PRINT*, '-------------------'
    616 c               PRINT*, 'En fin de ADVXP'
     614c                PRINT*, 'En fin de ADVXP'
    617615c           PRINT*,'S0(',i,j,l,')=',S0(i,j,l,ntra)
    618 c               print*, 'SSX(',i,j,l,')=',SSX(i,j,l,ntra)
     616c                print*, 'SSX(',i,j,l,')=',SSX(i,j,l,ntra)
    619617c           print*, 'SY(',i,j,l,')=',SY(i,j,l,ntra)
    620 c               print*, 'SZ(',i,j,l,')=',SZ(i,j,l,ntra)
     618c               print*, 'SZ(',i,j,l,')=',SZ(i,j,l,ntra)
    621619c            WRITE (*,*) 'On arrete !! - pbl en fin de ADVXP'
    622620c            STOP
     
    629627         SM(iip1,j,l) = SM(1,j,l)
    630628         S0(iip1,j,l,ntra) = S0(1,j,l,ntra)
    631          SSX(iip1,j,l,ntra) = SSX(1,j,l,ntra)
    632         SY(iip1,j,l,ntra) = SY(1,j,l,ntra)
    633         SZ(iip1,j,l,ntra) = SZ(1,j,l,ntra)
     629             SSX(iip1,j,l,ntra) = SSX(1,j,l,ntra)
     630            SY(iip1,j,l,ntra) = SY(1,j,l,ntra)
     631            SZ(iip1,j,l,ntra) = SZ(1,j,l,ntra)
    634632      END DO
    635633      END DO
  • LMDZ5/branches/testing/libf/dyn3d_common/advy.F

    r1999 r2641  
    99C  first-order moments (SOM) advection of tracer in Y direction  C
    1010C                                                                C
    11 C  Source : Pascal Simon ( Meteo, CNRM )                        C
    12 C  Adaptation : A.A. (LGGE)                                     C
     11C  Source : Pascal Simon ( Meteo, CNRM )                        C
     12C  Adaptation : A.A. (LGGE)                                     C
    1313C  Derniere Modif : 15/12/94 LAST
    14 C                                                                C
    15 C  sont les arguments d'entree pour le s-pg                      C
    16 C                                                                C
    17 C  argument de sortie du s-pg                                    C
    18 C                                                                C
     14C                                                                C
     15C  sont les arguments d'entree pour le s-pg                      C
     16C                                                                C
     17C  argument de sortie du s-pg                                    C
     18C                                                                C
    1919CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    2020CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
     
    2626C
    2727C
    28 #include "dimensions.h"
    29 #include "paramet.h"
    30 #include "comconst.h"
    31 #include "comvert.h"
    32 #include "comgeom2.h"
     28      include "dimensions.h"
     29      include "paramet.h"
     30      include "comgeom2.h"
    3331 
    3432C  Arguments :
  • LMDZ5/branches/testing/libf/dyn3d_common/advyp.F

    r1999 r2641  
    1111CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    1212C                                                                C
    13 C  Source : Pascal Simon ( Meteo, CNRM )                        C
    14 C  Adaptation : A.A. (LGGE)                                     C
     13C  Source : Pascal Simon ( Meteo, CNRM )                        C
     14C  Adaptation : A.A. (LGGE)                                     C
    1515C  Derniere Modif : 19/10/95 LAST
    16 C                                                                C
    17 C  sont les arguments d'entree pour le s-pg                      C
    18 C                                                                C
    19 C  argument de sortie du s-pg                                    C
    20 C                                                                C
     16C                                                                C
     17C  sont les arguments d'entree pour le s-pg                      C
     18C                                                                C
     19C  argument de sortie du s-pg                                    C
     20C                                                                C
    2121CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    2222CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
     
    2828C
    2929C
    30 #include "dimensions.h"
    31 #include "paramet.h"
    32 #include "comconst.h"
    33 #include "comvert.h"
    34 #include "comgeom.h"
     30      include "dimensions.h"
     31      include "paramet.h"
     32      include "comgeom.h"
    3533 
    3634C  Arguments :
  • LMDZ5/branches/testing/libf/dyn3d_common/advz.F

    r1999 r2641  
    1616C                                                                C
    1717C  dq est l'argument de sortie pour le s-pg                      C
    18 C                                                                C
     18C                                                                C
    1919CCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCCC
    2020C
    2121C  parametres principaux du modele
    2222C
    23 #include "dimensions.h"
    24 #include "paramet.h"
    25 #include "comconst.h"
    26 #include "comvert.h"
     23      include "dimensions.h"
     24      include "paramet.h"
    2725
    2826C    #include "traceur.h"
  • LMDZ5/branches/testing/libf/dyn3d_common/advzp.F

    r1999 r2641  
    3131C  parametres principaux du modele
    3232C
    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 "comgeom.h"
    3836C
    3937C  Arguments :
     
    356354      DO j = 1,jjp1
    357355          SM(iip1,j,l) = SM(1,j,l)
    358           S0(iip1,j,l,ntra) = S0(1,j,l,ntra)
     356          S0(iip1,j,l,ntra) = S0(1,j,l,ntra)
    359357          SSX(iip1,j,l,ntra) = SSX(1,j,l,ntra)
    360           SY(iip1,j,l,ntra) = SY(1,j,l,ntra)
     358          SY(iip1,j,l,ntra) = SY(1,j,l,ntra)
    361359          SZ(iip1,j,l,ntra) = SZ(1,j,l,ntra)
    362360      ENDDO
    363361      ENDDO
    364 c                                                                               C-------------------------------------------------------------
     362c                                                                                C-------------------------------------------------------------
    365363C *** Test : diag de la qqtite totale de tarceur
    366364C            dans l'atmosphere avant l'advection en z
  • LMDZ5/branches/testing/libf/dyn3d_common/bernoui.F

    r1999 r2641  
    2525c   -------------
    2626c
    27 #include "dimensions.h"
    28 #include "paramet.h"
    29 #include "logic.h"
     27      include "dimensions.h"
     28      include "paramet.h"
    3029c
    3130c   Arguments:
  • LMDZ5/branches/testing/libf/dyn3d_common/caldyn0.F90

    r2408 r2641  
    77!-------------------------------------------------------------------------------
    88  USE control_mod, ONLY: resetvarc
     9  USE comvert_mod, ONLY: ap, bp
    910  IMPLICIT NONE
    1011  include "dimensions.h"
    1112  include "paramet.h"
    12   include "comconst.h"
    13   include "comvert.h"
    1413  include "comgeom.h"
    1514!===============================================================================
  • LMDZ5/branches/testing/libf/dyn3d_common/conf_planete.F90

    r1999 r2641  
    1010USE ioipsl_getincom
    1111#endif
     12USE comconst_mod, ONLY: pi, g, molmass, kappa, cpp, omeg, rad, &
     13                        year_day, daylen, daysec, ihf
     14USE comvert_mod, ONLY: preff, pa
    1215IMPLICIT NONE
    1316!
     
    1518!   Declarations :
    1619!   --------------
    17 #include "dimensions.h"
    18 #include "comconst.h"
    19 #include "comvert.h"
     20
    2021!
    2122!   local:
  • LMDZ5/branches/testing/libf/dyn3d_common/convmas.F90

    r2408 r2641  
    99  include "paramet.h"
    1010  include "comgeom.h"
    11   include "logic.h"
    1211!===============================================================================
    1312! Arguments:
  • LMDZ5/branches/testing/libf/dyn3d_common/coordij.F

    r1999 r2641  
    1111c=======================================================================
    1212
     13      USE comconst_mod, ONLY: pi
     14     
    1315      IMPLICIT NONE
    1416      REAL lon,lat
     
    1618      INTEGER i,j
    1719
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comconst.h"
    21 #include "comgeom.h"
    22 #include "serre.h"
     20      include "dimensions.h"
     21      include "paramet.h"
     22      include "comgeom.h"
    2323
    2424      real zlon,zlat
  • LMDZ5/branches/testing/libf/dyn3d_common/disvert.F90

    r2160 r2641  
    1010  use new_unit_m, only: new_unit
    1111  use assert_m, only: assert
     12  USE comvert_mod, ONLY: ap, bp, nivsigs, nivsig, dpres, presnivs, &
     13                         pa, preff, scaleheight
     14  USE logic_mod, ONLY: ok_strato
    1215
    1316  IMPLICIT NONE
     
    1518  include "dimensions.h"
    1619  include "paramet.h"
    17   include "comvert.h"
    18   include "comconst.h"
    1920  include "iniprint.h"
    20   include "logic.h"
    2121
    2222!-------------------------------------------------------------------------------
     
    2424!          Triggered by the levels number llm.
    2525!-------------------------------------------------------------------------------
    26 ! Read    in "comvert.h":
     26! Read    in "comvert_mod":
    2727
    2828! pa !--- vertical coordinate is close to a PRESSURE COORDINATE FOR P
     
    3030
    3131! preff                      !--- REFERENCE PRESSURE                 (101325 Pa)
    32 ! Written in "comvert.h":
     32! Written in "comvert_mod":
    3333! ap(llm+1), bp(llm+1)       !--- Ap, Bp HYBRID COEFFICIENTS AT INTERFACES
    3434! aps(llm),  bps(llm)        !--- Ap, Bp HYBRID COEFFICIENTS AT MID-LAYERS
  • LMDZ5/branches/testing/libf/dyn3d_common/disvert_noterre.F

    r1999 r2641  
    1212      use ioipsl_getincom
    1313#endif
     14      USE comvert_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt,
     15     &                       nivsig,nivsigs,pa,preff,scaleheight
     16      USE comconst_mod, ONLY: kappa
     17      USE logic_mod, ONLY: hybrid
    1418
    1519      IMPLICIT NONE
    1620
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "comvert.h"
    20 #include "comconst.h"
    21 #include "logic.h"
    22 #include "iniprint.h"
     21      include "dimensions.h"
     22      include "paramet.h"
     23      include "iniprint.h"
    2324c
    2425c=======================================================================
  • LMDZ5/branches/testing/libf/dyn3d_common/divgrad.F

    r1999 r2641  
    2020c   -------------
    2121c
    22 #include "dimensions.h"
    23 #include "paramet.h"
    24 #include "comgeom.h"
    25 #include "comdissipn.h"
    26 #include "logic.h"
     22      include "dimensions.h"
     23      include "paramet.h"
     24      include "comgeom.h"
     25      include "comdissipn.h"
    2726c
    2827      INTEGER klevel
  • LMDZ5/branches/testing/libf/dyn3d_common/exner_hyb_m.F90

    r2056 r2641  
    3333    !
    3434    !
     35    USE comconst_mod, ONLY: jmp1, cpp, kappa, r
     36    USE comvert_mod, ONLY: preff
     37   
     38    IMPLICIT NONE
     39   
    3540    include "dimensions.h"
    3641    include "paramet.h"
    37     include "comconst.h"
    3842    include "comgeom.h"
    39     include "comvert.h"
    40     include "serre.h"
    4143
    4244    INTEGER  ngrid
  • LMDZ5/branches/testing/libf/dyn3d_common/exner_milieu_m.F90

    r2056 r2641  
    3030    !
    3131    !
     32    USE comconst_mod, ONLY: jmp1, cpp, kappa, r
     33    USE comvert_mod, ONLY: preff
     34   
     35    IMPLICIT NONE
     36   
    3237    include "dimensions.h"
    3338    include "paramet.h"
    34     include "comconst.h"
    3539    include "comgeom.h"
    36     include "comvert.h"
    37     include "serre.h"
    3840
    3941    INTEGER  ngrid
  • LMDZ5/branches/testing/libf/dyn3d_common/fxhyp_m.F90

    r2258 r2641  
    2222    use nrtype, only: pi, pi_d, twopi, twopi_d, k8
    2323    use principal_cshift_m, only: principal_cshift
     24    use serre_mod, only: clon, grossismx, dzoomx, taux
    2425
    2526    include "dimensions.h"
    2627    ! for iim
    27 
    28     include "serre.h"
    29     ! for clon, grossismx, dzoomx, taux
    3028
    3129    REAL, intent(out):: xprimm025(:), rlonv(:), xprimv(:) ! (iim + 1)
  • LMDZ5/branches/testing/libf/dyn3d_common/fxy.F

    r1999 r2641  
    55     ,                    rlatu2,yprimu2,
    66     , rlonu,xprimu,rlonv,xprimv,rlonm025,xprimm025,rlonp025,xprimp025)
     7
     8      USE comconst_mod, ONLY: pi
     9      USE serre_mod, ONLY: pxo,pyo,alphax,alphay,transx,transy
    710
    811      IMPLICIT NONE
     
    1417c
    1518c
    16 #include "dimensions.h"
    17 #include "paramet.h"
    18 #include "serre.h"
    19 #include "comconst.h"
     19      include "dimensions.h"
     20      include "paramet.h"
    2021
    2122       INTEGER i,j
  • LMDZ5/branches/testing/libf/dyn3d_common/fxysinus.F

    r1999 r2641  
    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/branches/testing/libf/dyn3d_common/fyhyp_m.F90

    r2258 r2641  
    1818    use coefpoly_m, only: coefpoly
    1919    use nrtype, only: k8
     20    use serre_mod, only: clat, grossismy, dzoomy, tauy
    2021
    2122    include "dimensions.h"
    2223    ! for jjm
    23 
    24     include "serre.h"
    25     ! for clat, grossismy, dzoomy, tauy
    2624
    2725    REAL, intent(out):: rlatu(jjm + 1), yyprimu(jjm + 1)
  • LMDZ5/branches/testing/libf/dyn3d_common/geopot.F

    r1999 r2641  
    2727c   -------------
    2828
    29 #include "dimensions.h"
    30 #include "paramet.h"
    31 #include "comvert.h"
     29      include "dimensions.h"
     30      include "paramet.h"
    3231
    3332c   Arguments:
  • LMDZ5/branches/testing/libf/dyn3d_common/gradiv.F

    r1999 r2641  
    1919      IMPLICIT NONE
    2020c
    21 #include "dimensions.h"
    22 #include "paramet.h"
    23 #include "comdissipn.h"
    24 #include "logic.h"
     21      include "dimensions.h"
     22      include "paramet.h"
     23      include "comdissipn.h"
    2524
    2625      INTEGER klevel
  • LMDZ5/branches/testing/libf/dyn3d_common/grilles_gcm_netcdf_sub.F90

    r2258 r2641  
    99SUBROUTINE grilles_gcm_netcdf_sub(masque,phis)
    1010
     11  USE comconst_mod, ONLY: cpp, kappa, g, omeg, daysec, rad, pi
     12  USE comvert_mod, ONLY: presnivs, preff, pa
     13 
    1114  IMPLICIT NONE
    1215
    1316  INCLUDE "dimensions.h"
    1417  INCLUDE "paramet.h"
    15   INCLUDE "comconst.h"
    1618  INCLUDE "comgeom.h"
    17   INCLUDE "comvert.h"
    1819  INCLUDE "netcdf.inc"
    19   INCLUDE "serre.h"
    2020
    2121
  • LMDZ5/branches/testing/libf/dyn3d_common/iniconst.F90

    r2056 r2641  
    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  USE comvert_mod, ONLY: disvert_type, pressure_exner
     16 
    1417  IMPLICIT NONE
    1518  !
     
    2124  include "dimensions.h"
    2225  include "paramet.h"
    23   include "comconst.h"
    24   include "temps.h"
    25   include "comvert.h"
    2626  include "iniprint.h"
    2727
  • LMDZ5/branches/testing/libf/dyn3d_common/inidissip.F90

    r1999 r2641  
    1212
    1313  USE control_mod, only : dissip_period,iperiod
     14  USE comconst_mod, ONLY: dissip_deltaz, dissip_factz, dissip_zref, &
     15                          dtdiss, dtvr, rad
     16  USE comvert_mod, ONLY: preff, presnivs
    1417
    1518  IMPLICIT NONE
     
    1720  include "paramet.h"
    1821  include "comdissipn.h"
    19   include "comconst.h"
    20   include "comvert.h"
    21   include "logic.h"
    2222  include "iniprint.h"
    2323
  • LMDZ5/branches/testing/libf/dyn3d_common/inigeom.F

    r2258 r2641  
    1818      use fxhyp_m, only: fxhyp
    1919      use fyhyp_m, only: fyhyp
     20      USE comconst_mod, ONLY: pi, g, omeg, rad
     21      USE logic_mod, ONLY: fxyhypb, ysinus
     22      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
     23     &          alphax,alphay,taux,tauy,transx,transy,pxo,pyo
    2024      IMPLICIT NONE
    2125c
    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"
     26      include "dimensions.h"
     27      include "paramet.h"
     28      include "comgeom2.h"
     29      include "comdissnew.h"
    2930
    3031c-----------------------------------------------------------------------
  • LMDZ5/branches/testing/libf/dyn3d_common/initdynav.F90

    r2298 r2641  
    99  use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid, &
    1010       dynhistave_file,dynhistvave_file,dynhistuave_file
     11  USE comconst_mod, ONLY: pi
     12  USE comvert_mod, ONLY: presnivs
     13  USE temps_mod, ONLY: itau_dyn
     14 
    1115  implicit none
    1216
     
    3438  include "dimensions.h"
    3539  include "paramet.h"
    36   include "comconst.h"
    37   include "comvert.h"
    3840  include "comgeom.h"
    39   include "temps.h"
    40   include "ener.h"
    41   include "logic.h"
    4241  include "description.h"
    43   include "serre.h"
    4442  include "iniprint.h"
    4543
  • LMDZ5/branches/testing/libf/dyn3d_common/initfluxsto.F

    r2298 r2641  
    99       USE IOIPSL
    1010#endif
     11      USE comconst_mod, ONLY: pi
     12      USE comvert_mod, ONLY: nivsigs
     13      USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
     14     
    1115      implicit none
    1216
     
    3842C
    3943C   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"
     44      include "dimensions.h"
     45      include "paramet.h"
     46      include "comgeom.h"
     47      include "description.h"
     48      include "iniprint.h"
    5149
    5250C   Arguments
     
    8684      CALL ymds2ju(zan, 1, idayref, 0.0, zjulian)
    8785      tau0 = itau_dyn
    88        
    89         do jj = 1, jjp1
     86       
     87        do jj = 1, jjp1
    9088        do ii = 1, iip1
    9189          rlong(ii,jj) = rlonu(ii) * 180. / pi
     
    113111     .             1, iip1, 1, jjm,
    114112     .             tau0, zjulian, tstep, vhoriid, filevid)
    115        
    116         rl(1,1) = 1.   
     113       
     114        rl(1,1) = 1.
    117115      call histbeg('defstoke.nc', 1, rl, 1, rl,
    118116     .             1, 1, 1, 1,
     
    131129      call histhori(fileid, iip1, rlong, jjp1, rlat, 'scalar',
    132130     .              'Grille points scalaires', thoriid)
    133        
     131       
    134132C
    135133C  Appel a histvert pour la grille verticale
     
    150148C
    151149C  Appels a histdef pour la definition des variables a sauvegarder
    152        
    153         CALL histdef(fileid, "phis", "Surface geop. height", "-",
     150       
     151        CALL histdef(fileid, "phis", "Surface geop. height", "-",
    154152     .                iip1,jjp1,thoriid, 1,1,1, -99, 32,
    155153     .                "once", t_ops, t_wrt)
     
    158156     .                iip1,jjp1,thoriid, 1,1,1, -99, 32,
    159157     .                "once", t_ops, t_wrt)
    160        
    161         CALL histdef(filedid, "dtvr", "tps dyn", "s",
     158       
     159        CALL histdef(filedid, "dtvr", "tps dyn", "s",
    162160     .                1,1,dhoriid, 1,1,1, -99, 32,
    163161     .                "once", t_ops, t_wrt)
     
    223221        call histsync(filedid)
    224222      endif
    225        
     223       
    226224#else
    227225! tell the user this routine should be run with ioipsl
  • LMDZ5/branches/testing/libf/dyn3d_common/inithist.F

    r2298 r2641  
    1010       use com_io_dyn_mod, only : histid,histvid,histuid,               &
    1111     &                        dynhist_file,dynhistv_file,dynhistu_file
    12 
     12       USE comconst_mod, ONLY: pi
     13       USE comvert_mod, ONLY: presnivs
     14       USE temps_mod, ONLY: itau_dyn
     15       
    1316      implicit none
    1417
     
    3841C
    3942C   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"
     43      include "dimensions.h"
     44      include "paramet.h"
     45      include "comgeom.h"
     46      include "description.h"
     47      include "iniprint.h"
    5148
    5249C   Arguments
  • LMDZ5/branches/testing/libf/dyn3d_common/inter_barxy_m.F90

    r1999 r2641  
    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/branches/testing/libf/dyn3d_common/interpost.F

    r1999 r2641  
    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 "comgeom2.h"
    1412
    1513c Arguments   
  • LMDZ5/branches/testing/libf/dyn3d_common/interpre.F

    r2160 r2641  
    66     s            unatppm,vnatppm,psppm)
    77
    8       USE control_mod
     8      USE comconst_mod, ONLY: g
     9      USE comvert_mod, ONLY: ap, bp
    910
    1011       implicit none
    1112
    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"
     13      include "dimensions.h"
     14      include "paramet.h"
     15      include "comdissip.h"
     16      include "comgeom2.h"
     17      include "description.h"
    2318
    2419c---------------------------------------------------
     
    7772          do j=1,jjm
    7873              do i=1,iip1
    79                   vnat(i,j,l)=-pbarv(i,j,l)/masseby(i,j,l)*cv(i,j)             
     74                  vnat(i,j,l)=-pbarv(i,j,l)/masseby(i,j,l)*cv(i,j)
    8075              enddo
    8176          enddo
     
    119114                 vnatppm(i,j,l)=vnat(i,j,llm-l+1)
    120115                 fluxwppm(i,j,l)=fluxw(i,j,llm-l+1)
    121                  qppm(i,j,l)=q(i,j,llm-l+1)                             
     116                 qppm(i,j,l)=q(i,j,llm-l+1)
    122117             enddo
    123118          enddo                               
  • LMDZ5/branches/testing/libf/dyn3d_common/invert_zoom_x_m.F90

    r2258 r2641  
    1111    use coefpoly_m, only: coefpoly
    1212    use nrtype, only: pi, pi_d, twopi_d, k8
     13    use serre_mod, only: clon
    1314
    1415    include "dimensions.h"
    1516    ! for iim
    16 
    17     include "serre.h"
    18     ! for clon
    1917
    2018    REAL(K8), intent(in):: Xf(0:), xtild(0:), Xprimt(0:) ! (0:2 * nmax)
  • LMDZ5/branches/testing/libf/dyn3d_common/limx.F

    r1999 r2641  
    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 "comgeom.h"
    2320c
    2421c
  • LMDZ5/branches/testing/libf/dyn3d_common/limy.F

    r1999 r2641  
    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 "comgeom.h"
    2422c
    2523c
  • LMDZ5/branches/testing/libf/dyn3d_common/limz.F

    r1999 r2641  
    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 "comgeom.h"
    2320c
    2421c
  • LMDZ5/branches/testing/libf/dyn3d_common/massbarxy.F90

    r2408 r2641  
    99  include "dimensions.h"
    1010  include "paramet.h"
    11   include "comconst.h"
    1211  include "comgeom.h"
    1312!===============================================================================
  • LMDZ5/branches/testing/libf/dyn3d_common/massdair.F

    r1999 r2641  
    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/branches/testing/libf/dyn3d_common/nxgrarot.F

    r1999 r2641  
    1919c
    2020c
    21 #include "dimensions.h"
    22 #include "paramet.h"
    23 #include "comdissipn.h"
    24 #include "logic.h"
     21      include "dimensions.h"
     22      include "paramet.h"
     23      include "comdissipn.h"
    2524c
    2625      INTEGER klevel
  • LMDZ5/branches/testing/libf/dyn3d_common/pentes_ini.F

    r1999 r2641  
    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 "comgeom2.h"
    2930
    3031c   Arguments:
     
    437438
    438439        DO l = 1,llm
    439         DO j = 1,jjp1
    440           DO i = 1,iip1
     440            DO j = 1,jjp1
     441              DO i = 1,iip1
    441442                IF (q(i,j,l,0).lt.0.)  THEN
    442443c                    PRINT*,'------------ BIP-----------'
     
    445446c                    PRINT*,'QY(',i,j,l,')=',q(i,j,l,2)
    446447c                    PRINT*,'QZ(',i,j,l,')=',q(i,j,l,3)
    447 c                            PRINT*,' PBL EN SORTIE DE PENTES'
     448c                            PRINT*,' PBL EN SORTIE DE PENTES'
    448449                     q(i,j,l,0)=0.
    449450c                    STOP
  • LMDZ5/branches/testing/libf/dyn3d_common/prather.F

    r1999 r2641  
    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 "comgeom2.h"
    2627
    2728c   Arguments:
  • LMDZ5/branches/testing/libf/dyn3d_common/principal_cshift_m.F90

    r2258 r2641  
    1212
    1313    use nrtype, only: twopi
     14    use serre_mod, only: clon
    1415
    1516    include "dimensions.h"
    1617    ! for iim
    17 
    18     include "serre.h"
    19     ! for clon
    2018
    2119    integer, intent(in):: is2
  • LMDZ5/branches/testing/libf/dyn3d_common/sortvarc.F

    r2160 r2641  
    77
    88      USE control_mod, ONLY: resetvarc
     9      USE comconst_mod, ONLY: dtvr, daysec, g, rad, omeg
     10      USE logic_mod, ONLY: read_start
     11      USE ener_mod, ONLY: etot,ptot,ztot,stot,ang,
     12     &                    etot0,ptot0,ztot0,stot0,ang0,
     13     &                    rmsdpdt,rmsv
    914      IMPLICIT NONE
    1015
     
    2732      INCLUDE "dimensions.h"
    2833      INCLUDE "paramet.h"
    29       INCLUDE "comconst.h"
    30       INCLUDE "comvert.h"
    3134      INCLUDE "comgeom.h"
    32       INCLUDE "ener.h"
    33       INCLUDE "logic.h"
    34       INCLUDE "temps.h"
    3535      INCLUDE "iniprint.h"
    3636
  • LMDZ5/branches/testing/libf/dyn3d_common/tourpot.F90

    r2408 r2641  
    99  include "paramet.h"
    1010  include "comgeom.h"
    11   include "logic.h"
    1211!===============================================================================
    1312! Arguments:
  • LMDZ5/branches/testing/libf/dyn3d_common/traceurpole.F

    r1999 r2641  
    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 "comgeom2.h"
     12      include "description.h"
    2113
    2214
  • LMDZ5/branches/testing/libf/dyn3d_common/ugeostr.F90

    r1999 r2641  
    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/branches/testing/libf/dyn3d_common/vitvert.F90

    r2408 r2641  
    55!-------------------------------------------------------------------------------
    66! Purpose: Compute vertical speed at sigma levels.
     7  USE comvert_mod, ONLY: bp
    78  IMPLICIT NONE
    89  include "dimensions.h"
    910  include "paramet.h"
    10   include "comvert.h"
    1111!===============================================================================
    1212! Arguments:
  • LMDZ5/branches/testing/libf/dyn3d_common/writedynav.F90

    r2298 r2641  
    88  USE infotrac, ONLY : nqtot, ttext
    99  use com_io_dyn_mod, only : histaveid, histvaveid, histuaveid
     10  USE comconst_mod, ONLY: cpp
     11  USE temps_mod, ONLY: itau_dyn
    1012
    1113  implicit none
     
    3133  include "dimensions.h"
    3234  include "paramet.h"
    33   include "comconst.h"
    34   include "comvert.h"
    3535  include "comgeom.h"
    36   include "temps.h"
    37   include "ener.h"
    38   include "logic.h"
    3936  include "description.h"
    40   include "serre.h"
    4137  include "iniprint.h"
    4238
  • LMDZ5/branches/testing/libf/dyn3d_common/writehist.F

    r2298 r2641  
    99      USE infotrac, ONLY : nqtot, ttext
    1010      use com_io_dyn_mod, only : histid,histvid,histuid
     11      USE temps_mod, ONLY: itau_dyn
     12     
    1113      implicit none
    1214
     
    3335C
    3436C   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"
     37      include "dimensions.h"
     38      include "paramet.h"
     39      include "comgeom.h"
     40      include "description.h"
     41      include "iniprint.h"
    4642
    4743C
Note: See TracChangeset for help on using the changeset viewer.