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/biometeorology_mod.f90

    r4182 r4227  
    2727! -----------------
    2828! $Id$
     29! implement new palm_date_time_mod
     30!
     31! 4223 2019-09-10 09:20:47Z gronemeier
    2932! Corrected "Former revisions" section
    3033!
     
    140143               surface_pressure
    141144
    142     USE date_and_time_mod,                                                     &
    143         ONLY:  calc_date_and_time, day_of_year, time_utc
    144 
    145145    USE grid_variables,                                                        &
    146146        ONLY:  ddx, dx, ddy, dy
     
    155155        ONLY:  netcdf_data_input_uvem, uvem_projarea_f, uvem_radiance_f,       &
    156156               uvem_irradiance_f, uvem_integration_f, building_obstruction_f
     157
     158    USE palm_date_time_mod,                                                    &
     159        ONLY:  get_date_time
    157160!
    158161!-- Import radiation model to obtain input for mean radiant temperature
     
    42264229!-- UVEM specific subroutines
    42274230
    4228 !---------------------------------------------------------------------------------------------------------------------!
     4231!--------------------------------------------------------------------------------------------------!
    42294232! Description:
    42304233! ------------
    42314234!> Module-specific routine for new module
    4232 !---------------------------------------------------------------------------------------------------------------------!
     4235!--------------------------------------------------------------------------------------------------!
    42334236 SUBROUTINE uvem_solar_position
    4234    
    4235     USE date_and_time_mod,                                                                                            &
    4236        ONLY:  calc_date_and_time, day_of_year, time_utc
    4237    
    4238     USE control_parameters,                                                                                           &
    4239        ONLY:  latitude, longitude   
     4237
     4238    USE control_parameters,                                                                        &
     4239       ONLY:  latitude, longitude, time_since_reference_point
    42404240
    42414241    IMPLICIT NONE
    4242    
    4243    
    4244     REAL(wp) ::  alpha       = 0.0_wp   !< solar azimuth angle in radiant   
    4245     REAL(wp) ::  doy_r       = 0.0_wp   !< real format of day_of_year           
    4246     REAL(wp) ::  declination = 0.0_wp   !< declination
    4247     REAL(wp) ::  dtor        = 0.0_wp   !< factor to convert degree to radiant
    4248     REAL(wp) ::  js          = 0.0_wp   !< parameter for solar position calculation
    4249     REAL(wp) ::  lat         = 52.39_wp !< latitude
    4250     REAL(wp) ::  lon         = 9.7_wp   !< longitude       
    4251     REAL(wp) ::  thetar      = 0.0_wp   !< angle for solar zenith angle calculation
    4252     REAL(wp) ::  thetasr     = 0.0_wp   !< angle for solar azimuth angle calculation   
    4253     REAL(wp) ::  zgl         = 0.0_wp   !< calculated exposure by direct beam   
    4254     REAL(wp) ::  woz         = 0.0_wp   !< calculated exposure by diffuse radiation
    4255     REAL(wp) ::  wsp         = 0.0_wp   !< calculated exposure by direct beam   
    4256    
    4257 
    4258     CALL calc_date_and_time
    4259     doy_r = real(day_of_year)   
     4242
     4243    INTEGER(iwp) ::  day_of_year = 0       !< day of year
     4244
     4245    REAL(wp) ::  alpha         = 0.0_wp    !< solar azimuth angle in radiant   
     4246    REAL(wp) ::  declination   = 0.0_wp    !< declination
     4247    REAL(wp) ::  dtor          = 0.0_wp    !< factor to convert degree to radiant
     4248    REAL(wp) ::  js            = 0.0_wp    !< parameter for solar position calculation
     4249    REAL(wp) ::  lat           = 52.39_wp  !< latitude
     4250    REAL(wp) ::  lon           = 9.7_wp    !< longitude
     4251    REAL(wp) ::  second_of_day = 0.0_wp    !< current second of the day
     4252    REAL(wp) ::  thetar        = 0.0_wp    !< angle for solar zenith angle calculation
     4253    REAL(wp) ::  thetasr       = 0.0_wp    !< angle for solar azimuth angle calculation   
     4254    REAL(wp) ::  zgl           = 0.0_wp    !< calculated exposure by direct beam   
     4255    REAL(wp) ::  woz           = 0.0_wp    !< calculated exposure by diffuse radiation
     4256    REAL(wp) ::  wsp           = 0.0_wp    !< calculated exposure by direct beam   
     4257
     4258
     4259    CALL get_date_time( time_since_reference_point, &
     4260                        day_of_year = day_of_year, second_of_day = second_of_day )
    42604261    dtor = pi / 180.0_wp
    42614262    lat = latitude
     
    42634264!
    42644265!-- calculation of js, necessary for calculation of equation of time (zgl) :
    4265     js=  72.0_wp * ( doy_r + ( time_utc / 86400.0_wp ) ) / 73.0_wp
     4266    js=  72.0_wp * ( REAL( day_of_year, KIND=wp ) + ( second_of_day / 86400.0_wp ) ) / 73.0_wp
    42664267!
    42674268!-- calculation of equation of time (zgl):
     
    42704271!
    42714272!-- calculation of apparent solar time woz:
    4272     woz = ( ( time_utc / 3600.0_wp ) - ( 4.0_wp * ( 15.0_wp - lon ) ) / 60.0_wp ) + ( zgl / 60.0_wp )
     4273    woz = ( ( second_of_day / 3600.0_wp ) - ( 4.0_wp * ( 15.0_wp - lon ) ) / 60.0_wp ) + ( zgl / 60.0_wp )
    42734274!
    42744275!-- calculation of hour angle (wsp):
Note: See TracChangeset for help on using the changeset viewer.