Ignore:
Timestamp:
Aug 24, 2016 3:47:17 PM (8 years ago)
Author:
kanani
Message:

changes in the course of urban surface model implementation

File:
1 edited

Legend:

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

    r2001 r2007  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Added calculation of solar directional vector for new urban surface
     23! model,
     24! accounted for urban_surface model in radiation_check_parameters,
     25! correction of comments for zenith angle.
    2326!
    2427! Former revisions:
     
    114117 
    115118    USE arrays_3d,                                                             &
    116         ONLY:  dzw, hyp, pt, q, ql, zw
     119        ONLY:  dzw, hyp, pt, q, ql, zu, zw
    117120
    118121    USE cloud_parameters,                                                      &
     
    199202                radiation = .FALSE.,                  & !< flag parameter indicating whether the radiation model is used
    200203                sun_up    = .TRUE.,                   & !< flag parameter indicating whether the sun is up or down
    201                 sw_radiation = .TRUE.                   !< flag parameter indicing whether shortwave radiation shall be calculated
     204                sw_radiation = .TRUE.,                 & !< flag parameter indicing whether shortwave radiation shall be calculated
     205                sun_direction = .FALSE.                 !< flag parameter indicing whether solar direction shall be calculated
    202206
    203207
     
    227231                time_utc_init = 43200.0_wp         !< UTC time at model start (noon)
    228232
    229     REAL(wp), DIMENSION(0:0) ::  zenith        !< solar zenith angle
     233    REAL(wp), DIMENSION(0:0) ::  zenith,         & !< cosine of solar zenith angle
     234                                 sun_dir_lat,    & !< solar directional vector in latitudes
     235                                 sun_dir_lon       !< solar directional vector in longitudes
    230236
    231237    REAL(wp), DIMENSION(:,:), ALLOCATABLE :: &
     
    468474           rad_lw_cs_hr, rad_lw_cs_hr_av, rad_lw_hr, rad_lw_hr_av, rad_sw_in,  &
    469475           rad_sw_in_av, rad_sw_out, rad_sw_out_av, rad_sw_cs_hr,              &
    470            rad_sw_cs_hr_av, rad_sw_hr, rad_sw_hr_av,                           &
    471            skip_time_do_radiation, time_radiation, unscheduled_radiation_calls
     476           rad_sw_cs_hr_av, rad_sw_hr, rad_sw_hr_av, sigma_sb,                 &
     477           skip_time_do_radiation, time_radiation, unscheduled_radiation_calls,&
     478           zenith, calc_zenith, sun_direction, sun_dir_lat, sun_dir_lon,       &
     479           day_init, time_utc_init
    472480
    473481
     
    761769   
    762770       IMPLICIT NONE
     771       
     772       LOGICAL ::  urban_surface_af = .FALSE.  !< auxiliary flag used for parameter check
     773
    763774
    764775       IF ( radiation_scheme /= 'constant'   .AND.                             &
     
    805816       ENDIF
    806817
    807        IF ( topography /= 'flat' )  THEN
     818!
     819!--    The following paramter check is temporarily extended by the urban_surface
     820!--    flag, until a better solution comes up to omit this check in case of
     821!--    urban surface model is used.
     822!--    Routine get_usm_info provides the value for the urban_surface flag,
     823!--    because the value cannot be retrieved via USE due to circular dependencies
     824!--    between modules radiation_model_mod and urban_surface_mod.
     825       CALL get_usm_info( urban_surface_af )
     826       IF ( topography /= 'flat'  .AND.  .NOT.  urban_surface_af )  THEN
    808827          message_string = 'radiation scheme cannot be used ' //               &
    809828                           'in combination with  topography /= "flat"'
     
    15651584
    15661585!
    1567 !--    Calculate zenith angle
     1586!--    Calculate cosine of solar zenith angle
    15681587       zenith(0) = SIN(lat) * SIN(declination) + COS(lat) * COS(declination)      &
    15691588                                            * COS(hour_angle)
    15701589       zenith(0) = MAX(0.0_wp,zenith(0))
     1590
     1591!
     1592!--    Calculate solar directional vector
     1593       IF ( sun_direction )  THEN
     1594!--       Direction in longitudes equals to sin(solar_azimuth) * sin(zenith)
     1595          sun_dir_lon(0) = -SIN(hour_angle) * COS(declination)
     1596!--       Direction in latitues equals to cos(solar_azimuth) * sin(zenith)
     1597          sun_dir_lat(0) = SIN(declination) * COS(lat) - COS(hour_angle) &
     1598                              * COS(declination) * SIN(lat)
     1599       ENDIF
    15711600
    15721601!
Note: See TracChangeset for help on using the changeset viewer.