Ignore:
Timestamp:
Sep 10, 2019 6:04:34 PM (5 years ago)
Author:
gronemeier
Message:

implement new palm_date_time_mod; replaced namelist parameters time_utc_init and day_of_year_init by origin_date_time

File:
1 edited

Legend:

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

    r4182 r4227  
    2525! -----------------
    2626! $Id$
     27! implement new palm_date_time_mod
     28!
     29! 4223 2019-09-10 09:20:47Z gronemeier
    2730! Corrected "Former revisions" section
    2831!
     
    7982        ONLY:  cpu_log, log_point_s
    8083
    81     USE date_and_time_mod,                                                     &
    82         ONLY: day_of_year_init, time_utc_init
    83 
    8484    USE indices,                                                               &
    8585        ONLY:  nbgp, nzb, nzt, nysg, nyng, nxlg, nxrg
    8686
    87 
    8887    USE land_surface_model_mod,                                                &
    8988        ONLY:  lsm_energy_balance, lsm_soil_model, lsm_swap_timelevel
     89
    9090    USE pegrid
    9191
     
    9494
    9595    USE kinds
     96
     97    USE palm_date_time_mod,                                                    &
     98        ONLY:  get_date_time, seconds_per_hour
    9699
    97100    USE radiation_model_mod,                                                   &
     
    132135
    133136    INTEGER(iwp) :: current_timestep_number_spinup = 0  !< number if timestep during spinup
     137    INTEGER(iwp) :: day_of_year                         !< day of the year
    134138 
    135139    LOGICAL :: run_control_header_spinup = .FALSE.  !< flag parameter for steering whether the header information must be output
    136140
    137     REAL(wp) ::  pt_spinup   !< temporary storage of temperature
    138     REAL(wp) ::  dt_save     !< temporary storage for time step
     141    REAL(wp) ::  pt_spinup      !< temporary storage of temperature
     142    REAL(wp) ::  dt_save        !< temporary storage for time step
     143    REAL(wp) ::  second_of_day  !< second of the day
    139144                 
    140145    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_save  !< temporary storage of temperature
     
    234239!--       shifted by one hour to simulate a lag between air temperature and
    235240!--       incoming radiation
     241          CALL get_date_time( simulated_time - spinup_time - seconds_per_hour, &
     242                              day_of_year=day_of_year,                         &
     243                              second_of_day=second_of_day                      )
     244
    236245          pt_spinup = spinup_pt_mean + spinup_pt_amplitude                     &
    237              * solar_angle (time_utc_init + time_since_reference_point - 3600.0)
     246                                     * solar_angle(day_of_year, second_of_day)
    238247
    239248!
     
    546555!-- Returns the cosine of the solar zenith angle at a given time. This routine
    547556!-- is similar to that for calculation zenith (see radiation_model_mod.f90)
    548     FUNCTION solar_angle( local_time )
     557    !> @todo Load function calc_zenith of radiation model instead of
     558    !>       rewrite the function here.
     559    FUNCTION solar_angle( day_of_year, second_of_day )
    549560
    550561       USE basic_constants_and_equations_mod,                                  &
     
    559570
    560571
    561        REAL(wp) ::  solar_angle     !< cosine of the solar zenith angle
    562 
    563        REAL(wp) ::  day             !< day of the year
    564        REAL(wp) ::  declination     !< solar declination angle
    565        REAL(wp) ::  hour_angle      !< solar hour angle
    566        REAL(wp) ::  time_utc        !< current time in UTC
    567        REAL(wp), INTENT(IN) :: local_time
    568 !
    569 !--    Calculate current day and time based on the initial values and simulation
    570 !--    time
    571 
    572        day = day_of_year_init + INT(FLOOR( local_time / 86400.0_wp ), KIND=iwp)
    573        time_utc = MOD(local_time, 86400.0_wp)
    574 
    575 
     572       INTEGER(iwp), INTENT(IN) ::  day_of_year  !< day of the year
     573
     574       REAL(wp)             ::  declination      !< solar declination angle
     575       REAL(wp)             ::  hour_angle       !< solar hour angle
     576       REAL(wp), INTENT(IN) ::  second_of_day    !< current time of the day in UTC
     577       REAL(wp)             ::  solar_angle      !< cosine of the solar zenith angle
    576578!
    577579!--    Calculate solar declination and hour angle   
    578        declination = ASIN( decl_1 * SIN(decl_2 * REAL(day, KIND=wp) - decl_3) )
    579        hour_angle  = 2.0_wp * pi * (time_utc / 86400.0_wp) + lon - pi
     580       declination = ASIN( decl_1 * SIN(decl_2 * REAL(day_of_year, KIND=wp) - decl_3) )
     581       hour_angle  = 2.0_wp * pi * (second_of_day / 86400.0_wp) + lon - pi
    580582
    581583!
     
    584586                     * COS(hour_angle)
    585587
    586 
    587588    END FUNCTION solar_angle
    588589
Note: See TracChangeset for help on using the changeset viewer.