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

    r4196 r4227  
    2525! -----------------
    2626! $Id$
     27! Replace function date_time_string by call to get_date_time
     28!
     29! 4223 2019-09-10 09:20:47Z gronemeier
    2730! replaced rotation angle from input-netCDF file
    2831! by namelist parameter 'rotation_angle'
     
    68696872        ONLY:  revision, run_date, run_time, run_zone, runnr, version
    68706873
    6871     USE date_and_time_mod,                                                     &
    6872        ONLY:   day_of_year_init, time_utc_init
    6873 
    68746874    USE netcdf_data_input_mod,                                                 &
    68756875        ONLY:  input_file_atts
    68766876
     6877    USE palm_date_time_mod,                                                    &
     6878        ONLY:  date_time_str_len, get_date_time
     6879
    68776880    IMPLICIT NONE
    68786881
    6879     CHARACTER(LEN=23) ::  origin_time_string  !< string containing date and time of origin
     6882    CHARACTER(LEN=date_time_str_len) ::  origin_time_string  !< string containing date-time of origin
    68806883
    68816884    CHARACTER(LEN=*), INTENT(IN)  ::  data_content  !< describes the type of data in file
     
    68856888    INTEGER, INTENT(IN)  ::  ncid      !< file id
    68866889!
    6887 !-- Compose date-time string for origin_time
    6888     origin_time_string = date_time_string( day_of_year_init, time_utc_init )
     6890!-- Get date-time string for origin_time
     6891    CALL get_date_time( 0.0_wp, date_time_str=origin_time_string )
    68896892
    68906893#if defined( __netcdf )
     
    72427245 END SUBROUTINE convert_utm_to_geographic
    72437246
    7244  !------------------------------------------------------------------------------!
    7245  ! Description:
    7246  ! ------------
    7247  !> Compose string containing date and time of format 'YYYY-MM-DD hh:mm:ss ZZZ'
    7248  !> from day_of_year and second_of_day.
    7249  !------------------------------------------------------------------------------!
    7250  FUNCTION date_time_string( day_of_year, second_of_day )
    7251 
    7252     IMPLICIT NONE
    7253 
    7254     CHARACTER(LEN=1) ::  plus_minus  !< either '+' or '-'
    7255 
    7256     CHARACTER(LEN=23) ::  date_time_string  !< string containing date and time
    7257 
    7258     INTEGER(iwp) ::  day          !< day of month
    7259     INTEGER(iwp) ::  err          !< error code
    7260     INTEGER(iwp) ::  i            !< loop index
    7261     INTEGER(iwp) ::  hour         !< hour of the day
    7262     INTEGER(iwp) ::  minute       !< minute of the hour
    7263     INTEGER(iwp) ::  month        !< month of year
    7264     INTEGER(iwp) ::  year = 2019  !< year (no leap year)
    7265     INTEGER(iwp) ::  zone = 0     !< time zone
    7266 
    7267     INTEGER(iwp), INTENT(IN) ::  day_of_year  !< day of year to start with
    7268 
    7269     INTEGER, DIMENSION(12) :: days_per_month = &  !< total number of days for
    7270     (/31,28,31,30,31,30,31,31,30,31,30,31/)       !< each month (no leap year)
    7271 
    7272     REAL(wp) ::  second  !< second of the minute
    7273 
    7274     REAL(wp), INTENT(IN) ::  second_of_day  !< second of the day
    7275 
    7276 
    7277     err = 0_iwp
    7278 !
    7279 !-- Check day_of_year
    7280     IF ( day_of_year < 1_iwp .OR. day_of_year > SUM(days_per_month) )  THEN
    7281        err = err + 1_iwp
    7282     ENDIF
    7283 !
    7284 !-- Check second_of_day
    7285     IF ( second_of_day < 0.0_wp  .OR.  second_of_day > 86400.0_wp )  THEN
    7286        err = err + 2_iwp
    7287     ENDIF
    7288 !
    7289 !-- Execute only if given values are valid
    7290     IF ( err == 0_iwp )  THEN
    7291 
    7292        day = day_of_year
    7293        month = 0_iwp
    7294 
    7295        DO  i = 1, 12
    7296           day = day - days_per_month(i)
    7297           IF ( day < 0 )  THEN
    7298              day = day + days_per_month(i)
    7299              month = i
    7300              EXIT
    7301           ENDIF
    7302        ENDDO
    7303 
    7304        hour = INT( second_of_day / 3600.0_wp, KIND=iwp )
    7305 
    7306        second = second_of_day - 3600.0_wp * REAL( hour, KIND=wp )
    7307 
    7308        minute =  INT( second / 60.0_wp, KIND=iwp )
    7309 
    7310        second = second - 60.0_wp * REAL( minute, KIND=wp )
    7311 
    7312        IF ( zone < 0_iwp )  THEN
    7313           plus_minus = '-'
    7314        ELSE
    7315           plus_minus = '+'
    7316        ENDIF
    7317 
    7318        WRITE( date_time_string, 100 )                               &
    7319           year, month, day, hour, minute, INT( second, KIND=iwp ),  &
    7320           plus_minus, zone
    7321 
    7322     ELSE
    7323 !
    7324 !--   Return empty string if input is invalid
    7325       date_time_string = REPEAT( " ", LEN(date_time_string) )
    7326 
    7327     ENDIF
    7328 
    7329  100 FORMAT (I4,'-',I2.2,'-',I2.2,1X,I2.2,':',I2.2,':',I2.2,1X,A1,I2.2)
    7330 
    7331  END FUNCTION date_time_string
    7332 
    73337247 END MODULE netcdf_interface
Note: See TracChangeset for help on using the changeset viewer.