SUBROUTINE init_report_vars(nrot_years, nperiods) USE pd_dates_vars USE pd_update_vars USE pd_report_vars USE pd_var_tables USE mandate_vars IMPLICIT NONE INTEGER :: nrot_years ! Minimum is 1 INTEGER :: nperiods !24 is minimum value per rotation year INTEGER :: status = 0 INTEGER :: get_nperiods INTEGER :: alloc_pd_vars INTEGER :: i,j,k,m,p,y,z ! local loop variable include 'command.inc' !declarations for commandline args status = alloc_pd_vars(nrot_years, nperiods) if( report_debug.eq.1 ) then print *, "Status of alloc_pd_vars: ", status end if ! Init the period start and stop dates for "report" variable counters ! yrly counters DO y=0, nrot_years yrly_dates(y)%sd = 1 yrly_dates(y)%sm = 1 IF (y == 0) THEN yrly_dates(y)%sy = 1 ELSE yrly_dates(y)%sy = y END IF yrly_dates(y)%ed = 31 yrly_dates(y)%em = 12 yrly_dates(y)%ey = y END DO ! monthly counters DO y=0, nrot_years ! monthly counters DO m=1, 12 monthly_dates(m,y)%sd = 1 monthly_dates(m,y)%sm = m IF (y == 0) THEN monthly_dates(m,y)%sy = 1 ELSE monthly_dates(m,y)%sy = y END IF IF ( (m==1).or.(m==3).or.(m==5).or.(m==7).or. & (m==8).or.(m==10).or.(m==12) ) THEN monthly_dates(m,y)%ed = 31 ELSE IF ( (m==4).or.(m==6).or.(m==9).or.(m==11) ) THEN monthly_dates(m,y)%ed = 30 ELSE ! m==2 (Feb) monthly_dates(m,y)%ed = 29 END IF monthly_dates(m,y)%em = m monthly_dates(m,y)%ey = y END DO END DO ! half month counters i = 0 DO y = 1, nrot_years DO m = 1, 12 ! 1st half month period i = i + 1 hmonth_dates(i)%sd = 1 hmonth_dates(i)%sm = m hmonth_dates(i)%sy = y hmonth_dates(i)%ed = 14 hmonth_dates(i)%em = m hmonth_dates(i)%ey = y ! 2nd half month period i = i + 1 hmonth_dates(i)%sd = 15 hmonth_dates(i)%sm = m hmonth_dates(i)%sy = y IF ( (m==1).or.(m==3).or.(m==5).or.(m==7).or. & (m==8).or.(m==10).or.(m==12) ) THEN hmonth_dates(i)%ed = 31 ELSE IF ( (m==4).or.(m==6).or.(m==9).or.(m==11) ) THEN hmonth_dates(i)%ed = 30 ELSE ! m==2 (Feb) hmonth_dates(i)%ed = 29 END IF hmonth_dates(i)%em = m hmonth_dates(i)%ey = y END DO END DO ! init period counters ! Init the "start dates" i = 0 DO y = 1, nrot_years DO m = 1, 12 ! 1st half month period i = i + 1 period_dates(i)%sd = 1 period_dates(i)%sm = m period_dates(i)%sy = y period_dates(i)%ed = 14 period_dates(i)%em = m period_dates(i)%ey = y ! Hmm, this doesn't look like an efficient way to do this ! but, if it works that will be fine for now ! Get all op dates in first "half" of month FORALL (z=1:size(mandate), & mandate(z)%d > 1 .AND. mandate(z)%d < 15 .AND. & mandate(z)%m == m .AND. mandate(z)%y == y) i = i + 1 period_dates(i)%sd = mandate(z)%d period_dates(i)%sm = mandate(z)%m period_dates(i)%sy = mandate(z)%y period_dates(i)%ed = 14 period_dates(i)%em = m period_dates(i)%ey = y ! Fix previous period end date (day) period_dates(i-1)%ed = period_dates(i)%sd-1 END FORALL ! 2nd half month period i = i + 1 period_dates(i)%sd = 15 period_dates(i)%sm = m period_dates(i)%sy = y IF ( (m==1).or.(m==3).or.(m==5).or.(m==7).or. & (m==8).or.(m==10).or.(m==12) ) THEN period_dates(i)%ed = 31 ELSE IF ( (m==4).or.(m==6).or.(m==9).or.(m==11) ) THEN period_dates(i)%ed = 30 ELSE ! m==2 (Feb) period_dates(i)%ed = 29 END IF period_dates(i)%em = m period_dates(i)%ey = y ! Get all op dates in second "half" of month SELECT CASE (m) CASE (1,3,5,7,8,10) FORALL (z=1:size(mandate), mandate(z)%d > 15 .AND. & mandate(z)%d <= 31 .AND. & mandate(z)%m == m .AND. mandate(z)%y == y) i = i + 1 period_dates(i)%sd = mandate(z)%d period_dates(i)%sm = mandate(z)%m period_dates(i)%sy = mandate(z)%y period_dates(i)%em = m period_dates(i)%ey = y period_dates(i)%ed = 31 ! Fix previous period end date (day) period_dates(i-1)%ed = period_dates(i)%sd-1 END FORALL CASE (4,6,9,11) FORALL (z=1:size(mandate), mandate(z)%d > 15 .AND. & mandate(z)%d <= 31 .AND. & mandate(z)%m == m .AND. mandate(z)%y == y) i = i + 1 period_dates(i)%sd = mandate(z)%d period_dates(i)%sm = mandate(z)%m period_dates(i)%sy = mandate(z)%y period_dates(i)%em = m period_dates(i)%ey = y period_dates(i)%ed = 30 ! Fix previous period end date (day) period_dates(i-1)%ed = period_dates(i)%sd-1 END FORALL CASE DEFAULT FORALL (z=1:size(mandate), mandate(z)%d > 15 .AND. & mandate(z)%d <= 31 .AND. & mandate(z)%m == m .AND. mandate(z)%y == y) i = i + 1 period_dates(i)%sd = mandate(z)%d period_dates(i)%sm = mandate(z)%m period_dates(i)%sy = mandate(z)%y period_dates(i)%em = m period_dates(i)%ey = y period_dates(i)%ed = 29 ! Fix previous period end date (day) period_dates(i-1)%ed = period_dates(i)%sd-1 END FORALL END SELECT END DO END DO ! print all date initialized "counters" if( report_debug.eq.1 ) then ! yrly counters DO y=0, nrot_years print *, "yrly_dates(",y,")", yrly_dates(y) END DO ! monthly counters DO y=0, nrot_years ! monthly counters DO m=1, 12 print *, "monthly_dates(",m,",",y,")", monthly_dates(m,y) END DO END DO ! half month counters DO j = 1, nrot_years*24 print *, "hmonth_dates(",j,")", hmonth_dates(j) END DO ! period counters DO i=1, nperiods print *, "period_dates(",i,")", period_dates(i) END DO end if ! print all "update" values if( report_debug.eq.1 ) then DO i=1,Max_yrly_vars print *, "yrly_update(",i,")%val", yrly_update(i)%val, & yrly_update(i)%cnt, yrly_update(i)%date, & yrly_update(i)%date%ed END DO ! ! DO i=1,Max_yrly_vars ! print *, "yrly_update(",i,")%val", yrly_update(i)%val, & ! yrly_update(i)%cnt ! END DO ! DO i=1,Max_monthly_vars ! print *, "monthly_update(",i,")%val", monthly_update(i)%val, & ! monthly_update(i)%cnt ! END DO ! DO i=1,Max_hmonth_vars ! print *, "hmonth_update(",i,")%val", hmonth_update(i)%val, & ! hmonth_update(i)%cnt ! END DO ! DO i=Min_period_vars,Max_period_vars ! print *, "period_update(",i,")%val", period_update(i)%val, & ! period_update(i)%cnt ! END DO end if END SUBROUTINE init_report_vars