Ignore:
Timestamp:
Dec 10, 2018 9:44:36 AM (5 years ago)
Author:
moh.hefny
Message:

fix time variables during solar positions calc

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r3608 r3616  
    2828! -----------------
    2929! $Id$
     30! fix manipulation of time variables in radiation_presimulate_solar_pos
     31!
     32! 3608 2018-12-07 12:59:57Z suehring $
    3033! Bugfix radiation output
    3134!
     
    560563
    561564    USE date_and_time_mod,                                                     &
    562         ONLY:  calc_date_and_time, d_hours_day, d_seconds_hour, day_of_year,   &
    563                d_seconds_year, day_of_year_init, time_utc_init, time_utc
     565        ONLY:  calc_date_and_time, d_hours_day, d_seconds_hour, d_seconds_year,&
     566               day_of_year, d_seconds_year, day_of_month, day_of_year_init,    &
     567               init_date_and_time, month_of_year, time_utc_init, time_utc
    564568
    565569    USE indices,                                                               &
     
    79697973!------------------------------------------------------------------------------!
    79707974   SUBROUTINE radiation_presimulate_solar_pos
     7975
    79717976      IMPLICIT NONE
    79727977
    79737978      INTEGER(iwp)                              ::  it, i, j
     7979      INTEGER(iwp)                              ::  day_of_month_prev,month_of_year_prev
    79747980      REAL(wp)                                  ::  tsrp_prev
    79757981      REAL(wp)                                  ::  simulated_time_prev
     
    79897995      tsrp_prev = time_since_reference_point
    79907996      simulated_time_prev = simulated_time
     7997      day_of_month_prev = day_of_month
     7998      month_of_year_prev = month_of_year
    79917999      sun_direction = .TRUE.
    79928000
     
    80078015         CALL simulate_pos
    80088016      ENDDO
    8009 
     8017!
     8018!--   Return date and time to its original values
    80108019      time_since_reference_point = tsrp_prev
    80118020      simulated_time = simulated_time_prev
     8021      day_of_month = day_of_month_prev
     8022      month_of_year = month_of_year_prev
     8023      CALL init_date_and_time
    80128024
    80138025!--   Allocate global vars which depend on ndsidir
Note: See TracChangeset for help on using the changeset viewer.