Ignore:
Timestamp:
Apr 13, 2015, 10:21:09 AM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes 2216:2237 into testing branch

Location:
LMDZ5/branches/testing
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dpar/calfis_p.F

    r2056 r2258  
    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/branches/testing/libf/dyn3dpar/ce0l.F90

    r1999 r2258  
    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/branches/testing/libf/dyn3dpar/conf_gcm.F90

    r2160 r2258  
    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/branches/testing/libf/dyn3dpar/gcm.F

    r2187 r2258  
    2424! Only INCA needs these informations (from the Earth's physics)
    2525      USE indice_sol_mod
     26      USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    2627#endif
    2728
    2829#ifdef CPP_PHYS
    29       USE mod_grid_phy_lmdz
    30       USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    31       USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    32       USE dimphy
    33       USE comgeomphy
     30!      USE mod_grid_phy_lmdz
     31!      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
     32!      USE dimphy
     33!      USE comgeomphy
    3434#endif
    3535      IMPLICIT NONE
     
    8484#endif
    8585
    86       INTEGER         longcles
    87       PARAMETER     ( longcles = 20 )
    88       REAL  clesphy0( longcles )
    89       SAVE  clesphy0
    90 
    91 
    92 
    9386      REAL zdtvr
    9487
     
    112105
    113106      LOGICAL lafin
    114 c      INTEGER ij,iq,l,i,j
    115       INTEGER i,j
    116 
    117107
    118108      real time_step, t_wrt, t_ops
    119109
    120 
    121       LOGICAL call_iniphys
    122       data call_iniphys/.true./
    123110
    124111c+jld variables test conservation energie
     
    143130
    144131c-----------------------------------------------------------------------
    145 c    variables pour l'initialisation de la physique :
    146 c    ------------------------------------------------
    147       INTEGER ngridmx
    148       PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    149       REAL zcufi(ngridmx),zcvfi(ngridmx)
    150       REAL latfi(ngridmx),lonfi(ngridmx)
    151       REAL airefi(ngridmx)
    152       SAVE latfi, lonfi, airefi
    153      
    154       INTEGER :: ierr
    155 
    156 
    157 c-----------------------------------------------------------------------
    158132c   Initialisations:
    159133c   ----------------
     
    172146c  ---------------------------------------
    173147c
    174 ! Ehouarn: dump possibility of using defrun
    175 !#ifdef CPP_IOIPSL
    176       CALL conf_gcm( 99, .TRUE. , clesphy0 )
     148      CALL conf_gcm( 99, .TRUE. )
    177149      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    178150     s "iphysiq must be a multiple of iperiod", 1)
    179 !#else
    180 !      CALL defrun( 99, .TRUE. , clesphy0 )
    181 !#endif
    182151c
    183152c
     
    193162#ifdef CPP_PHYS
    194163        CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
    195 #endif
     164!#endif
     165!      CALL set_bands
     166!#ifdef CPP_PHYS
     167      CALL Init_interface_dyn_phys
     168#endif
     169      CALL barrier
     170
    196171      CALL set_bands
    197 #ifdef CPP_PHYS
    198       CALL Init_interface_dyn_phys
    199 #endif
    200       CALL barrier
    201 
    202172      if (mpi_rank==0) call WriteBands
    203173      call SetDistrib(jj_Nb_Caldyn)
     
    207177c$OMP END PARALLEL
    208178
    209 #ifdef CPP_PHYS
    210 c$OMP PARALLEL
    211       call InitComgeomphy
    212 c$OMP END PARALLEL
    213 #endif
     179!#ifdef CPP_PHYS
     180!c$OMP PARALLEL
     181!      call InitComgeomphy ! now done in iniphysiq
     182!c$OMP END PARALLEL
     183!#endif
    214184
    215185!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    431401c   Initialisation de la physique :
    432402c   -------------------------------
    433       IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100)) THEN
    434          latfi(1)=rlatu(1)
    435          lonfi(1)=0.
    436          zcufi(1) = cu(1)
    437          zcvfi(1) = cv(1)
    438          DO j=2,jjm
    439             DO i=1,iim
    440                latfi((j-2)*iim+1+i)= rlatu(j)
    441                lonfi((j-2)*iim+1+i)= rlonv(i)
    442                zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
    443                zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
    444             ENDDO
    445          ENDDO
    446          latfi(ngridmx)= rlatu(jjp1)
    447          lonfi(ngridmx)= 0.
    448          zcufi(ngridmx) = cu(ip1jm+1)
    449          zcvfi(ngridmx) = cv(ip1jm-iim)
    450          CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    451 
    452          WRITE(lunout,*)
    453      .       'GCM: WARNING!!! vitesse verticale nulle dans la physique'
     403      IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
    454404! Physics:
    455405#ifdef CPP_PHYS
    456          CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
    457      &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
     406         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
     407     &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
    458408     &                iflag_phys)
    459409#endif
    460          call_iniphys=.false.
    461       ENDIF ! of IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100))
     410      ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    462411
    463412
     
    550499
    551500c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
    552       CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    553      .              time_0)
     501      CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,time_0)
    554502c$OMP END PARALLEL
    555503
  • LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F

    r2187 r2258  
    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.