Ignore:
Timestamp:
Mar 9, 2015, 7:38:03 AM (10 years ago)
Author:
Ehouarn Millour
Message:

Some cleanup: remove (unused) clesph0 from dynamics.
EM

Location:
LMDZ5/trunk/libf/dyn3dpar
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dpar/calfis_p.F

    r2037 r2221  
    2121     $                  pdq,
    2222     $                  flxw,
    23      $                  clesphy0,
    2423     $                  pdufi,
    2524     $                  pdvfi,
     
    140139      REAL,INTENT(OUT) :: pdqfi(iip1,jjp1,llm,nqtot) ! tendency on tracers
    141140      REAL,INTENT(OUT) :: pdpsfi(iip1,jjp1) ! tendency on surface pressure (Pa/s)
    142 
    143       INTEGER,PARAMETER :: longcles = 20
    144       REAL,INTENT(IN) :: clesphy0( longcles ) ! unused
    145141
    146142#ifdef CPP_PHYS
     
    636632     .             zphis_omp,
    637633     .             presnivs_omp,
    638      .             clesphy0,
    639634     .             zufi_omp,
    640635     .             zvfi_omp,
    641636     .             ztfi_omp,
    642637     .             zqfi_omp,
    643 c#ifdef INCA
    644638     .             flxwfi_omp,
    645 c#endif
    646639     .             zdufi_omp,
    647640     .             zdvfi_omp,
  • LMDZ5/trunk/libf/dyn3dpar/ce0l.F90

    r1984 r2221  
    4848#endif
    4949
    50   INTEGER, PARAMETER            :: longcles=20
    5150  INTEGER                       :: ierr
    52   REAL,    DIMENSION(longcles)  :: clesphy0
    5351  REAL,    DIMENSION(iip1,jjp1) :: masque
    5452  CHARACTER(LEN=15)             :: calnd
    5553  REAL,    DIMENSION(iip1,jjp1) :: phis ! geopotentiel au sol
    5654!-------------------------------------------------------------------------------
    57   CALL conf_gcm( 99, .TRUE. , clesphy0 )
     55  CALL conf_gcm( 99, .TRUE. )
    5856
    5957#ifdef CPP_MPI
  • LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F90

    r2151 r2221  
    22! $Id$
    33
    4 SUBROUTINE conf_gcm( tapedef, etatinit, clesphy0 )
     4SUBROUTINE conf_gcm( tapedef, etatinit )
    55
    66  USE control_mod
     
    2626  !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
    2727  !     -metres  du zoom  avec  celles lues sur le fichier start .
    28   !      clesphy0 :  sortie  .
    29 
    30   LOGICAL etatinit
    31   INTEGER tapedef
    32 
    33   INTEGER        longcles
    34   PARAMETER(     longcles = 20 )
    35   REAL clesphy0( longcles )
     28
     29  LOGICAL,INTENT(IN) :: etatinit
     30  INTEGER,INTENT(IN) :: tapedef
    3631
    3732  !   Declarations :
     
    4439  include "temps.h"
    4540  include "comconst.h"
    46 
    47   ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    48   ! include "clesphys.h"
    4941  include "iniprint.h"
    5042
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r2180 r2221  
    8484#endif
    8585
    86       INTEGER         longcles
    87       PARAMETER     ( longcles = 20 )
    88       REAL  clesphy0( longcles )
    89       SAVE  clesphy0
    90 
    91 
    92 
    9386      REAL zdtvr
    9487
     
    172165c  ---------------------------------------
    173166c
    174 ! Ehouarn: dump possibility of using defrun
    175 !#ifdef CPP_IOIPSL
    176       CALL conf_gcm( 99, .TRUE. , clesphy0 )
     167      CALL conf_gcm( 99, .TRUE. )
    177168      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    178169     s "iphysiq must be a multiple of iperiod", 1)
    179 !#else
    180 !      CALL defrun( 99, .TRUE. , clesphy0 )
    181 !#endif
    182170c
    183171c
     
    550538
    551539c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
    552       CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    553      .              time_0)
     540      CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,time_0)
    554541c$OMP END PARALLEL
    555542
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r2180 r2221  
    55c
    66
    7       SUBROUTINE leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    8      &                    time_0)
     7      SUBROUTINE leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,time_0)
    98
    109      use exner_hyb_m, only: exner_hyb
     
    7776#include "academic.h"
    7877     
    79       INTEGER,PARAMETER :: longcles = 20
    80       REAL,INTENT(IN) :: clesphy0( longcles ) ! not used
    8178      REAL,INTENT(IN) :: time_0 ! not used
    8279
     
    831828     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    832829     $               du,dv,dteta,dq,
    833      $               flxw,
    834      $               clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
     830     $               flxw, dufi,dvfi,dtetafi,dqfi,dpfi  )
    835831!        CALL FTRACE_REGION_END("calfis")
    836832        ijb=ij_begin
Note: See TracChangeset for help on using the changeset viewer.