Changeset 2422


Ignore:
Timestamp:
Jan 6, 2016, 12:37:41 PM (8 years ago)
Author:
Ehouarn Millour
Message:

Small modification in the way time and calendar are handled: Now all the time keeping is done in the physics and only the timestep is transfered from the dynamics to the physics. Due to changes in computations and roundoffs this will change reference bench results.
The implementation of this change in phymar is left as future work.
EM

Location:
LMDZ5/trunk/libf
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dynphy_lonlat/phydev/callphysiq_mod.F90

    r2418 r2422  
    5757              debut_split,    &
    5858              lafin_split,    &
    59               jD_cur,         &
    60               jH_cur_split,   &
    6159              zdt_split,      &
    6260              zplev_omp,      &
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/callphysiq_mod.F90

    r2421 r2422  
    7171              debut_split,    &
    7272              lafin_split,    &
    73               jD_cur,         &
    74               jH_cur_split,   &
    7573              zdt_split,      &
    7674              zplev_omp,      &
  • LMDZ5/trunk/libf/phydev/physiq_mod.F90

    r2418 r2422  
    77
    88      SUBROUTINE physiq (nlon,nlev, &
    9      &            debut,lafin,jD_cur, jH_cur,pdtphys, &
     9     &            debut,lafin,pdtphys, &
    1010     &            paprs,pplay,pphi,pphis,presnivs, &
    1111     &            u,v,t,qx, &
     
    3535      integer,intent(in) :: nlon ! number of atmospheric colums
    3636      integer,intent(in) :: nlev ! number of vertical levels (should be =klev)
    37       real,intent(in) :: jD_cur ! current day number (Julian day)
    38       real,intent(in) :: jH_cur ! current time of day (as fraction of day)
    3937      logical,intent(in) :: debut ! signals first call to physics
    4038      logical,intent(in) :: lafin ! signals last call to physics
  • LMDZ5/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r2421 r2422  
    934934
    935935       call physiq(ngrid,llm, &
    936             firstcall,lastcall, day,time,timestep, &
     936            firstcall,lastcall,timestep, &
    937937            plev,play,phi,phis,presnivs, &
    938938            u,v, rot, temp,q,omega2, &
  • LMDZ5/trunk/libf/phylmd/phys_cal_mod.F90

    r2358 r2422  
    5252  END SUBROUTINE  phys_cal_init
    5353
    54   SUBROUTINE phys_cal_update(jD_cur, jH_cur)
     54  SUBROUTINE phys_cal_update(julian_date)
    5555    ! This subroutine updates the module saved variables.
    5656
    5757    USE IOIPSL, only: ju2ymds, ymds2ju, ioget_mon_len, ioget_year_len
    58    
    59     REAL, INTENT(IN) :: jD_cur ! jour courant a l'appel de la physique (jour julien)
    60     REAL, INTENT(IN) :: jH_cur ! heure courante a l'appel de la physique (jour julien)
     58    IMPLICIT NONE
     59    REAL, INTENT(IN) :: julian_date
     60
     61    jD_cur=INT(julian_date)
     62    jH_cur=julian_date-jD_cur
    6163   
    6264    CALL ju2ymds(jD_cur+jH_cur, year_cur, mth_cur, day_cur, hour)
     
    6870    days_elapsed = jD_cur - jD_1jan
    6971
    70     ! Get lenght of acutual month
     72    ! Get lenght of current month
    7173    mth_len = ioget_mon_len(year_cur,mth_cur)
    7274
     75    ! Get length of current year
    7376    year_len = ioget_year_len(year_cur)
    7477
  • LMDZ5/trunk/libf/phylmd/physiq_mod.F90

    r2421 r2422  
    1010
    1111SUBROUTINE physiq (nlon,nlev, &
    12      debut,lafin,jD_cur_,jH_cur_,pdtphys_, &
     12     debut,lafin,pdtphys_, &
    1313     paprs,pplay,pphi,pphis,presnivs, &
    1414     u,v,rot,t,qx, &
     
    2020  USE geometry_mod, ONLY: cell_area, latitude_deg, longitude_deg
    2121  USE phys_cal_mod, only: year_len, mth_len, days_elapsed, jh_1jan, year_cur, &
    22        mth_cur,jD_cur, jH_cur, jD_ref, phys_cal_update
     22       mth_cur,jD_cur, jH_cur, jD_ref
    2323  USE write_field_phy
    2424  USE dimphy
     
    2929  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
    3030  USE phystokenc_mod, ONLY: offline, phystokenc
    31   USE time_phylmdz_mod, only: raz_date, day_step_phy
     31  USE time_phylmdz_mod, only: raz_date, day_step_phy, update_time
    3232  USE vampir
    3333  USE pbl_surface_mod, ONLY : pbl_surface
     
    226226  INTEGER nlon
    227227  INTEGER nlev
    228   REAL, intent(in):: jD_cur_, jH_cur_
    229 ! JD_cur and JH_cur to be used in physics are in phys_cal_mod
    230228  REAL,INTENT(IN) :: pdtphys_
    231229! NB: pdtphys to be used in physics is in time_phylmdz_mod
     
    915913  ! Gestion calendrier : mise a jour du module phys_cal_mod
    916914  !
    917   JD_cur=JD_cur_
    918   JH_cur=JH_cur_
    919915  pdtphys=pdtphys_
    920   CALL phys_cal_update(jD_cur,jH_cur)
     916  CALL update_time(pdtphys)
    921917
    922918  !======================================================================
  • LMDZ5/trunk/libf/phylmd/time_phylmdz_mod.F90

    r2344 r2422  
    7777  END SUBROUTINE init_iteration
    7878
     79  SUBROUTINE update_time(pdtphys_)
     80  ! This subroutine updates the module saved variables.
     81  USE ioipsl, ONLY : ymds2ju
     82  USE phys_cal_mod, ONLY: phys_cal_update
     83  USE print_control_mod, ONLY: lunout
     84  IMPLICIT NONE
     85    REAL,INTENT(IN) :: pdtphys_
     86    REAL            :: julian_date
     87   
     88    ! Check if the physics timestep has changed
     89    IF ( ABS( (pdtphys-pdtphys_) / ((pdtphys+pdtphys_)/2))> 10.*EPSILON(pdtphys_)) THEN
     90       WRITE(lunout,*) "WARNING ! Physics time step changes from a call to the next",pdtphys_,pdtphys
     91       WRITE(lunout,*) "Not sure the physics parametrizations can handle this..."
     92    ENDIF
     93    pdtphys=pdtphys_
     94   
     95    ! Update elapsed time since begining of run:
     96    current_time=current_time+pdtphys
     97
     98    ! Compute corresponding Julian date and update calendar
     99    CALL ymds2ju(annee_ref,1,day_ini,start_time+current_time,julian_date)
     100    CALL phys_cal_update(julian_date)
     101   
     102  END SUBROUTINE update_time
     103
    79104END MODULE time_phylmdz_mod     
    80105
Note: See TracChangeset for help on using the changeset viewer.