Changeset 2221


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
Files:
1 deleted
21 edited

Legend:

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

    r2037 r2221  
    2121     $                  pdq,
    2222     $                  flxw,
    23      $                  clesphy0,
    2423     $                  pdufi,
    2524     $                  pdvfi,
     
    131130      REAL,INTENT(OUT) :: pdpsfi(iip1,jjp1) ! tendency on surface pressure (Pa/s)
    132131
    133       INTEGER,PARAMETER :: longcles = 20
    134       REAL,INTENT(IN) :: clesphy0( longcles ) ! unused
    135 
    136132
    137133c    Local variables :
     
    465461     .             zphis,
    466462     .             presnivs,
    467      .             clesphy0,
    468463     .             zufi,
    469464     .             zvfi,
  • LMDZ5/trunk/libf/dyn3d/ce0l.F90

    r1984 r2221  
    4141#include "temps.h"
    4242#include "logic.h"
    43   INTEGER, PARAMETER            :: longcles=20
    44   REAL,    DIMENSION(longcles)  :: clesphy0
    4543  REAL,    DIMENSION(iip1,jjp1) :: masque
    4644  CHARACTER(LEN=15)             :: calnd
    4745  REAL,    DIMENSION(iip1,jjp1) :: phis ! geopotentiel au sol
    4846!-------------------------------------------------------------------------------
    49   CALL conf_gcm( 99, .TRUE. , clesphy0 )
     47  CALL conf_gcm( 99, .TRUE. )
    5048
    5149  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
  • LMDZ5/trunk/libf/dyn3d/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
     
    2323  !     etatinit  :     = TRUE   , on ne  compare pas les valeurs des para-
    2424  !     -metres  du zoom  avec  celles lues sur le fichier start .
    25   !      clesphy0 :  sortie  .
    26 
    27   LOGICAL etatinit
    28   INTEGER tapedef
    29 
    30   INTEGER        longcles
    31   PARAMETER(     longcles = 20 )
    32   REAL clesphy0( longcles )
     25
     26  LOGICAL,INTENT(IN) :: etatinit
     27  INTEGER,INTENT(IN) :: tapedef
    3328
    3429  !   Declarations :
     
    4136  include "temps.h"
    4237  include "comconst.h"
    43 
    44   ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    45   ! include "clesphys.h"
    4638  include "iniprint.h"
    4739
     
    381373  ip_ebil_dyn = 0
    382374  CALL getin('ip_ebil_dyn',ip_ebil_dyn)
    383 
    384   DO i = 1, longcles
    385      clesphy0(i) = 0.
    386   ENDDO
    387375
    388376  !cc  ....   P. Le Van , ajout  le 7/03/95 .pour le zoom ...
  • LMDZ5/trunk/libf/dyn3d/gcm.F

    r2151 r2221  
    9090!#include "indicesol.h"
    9191#endif
    92       INTEGER         longcles
    93       PARAMETER     ( longcles = 20 )
    94       REAL  clesphy0( longcles )
    95       SAVE  clesphy0
    96 
    97 
    9892
    9993      REAL zdtvr
     
    175169c  ---------------------------------------
    176170c
    177 ! Ehouarn: dump possibility of using defrun
    178 !#ifdef CPP_IOIPSL
    179       CALL conf_gcm( 99, .TRUE. , clesphy0 )
     171      CALL conf_gcm( 99, .TRUE.)
    180172      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    181173     s "iphysiq must be a multiple of iperiod", 1)
    182 !#else
    183 !      CALL defrun( 99, .TRUE. , clesphy0 )
    184 !#endif
    185174
    186175!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    530519
    531520
    532       CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    533      .              time_0)
     521      CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,time_0)
    534522
    535523      END
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r2039 r2221  
    44c
    55c
    6       SUBROUTINE leapfrog(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    7      &                    time_0)
     6      SUBROUTINE leapfrog(ucov,vcov,teta,ps,masse,phis,q,time_0)
    87
    98
     
    7069#include "academic.h"
    7170
    72 ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    73 ! #include "clesphys.h"
    74 
    75       INTEGER,PARAMETER :: longcles = 20
    76       REAL,INTENT(IN) :: clesphy0( longcles ) ! not used
    7771      REAL,INTENT(IN) :: time_0 ! not used
    7872
     
    446440     $               ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
    447441     $               du,dv,dteta,dq,
    448      $               flxw,
    449      $               clesphy0, dufi,dvfi,dtetafi,dqfi,dpfi  )
     442     $               flxw,dufi,dvfi,dtetafi,dqfi,dpfi  )
    450443
    451444c      ajout des tendances physiques:
  • LMDZ5/trunk/libf/dyn3d_common/grilles_gcm_netcdf_sub.F90

    r1984 r2221  
    3131  INTEGER out_latudim,out_latvdim,out_dim(3)
    3232  INTEGER out_levdim
    33 
    34   INTEGER, PARAMETER :: longcles = 20
    35   REAL  clesphy0(longcles)
    3633
    3734  INTEGER start(4),COUNT(4)
     
    6057  pa= 50000.
    6158
    62   CALL conf_gcm( 99, .TRUE. , clesphy0 )
     59  CALL conf_gcm( 99, .TRUE. )
    6360  CALL iniconst
    6461  CALL inigeom
  • 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
  • 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
  • LMDZ5/trunk/libf/phydev/physiq.F90

    r2097 r2221  
    44      SUBROUTINE physiq (nlon,nlev, &
    55     &            debut,lafin,jD_cur, jH_cur,pdtphys, &
    6      &            paprs,pplay,pphi,pphis,presnivs,clesphy0, &
     6     &            paprs,pplay,pphi,pphis,presnivs, &
    77     &            u,v,t,qx, &
    88     &            flxmass_w, &
     
    4545      real,intent(in) :: pphis(klon) ! surface geopotential
    4646      real,intent(in) :: presnivs(klev) ! pseudo-pressure (Pa) of mid-layers
    47       integer,parameter :: longcles=20
    48       real,intent(in) :: clesphy0(longcles) ! Not used
    4947      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
    5048      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
  • LMDZ5/trunk/libf/phylmd/lmdz1d.F90

    r2191 r2221  
    203203!  Call to physiq
    204204!---------------------------------------------------------------------
    205       integer, parameter :: longcles=20
    206205      logical :: firstcall=.true.
    207206      logical :: lastcall=.false.
    208207      real :: phis    = 0.0
    209       real :: clesphy0(longcles) = 0.0
    210208      real :: dpsrf
    211209
     
    365363!---------------------------------------------------------------------
    366364
    367       call conf_gcm( 99, .TRUE. , clesphy0 )
     365      call conf_gcm( 99, .TRUE. )
    368366!-----------------------------------------------------------------------
    369367!   Choix du calendrier
     
    618616! Ecriture du startphy avant le premier appel a la physique.
    619617! On le met juste avant pour avoir acces a tous les champs
    620 ! NB: les clesphy0 seront remplies dans phyredem d'apres les flags lus dans gcm.def
    621618
    622619      if (ok_writedem) then
     
    859856     &              firstcall,lastcall,                                     &
    860857     &              day,time,timestep,                                      &
    861      &              plev,play,phi,phis,presnivs,clesphy0,                   &
     858     &              plev,play,phi,phis,presnivs,                            &
    862859     &              u,v,temp,q,omega2,                                      &
    863860     &              du_phys,dv_phys,dt_phys,dq,dpsrf,                        &
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2213 r2221  
    44SUBROUTINE physiq (nlon,nlev, &
    55     debut,lafin,jD_cur, jH_cur,pdtphys, &
    6      paprs,pplay,pphi,pphis,presnivs,clesphy0, &
     6     paprs,pplay,pphi,pphis,presnivs, &
    77     u,v,t,qx, &
    88     flxmass_w, &
     
    283283  !$OMP THREADPRIVATE(ok_hf)
    284284
    285   INTEGER        longcles
    286   PARAMETER    ( longcles = 20 )
    287   REAL clesphy0( longcles      )
     285  INTEGER,PARAMETER :: longcles=20
     286  REAL,SAVE :: clesphy0(longcles)
     287  !$OMP THREADPRIVATE(clesphy0)
    288288  !
    289289  ! Variables propres a la physique
  • LMDZ5/trunk/libf/phymar/physiq.F90

    r2104 r2221  
    1010      SUBROUTINE physiq (nlon,nlev, &
    1111     &            debut,lafin,jD_cur, jH_cur,pdtphys, &
    12      &            paprs,pplay,pphi,pphis,ppresnivs,clesphy0, &
     12     &            paprs,pplay,pphi,pphis,ppresnivs, &
    1313     &            u,v,t,qx, &
    1414     &            flxmass_w, &
     
    118118      real,intent(in) :: pphis(klon) ! surface geopotential
    119119      real,intent(in) :: ppresnivs(klev) ! pseudo-pressure (Pa) of mid-layers
    120       integer,parameter :: longcles=20
    121       real,intent(in) :: clesphy0(longcles) ! Not used
    122120      real,intent(in) :: u(klon,klev) ! eastward zonal wind (m/s)
    123121      real,intent(in) :: v(klon,klev) ! northward meridional wind (m/s)
Note: See TracChangeset for help on using the changeset viewer.