Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(inout), | DIMENSION(:) | :: | MonWeekDay | ||
integer, | intent(inout), | DIMENSION(:) | :: | DSTIndex | ||
integer, | optional | :: | DSTActStMon | |||
integer, | optional | :: | DSTActStDay | |||
integer, | optional | :: | DSTActEnMon | |||
integer, | optional | :: | DSTActEnDay |
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE SetDSTDateRanges(MonWeekDay,DSTIndex,DSTActStMon,DSTActStDay,DSTActEnMon,DSTActEnDay)
! SUBROUTINE INFORMATION:
! AUTHOR Linda Lawrie
! DATE WRITTEN March 2012
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! With multiple year weather files (or repeating weather files that rollover day),
! need to set DST (Daylight Saving Time) dates at start of environment or year.
! DST is only projected for one year.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: JulianDay
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(INOUT),DIMENSION(:) :: MonWeekDay ! Weekday of each day 1 of month
INTEGER, INTENT(INOUT),DIMENSION(:) :: DSTIndex ! DST Index for each julian day (1:366)
INTEGER, OPTIONAL :: DSTActStMon
INTEGER, OPTIONAL :: DSTActStDay
INTEGER, OPTIONAL :: DSTActEnMon
INTEGER, OPTIONAL :: DSTActEnDay
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName='SetDSTDateRanges: '
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ActStartMonth ! Actual Start Month
INTEGER :: ActStartDay ! Actual Start Day of Month
INTEGER :: ActEndMonth ! Actual End Month
INTEGER :: ActEndDay ! Actual End Day of Month
INTEGER :: ThisDay ! Day of Month
INTEGER :: JDay
INTEGER :: JDay1
LOGICAL :: ErrorsFound
INTEGER, DIMENSION(12) :: ActEndDayOfMonth
ErrorsFound=.false.
ActEndDayOfMonth=EndDayOfMonth
ActEndDayOfMonth(2)=EndDayOfMonth(2)+LeapYearAdd
IF (DST%StDateType == MonthDay) THEN
ActStartMonth =DST%StMon
ActStartDay =DST%StDay
ELSEIF (DST%StDateType == NthDayInMonth) THEN
ThisDay=DST%StWeekday-MonWeekDay(DST%StMon)+1
DO WHILE (ThisDay <= 0)
ThisDay=ThisDay+7
ENDDO
ThisDay=ThisDay+7*(DST%StDay-1)
IF (ThisDay > ActEndDayOfMonth(DST%StMon)) THEN
CALL ShowSevereError(RoutineName//'Determining DST: DST Start Date, Nth Day of Month, not enough Nths')
ErrorsFound=.true.
ELSE
ActStartMonth =DST%StMon
ActStartDay =ThisDay
ENDIF
ELSE ! LastWeekDayInMonth
ThisDay=DST%StWeekday-MonWeekDay(DST%StMon)+1
DO WHILE (ThisDay+7 <= ActEndDayOfMonth(DST%StMon))
ThisDay=ThisDay+7
ENDDO
ActStartMonth =DST%StMon
ActStartDay =ThisDay
ENDIF
IF (DST%EnDateType == MonthDay) THEN
ActEndMonth =DST%EnMon
ActEndDay =DST%EnDay
ELSEIF (DST%EnDateType == NthDayInMonth) THEN
ThisDay=DST%EnWeekday-MonWeekDay(DST%EnMon)+1
DO WHILE (ThisDay <= 0)
ThisDay=ThisDay+7
ENDDO
ThisDay=ThisDay+7*(DST%EnDay-1)
IF (ThisDay > ActEndDayOfMonth(DST%EnMon)) THEN
CALL ShowSevereError(RoutineName//'Determining DST: DST End Date, Nth Day of Month, not enough Nths')
ErrorsFound=.true.
ELSE
ActEndMonth =DST%EnMon
ActEndDay =ThisDay
ENDIF
ELSE ! LastWeekDayInMonth
ThisDay=DST%EnWeekday-MonWeekDay(DST%EnMon)+1
DO WHILE (ThisDay+7 <= ActEndDayOfMonth(DST%EnMon))
ThisDay=ThisDay+7
ENDDO
ActEndMonth =DST%EnMon
ActEndDay =ThisDay
ENDIF
IF (ErrorsFound) THEN
CALL ShowFatalError(RoutineName//'Program terminates due to preceding condition(s).')
ENDIF
IF (PRESENT(DSTActStMon)) THEN
DSTActStMon=ActStartMonth
DSTActStDay=ActStartDay
DSTActEnMon=ActEndMonth
DSTActEnDay=ActEndDay
ENDIF
DSTIndex=0
JDay =JulianDay(ActStartMonth,ActStartDay,LeapYearAdd)
JDay1=JulianDay(ActEndMonth,ActEndDay,LeapYearAdd)
IF (JDay1 >= JDay) THEN
DSTIndex(JDay:JDay1)=1
ELSE
DSTIndex(JDay:366)=1
DSTIndex(1:JDay1)=1
ENDIF
RETURN
END SUBROUTINE SetDSTDateRanges