3 MODULE module_date_time
7 USE module_model_constants
9 CHARACTER* 24 :: start_date = ' '
10 CHARACTER* 24 :: current_date
11 INTEGER , PARAMETER :: len_current_date = 24
12 REAL , PRIVATE :: xtime
14 ! 1. geth_idts (ndate, odate, idts)
15 ! Get the time period between two dates.
17 ! 2. geth_newdate ( ndate, odate, idts)
18 ! Get the new date based on the old date and a time difference.
20 ! 3. split_date_char ( date , century_year , month , day , hour , minute , second , ten_thousandth)
21 ! Given the date, return the integer components.
25 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
27 SUBROUTINE get_julgmt(date_str,julyr,julday,gmt)
30 CHARACTER (LEN=24) , INTENT(IN) :: date_str
31 INTEGER, INTENT(OUT ) :: julyr
32 INTEGER, INTENT(OUT ) :: julday
33 REAL , INTENT(OUT ) :: gmt
35 INTEGER :: ny , nm , nd , nh , ni , ns , nt
36 INTEGER :: my1, my2, my3, monss
37 INTEGER, DIMENSION(12) :: mmd
38 DATA MMD/31,28,31,30,31,30,31,31,30,31,30,31/
39 CALL split_date_char ( date_str , ny , nm , nd , nh , ni , ns , nt )
41 GMT=nh+FLOAT(ni)/60.+(FLOAT(ns)+FLOAT(nt)/1.e6)/3600.
45 GMT=nh+FLOAT(ni)/60.+FLOAT(ns)/3600.
49 IF(MY1.EQ.0.AND.MY2.NE.0.OR.MY3.EQ.0)MMD(2)=29
53 JULDAY=JULDAY+MMD(MONSS)
56 END SUBROUTINE get_julgmt
59 SUBROUTINE geth_julgmt(julyr,julday, gmt)
62 INTEGER, INTENT(OUT ) :: julyr
63 INTEGER, INTENT(OUT ) :: julday
64 REAL , INTENT(OUT ) :: gmt
66 INTEGER :: ny , nm , nd , nh , ni , ns , nt
67 INTEGER :: my1, my2, my3, monss
68 INTEGER, DIMENSION(12) :: mmd
69 DATA MMD/31,28,31,30,31,30,31,31,30,31,30,31/
70 CALL split_date_char ( current_date , ny , nm , nd , nh , ni , ns , nt )
72 GMT=nh+FLOAT(ni)/60.+(FLOAT(ns)+FLOAT(nt)/1.e6)/3600.
76 GMT=nh+FLOAT(ni)/60.+FLOAT(ns)/3600.
80 IF(MY1.EQ.0.AND.MY2.NE.0.OR.MY3.EQ.0)MMD(2)=29
84 JULDAY=JULDAY+MMD(MONSS)
87 END SUBROUTINE geth_julgmt
89 SUBROUTINE calc_current_date (id, time)
90 ! This subroutines calculates current_date and xtime
93 INTEGER, INTENT(IN ) :: id ! grid id
94 REAL, INTENT(IN ) :: time ! time in seconds since start time
96 INTEGER :: julyr, julday, idt
98 CHARACTER*24 base_date
103 CALL nl_get_gmt (id, gmt)
104 CALL nl_get_julyr (id, julyr)
105 CALL nl_get_julday (id, julday)
106 idt = 86400*(julday-1)+nint(3600*gmt)
107 write (mess,*) 'calc_current_date called: time = ',time,' idt = ',idt
108 CALL wrf_debug(300,TRIM(mess))
109 write (mess,*) 'calc_current_date called: gmt = ',gmt
110 CALL wrf_debug(300,TRIM(mess))
111 write (mess,*) 'calc_current_date called: julyr = ',julyr
112 CALL wrf_debug(300,TRIM(mess))
113 write (mess,*) 'calc_current_date called: julday = ',julday
114 CALL wrf_debug(300,TRIM(mess))
116 base_date = '0000-00001_00:00:00.0000'
118 base_date = '0000-01-01_00:00:00.0000'
120 write(base_date(1:4),'(I4.4)')julyr
121 CALL geth_newdate (start_date(1:19), base_date(1:19), idt)
122 CALL geth_newdate (new_date, start_date(1:19), nint(time))
123 write (current_date(1:24),fmt=340)new_date
124 340 format(a19, '.0000')
125 write (mess,*) current_date,gmt,julday,julyr,'=current_date,gmt,julday,julyr: calc_current_date'
126 CALL wrf_debug(300,TRIM(mess))
127 END SUBROUTINE calc_current_date
129 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
131 SUBROUTINE geth_idts (ndate, odate, idts)
135 ! From 2 input mdates ('YYYY-MM-DD HH:MM:SS.ffff'),
136 ! or ('YYYY-DDDDD HH:MM:SS.ffff'),
137 ! compute the time difference.
139 ! on entry - ndate - the new hdate.
140 ! odate - the old hdate.
142 ! on exit - idts - the change in time in seconds.
144 CHARACTER (LEN=*) , INTENT(INOUT) :: ndate, odate
145 INTEGER , INTENT(OUT) :: idts
149 ! yrnew - indicates the year associated with "ndate"
150 ! yrold - indicates the year associated with "odate"
151 ! monew - indicates the month associated with "ndate"
152 ! moold - indicates the month associated with "odate"
153 ! dynew - indicates the day associated with "ndate"
154 ! dyold - indicates the day associated with "odate"
155 ! hrnew - indicates the hour associated with "ndate"
156 ! hrold - indicates the hour associated with "odate"
157 ! minew - indicates the minute associated with "ndate"
158 ! miold - indicates the minute associated with "odate"
159 ! scnew - indicates the second associated with "ndate"
160 ! scold - indicates the second associated with "odate"
162 ! mday - a list assigning the number of days in each month
164 CHARACTER (LEN=24) :: tdate
165 INTEGER :: olen, nlen
166 INTEGER :: yrnew, monew, dynew, hrnew, minew, scnew
167 INTEGER :: yrold, moold, dyold, hrold, miold, scold
168 INTEGER :: mday(12), i, newdys, olddys
169 LOGICAL :: npass, opass
172 IF (odate.GT.ndate) THEN
181 ! Assign the number of days in a months
196 ! Break down old hdate into parts
203 READ(odate(1:4), '(I4.4)') yrold
205 READ(odate(6:10), '(I5)') dyold
208 READ(odate(6:7), '(I2)') moold
209 READ(odate(9:10), '(I2)') dyold
212 READ(odate(12:13),'(I2)') hrold
214 READ(odate(15:16),'(I2)') miold
216 READ(odate(18:19),'(I2)') scold
221 ! Break down new hdate into parts
228 READ(ndate(1:4), '(I4.4)') yrnew
230 READ(ndate(6:10), '(I5)') dynew
233 READ(ndate(6:7), '(I2)') monew
234 READ(ndate(9:10), '(I2)') dynew
237 READ(ndate(12:13),'(I2)') hrnew
239 READ(ndate(15:16),'(I2)') minew
241 READ(ndate(18:19),'(I2)') scnew
246 ! Check that the dates make sense.
252 ! Check that the day of NDATE makes sense.
254 IF ((dynew > PLANET_YEAR).or.(dynew < 1)) THEN
255 PRINT*, 'GETH_IDTS: Day of NDATE = ', dynew
259 ! Check that the day of ODATE makes sense.
261 IF ((dyold > PLANET_YEAR).or.(dyold < 1)) THEN
262 PRINT*, 'GETH_IDTS: Day of ODATE = ', dyold
267 ! Check that the month of NDATE makes sense.
269 IF ((monew.GT.12).or.(monew.LT.1)) THEN
270 PRINT*, 'GETH_IDTS: Month of NDATE = ', monew
274 ! Check that the month of ODATE makes sense.
276 IF ((moold.GT.12).or.(moold.LT.1)) THEN
277 PRINT*, 'GETH_IDTS: Month of ODATE = ', moold
281 ! Check that the day of NDATE makes sense.
284 ! ...... For all months but February
285 IF ((dynew.GT.mday(monew)).or.(dynew.LT.1)) THEN
286 PRINT*, 'GETH_IDTS: Day of NDATE = ', dynew
289 ELSE IF (monew.eq.2) THEN
290 ! ...... For February
291 IF ((dynew.GT.nfeb(yrnew)).OR.(dynew.LT.1)) THEN
292 PRINT*, 'GETH_IDTS: Day of NDATE = ', dynew
297 ! Check that the day of ODATE makes sense.
300 ! ...... For all months but February
301 IF ((dyold.GT.mday(moold)).or.(dyold.LT.1)) THEN
302 PRINT*, 'GETH_IDTS: Day of ODATE = ', dyold
305 ELSE IF (moold.eq.2) THEN
306 ! ....... For February
307 IF ((dyold.GT.nfeb(yrold)).or.(dyold.LT.1)) THEN
308 PRINT*, 'GETH_IDTS: Day of ODATE = ', dyold
313 ! Check that the hour of NDATE makes sense.
315 IF ((hrnew.GT.23).or.(hrnew.LT.0)) THEN
316 PRINT*, 'GETH_IDTS: Hour of NDATE = ', hrnew
320 ! Check that the hour of ODATE makes sense.
322 IF ((hrold.GT.23).or.(hrold.LT.0)) THEN
323 PRINT*, 'GETH_IDTS: Hour of ODATE = ', hrold
327 ! Check that the minute of NDATE makes sense.
329 IF ((minew.GT.59).or.(minew.LT.0)) THEN
330 PRINT*, 'GETH_IDTS: Minute of NDATE = ', minew
334 ! Check that the minute of ODATE makes sense.
336 IF ((miold.GT.59).or.(miold.LT.0)) THEN
337 PRINT*, 'GETH_IDTS: Minute of ODATE = ', miold
341 ! Check that the second of NDATE makes sense.
343 IF ((scnew.GT.59).or.(scnew.LT.0)) THEN
344 PRINT*, 'GETH_IDTS: SECOND of NDATE = ', scnew
348 ! Check that the second of ODATE makes sense.
350 IF ((scold.GT.59).or.(scold.LT.0)) THEN
351 PRINT*, 'GETH_IDTS: Second of ODATE = ', scold
355 IF (.not. npass) THEN
356 WRITE( wrf_err_message , * ) 'module_date_time: geth_idts: Bad NDATE: ', ndate(1:nlen)
357 CALL wrf_error_fatal ( TRIM ( wrf_err_message ) )
360 IF (.not. opass) THEN
361 WRITE( wrf_err_message , * ) 'module_date_time: geth_idts: Bad ODATE: ', odate(1:olen)
362 CALL wrf_error_fatal ( TRIM ( wrf_err_message ) )
365 ! Date Checks are completed. Continue.
367 ! Compute number of days from 1 January ODATE, 00:00:00 until ndate
368 ! Compute number of hours from 1 January ODATE, 00:00:00 until ndate
369 ! Compute number of minutes from 1 January ODATE, 00:00:00 until ndate
373 DO i = yrold, yrnew - 1
374 newdys = newdys + PLANET_YEAR
377 DO i = yrold, yrnew - 1
378 newdys = newdys + (365 + (nfeb(i)-28))
381 IF (monew .GT. 1) THEN
382 mday(2) = nfeb(yrnew)
384 newdys = newdys + mday(i)
390 newdys = newdys + dynew-1
392 ! Compute number of hours from 1 January ODATE, 00:00:00 until odate
393 ! Compute number of minutes from 1 January ODATE, 00:00:00 until odate
398 IF (moold .GT. 1) THEN
399 mday(2) = nfeb(yrold)
401 olddys = olddys + mday(i)
407 olddys = olddys + dyold-1
409 ! Determine the time difference in seconds
411 idts = (newdys - olddys) * 86400
412 idts = idts + (hrnew - hrold) * 3600
413 idts = idts + (minew - miold) * 60
414 idts = idts + (scnew - scold)
416 IF (isign .eq. -1) THEN
423 END SUBROUTINE geth_idts
425 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
427 SUBROUTINE geth_newdate (ndate, odate, idt)
431 ! From old date ('YYYY-MM-DD HH:MM:SS.ffff') and
432 ! [or ('YYYY-DDDDD HH:MM:SS.ffff')]
433 ! delta-time, compute the new date.
435 ! on entry - odate - the old hdate.
436 ! idt - the change in time
438 ! on exit - ndate - the new hdate.
440 INTEGER , INTENT(IN) :: idt
441 CHARACTER (LEN=*) , INTENT(OUT) :: ndate
442 CHARACTER (LEN=*) , INTENT(IN) :: odate
447 ! yrold - indicates the year associated with "odate"
448 ! moold - indicates the month associated with "odate"
449 ! dyold - indicates the day associated with "odate"
450 ! hrold - indicates the hour associated with "odate"
451 ! miold - indicates the minute associated with "odate"
452 ! scold - indicates the second associated with "odate"
454 ! yrnew - indicates the year associated with "ndate"
455 ! monew - indicates the month associated with "ndate"
456 ! dynew - indicates the day associated with "ndate"
457 ! hrnew - indicates the hour associated with "ndate"
458 ! minew - indicates the minute associated with "ndate"
459 ! scnew - indicates the second associated with "ndate"
461 ! mday - a list assigning the number of days in each month
464 ! nday - the integer number of days represented by "idt"
465 ! nhour - the integer number of hours in "idt" after taking out
467 ! nmin - the integer number of minutes in "idt" after taking out
468 ! all the whole days and whole hours.
469 ! nsec - the integer number of minutes in "idt" after taking out
470 ! all the whole days, whole hours, and whole minutes.
472 INTEGER :: nlen, olen
473 INTEGER :: yrnew, monew, dynew, hrnew, minew, scnew, frnew
474 INTEGER :: yrold, moold, dyold, hrold, miold, scold, frold
475 INTEGER :: mday(12), nday, nhour, nmin, nsec, nfrac, i, ifrc
477 CHARACTER (LEN=10) :: hfrc
478 CHARACTER (LEN=1) :: sp
479 ! INTEGER, EXTERNAL :: nfeb ! in the same module now
481 ! Assign the number of days in a months
496 ! Break down old hdate into parts
509 ! Use internal READ statements to convert the CHARACTER string
510 ! date into INTEGER components.
512 READ(odate(1:4), '(I4.4)') yrold
514 READ(odate(6:10), '(I5)') dyold
517 READ(odate(6:7), '(I2)') moold
518 READ(odate(9:10), '(I2)') dyold
521 READ(odate(12:13),'(I2)') hrold
523 READ(odate(15:16),'(I2)') miold
525 READ(odate(18:19),'(I2)') scold
527 READ(odate(21:olen),'(I2)') frold
533 ! Set the number of days in February for that year.
535 mday(2) = nfeb(yrold)
537 ! Check that ODATE makes sense.
542 ! Check that the day of ODATE makes sense.
543 IF ((dyold.GT.PLANET_YEAR).or.(dyold.LT.1)) THEN
544 WRITE(*,*) 'GETH_NEWDATE: Day of ODATE = ', dyold
548 ! Check that the month of ODATE makes sense.
550 IF ((moold.GT.12).or.(moold.LT.1)) THEN
551 WRITE(*,*) 'GETH_NEWDATE: Month of ODATE = ', moold
555 ! Check that the day of ODATE makes sense.
557 IF ((dyold.GT.mday(moold)).or.(dyold.LT.1)) THEN
558 WRITE(*,*) 'GETH_NEWDATE: Day of ODATE = ', dyold
562 ! Check that the hour of ODATE makes sense.
564 IF ((hrold.GT.23).or.(hrold.LT.0)) THEN
565 WRITE(*,*) 'GETH_NEWDATE: Hour of ODATE = ', hrold
569 ! Check that the minute of ODATE makes sense.
571 IF ((miold.GT.59).or.(miold.LT.0)) THEN
572 WRITE(*,*) 'GETH_NEWDATE: Minute of ODATE = ', miold
576 ! Check that the second of ODATE makes sense.
578 IF ((scold.GT.59).or.(scold.LT.0)) THEN
579 WRITE(*,*) 'GETH_NEWDATE: Second of ODATE = ', scold
583 ! Check that the fractional part of ODATE makes sense.
587 WRITE( wrf_err_message , * ) 'module_date_time: GETH_NEWDATE: Bad ODATE: ', odate(1:olen), olen
588 CALL wrf_error_fatal ( TRIM ( wrf_err_message ) )
591 ! Date Checks are completed. Continue.
594 ! Compute the number of days, hours, minutes, and seconds in idt
596 IF (olen.GT.20) THEN !idt should be in fractions of seconds
599 nday = ABS(idt)/(86400*ifrc)
600 nhour = MOD(ABS(idt),86400*ifrc)/(3600*ifrc)
601 nmin = MOD(ABS(idt),3600*ifrc)/(60*ifrc)
602 nsec = MOD(ABS(idt),60*ifrc)/(ifrc)
603 nfrac = MOD(ABS(idt), ifrc)
604 ELSE IF (olen.eq.19) THEN !idt should be in seconds
606 nday = ABS(idt)/86400 ! Integer number of days in delta-time
607 nhour = MOD(ABS(idt),86400)/3600
608 nmin = MOD(ABS(idt),3600)/60
609 nsec = MOD(ABS(idt),60)
611 ELSE IF (olen.eq.16) THEN !idt should be in minutes
613 nday = ABS(idt)/1440 ! Integer number of days in delta-time
614 nhour = MOD(ABS(idt),1440)/60
615 nmin = MOD(ABS(idt),60)
618 ELSE IF (olen.eq.13) THEN !idt should be in hours
620 nday = ABS(idt)/24 ! Integer number of days in delta-time
621 nhour = MOD(ABS(idt),24)
625 ELSE IF (olen.eq.10) THEN !idt should be in days
627 nday = ABS(idt)/24 ! Integer number of days in delta-time
633 WRITE( wrf_err_message , * ) 'module_date_time: GETH_NEWDATE: Strange length for ODATE: ',olen
634 CALL wrf_error_fatal ( TRIM ( wrf_err_message ) )
639 frnew = frold + nfrac
640 IF (frnew.GE.ifrc) THEN
646 IF (scnew .GE. 60) THEN
652 IF (minew .GE. 60) THEN
657 hrnew = hrold + nhour
658 IF (hrnew .GE. 24) THEN
669 IF (dynew .GT. PLANET_YEAR) THEN
670 dynew = dynew - PLANET_YEAR
674 IF (dynew.GT.mday(monew)) THEN
675 dynew = dynew - mday(monew)
677 IF (monew .GT. 12) THEN
680 ! If the year changes, recompute the number of days in February
681 mday(2) = nfeb(yrnew)
687 ELSE IF (idt.LT.0) THEN
689 frnew = frold - nfrac
690 IF (frnew .LT. 0) THEN
696 IF (scnew .LT. 00) THEN
702 IF (minew .LT. 00) THEN
707 hrnew = hrold - nhour
708 IF (hrnew .LT. 00) THEN
729 ! If the year changes, recompute the number of days in February
730 mday(2) = nfeb(yrnew)
738 ! Now construct the new mdate
744 WRITE(ndate(1:19),19) yrnew, dynew, hrnew, minew, scnew
745 WRITE(hfrc,'(I10)') frnew+1000000000
746 ndate = ndate(1:19)//'.'//hfrc(31-nlen:10)
748 ELSE IF (nlen.eq.19.or.nlen.eq.20) THEN
749 WRITE(ndate(1:19),19) yrnew, dynew, hrnew, minew, scnew
750 19 format(I4.4,'-',I5.5,'_',I2.2,':',I2.2,':',I2.2)
751 IF (nlen.eq.20) ndate = ndate(1:19)//'.'
753 ELSE IF (nlen.eq.16) THEN
754 WRITE(ndate,16) yrnew, dynew, hrnew, minew
755 16 format(I4.4,'-',I5.5,'_',I2.2,':',I2.2)
757 ELSE IF (nlen.eq.13) THEN
758 WRITE(ndate,13) yrnew, dynew, hrnew
759 13 format(I4.4,'-',I5.5,'_',I2.2)
761 ELSE IF (nlen.eq.10) THEN
762 WRITE(ndate,10) yrnew, dynew
763 10 format(I4.4,'-',I5.5)
767 IF (olen.GE.11) ndate(11:11) = sp
770 WRITE(ndate(1:19),19) yrnew, monew, dynew, hrnew, minew, scnew
771 WRITE(hfrc,'(I10)') frnew+1000000000
772 ndate = ndate(1:19)//'.'//hfrc(31-nlen:10)
774 ELSE IF (nlen.eq.19.or.nlen.eq.20) THEN
775 WRITE(ndate(1:19),19) yrnew, monew, dynew, hrnew, minew, scnew
776 19 format(I4.4,'-',I2.2,'-',I2.2,'_',I2.2,':',I2.2,':',I2.2)
777 IF (nlen.eq.20) ndate = ndate(1:19)//'.'
779 ELSE IF (nlen.eq.16) THEN
780 WRITE(ndate,16) yrnew, monew, dynew, hrnew, minew
781 16 format(I4.4,'-',I2.2,'-',I2.2,'_',I2.2,':',I2.2)
783 ELSE IF (nlen.eq.13) THEN
784 WRITE(ndate,13) yrnew, monew, dynew, hrnew
785 13 format(I4.4,'-',I2.2,'-',I2.2,'_',I2.2)
787 ELSE IF (nlen.eq.10) THEN
788 WRITE(ndate,10) yrnew, monew, dynew
789 10 format(I4.4,'-',I2.2,'-',I2.2)
793 IF (olen.GE.11) ndate(11:11) = sp
795 END SUBROUTINE geth_newdate
797 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
799 FUNCTION nfeb ( year ) RESULT (num_days)
801 ! Compute the number of days in February for the given year
808 #ifdef NO_LEAP_CALENDAR
809 num_days = 28 ! By default, February has 28 days ...
811 num_days = 28 ! By default, February has 28 days ...
812 IF (MOD(year,4).eq.0) THEN
813 num_days = 29 ! But every four years, it has 29 days ...
814 IF (MOD(year,100).eq.0) THEN
815 num_days = 28 ! Except every 100 years, when it has 28 days ...
816 IF (MOD(year,400).eq.0) THEN
817 num_days = 29 ! Except every 400 years, when it has 29 days.
825 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
826 SUBROUTINE split_date_char ( date , century_year , month , day , hour , minute , second , ten_thousandth)
832 CHARACTER(LEN=24) , INTENT(IN) :: date
836 INTEGER , INTENT(OUT) :: century_year , month , day , hour , minute , second , ten_thousandth
838 READ(date,FMT='( I4.4)') century_year
841 READ(date,FMT='( 5X,I5.5)') day
843 READ(date,FMT='( 5X,I2.2)') month
844 READ(date,FMT='( 8X,I2.2)') day
846 READ(date,FMT='(11X,I2.2)') hour
847 READ(date,FMT='(14X,I2.2)') minute
848 READ(date,FMT='(17X,I2.2)') second
849 READ(date,FMT='(20X,I4.4)') ten_thousandth
851 END SUBROUTINE split_date_char
853 SUBROUTINE init_module_date_time
854 END SUBROUTINE init_module_date_time
856 END MODULE module_date_time
860 ! TBH: Linkers whine if these routines are placed inside the module. Not
861 ! TBH: sure if these should live here or inside an external package. They
862 ! TBH: have dependencies both on WRF (for the format of the WRF date-time
863 ! TBH: strings) and on the time manager. Currently, the format of the WRF
864 ! TBH: date-time strings is a slight variant on ISO 8601 (ISO is
865 ! TBH: "YYYY-MM-DDThh:mm:ss" while WRF is "YYYY-MM-DD_hh:mm:ss"). If we
866 ! TBH: change the WRF format to match the standard, then we remove the
867 ! TBH: WRF dependence...
869 ! Converts WRF date-time string into an WRFU_Time object.
870 ! The format of the WRF date-time strings is a slight variant on ISO 8601:
871 ! ISO is "YYYY-MM-DDThh:mm:ss" while WRF is "YYYY-MM-DD_hh:mm:ss".
872 SUBROUTINE wrf_atotime ( str, time )
874 CHARACTER (LEN=*), INTENT(INOUT) :: str
875 TYPE(WRFU_Time), INTENT(OUT) :: time
876 INTEGER yr, mm, dd, h, m, s, ms
878 IF ( LEN( str ) .GE. 20 ) THEN
879 IF ( str(20:20) .EQ. '.' ) THEN
881 READ(str,'(I4.4,1x,I5.5,1x,I2.2,1x,I2.2,1x,I2.2,1x,I4.4)') yr,dd,h,m,s,ms
884 READ(str,34) yr,mm,dd,h,m,s,ms
886 ! last four digits are ten-thousandths of a sec, convert to ms
890 READ(str,'(I4.4,1x,I5.5,1x,I2.2,1x,I2.2,1x,I2.2)') yr,dd,h,m,s
893 READ(str,33) yr,mm,dd,h,m,s
899 READ(str,'(I4.4,1x,I5.5,1x,I2.2,1x,I2.2,1x,I2.2)') yr,dd,h,m,s
902 READ(str,33) yr,mm,dd,h,m,s
906 CALL WRFU_TimeSet( time, YY=yr, MM=mm, DD=dd, H=h, M=m, S=s, MS=ms, rc=rc )
907 CALL wrf_check_error( WRFU_SUCCESS, rc, &
908 'WRFU_TimeSet() in wrf_atotime() FAILED', &
911 33 FORMAT (I4.4,1x,I2.2,1x,I2.2,1x,I2.2,1x,I2.2,1x,I2.2)
912 34 FORMAT (I4.4,1x,I2.2,1x,I2.2,1x,I2.2,1x,I2.2,1x,I2.2,1x,I4.4)
914 END SUBROUTINE wrf_atotime
916 ! Converts an WRFU_Time object into a WRF date-time string.
917 ! The format of the WRF date-time strings is a slight variant on ISO 8601:
918 ! ISO is "YYYY-MM-DDThh:mm:ss" while WRF is "YYYY-MM-DD_hh:mm:ss".
919 SUBROUTINE wrf_timetoa ( time, str )
920 USE module_utility, ONLY : WRFU_Time, WRFU_TimeGet, WRFU_SUCCESS
922 TYPE(WRFU_Time), INTENT(INOUT) :: time
923 CHARACTER (LEN=*), INTENT(OUT) :: str
925 CHARACTER (LEN=256) :: mess, tmpstr
927 IF ( LEN(str) < 19 ) THEN
928 CALL wrf_error_fatal( 'wrf_timetoa: str is too short' )
931 CALL WRFU_TimeGet( time, timeString=tmpstr, rc=rc )
932 WRITE(mess,*)'WRFU_TimeGet() returns ',rc,' in wrf_timetoa() FAILED: timeString >',TRIM(tmpstr),'<'
933 CALL wrf_check_error( WRFU_SUCCESS, rc, &
937 ! change ISO 8601 'T' to WRF '_' and hack off fraction if str is not
938 ! big enough to hold it
939 strlen = MIN( LEN(str), LEN_TRIM(tmpstr) )
941 str(1:strlen) = tmpstr(1:strlen)
943 WRITE (mess,*) 'DEBUG wrf_timetoa(): returning with str = [',TRIM(str),']'
944 CALL wrf_debug ( 150 , TRIM(mess) )
946 END SUBROUTINE wrf_timetoa
948 ! Converts an WRFU_TimeInterval object into a time-interval string.
949 SUBROUTINE wrf_timeinttoa ( timeinterval, str )
952 TYPE(WRFU_TimeInterval), INTENT(INOUT) :: timeinterval
953 CHARACTER (LEN=*), INTENT(OUT) :: str
955 CHARACTER (LEN=256) :: mess
956 CALL WRFU_TimeIntervalGet( timeinterval, timeString=str, rc=rc )
957 CALL wrf_check_error( WRFU_SUCCESS, rc, &
958 'WRFU_TimeIntervalGet() in wrf_timeinttoa() FAILED', &
961 WRITE (mess,*) 'DEBUG wrf_timeinttoa(): returning with str = [',TRIM(str),']'
962 CALL wrf_debug ( 150 , TRIM(mess) )
964 END SUBROUTINE wrf_timeinttoa
968 ! Debug routine to print key clock information.
969 ! Every printed line begins with pre_str.
970 SUBROUTINE wrf_clockprint ( level, clock, pre_str )
972 INTEGER, INTENT( IN) :: level
973 TYPE(WRFU_Clock), INTENT( IN) :: clock
974 CHARACTER (LEN=*), INTENT( IN) :: pre_str
976 INTEGER :: debug_level
977 TYPE(WRFU_Time) :: currTime, startTime, stopTime
978 TYPE(WRFU_TimeInterval) :: timeStep
979 CHARACTER (LEN=64) :: currTime_str, startTime_str, stopTime_str
980 CHARACTER (LEN=64) :: timeStep_str
981 CHARACTER (LEN=256) :: mess
982 CALL get_wrf_debug_level( debug_level )
983 IF ( level .LE. debug_level ) THEN
984 CALL WRFU_ClockGet( clock, CurrTime=currTime, StartTime=startTime, &
985 StopTime=stopTime, TimeStep=timeStep, rc=rc )
986 CALL wrf_check_error( WRFU_SUCCESS, rc, &
987 'wrf_clockprint: WRFU_ClockGet() FAILED', &
990 CALL wrf_timetoa( currTime, currTime_str )
991 CALL wrf_timetoa( startTime, startTime_str )
992 CALL wrf_timetoa( stopTime, stopTime_str )
993 CALL wrf_timeinttoa( timeStep, timeStep_str )
994 WRITE (mess,*) TRIM(pre_str),' clock start time = ',TRIM(startTime_str)
995 CALL wrf_message(TRIM(mess))
996 WRITE (mess,*) TRIM(pre_str),' clock current time = ',TRIM(currTime_str)
997 CALL wrf_message(TRIM(mess))
998 WRITE (mess,*) TRIM(pre_str),' clock stop time = ',TRIM(stopTime_str)
999 CALL wrf_message(TRIM(mess))
1000 WRITE (mess,*) TRIM(pre_str),' clock time step = ',TRIM(timeStep_str)
1001 CALL wrf_message(TRIM(mess))
1004 END SUBROUTINE wrf_clockprint