Changeset 4364 for palm/trunk/SOURCE/salsa_mod.f90
- Timestamp:
- Jan 8, 2020 2:12:31 AM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/salsa_mod.f90
r4360 r4364 26 26 ! ----------------- 27 27 ! $Id$ 28 ! Set time coordinate in the input data relative to origin_time rather than to 29 ! 00:00:00 UTC 30 ! 31 ! 4360 2020-01-07 11:25:50Z suehring 28 32 ! Introduction of wall_flags_total_0, which currently sets bits based on static 29 33 ! topography information used in wall_flags_static_0 … … 526 530 REAL(wp) :: ocsv_init = nclim !< Init value for semi-volatile organic gases 527 531 REAL(wp) :: rhlim = 1.20_wp !< RH limit in %/100. Prevents unrealistical RH 528 REAL(wp) :: time_utc_init !< time in seconds-of-day of origin_date_time529 532 REAL(wp) :: skip_time_do_salsa = 0.0_wp !< Starting time of SALSA (s) 530 533 ! … … 8579 8582 SUBROUTINE salsa_emission_update 8580 8583 8581 USE palm_date_time_mod, &8582 ONLY: get_date_time8583 8584 8584 IMPLICIT NONE 8585 8585 … … 8587 8587 8588 8588 IF ( time_since_reference_point >= skip_time_do_salsa ) THEN 8589 !8590 !-- Get time_utc_init from origin_date_time8591 CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )8592 8589 8593 8590 IF ( next_aero_emission_update <= & 8594 MAX( time_since_reference_point, 0.0_wp ) + time_utc_init) THEN8591 MAX( time_since_reference_point, 0.0_wp ) ) THEN 8595 8592 CALL salsa_emission_setup( .FALSE. ) 8596 8593 ENDIF 8597 8594 8598 8595 IF ( next_gas_emission_update <= & 8599 MAX( time_since_reference_point, 0.0_wp ) + time_utc_init) THEN8596 MAX( time_since_reference_point, 0.0_wp ) ) THEN 8600 8597 IF ( salsa_emission_mode == 'read_from_file' .AND. .NOT. salsa_gases_from_chem ) & 8601 8598 THEN … … 9143 9140 ELSEIF ( aero_emission_att%lod == 2 ) THEN 9144 9141 ! 9145 !-- Get time_utc_init from origin_date_time 9146 CALL get_date_time( 0.0_wp, second_of_day = time_utc_init ) 9147 ! 9148 !-- Obtain time index for current point in time. Note, the time coordinate in the input 9149 !-- file is relative to time_utc_init. 9150 aero_emission_att%tind = MINLOC( ABS( aero_emission_att%time - ( & 9151 time_utc_init + MAX( time_since_reference_point,& 9152 0.0_wp) ) ), DIM = 1 ) - 1 9142 !-- Obtain time index for current point in time. 9143 aero_emission_att%tind = MINLOC( ABS( aero_emission_att%time - & 9144 MAX( time_since_reference_point, 0.0_wp ) ), & 9145 DIM = 1 ) - 1 9153 9146 ! 9154 9147 !-- Allocate the data input array always before reading in the data and deallocate after … … 9653 9646 ELSEIF ( lod_gas_emissions == 2 ) THEN 9654 9647 ! 9655 !-- Get time_utc_init from origin_date_time 9656 CALL get_date_time( 0.0_wp, second_of_day = time_utc_init ) 9657 ! 9658 !-- Obtain time index for current point in time. Note, the time coordinate in the input file is 9659 !-- relative to time_utc_init. 9660 chem_emission_att%i_hour = MINLOC( ABS( gas_emission_time - ( time_utc_init + & 9661 MAX( time_since_reference_point, 0.0_wp) ) ), DIM = 1 ) - 1 9648 !-- Obtain time index for current point in time. 9649 chem_emission_att%i_hour = MINLOC( ABS( gas_emission_time - & 9650 MAX( time_since_reference_point, 0.0_wp ) ), DIM = 1 ) - 1 9662 9651 ! 9663 9652 !-- Allocate the data input array always before reading in the data and deallocate after (NOTE … … 12245 12234 !-- Determine interpolation factor and limit it to 1. This is because t+dt can slightly exceed 12246 12235 !-- time(tind_p) before boundary data is updated again. 12247 fac_dt = ( time_utc_init + time_since_reference_point - & 12248 salsa_nest_offl%time(salsa_nest_offl%tind) + dt_3d ) / & 12236 fac_dt = ( time_since_reference_point - salsa_nest_offl%time(salsa_nest_offl%tind) + dt_3d ) / & 12249 12237 ( salsa_nest_offl%time(salsa_nest_offl%tind_p) - & 12250 12238 salsa_nest_offl%time(salsa_nest_offl%tind) ) … … 12532 12520 nmass_bins = nbins_aerosol * ncomponents_mass 12533 12521 ! 12534 !-- Get time_utc_init from origin_date_time12535 CALL get_date_time( 0.0_wp, second_of_day = time_utc_init )12536 !12537 12522 !-- Allocate arrays for reading boundary values. Arrays will incorporate 2 time levels in order to 12538 12523 !-- interpolate in between. … … 12580 12565 !-- input is only required for the 3D simulation, not for the soil/wall spinup. However, as the 12581 12566 !-- spinup time is added to the end_time, this must be considered here. 12582 IF ( end_time - spinup_time > & 12583 salsa_nest_offl%time(salsa_nest_offl%nt-1) - time_utc_init ) THEN 12567 IF ( end_time - spinup_time > salsa_nest_offl%time(salsa_nest_offl%nt-1) ) THEN 12584 12568 message_string = 'end_time of the simulation exceeds the time dimension in the dynamic'//& 12585 12569 ' input file.' … … 12587 12571 ENDIF 12588 12572 12589 IF ( salsa_nest_offl%time(0) /= time_utc_init) THEN12590 message_string = 'Offline nesting: time dimension must start at time_utc_init.'12573 IF ( salsa_nest_offl%time(0) /= 0.0_wp ) THEN 12574 message_string = 'Offline nesting: time dimension must start at 0.0.' 12591 12575 CALL message( 'salsa_nesting_offl_init', 'PA0691', 1, 2, 0, 6, 0 ) 12592 12576 ENDIF … … 12756 12740 !-- Check if dynamic driver data input is required. 12757 12741 IF ( salsa_nest_offl%time(salsa_nest_offl%tind_p) <= MAX( time_since_reference_point, 0.0_wp) & 12758 + time_utc_init.OR. .NOT. salsa_nest_offl%init ) THEN12742 .OR. .NOT. salsa_nest_offl%init ) THEN 12759 12743 CONTINUE 12760 12744 ! … … 12765 12749 ! 12766 12750 !-- Obtain time index for current point in time. 12767 salsa_nest_offl%tind = MINLOC( ABS( salsa_nest_offl%time - ( time_utc_init +&12768 MAX( time_since_reference_point, 0.0_wp)) ), DIM = 1 ) - 112751 salsa_nest_offl%tind = MINLOC( ABS( salsa_nest_offl%time - & 12752 MAX( time_since_reference_point, 0.0_wp ) ), DIM = 1 ) - 1 12769 12753 salsa_nest_offl%tind_p = salsa_nest_offl%tind + 1 12770 12754 !
Note: See TracChangeset
for help on using the changeset viewer.