Ignore:
Timestamp:
Oct 13, 2017 6:09:32 PM (6 years ago)
Author:
maronga
Message:

introduced new module date_and_time_mod

File:
1 edited

Legend:

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

    r2516 r2544  
    2626! -----------------
    2727! $Id$
     28! Date and time quantities are now read from date_and_time_mod. Solar constant is
     29! read from radiation_model_mod
     30!
     31! 2516 2017-10-04 11:03:04Z suehring
    2832! Remove tabs
    2933!
     
    171175        ONLY:  cpu_log, log_point, log_point_s
    172176     
     177    USE date_and_time_mod,                                                     &
     178        ONLY:  d_seconds_year, day_of_year_init, time_utc_init
     179   
    173180    USE grid_variables,                                                        &
    174181        ONLY:  dx, dy, ddx, ddy, ddx2, ddy2
     
    189196   
    190197    USE radiation_model_mod,                                                   &
    191         ONLY:  radiation, calc_zenith, zenith, day_init, time_utc_init,        &
     198        ONLY:  radiation, calc_zenith, zenith,                                 &
    192199               rad_net, rad_sw_in, rad_lw_in, rad_sw_out, rad_lw_out,          &
    193                sigma_sb, sun_direction, sun_dir_lat, sun_dir_lon,              &
    194                force_radiation_call
     200               sigma_sb, solar_constant, sun_direction, sun_dir_lat,           &
     201               sun_dir_lon, force_radiation_call
    195202
    196203    USE statistics,                                                            &
     
    17571764    SUBROUTINE usm_calc_diffusion_radiation
    17581765   
    1759         REAL(wp), PARAMETER                          ::  sol_const = 1367.0_wp   !< solar conbstant
    17601766        REAL(wp), PARAMETER                          :: lowest_solarUp = 0.1_wp  !< limit the sun elevation to protect stability of the calculation
    17611767        INTEGER(iwp)                                 :: i, j
    1762         REAL(wp), PARAMETER                          ::  year_seconds = 86400._wp * 365._wp
    17631768        REAL(wp)                                     ::  year_angle              !< angle
    17641769        REAL(wp)                                     ::  etr                     !< extraterestrial radiation
     
    17701775       
    17711776!--     Calculate current day and time based on the initial values and simulation time
    1772         year_angle = ((day_init*86400) + time_utc_init+time_since_reference_point) &
    1773                        / year_seconds * 2.0_wp * pi
    1774        
    1775         etr = sol_const * (1.00011_wp +                                            &
    1776                           0.034221_wp * cos(year_angle) +                          &
    1777                           0.001280_wp * sin(year_angle) +                          &
    1778                           0.000719_wp * cos(2.0_wp * year_angle) +                 &
     1777        year_angle = ( (day_of_year_init * 86400) + time_utc_init              &
     1778                        + time_since_reference_point )  * d_seconds_year       &
     1779                        * 2.0_wp * pi
     1780       
     1781        etr = solar_constant * (1.00011_wp +                                   &
     1782                          0.034221_wp * cos(year_angle) +                      &
     1783                          0.001280_wp * sin(year_angle) +                      &
     1784                          0.000719_wp * cos(2.0_wp * year_angle) +             &
    17791785                          0.000077_wp * sin(2.0_wp * year_angle))
    17801786       
Note: See TracChangeset for help on using the changeset viewer.