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

Merged trunk changes 2216:2237 into testing branch

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dmem/gcm.F

    r2187 r2258  
    11!
    2 ! $Id$
     2! $Id: $
    33!
    44c
     
    2323! Only INCA needs these informations (from the Earth's physics)
    2424      USE indice_sol_mod
     25      USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    2526#endif
    2627
    2728#ifdef CPP_PHYS
    28       USE mod_grid_phy_lmdz
    29       USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    30       USE mod_phys_lmdz_omp_data, ONLY: klon_omp
    31       USE dimphy
    32       USE comgeomphy
     29!      USE mod_grid_phy_lmdz
     30!      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
     31!      USE dimphy
     32!      USE comgeomphy
    3333#endif
    3434      IMPLICIT NONE
     
    8383#endif
    8484
    85       INTEGER         longcles
    86       PARAMETER     ( longcles = 20 )
    87       REAL  clesphy0( longcles )
    88       SAVE  clesphy0
    89 
    90 
    91 
    9285      REAL zdtvr
    9386
     
    111104
    112105      LOGICAL lafin
    113 c      INTEGER ij,iq,l,i,j
    114       INTEGER i,j
    115 
    116106
    117107      real time_step, t_wrt, t_ops
    118 
    119 
    120       LOGICAL call_iniphys
    121       data call_iniphys/.true./
    122108
    123109c+jld variables test conservation energie
     
    142128
    143129c-----------------------------------------------------------------------
    144 c    variables pour l'initialisation de la physique :
    145 c    ------------------------------------------------
    146       INTEGER ngridmx
    147       PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    148       REAL zcufi(ngridmx),zcvfi(ngridmx)
    149       REAL latfi(ngridmx),lonfi(ngridmx)
    150       REAL airefi(ngridmx)
    151       SAVE latfi, lonfi, airefi
    152      
    153       INTEGER :: ierr
    154 
    155 
    156 c-----------------------------------------------------------------------
    157130c   Initialisations:
    158131c   ----------------
     
    171144c  ---------------------------------------
    172145c
    173 ! Ehouarn: dump possibility of using defrun
    174 !#ifdef CPP_IOIPSL
    175       CALL conf_gcm( 99, .TRUE. , clesphy0 )
     146      CALL conf_gcm( 99, .TRUE. )
    176147      if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    177148     s "iphysiq must be a multiple of iperiod", 1)
    178 !#else
    179 !      CALL defrun( 99, .TRUE. , clesphy0 )
    180 !#endif
    181149c
    182150c
     
    192160#ifdef CPP_PHYS
    193161        CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
    194 #endif
     162!#endif
     163!      CALL set_bands
     164!#ifdef CPP_PHYS
     165      CALL Init_interface_dyn_phys
     166#endif
     167      CALL barrier
     168
    195169      CALL set_bands
    196 #ifdef CPP_PHYS
    197       CALL Init_interface_dyn_phys
    198 #endif
    199       CALL barrier
    200 
    201170      if (mpi_rank==0) call WriteBands
    202171      call Set_Distrib(distrib_caldyn)
     
    206175c$OMP END PARALLEL
    207176
    208 #ifdef CPP_PHYS
    209 c$OMP PARALLEL
    210       call InitComgeomphy
    211 c$OMP END PARALLEL
    212 #endif
     177!#ifdef CPP_PHYS
     178!c$OMP PARALLEL
     179!      call InitComgeomphy ! now done in iniphysiq
     180!c$OMP END PARALLEL
     181!#endif
    213182
    214183c-----------------------------------------------------------------------
     
    225194        call ioconf_calendar('noleap')
    226195        write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
    227       else if (calend == 'earth_366d') then
     196      else if (calend == 'gregorian') then
    228197        call ioconf_calendar('gregorian')
    229198        write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
     
    321290
    322291C
    323 C on remet le calendrier à zero si demande
     292C on remet le calendrier \`a zero si demande
    324293c
    325294      IF (start_time /= starttime) then
    326295        WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
    327      &,' fichier restart ne correspond pas à celle lue dans le run.def'
     296     &,' fichier restart ne correspond pas a celle lue dans le run.def'
    328297        IF (raz_date == 1) then
    329298          WRITE(lunout,*)'Je prends l''heure lue dans run.def'
     
    431400c   Initialisation de la physique :
    432401c   -------------------------------
    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'
     402      IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
    454403! Physics:
    455404#ifdef CPP_PHYS
    456          CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
    457      &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
    458      &                iflag_phys)
    459 #endif
    460          call_iniphys=.false.
    461       ENDIF ! of IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100))
     405         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
     406     &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
     407     &                iflag_phys)
     408#endif
     409      ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    462410
    463411
     
    547495
    548496c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
    549       CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,clesphy0,
    550      .              time_0)
     497      CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,time_0)
    551498c$OMP END PARALLEL
    552499
Note: See TracChangeset for help on using the changeset viewer.