Ignore:
Timestamp:
Dec 14, 2015, 11:43:09 AM (9 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes r2298:2396 into testing branch

Location:
LMDZ5/branches/testing
Files:
1 deleted
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dpar/bands.F90

    r1910 r2408  
    9393   SUBROUTINE  Set_Bands
    9494     USE parallel_lmdz
    95 #ifdef CPP_PHYS
    96 ! Ehouarn: what follows is only related to // physics
    97      USE mod_phys_lmdz_para, ONLY : jj_para_begin,jj_para_end
    98 #endif
    9995     IMPLICIT NONE
    10096     INCLUDE 'dimensions.h'   
    101      INTEGER :: i
    102        
     97     INTEGER :: i, ij
     98     INTEGER :: jj_para_begin(0:mpi_size-1)
     99     INTEGER :: jj_para_end(0:mpi_size-1)
     100       
    103101      do i=0,mpi_size-1
    104102         jj_nb_vanleer2(i)=(jjm+1)/mpi_size
     
    106104      enddo
    107105         
    108 #ifdef CPP_PHYS
     106      jj_para_begin(0)=1
     107      ij=distrib_phys(0)+iim-1
     108      jj_para_end(0)=((ij-1)/iim)+1
     109     
     110      DO i=1,mpi_Size-1
     111        ij=ij+1
     112        jj_para_begin(i)=((ij-1)/iim)+1
     113        ij=ij+distrib_phys(i)-1
     114        jj_para_end(i)=((ij-1)/iim)+1
     115      ENDDO
     116 
    109117      do i=0,MPI_Size-1
    110118        jj_Nb_physic(i)=jj_para_end(i)-jj_para_begin(i)+1
     
    127135        endif
    128136      enddo
    129 #endif     
    130137     
    131138    end subroutine Set_Bands
  • LMDZ5/branches/testing/libf/dyn3dpar/gcm.F

    r2298 r2408  
    1414      USE parallel_lmdz
    1515      USE infotrac
    16 #ifdef CPP_PHYS
    17       USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
    18 #endif
     16!#ifdef CPP_PHYS
     17!      USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
     18!#endif
    1919      USE mod_hallo
    2020      USE Bands
     
    3030
    3131#ifdef CPP_PHYS
    32 !      USE mod_grid_phy_lmdz
    33 !      USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    34 !      USE dimphy
    35 !      USE comgeomphy
     32  USE iniphysiq_mod, ONLY: iniphysiq
    3633#endif
    3734      IMPLICIT NONE
     
    162159      call Read_Distrib
    163160
    164 #ifdef CPP_PHYS
    165         CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
     161!#ifdef CPP_PHYS
     162!        CALL Init_Phys_lmdz(iim,jjp1,llm,mpi_size,distrib_phys)
    166163!#endif
    167164!      CALL set_bands
    168165!#ifdef CPP_PHYS
    169       CALL Init_interface_dyn_phys
    170 #endif
     166!      CALL Init_interface_dyn_phys
     167!#endif
    171168      CALL barrier
    172169
     
    406403! Physics:
    407404#ifdef CPP_PHYS
    408          CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
    409      &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
     405         CALL iniphysiq(iim,jjm,llm,
     406     &                distrib_phys(mpi_rank),comm_lmdz,
     407     &                daysec,day_ini,dtphys/nsplit_phys,
     408     &                rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,
    410409     &                iflag_phys)
    411410#endif
  • LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F

    r2298 r2408  
    258258   1  CONTINUE ! Matsuno Forward step begins here
    259259
     260c   date: (NB: date remains unchanged for Backward step)
     261c   -----
     262
    260263      jD_cur = jD_ref + day_ini - day_ref +                             &
    261      &          itau/day_step
     264     &          (itau+1)/day_step
    262265      jH_cur = jH_ref + start_time +                                    &
    263      &         mod(itau,day_step)/float(day_step)
     266     &         mod(itau+1,day_step)/float(day_step)
    264267      if (jH_cur > 1.0 ) then
    265268        jD_cur = jD_cur +1.
     
    356359c-----------------------------------------------------------------------
    357360
    358 c   date:
     361c   date: (NB: only leapfrog step requires recomputing date)
    359362c   -----
    360363
     364      IF (leapf) THEN
     365        jD_cur = jD_ref + day_ini - day_ref +
     366     &            (itau+1)/day_step
     367        jH_cur = jH_ref + start_time +
     368     &           mod(itau+1,day_step)/float(day_step)
     369        if (jH_cur > 1.0 ) then
     370          jD_cur = jD_cur +1.
     371          jH_cur = jH_cur -1.
     372        endif
     373      ENDIF
    361374
    362375c   gestion des appels de la physique et des dissipations:
     
    720733
    721734           jD_cur = jD_ref + day_ini - day_ref
    722      $        + itau/day_step
     735     $        + (itau+1)/day_step
    723736
    724737           IF (planet_type .eq."generic") THEN
     
    728741
    729742           jH_cur = jH_ref + start_time +                                &
    730      &              mod(itau,day_step)/float(day_step)
     743     &              mod(itau+1,day_step)/float(day_step)
    731744!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
    732745           if (jH_cur > 1.0 ) then
     
    747760      IF (ip_ebil_dyn.ge.1 ) THEN
    748761          ztit='bil dyn'
    749 ! Ehouarn: be careful, diagedyn is Earth-specific (includes ../phylmd/..)!
     762! Ehouarn: be careful, diagedyn is Earth-specific!
    750763           IF (planet_type.eq."earth") THEN
    751 #ifdef CPP_EARTH
    752764            CALL diagedyn(ztit,2,1,1,dtphys
    753765     &    , ucov    , vcov , ps, p ,pk , teta , q(:,:,1), q(:,:,2))
    754 #endif
    755766           ENDIF
    756767      ENDIF
Note: See TracChangeset for help on using the changeset viewer.