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

    r4182 r4227  
    2626! -----------------
    2727! $Id$
     28! Change call to calc_zenith
     29!
     30! 4223 2019-09-10 09:20:47Z gronemeier
    2831! Corrected "Former revisions" section
    2932!
     
    227230 SUBROUTINE photolysis_simple
    228231
     232    USE palm_date_time_mod,                                                    &
     233        ONLY:  get_date_time
     234
    229235    USE radiation_model_mod,                                                   &
    230236        ONLY:  calc_zenith, cos_zenith
     
    232238    IMPLICIT NONE
    233239
    234     INTEGER(iwp) :: iphot,iav !< loop indix for photolysis reaction
    235     REAL(wp)     :: coszi     !< 1./cosine of zenith angle
     240    INTEGER(iwp) :: day_of_year  !< day of the year
     241    INTEGER(iwp) :: iav          !< loop indix for photolysis reaction
     242    INTEGER(iwp) :: iphot        !< loop indix for photolysis reaction
     243
     244    REAL(wp)     :: coszi          !< 1./cosine of zenith angle
     245    REAL(wp)     :: second_of_day  !< second of the day
    236246
    237247    DO  iphot = 1, nphot
     
    239249    ENDDO
    240250
    241     CALL calc_zenith
     251    CALL get_date_time( time_since_reference_point, &
     252                        day_of_year=day_of_year, second_of_day=second_of_day )
     253    CALL calc_zenith( day_of_year, second_of_day )
    242254
    243255    IF ( cos_zenith > 0.0_wp ) THEN
Note: See TracChangeset for help on using the changeset viewer.