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

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

Location:
LMDZ5/trunk/libf/dyn3dmem
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dmem/calfis_loc.F

    r2037 r2221  
    2121     $                  pdq,
    2222     $                  flxw,
    23      $                  clesphy0,
    2423     $                  pdufi,
    2524     $                  pdvfi,
     
    141140      REAL,INTENT(OUT) :: pdqfi(iip1,jjb_u:jje_u,llm,nqtot) ! tendency on tracers
    142141      REAL,INTENT(OUT) :: pdpsfi(iip1,jjb_u:jje_u) ! tendency on surface pressure (Pa/s)
    143 
    144       INTEGER,PARAMETER :: longcles = 20
    145       REAL,INTENT(IN) :: clesphy0( longcles ) ! unused
    146 
    147142
    148143#ifdef CPP_PHYS
     
    674669     .             zphis_omp,
    675670     .             presnivs_omp,
    676      .             clesphy0,
    677671     .             zufi_omp,
    678672     .             zvfi_omp,
    679673     .             ztfi_omp,
    680674     .             zqfi_omp,
    681 c#ifdef INCA
    682675     .             flxwfi_omp,
    683 c#endif
    684676     .             zdufi_omp,
    685677     .             zdvfi_omp,
  • LMDZ5/trunk/libf/dyn3dmem/call_calfis_mod.F90

    r2021 r2221  
    6868 
    6969 
    70   SUBROUTINE call_calfis(itau,lafin,clesphy0,ucov_dyn,vcov_dyn,teta_dyn,masse_dyn,ps_dyn, &
     70  SUBROUTINE call_calfis(itau,lafin,ucov_dyn,vcov_dyn,teta_dyn,masse_dyn,ps_dyn, &
    7171                         phis_dyn,q_dyn,flxw_dyn)
    7272  USE dimensions_mod
     
    9191    INTEGER,INTENT(IN) :: itau ! (time) iteration step number
    9292    LOGICAL,INTENT(IN) :: lafin ! .true. if final time step
    93     REAL,INTENT(IN) :: clesphy0( : ) ! not used   
    9493    REAL,INTENT(INOUT) :: ucov_dyn(ijb_u:ije_u,llm) ! covariant zonal wind
    9594    REAL,INTENT(INOUT) :: vcov_dyn(ijb_v:ije_v,llm) ! covariant meridional wind
     
    231230                     ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,   &
    232231                     du,dv,dteta,dq,                             &
    233                      flxw,                                       &
    234                      clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
     232                     flxw, dufi,dvfi,dtetafi,dqfi,dpfi  )
    235233
    236234    ijb=ij_begin
  • LMDZ5/trunk/libf/dyn3dmem/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/dyn3dmem/conf_gcm.F90

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

    r2180 r2221  
    8383#endif
    8484
    85       INTEGER         longcles
    86       PARAMETER     ( longcles = 20 )
    87       REAL  clesphy0( longcles )
    88       SAVE  clesphy0
    89 
    90 
    91 
    9285      REAL zdtvr
    9386
     
    172165c
    173166! Ehouarn: dump possibility of using defrun
    174 !#ifdef CPP_IOIPSL
    175       CALL conf_gcm( 99, .TRUE. , clesphy0 )
     167      CALL conf_gcm( 99, .TRUE. )
    176168      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    177169     s "iphysiq must be a multiple of iperiod", 1)
    178 !#else
    179 !      CALL defrun( 99, .TRUE. , clesphy0 )
    180 !#endif
    181170c
    182171c
     
    547536
    548537c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
    549       CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    550      .              time_0)
     538      CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,time_0)
    551539c$OMP END PARALLEL
    552540
  • LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F

    r2185 r2221  
    99
    1010      SUBROUTINE leapfrog_loc(ucov0,vcov0,teta0,ps0,
    11      &                        masse0,phis0,q0,clesphy0,
    12      &                        time_0)
     11     &                        masse0,phis0,q0,time_0)
    1312
    1413       USE misc_mod
     
    8281!      include "mpif.h"
    8382     
    84       INTEGER,PARAMETER :: longcles = 20
    85       REAL,INTENT(IN) :: clesphy0( longcles ) ! not used
    8683      REAL,INTENT(IN) :: time_0 ! not used
    8784
     
    757754       IF( apphys )  THEN
    758755       
    759          CALL call_calfis(itau,lafin,clesphy0,ucov,vcov,teta,masse,ps, 
     756         CALL call_calfis(itau,lafin,ucov,vcov,teta,masse,ps, 
    760757     &                     phis,q,flxw)
    761758! #ifdef DEBUG_IO   
     
    882879!      $               du,dv,dteta,dq,
    883880!      $               flxw,
    884 !      $               clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
     881!      $               dufi,dvfi,dtetafi,dqfi,dpfi  )
    885882! !        CALL FTRACE_REGION_END("calfis")
    886883! !        ijb=ij_begin
Note: See TracChangeset for help on using the changeset viewer.