<%@ Language=VBScript %>

<% 
Option Explicit

' Author: James D. (Jim) Miller
' Version: 5.0
' 10:47 PM Thu April 6, 2023

' Buffer and release all at once...
Response.Buffer = True 
%>

<!-- #include file="common/adovbs.inc" -->
<!-- #include file="common/headers.asp" -->
<!-- #include file="common/connection_code.asp" -->

<%
'==========================================
' Common Variables (globals)
'==========================================

Dim DBConnection, rstDate, rstTelem, rstStations, rstLatestDate, rstMostRecent, rstMinMaxFifteenMinData, rstTimeZone
Dim dteMaxTimeStamp
Dim strSQL, strNameForPlot, intMaxGust, intNonPlottingHeight, intTempDiffScalingThreshold
Dim strTitle, strHGSL
Dim sglTempMax, sglTempMin, sglPressureMin, sglPressureMax, sglTempRange, sglDewPointMin, blnDewPointData
Dim strMRTime, strMRWindAvg, strMRWindMax, strMRWindDir, strMRTemp, strMRPressure, strMRDewPoint
Dim Chart
Dim Filename
Dim WeatherTypes, WeatherTypes_URL, WeatherTypes_count, DaysChoices
Dim dteStartDateTime, dteEndDateTime, dteStartDate_forLabels
Dim TimeLabels, TheHour, DayValue, DaysDecSinceRef, intHour
Dim blnMinMax, blnFoundSomeData
Dim intTheColor
Dim strRandomNameString, strFileName2, strOrderBy, intColorScaleFactor
Dim fsoObject, fdrObject, filObject
Dim intFileCount
Dim blnDayLightSavingsTime
Dim dtePostedDate, blnPostedDate_default
Dim intJ, intDays, intXLabels, dblDaysIncrement, dblDaysFraction, dblFractionalPart, dteLabelDate, intLabelsPerDay
Dim dblDPmin, dblDPmax
Dim dblWindNormFactor, intRed, intGreen, intBlue, intGray
Dim strRegionURL, strSensor, strInitializeTimer, strLocation
Dim serverTimeArray, serverTime, intPixelBottomShift, intPixelRightShift, intPixelRightShift_tweak
Dim strShowImages_command
Dim vrtReturnFromMINMAX
Dim intMinutes, dblFiveMinutes, intSeconds_FromMinutes, intSeconds_FromSeconds, intDelay_to_5min
Dim strButtonLabel
Dim strTimeZone, dicTZ
Dim arrRegions, strRegionValue, strRegion, strRegionState
Dim strDebugMessage
Dim dteNowTime, dteStartDateTime_forQuery
Dim str24Hrs_state, strTimer_state, strTimer_value, strRA_state

'=============================================================================================
' Functions and Subroutines
'=============================================================================================

Sub RBC(strTheString)
   Response.Write strTheString & "<BR>" & Chr(10)
End Sub

'Alias for RBC
Sub RWBR(strTheString)
   RBC strTheString
End Sub

Sub RC(strTheString)
   Response.Write strTheString & Chr(10)
End Sub

'This will not make a new line in the HTML file.
Sub RW(strTheString)
   Response.Write strTheString
End Sub

Sub MinMax(ByVal dblNewValue, ByRef dblMax, ByRef dblMin)
     
   If (dblNewValue > dblMax) Then
      dblMax = dblNewValue
   End If
   
   If (dblNewValue < dblMin) Then
      dblMin = dblNewValue
   End If
   
End Sub

Function DaylightTime(strMRTime)
   Dim strMRTime_DLS
   If (strMRTime <> "-") Then
      If (dayLightSavingsTime(strMRTime)) Then
         strMRTime_DLS = DateAdd("h",1,strMRTime)
      Else
         strMRTime_DLS = strMRTime
      End If
   Else
      strMRTime_DLS = "-"
   End If
   DaylightTime = strMRTime_DLS
End Function

Function AgeOfData(strMRTime)
   If (strMRTime <> "-") Then
      ' The following line works mainly because strMRTime is in standard time. So no problem with HI.
      AgeOfData = DateDiff("n", DaylightTime(strMRTime), Now()) + 60 * dicTZ.item(strTimeZone)
   Else
      AgeOfData = "-"
   End If
End Function

Function MinMaxFifteenMinData(strMode, strVariableName)
   ' Check to see if there is data for the specified field.  And if there is,
   ' find either the max or min of the specified variable

   strSQL = "Select " & strMode & "(" & strVariableName & ") AS TheExtreme From FifteenMinData WHERE ([StationName] = '" & strLocation & "') AND " & _
                              "([DateTimeStamp] <=     #" & dteEndDateTime & "#) AND " & _
                              "([DateTimeStamp] >=     #" & dteStartDateTime_forQuery & "#)"                                            
   
   PopulateStaticRecordset DBConnection, strSQL, rstMinMaxFifteenMinData

   ' Check for data (because sites don't have min max data on the temperature)
   If (rstMinMaxFifteenMinData.RecordCount = 0) Then
      MinMaxFifteenMinData = -999
   Else 
      rstMinMaxFifteenMinData.MoveFirst
      MinMaxFifteenMinData = rstMinMaxFifteenMinData("TheExtreme")
   End If

   CloseRecordSet rstMinMaxFifteenMinData
End Function

Function DaysDecSinceRefF()
 
   Dim dteRecordTime
   Dim TheMin
 
   If (intDays = 1) Then
      TheMin = rstTelem("TimeMin")
   Else
      TheMin = 0
   End If
 
   dteRecordTime = rstTelem("TimeMDY") + TimeSerial(rstTelem("TimeHr"), TheMin, 0)   
   
   DaysDecSinceRefF = CDbl(  DateDiff("n", dteStartDateTime, dteRecordTime)  ) / 1440 
   
End Function

Function DaysDec( dteTime)
   ' 86400 = 24.0*60.0*60.0  (Seconds in a day).

   ' Decimal day as measured from the midnight start time.
   'RWBR "dteTime = " & dteTime
   DaysDec = CDbl( DateDiff("s", dteStartDateTime, dteTime) ) / 86400.0

End Function

Sub IPMessage()
   Dim UserIPAddress
   UserIPAddress = Request.ServerVariables("HTTP_X_FORWARDED_FOR")
   If UserIPAddress = "" Then
     UserIPAddress = Request.ServerVariables("REMOTE_ADDR")
   End If
   
   If (UserIPAddress = "50.35.244.236") Then
   'If (UserIPAddress = "138.236.65.69") Then
      RWBR "Message to " & UserIPAddress & ":"
      RWBR "Eric, I'm guessing this IP address is you. I tried to email you a few days ago. It bounced back. Looks like you're no longer using this email address: [email protected]. You're one of Waconia's most frequent users and it would be good to be able to email you if I'm working on a problem. Let me know. I'll take this message off in a few days. Thanks, Jim ([email protected])"
   End If
   
End Sub

Function DirectionLabel (WindDeg)
   If     (WindDeg > 345 And WindDeg <= 360) Then 
      DirectionLabel = "North"
   ElseIf (WindDeg >   0 And WindDeg <=  15) Then 
      DirectionLabel = "North"
   
   ElseIf (WindDeg >  15 And WindDeg <=  45) Then 
      DirectionLabel = "NNE"
   ElseIf (WindDeg >  45 And WindDeg <=  75) Then 
      DirectionLabel = "ENE"
   ElseIf (WindDeg >  75 And WindDeg <= 105) Then 
      DirectionLabel = "East"
   ElseIf (WindDeg > 105 And WindDeg <= 135) Then 
      DirectionLabel = "ESE"
   ElseIf (WindDeg > 135 And WindDeg <= 165) Then 
      DirectionLabel = "SSE"
   ElseIf (WindDeg > 165 And WindDeg <= 195) Then 
      DirectionLabel = "South"
   ElseIf (WindDeg > 195 And WindDeg <= 225) Then 
      DirectionLabel = "SSW"
   ElseIf (WindDeg > 225 And WindDeg <= 255) Then 
      DirectionLabel = "WSW"
   ElseIf (WindDeg > 255 And WindDeg <= 285) Then 
      DirectionLabel = "West"
   ElseIf (WindDeg > 285 And WindDeg <= 315) Then 
      DirectionLabel = "WNW"
   ElseIf (WindDeg > 315 And WindDeg <= 345) Then 
      DirectionLabel = "NNW"
   Else 
      DirectionLabel = "Var"
   End If
   
   If     (WindDeg =  45) Then 
      DirectionLabel = "NE"
   ElseIf (WindDeg = 135) Then
      DirectionLabel = "SE"
   ElseIf (WindDeg = 225) Then
      DirectionLabel = "SW"
   ElseIf (WindDeg = 315) Then
      DirectionLabel = "NW"
   End If
End Function

Sub AddHorizontalLine_gray(intLineWidth, intColor, dblYvalue)

   Chart.AddSeries (5)
   Chart.linewidth = intLineWidth
   Chart.SeriesInLegend = false

   'MyChartAddXY 0, dblYvalue, "", strColor   
   'MyChartAddXY intDays+1, dblYvalue, "", RGB(&hFF,&hFF,&hFF)

   ' The -0.009 extends the line all the way to the left edge of the 1-day chart.
   MyChartAddXY      -0.009, dblYvalue, "", RGB(intColor, intColor, intColor)  
   MyChartAddXY intDays+1.0, dblYvalue, "", RGB(intColor, intColor, intColor)

End Sub

Sub AddHorizontalLine_color(intLineWidth, intRed, intGreen, intBlue, dblYvalue)

   Chart.AddSeries (5)
   Chart.linewidth = intLineWidth
   Chart.SeriesInLegend = false

   MyChartAddXY      -0.009, dblYvalue, "", RGB(intRed, intGreen, intBlue)  
   MyChartAddXY intDays+1.0, dblYvalue, "", RGB(intRed, intGreen, intBlue)

End Sub

Sub MyChartAddXY(dblXValue, dblYValue, strXLabel, intColor)

   ' Feed only NON-Null values to the AddXY method.
   If (Not IsNull(dblYValue)) Then
      Chart.AddXY dblXValue, dblYValue, strXLabel, intColor
   End If

End Sub

Sub AddVerticalLine( dblXValue, intLineWidth)

   Dim intColor, intGray, intColor_Red, intColor_Green, intColor_Blue
   
   Chart.AddSeries (5)
   Chart.linewidth = intLineWidth
   Chart.SeriesInLegend = false

   intGray = 75  ' 0 (black) to 255 (white)
   
   intColor_Red = intGray
   intColor_Green = intGray
   intColor_Blue = intGray
   
   intColor = RGB(intColor_Red, intColor_Green, intColor_Blue)
   'intColor = vbBlack
   
   MyChartAddXY           dblXValue, Chart.VertAxisMin, "", intColor  
   MyChartAddXY           dblXValue, Chart.VertAxisMax, "", intColor
   
End Sub

Sub UpdateTraceRecordSet_DeltaP(ByRef rstTelem, ByRef dicTraceIO)
   Dim strWestSite, strEastSite
   
   strWestSite = dicTraceIO.Item("WestSite")
   strEastSite = dicTraceIO.Item("EastSite")

   dicTraceIO.Item("FoundData_ForThisTrace") = False

   If (intDays = 1) then
      ' This query uses an interesting trick to accomplish the delta-P
      ' calculation.  It selects all the needed data from two sites and then
      ' groups it by time.  It feeds the SUM operator with logic from the IIF
      ' operator.  That is how the delta is calculated.  The HAVING clause
      ' insures that only groups with a count of 2 are used.

      ' Get the most recent 24 hours of data. This modification of dteStartDateTime_forQuery is in support
      ' of the 24h plot.
      If ((strMRTime <> "-") And (DaysDec(strMRTime) > 0.0) And (DaysDec(strMRTime) < 1.0) And (str24Hrs_state = "checked")) Then
         dteStartDateTime_forQuery = DateAdd("d", -1, DateAdd("n", 0, strMRTime))
      End If
      
      strSQL = "SELECT DateTimeStamp, TimeMDY, TimeHr, TimeMin, SUM(IIf([StationName]='" & strWestSite & "',+[Pressure],-[Pressure])) AS DeltaP " & _
               "FROM FifteenMinData " & _
               "WHERE ((StationName) In ('" & strWestSite & "','" & strEastSite & "')) AND " & _
               "      ([DateTimeStamp] <=     #" & dteEndDateTime    & "#) AND " & _
               "      ([DateTimeStamp] >=     #" & dteStartDateTime_forQuery & "#) " & _
               "GROUP BY DateTimeStamp, TimeMDY, TimeHr, TimeMin " & _
               "HAVING (((Count(DateTimeStamp))=2)) " & _
               "ORDER BY TimeMDY ASC, TimeHr ASC, TimeMin ASC"   
   
   Else

      strSQL = "SELECT DateTimeStamp, TimeMDY, TimeHr, TimeMin, SUM(IIf([StationName]='" & strWestSite & "',+[Pressure],-[Pressure])) AS DeltaP1 " & _
               "FROM FifteenMinData " & _
               "WHERE ((StationName) In ('" & strWestSite & "','" & strEastSite & "')) AND " & _
               "      ([DateTimeStamp] <=     #" & dteEndDateTime    & "#) AND " & _
               "      ([DateTimeStamp] >=     #" & dteStartDateTime_forQuery & "#) " & _
               "GROUP BY DateTimeStamp, TimeMDY, TimeHr, TimeMin " & _
               "HAVING (((Count(DateTimeStamp))=2)) " & _
               "ORDER BY TimeMDY ASC, TimeHr ASC, TimeMin ASC"   

      ' And now we feed the query above into the aggregation query below
      ' (another interesting SQL trick).

      strSQL = "SELECT TimeMDY, TimeHr, AVG(DeltaP1) AS DeltaP " & _
               "FROM (" & strSQL & ") " & _
               "GROUP BY TimeMDY, TimeHr " & _
               "ORDER BY TimeMDY ASC , TimeHr ASC "

   End If

   'RWBR dteStartDateTime_forQuery & "--------" & dteEndDateTime
   PopulateStaticRecordset DBConnection, strSQL, rstTelem

   If (Not rstTelem.BOF) Then 
      dicTraceIO.Item("FoundData") = True
      dicTraceIO.Item("FoundData_ForThisTrace") = True
   End If
   
End Sub

Sub UpdateTraceRecordSet(ByVal strSensor_DBName, ByRef rstTelem, ByRef dicTraceIO)

   Dim strSensorSelectClause

   dicTraceIO.Item("FoundData_ForThisTrace") = False
   
   If (intDays = 1) Then
      'RWBR "Diff: Post-Now = " & DateDiff("h", dtePostedDate, Now())
      If ((strMRTime <> "-") And (DaysDec(strMRTime) > 0.0) And (DaysDec( strMRTime) < 1.0) And (str24Hrs_state = "checked")) Then
         ' Go back a full day. This modification of dteStartDateTime_forQuery is in support 
         ' of the 24h plot.
         dteStartDateTime_forQuery = DateAdd("d", -1, DateAdd("n", 0, strMRTime))
      End If
      
      strSQL = "SELECT StationName, DateTimeStamp, TimeMDY, TimeMin, TimeHr, " & strSensor_DBName & " " & _
               "FROM FifteenMinData " & _ 
               "WHERE ([StationName] = '" & strLocation & "') AND " & _
                     "([DateTimeStamp] <=     #" & dteEndDateTime    & "#) AND " & _
                     "([DateTimeStamp] >=     #" & dteStartDateTime_forQuery     & "#) AND " & _
                     "(" & strSensor_DBName & " Is Not Null) " & _
               "ORDER BY TimeMDY ASC, TimeHr ASC, TimeMin ASC"                  
   Else   
      
      If (strSensor_DBName = "TempMax") or (strSensor_DBName = "WindGust") Then
         strSensorSelectClause = "MAX(A." & strSensor_DBName & ") AS " & strSensor_DBName
         
      ElseIf (strSensor_DBName = "TempMin") Then
         strSensorSelectClause = "MIN(A." & strSensor_DBName & ") AS " & strSensor_DBName
            
      Else
         strSensorSelectClause = "AVG(A." & strSensor_DBName & ") AS " & strSensor_DBName
      
      End If
      
      strSQL = "SELECT TimeMDY, TimeHr, FIRST(A.StationName) AS StationName, AVG(A.DateTimeStamp) AS DateTimeStamp, " & strSensorSelectClause & " " & _
               "FROM FifteenMinData AS A " & _ 
               "WHERE ([StationName] = '" & strLocation & "') AND " & _
                     "([DateTimeStamp] <=     #" & dteEndDateTime    & "#) AND " & _
                     "([DateTimeStamp] >=     #" & dteStartDateTime_forQuery     & "#) AND " & _
                     "(" & strSensor_DBName & " Is Not Null) " & _
               "GROUP BY TimeMDY, TimeHr " & _
               "ORDER BY TimeMDY ASC, TimeHr ASC"       
   End If

   'RWBR strSQL
   PopulateStaticRecordset DBConnection, strSQL, rstTelem
   
   If (Not rstTelem.BOF) Then 
      dicTraceIO.Item("FoundData") = True
      dicTraceIO.Item("FoundData_ForThisTrace") = True
   End If

End Sub

Sub AddTrace(strSensorName, dblYScaleFactor, intSeriesType, strSeriesTitle, intLineWidth, intColor, ByRef dicTraceIO)
   Dim intTraceArray_index
   Dim intYesterdayColor, intGray 
   Dim dblYMin, dblYMax, dblYValue, dblYValue_raw
   Dim dblXValue, dblXValue_raw
   
   Dim dblX_Previous, dblY_Previous
   dblX_Previous = -999 : dblY_Previous = -999
   
   
   If (strSensorName = "DeltaP") Then
      UpdateTraceRecordSet_DeltaP         rstTelem, dicTraceIO
   Else
      UpdateTraceRecordSet strSensorName, rstTelem, dicTraceIO
   End If
   
   If (dicTraceIO.Item("FoundData_ForThisTrace") = False) Then
      CloseRecordSet rstTelem
      Exit Sub
   End If
   
   
   dblYMax = dicTraceIO.Item("YMax") 
   dblYMin = dicTraceIO.Item("YMin") 
   
   If intSeriesType = 6 Then
      intGray = 200
      intYesterdayColor = RGB(intGray,intGray,intGray)
   Else
      intYesterdayColor = intColor
   End If
   
   'Instantiate the running averages in JavaScript.
   instantiateRunningAverages( strSensorName)
   
   If (intDays = 1) Then
      rstTelem.MoveFirst
      
      'First plot yesterday's data.
      Chart.AddSeries( intSeriesType)
      Chart.SeriesInLegend = False      
      Chart.linewidth = 1
      
      RA_y.reset( rstTelem.RecordCount)
      RA_x.reset( rstTelem.RecordCount)
            
      Do Until rstTelem.EOF
         If Not IsNull( rstTelem( strSensorName)) Then         
            dblYValue_raw = CDbl(rstTelem( strSensorName))
            dblXValue_raw = DaysDecSinceRefF()
            
            ' Do a running average if requested.
            If (strRA_state = "checked") AND (rstTelem.RecordCount > 5) Then
               dblYValue = RA_y.update( dblYValue_raw) * dblYScaleFactor
               dblXValue = RA_x.update( dblXValue_raw)
            Else
               dblYValue = dblYValue_raw * dblYScaleFactor
               dblXValue = dblXValue_raw               
            End If
            
            If (dblXValue < 0.0) Then
               'Display yesterday's data on the current single-day plot.
               
               'Add 1.0 to move these yesterday points onto today's plot.
               MyChartAddXY dblXValue + 1.0, dblYValue, "", intYesterdayColor
               MinMax dblYValue, dblYMax, dblYMin
               'dicTraceIO.Item("FoundData") = True
               
               ' Save a starter point for today's data trace.
               dblX_Previous = dblXValue
               dblY_Previous = dblYValue

            Else
               'At the start of today's data, exit this first loop.
               Exit Do
            End If
         
         End If
         rstTelem.MoveNext         
      Loop
      
      'Then start a new trace for today's data.
      Chart.AddSeries( intSeriesType)      
      Chart.linewidth = intLineWidth
      Chart.SeriesTitle = strSeriesTitle 
      
      'First, plot the last point from yesterday's data. This makes
      'the trace lines visible for the first point of the day (2 points needed).
      If dblX_Previous <> -999 Then
         MyChartAddXY dblX_Previous, dblY_Previous, "", intColor
      End If
      
      Do Until rstTelem.EOF
         If Not IsNull( rstTelem( strSensorName)) Then
            dblYValue_raw = CDbl(rstTelem( strSensorName))
            dblXValue_raw = DaysDecSinceRefF()
            
            ' Do a running average if requested.
            If (strRA_state = "checked") AND (rstTelem.RecordCount > 5) Then
               dblYValue = RA_y.update( dblYValue_raw) * dblYScaleFactor
               dblXValue = RA_x.update( dblXValue_raw)
            Else
               dblYValue = dblYValue_raw * dblYScaleFactor
               dblXValue = dblXValue_raw               
            End If
            
            MyChartAddXY dblXValue, dblYValue, "", intColor
            MinMax dblYValue, dblYMax, dblYMin
            'dicTraceIO.Item("FoundData") = True
         End If
         rstTelem.MoveNext
      Loop
   
   Else
      ' Multi-day charts.
      
      ReDim dblTraceArray( rstTelem.recordcount - 1)
   
      Chart.AddSeries( intSeriesType)
      Chart.linewidth = intLineWidth
      Chart.SeriesTitle = strSeriesTitle
      
      intTraceArray_index = 0
      rstTelem.MoveFirst
      
      ' Reset the running average objects with each new trace.
      RA_y.reset( rstTelem.RecordCount)
      RA_x.reset( rstTelem.RecordCount)
      
      Do Until rstTelem.EOF
         If Not IsNull( rstTelem( strSensorName)) Then
            dblYValue_raw = CDbl(rstTelem( strSensorName))
            dblXValue_raw = DaysDecSinceRefF()
            
            ' Do a running average if requested.
            If (strRA_state = "checked") AND (rstTelem.RecordCount > 5) Then
               dblYValue = RA_y.update( dblYValue_raw) * dblYScaleFactor
               dblXValue = RA_x.update( dblXValue_raw)
            Else
               dblYValue = dblYValue_raw * dblYScaleFactor
               dblXValue = dblXValue_raw               
            End If
            
            ' For these multi-day plots, use the Array approach to save some time.
            dblTraceArray( intTraceArray_index) = Array( dblXValue, dblYValue, "", intColor)
            intTraceArray_index = intTraceArray_index + 1
            MinMax dblYValue, dblYMax, dblYMin
            'dicTraceIO.Item("FoundData") = True
         End If
         rstTelem.MoveNext
      Loop
      
      Chart.AddXYArray dblTraceArray
   
   End If
   
   ' Note that this assignment can not be made in the call to MinMax. It can't modify the
   ' dictionary values directly (unless you passed it the whole dictionary).
   dicTraceIO.Item("YMax") = dblYMax
   dicTraceIO.Item("YMin") = dblYMin
      
   CloseRecordSet rstTelem   
      
End Sub

Sub PlotTheChart()

   ' Set the ContentType
   'Response.ContentType = "image/JPEG"

   ' Instantiate the Chart component
   Set Chart = Server.CreateObject ("ASPChart.Chart")
   Chart.JPEGQuality = 80

   Dim dblTraceArray, intTraceArray_index, dicTraceIO
   
   ' Use this to facilitate a general ByReference argument to the AddTrace subroutine.
   Set dicTraceIO = Server.CreateObject("Scripting.Dictionary")
   dicTraceIO.Add "YMax", -999
   dicTraceIO.Add "YMin", 999
   dicTraceIO.Add "FoundData", False
   dicTraceIO.Add "FoundData_ForThisTrace", False
   'Used for Delta-P calculations.
   dicTraceIO.Add "WestSite", ""
   dicTraceIO.Add "EastSite", ""
   
   ' Set dteStartDate_forLabels and dteStartDateTime for use in queries and chart labels...
   dteStartDate_forLabels = DateAdd("d", (1 - intDays), dtePostedDate)
   
   ' The following is a somewhat clumsy way to deal with daylight savings time and 
   ' timezone. Noteworthy here is the way that start and end times are shifted 
   ' back during periods of daylight savings time. This, coupled with the way that 
   ' points are plotted using a decimal day value that is calculated relative to 
   ' the starting point AND using the standard time values that are in the 
   ' database, has the net effect of shifting the standard to DLS values. It's all 
   ' a bit confusing. Not completely sure why I originally did it this way. 
   ' But one advantage is that when aggregating large amounts of data 
   ' (like in the 25 day plot) each data point does not need to be converted. This 
   ' is an efficiency that is probably not noticeable on recent computers (2015), 
   ' but probably was worth considering when I first did this 20-some years ago.
   
   dteStartDateTime = DateAdd("d", (1 - intDays), dtePostedDate)
   dteEndDateTime = DateAdd("d", 1, dtePostedDate)
   dteNowTime = DateAdd( "h", dicTZ.item(strTimeZone), Now())
   If (blnDayLightSavingsTime) Then
      dteNowTime = DateAdd("h", -1, dteNowTime) 
      If (strTimeZone <> "H") Then
         dteStartDateTime = DateAdd("h", -1, dteStartDateTime)   
         dteEndDateTime = DateAdd("h", -1, dteEndDateTime) 
      End If
   End If
   
   ' Initialize the start time for the queries. This will later get modified for the 24h
   ' versions of the 1-day charts.
   dteStartDateTime_forQuery = dteStartDateTime
     
   ' Add a separate (pseudo) trace to do the x-axis labeling.  Shift the y
   ' value by negative 200 so the points don't show on the plot. Also prevent
   ' it from showing in the legend.
   '
   ' Have tried more direct methods of charting the labels as part of the data
   ' traces but always ran into problems.  This somewhat indirect (but
   ' successful) method offers more control and is general for any numeric
   ' based x axis.

   Chart.AddSeries (5)
   Chart.linewidth = 0
   Chart.SeriesTitle = " "
   Chart.SeriesInLegend = False   
   
   If (intDays = 1) Then
      TimeLabels = Array("12m","1","2","3","4","5","6am","7","8","9","10","11","12n","1","2","3","4","5","6pm","7","8","9","10","11","12m")

      For intHour = 0 to 24
         ' The key difference in this dummy trace is that it has a parameter
         ' for the label.  All the data traces below have an empty string in
         ' that position.

         MyChartAddXY (CDbl(intHour)/24.0), 0 - 200, TimeLabels(intHour), vbWhite   
      Next
      
   Else      
      ' Make a special label trace (dummy) for multiple-day charts...
      
      If (intDays >= 2) AND (intDays <= 4) Then
         intLabelsPerDay = 4
      ElseIf (intDays >= 5) AND (intDays <= 9) Then
         intLabelsPerDay = 2
      ElseIf (intDays >= 10) AND (intDays <= 25) Then
         intLabelsPerDay = 1
      Else
         ' Shouldn't be able to get here...
      End If      

      intXLabels = (intDays * intLabelsPerDay) + 1
      ' Dim the dynamic array...
      ReDim strTimeLabels(intXLabels)
      dblDaysIncrement = 1 / intLabelsPerDay
         
      For intJ = 0 To intXLabels - 1
         dblDaysFraction = intJ * dblDaysIncrement
         
         ' Put a Day label on the integer values (midnight)...
         If (dblDaysFraction = Int(dblDaysFraction)) Then
            dteLabelDate = DateAdd("d", Int(dblDaysFraction), dteStartDate_forLabels)
            strTimeLabels(intJ) = Left(WeekDayName(WeekDay(dteLabelDate), True),2) & "-" & Day(dteLabelDate)
         Else
            dblFractionalPart = dblDaysFraction - Int(dblDaysFraction)
            If (dblFractionalPart = 0.50) Then
               ' Suppress the 12n marks for 7 though 9.
               If (intDays <= 6) Then
                  strTimeLabels(intJ) = "12n"
               Else
                  strTimeLabels(intJ) = ""
               End If
            Else
               strTimeLabels(intJ) = "" 'CStr(dblDaysFraction)
            End If      
         End If
      Next

      ' Plot the pseudo trace....         
      For intJ = 0 To intXLabels - 1
         ' The key difference in this pseudo trace is that it has a parameter
         ' for the label. All the data traces below have an empty string in
         ' that position.

         MyChartAddXY intJ * dblDaysIncrement, 0 - 200, strTimeLabels(intJ), vbWhite   
      Next      

   End If

   '===============================================================================
   ' Populate trace(s) depending on the sensor or plot type...
   '===============================================================================  
   
   If (left(strSensor,4) = "Wind") Then
   
      intGray = 175
      
      ' Make horizontal lines for the compass points. Do this before adding the
      ' trace lines so data points will lay on top of this reference lines.
       
      If (strSensor = "Wind36") Then
         AddHorizontalLine_gray 1, intGray,  45 * dblWindNormFactor
         AddHorizontalLine_gray 1, intGray, 135 * dblWindNormFactor
         AddHorizontalLine_gray 1, intGray, 225 * dblWindNormFactor
         AddHorizontalLine_gray 1, intGray, 315 * dblWindNormFactor
      End If
     
      ' These are common to both Wind40 and Wind36
      AddHorizontalLine_gray 1, intGray,   0 * dblWindNormFactor
      AddHorizontalLine_gray 1, intGray,  90 * dblWindNormFactor
      AddHorizontalLine_gray 1, intGray, 180 * dblWindNormFactor
      AddHorizontalLine_gray 1, intGray, 270 * dblWindNormFactor
      AddHorizontalLine_gray 1, intGray, 360 * dblWindNormFactor
      
      AddTrace "WindDirection", dblWindNormFactor, 6, "Direction               ",     3, vbWhite,             dicTraceIO
      AddTrace "WindGust",      1.0,               5, "Maximum Speed",                2, RGB(&h00,&h80,&h80), dicTraceIO     
      intMaxGust = dicTraceIO.Item("YMax")
      AddTrace "WindSpeed",     1.0,               5, "Average Speed",                2, vbRed,               dicTraceIO
      
      If dicTraceIO.Item("FoundData") Then
      
         ' To be consistent with the other sensor charts, putting these scale
         ' limits here, after the trace filling calls above.

         Chart.VertAxisMin = 0.0  '-10
         If     (intMaxGust > 40) then
            Chart.VertAxisMax = CDbl(intMaxGust)
         Else
            Chart.VertAxisMax = 40.0
         End If
               
         Chart.AddAxisLabel 1, "Wind Speed (mph)"

         If (intDays > 1) then
            Chart.ChartTitleAdd  " Wind at " & strNameForPlot 
            Chart.HorizAxisMin = 0.00      
         Else
            Chart.ChartTitleAdd  " Wind at " & strNameForPlot & " on " & WeekDayName(WeekDay(dtePostedDate)) & " " & dtePostedDate
            Chart.HorizAxisMin = 0.04      
         End If

         ' Use tweak of -4 if there is a carriage return after each image element
         ' in the div.
         intPixelRightShift_tweak = -4
         If (intDays >= 10) Then
            Chart.Width = 1250 + 61  ' The 61 helps to get the days to line up with the temperature chart.
            intPixelRightShift = -210 + intPixelRightShift_tweak - 3  ' The -3 is a secondary tweak needed after I added the 61 in the line above.
         Else
            Chart.Width = 855
            intPixelRightShift = -188 + intPixelRightShift_tweak
         End If

         ' Set the chart height based on the y-axis maximum value.  Scale up the
         ' plotting area by the ratio of intMaxGust/40.

         intNonPlottingHeight =  75 
         If (intMaxGust > 40) then    
            Chart.Height = ((500 - intNonPlottingHeight) * (intMaxGust/40)) + intNonPlottingHeight
            ' This gets used in the style-sheet the positions the directions-overlay image.
            intPixelBottomShift = Fix((intMaxGust * 0.320) - 11)  'This is always positive.
            
         Else
            Chart.Height = 500
            intPixelBottomShift = 0
         End If
         
         Chart.LeftAxisIncrement = 5
      
      End If

   ElseIf (strSensor = "Temperature") Then
         
      ' Do this one first. This one should return data for any type
      ' of temperature plot. If not, don't try the other parts.
      AddTrace "TempAvg", 1, 5, "Dry Bulb", 2, vbRed, dicTraceIO  
            
      If dicTraceIO.Item("FoundData") Then
         
         If (MinMaxFifteenMinData("Min","TempMin") <> -999) Then
            AddTrace "TempMin", 1, 5, "  Min", 1, vbBlack, dicTraceIO
            AddTrace "TempMax", 1, 5, "  Max", 1, vbBlack, dicTraceIO
         End If
         
         If (MinMaxFifteenMinData("Min","DewPoint") <> -999) Then
            AddTrace "DewPoint", 1, 5, "Dew Point", 2, RGB(&h00,&h80,&h80), dicTraceIO
         End If
      
         ' Ongoing (overall) Min and Max values are collected in dicTraceIO as each trace
         ' generated.
         sglTempMin = dicTraceIO("YMin")
         sglTempMax = dicTraceIO("YMax")
         sglTempRange = sglTempMax - sglTempMin
         
         ' To be consistent with the other sensor charts, putting these scale
         ' limits here, after the trace filling loop above. But seems to work
         ' either way here...

         intTempDiffScalingThreshold = 40
         intNonPlottingHeight = 108
         If (sglTempRange < intTempDiffScalingThreshold) then
            Chart.VertAxisMin = sglTempMin - ((intTempDiffScalingThreshold - sglTempRange)/2)
            Chart.VertAxisMax = sglTempMax + ((intTempDiffScalingThreshold - sglTempRange)/2)
            Chart.Height = 500
         Else
            ' The 0.2 keeps the max and min data from being obscured by the outer
            ' boundaries of the charting area.
            Chart.VertAxisMin = sglTempMin - 0.2     
            Chart.VertAxisMax = sglTempMax + 0.2
            Chart.Height = ((500 - intNonPlottingHeight) * (sglTempRange/intTempDiffScalingThreshold)) + intNonPlottingHeight    
         End If

         Chart.LeftAxisIncrement = 5
         
         
         ' Y axis label
         Chart.AddAxisLabel 1, "Temperature (F)"
             
         If (intDays > 1) Then
            Chart.ChartTitleAdd  " Temperature at " & strNameForPlot
         Else
            Chart.ChartTitleAdd  " Temperature at " & strNameForPlot & " on " & WeekDayName(WeekDay(dtePostedDate)) & " " & dtePostedDate
         End If    

         If (intDays >= 10) Then
            Chart.Width = 1250
         Else
            Chart.Width = 791  '780            
         End If

      End If
      
   ElseIf (strSensor = "Pressure") Then

      ' The Pressure Plot.
      
      AddTrace "Pressure", 1.0, 5, "no trace label", 2, vbRed, dicTraceIO
      
      If dicTraceIO.Item("FoundData") Then
      
         Chart.SeriesInLegend = False
         sglPressureMin = dicTraceIO.Item("YMin")
         sglPressureMax = dicTraceIO.Item("YMax")
         
         Chart.AddAxisLabel 1, "Pressure (Inches Hg)"
                  
         If (intDays > 1) then
            Chart.ChartTitleAdd  " Barometer at " & strNameForPlot
         Else
            Chart.ChartTitleAdd  " Barometer at " & strNameForPlot & " on " & WeekDayName(WeekDay(dtePostedDate)) & " " & dtePostedDate
         end If    
      
         ' Note: these axis limits only work if they come after
         ' the chart filling loop above...

         If (sglPressureMin < 29.42) then 
            Chart.VertAxisMin = sglPressureMin - 0.005
         Else
            Chart.VertAxisMin = 29.41
         End If    
         
         If (sglPressureMax > 30.42) then 
            Chart.VertAxisMax = sglPressureMax + 0.005
         Else
            Chart.VertAxisMax = 30.43
         End If        
            
         If (sglPressureMin = 0) then
            Chart.VertAxisMin = -0.5
            Chart.VertAxisMax =  0.5   
         End If
         
         Chart.LeftAxisIncrement = 0.1
         
         'Chart.AddAxisLabel 1, "Pressure (Inches Hg)"
         
         Chart.Height = 500
         If (intDays >= 10) Then
            Chart.Width = 1128
         Else
            Chart.Width = 685
         End If

      End If
  
   ElseIf (Left(strSensor,6) = "DeltaP") Then

      ' The Delta-P plot.
      
      ' Add some horizontal lines
      Chart.AddSeries (5)
      Chart.linewidth = 2
      Chart.SeriesInLegend = False
      MyChartAddXY 0, 0, "", vbBlack   
      If (Request.QueryString("specName") = "") Then
         MyChartAddXY intDays+1, 0, "", vbWhite
      Else
         ' Gray line (if request is for the 50Webs example chart page).
         MyChartAddXY intDays+1, 0, "", RGB(&hB5,&hB5,&hB5)     
      End If
      
      ' Add the delta-P traces.
      
      If (strSensor = "DeltaP1") Then
               
         dicTraceIO("WestSite") = "PORTLAND"
         dicTraceIO("EastSite") = "THE DALLES"
         AddTrace "DeltaP", 1.0, 5, "Portland - The Dalles ", 2, RGB(&h00,&h80,&h80), dicTraceIO
         
         dicTraceIO("WestSite") = "THE DALLES"
         dicTraceIO("EastSite") = "PASCO"
         AddTrace "DeltaP", 1.0, 5, "The Dalles - Pasco", 2, vbRed, dicTraceIO
         
         '"NORTH BEND", "PASCO"
               
      ElseIf (strSensor = "DeltaP2") Then
         
         dicTraceIO("WestSite") = "KTTD"
         dicTraceIO("EastSite") = "KDLS"
         AddTrace "DeltaP", 1.0, 5, "Troutdale - The Dalles", 2, RGB(&h00,&h80,&h80), dicTraceIO
         
         dicTraceIO("WestSite") = "KDLS"
         dicTraceIO("EastSite") = "KHRI"
         AddTrace "DeltaP", 1.0, 5, "The Dalles - Hermiston", 2, vbRed, dicTraceIO
         
         ' dicTraceIO("WestSite") = "KTTD"
         ' dicTraceIO("EastSite") = "KHRI"
         ' AddTrace "DeltaP", 1.0, 5, "Troutdale - Hermiston", 2, vbBlue, dicTraceIO

      End If
      
      If dicTraceIO.Item("FoundData") Then
         
         ' Force limits on the Y axis for the Delta-P chart. Note: these must come
         ' after the trace filling calls above...
         
         dblDPmin = dicTraceIO("YMin")
         dblDPmax = dicTraceIO("YMax")
         
         If (dblDPmin < -0.08) Then
            Chart.VertAxisMin = dblDPmin - .001
         Else
            Chart.VertAxisMin = -0.08
         End If
         
         If (dblDPmax > 0.18) Then
            Chart.VertAxisMax = dblDPmax + 0.001
         Else
            Chart.VertAxisMax = 0.18
         End If
           
           
         If (intDays > 1) Then
            Chart.ChartTitleAdd  "Delta-P"
         Else
            Chart.ChartTitleAdd  "Delta-P on " & WeekDayName(WeekDay(dtePostedDate)) & " " & dtePostedDate
         End If    
         
         Chart.LeftAxisIncrement = 0.05
         
         Chart.AddAxisLabel 1, "Pressure Differential (Inches Hg)"
         
         If (intDays >= 10) Then
            Chart.Width = 1270
         Else
            Chart.Width = 875
         End If
         
         ' Scale the height of the image if the y range is larger than the default of 0.26.
         intNonPlottingHeight = 90
         If ((Chart.VertAxisMax - Chart.VertAxisMin) > 0.26) Then    
            Chart.Height = ((510 - intNonPlottingHeight) * ((Chart.VertAxisMax - Chart.VertAxisMin)/0.26)) + intNonPlottingHeight
         Else
            Chart.Height = 510
         End If         
         
      End If
   
   Else
      ' Shouldn't ever get here...
      'RBC "No data or no match found for the specified sensor type." 
   End If 

   '=============================================================================
   ' Control chart axes and labeling...
   ' (This is done for every type of plot)
   '=============================================================================

   If dicTraceIO.Item("FoundData") Then
      
      ' Plot the LatestRecord and the NOW lines.
      If ((intDays = 1) and (str24Hrs_state = "checked")) Then
         AddVerticalLine DaysDec( strMRTime),  1
         AddVerticalLine DaysDec( dteNowTime), 1
      End If
        
      Chart.HorizAxisMax = intDays
      Chart.ShowMinorTicks false, false  
        
      If (intDays > 1) then
         ' Set Horizontal Axis Label Style to: Axis Scales (2)
         Chart.HLabelStyle = 0
                  
         If (blnDayLightSavingsTime And (strTimeZone <> "H")) Then
            Chart.AddAxisLabel 2, "Days Starting with " & WeekDayName(WeekDay(dteStartDate_forLabels)) & " " & FormatDateTime(dteStartDate_forLabels, vbShortDate) & " (" & strTimeZone & "DT)"
         Else
            Chart.AddAxisLabel 2, "Days Starting with " & WeekDayName(WeekDay(dteStartDate_forLabels)) & " " & FormatDateTime(dteStartDate_forLabels, vbShortDate) & " (" & strTimeZone & "ST)"
         End If
         Chart.HorizAxisMin = 0.0     
      Else
         ' Set Horizontal Axis Label Style to: Automatic (0)      
         Chart.HLabelStyle = 0
             
         If (blnDayLightSavingsTime And (strTimeZone <> "H")) Then
            Chart.AddAxisLabel 2, "Hour of the Day (" & strTimeZone & "DT)"
         Else
            Chart.AddAxisLabel 2, "Hour of the Day (" & strTimeZone & "ST)"
         End If
         
         ' Make a little more room on the y axis for the last point from yesterday. The
         ' square boxes (markers) for the direction trace enforce a little more room on 
         ' their own, so the non-wind plots require a little more wiggle room on each 
         ' end of the x-axis.
         If (left(strSensor,4) = "Wind") Then
            Chart.HorizAxisMin = -0.001
            Chart.HorizAxisMax = intDays + 0.001
         Else
            'Chart.HorizAxisMin = 0.00
            Chart.HorizAxisMin = -0.003  
            Chart.HorizAxisMax = intDays + 0.003            
         End If
      End If

      Chart.ChartTitleFont.Size = 16
      Chart.ChartTitleFont.Name = "Arial"    
      'Chart.ChartTitleFontColor = vbBlue
      Chart.ChartTitleFontColor = RGB(&h00,&h80,&h80)    
      Chart.LegendFont.Size = 10
      Chart.AxisLabelFontBottom.Size = 10
      Chart.AxisLabelFontLeft.Size = 10
        
      Chart.BevelOuter = false
      
      If (Request.QueryString("specName") <> "") Then
         Chart.GradientVisible = false
      Else
         Chart.GradientVisible = true
      End If
      Chart.GradientStartColor = RGB(&hff,&hcc,&h99)
      Chart.GradientEndColor = vbWhite
      
      Chart.PanelColor = vbWhite
      Chart.View3D = false
      Chart.LegendVisible = true
      Chart.LegendStyle = 1

      ' Set the filename, save the image and write the image tag.
        
      ' Do this with sessionID and random name generated via the
      ' FileSystemObject. First make a string with a random name in it. Use
      ' split here to get rid of the txt extension that normally is returned.

      strRandomNameString = Split(Server.CreateObject("Scripting.FileSystemObject").GetTempName,".")(0)
      If (Request.QueryString("specName") <> "") Then
         strFileName2 = Request.QueryString("specName") & ".jpg"
      Else
         strFileName2 = "S" & "_" & Session.SessionID & "_" & strRandomNameString & ".jpg" 
      End If

      'Response.Write "filename = " & strPathToImageDir & strFileName2
        
      Chart.FileName = strPathToImageDir & strFileName2
      Chart.SaveChart
      'Response.Write "path = " & strPathToImageDir & strFileName2
     
      ' Put these two images into a DIV element that doesn't wrap! Then
      ' position the directions overlay relative to the original chart image.

      RC "<div style=""white-space:nowrap;"">"
      RC "<img id='chartimage' style=""visibility:hidden"" src=" & strURLPathToImageDir & strFileName2 & "'>"
      If (strSensor = "Wind40") Then
         RC "<img id='directions' src='pictures/directions_40.gif' style=""visibility:hidden; position:relative; left:" & intPixelRightShift & "px; bottom:" & _
            intPixelBottomShift & "px"">"
      ElseIf (strSensor = "Wind36") Then
         RC "<img id='directions' src='pictures/directions_36.gif' style=""visibility:hidden; position:relative; left:" & intPixelRightShift & "px; bottom:" & _
            intPixelBottomShift & "px"">"
      Else
         ' Could add secondary images for other sensors types here...
      End If
      RC "</div>"

      ' Destroy the object
      Set Chart = nothing
        
   Else
      Response.Write "The query has returned no data for the selected sensor and location."
   End If
     
End Sub

Function TimeZone( strStationName)
   strSQL = "SELECT StationNames.StationName, StationNames.NickName, StationNames.TimeZone FROM StationNames " & _
            "WHERE ([StationName]='" & strStationName  & "') "
   
   PopulateStaticRecordset DBConnection, strSQL, rstTimeZone

   If (rstTimeZone.RecordCount = 0) Then
      TimeZone = "?"
   Else 
      rstTimeZone.MoveFirst
      TimeZone = rstTimeZone("TimeZone")
   End If

   CloseRecordSet rstTimeZone
End Function

Function RegionString( strRegion)
   If (strRegion = "MN") Then
      RegionString = "Minnesota Weather"
   ElseIf (strRegion = "CR") Then
      RegionString = "Columbia Basin Weather"
   ElseIf (strRegion = "Misc") Then
      RegionString = "Misc. Weather Stations"
   Else
      RWBR "No match when branching on Region."
   End If
End Function



'=======================================================================================
' Main program body (start here and execute every time in)
'=======================================================================================
  
' Build the page
%>

<html>
<head>
<meta name='Author' content='James D. (Jim) Miller'>
<meta name='keywords' 
      content='WA,Washington,OR,Orgeon,MN,Minnesota,columbia,basin,weather,chart,plot,roosevelt,
               windsurfing,gorge,richland,wind,temperature,pressure,dewpoint'>             
<meta charset="UTF-8">

<!-- Icon for browsers using Waconia.  --> 
<link rel='SHORTCUT ICON' href='pictures/favicon.ico'>
<title>Waconia Weather Database</title>

<style>
   TD {font-family: Times;}
   TD.data {font-family: Arial;}

   A         {color:#008080; text-decoration:underline}
   A:hover   {color:#008080; text-decoration:none; background:#FFF1E3}

   A.noline       {color:#008080; text-decoration:none;      font-size:18pt; font-weight:bolder;                   }
   A.noline:hover {color:#008080; text-decoration:underline; font-size:18pt; font-weight:bolder; background:#FFCC99}
   
   span.regionstring {color:#008080; font-size:18pt; font-weight:bolder;}
   
   div.pageblock {min-width: 650px; max-width: 1000px;}
</style>

<!--[if IE]>
   <style>
      div.pageblock {width: expression(document.body.clientWidth > 1000? "1000px": "auto" )};
   </style>
<![endif]-->   

</head>

<%  

' Connect to the database.
'OpenDataConnection DBConnection, strConnectionString

' Or, connect using another method as documented here:
' https://saplsmw.com/Use_Classic_ASP_with_Access_Databases_in_Windows_10
' (note: had to install AccessDatabaseEngine.exe)
Set DBConnection = CreateObject("ADODB.Connection")
DBConnection.Provider = "Microsoft.ACE.OLEDB.12.0"
DBConnection.Open "C:\Users\Jim\Documents\webcontent\waconia\data\telem.mdb"

Set dicTZ = Server.CreateObject("Scripting.Dictionary")
dicTZ.Add "H",  -4
dicTZ.Add "AK", -3
dicTZ.Add "P",  -2
dicTZ.Add "M",  -1
dicTZ.Add "C",   0
dicTZ.Add "E",   1
dicTZ.Add "J",  15
dicTZ.Add "NZ", 18

serverTimeArray = split(Now()," ")
serverTime = serverTimeArray(1)

' Establish defaults

' Region_state (hidden) is used to facilitate changing the location to a default value
' when the region is changed.
If (Request.QueryString("Region_state") = "") Then 
   strRegionState = "new"
Else
   strRegionState = Request.QueryString("Region_state")
End If

If (Request.QueryString("Region") = "") Then 
   strRegion = "CR"
Else
   strRegion = Request.QueryString("Region")
End If

If (Request.QueryString("chk24Hrs") = "on") Then
   str24Hrs_state = "checked"
Else
   str24Hrs_state = "" 
End If

If (Request.QueryString("chkRA") = "on") Then
   strRA_state = "checked"
Else
   strRA_state = "" 
End If

If (Request.QueryString("chkTimer") = "on") Then
   strTimer_state = "checked"
Else
   strTimer_state = ""
End If

If (strTimer_state = "checked") Then
   'Check to see how far off the 5-minute mark. This should serve
   'to compensate for the drift in the client side timer.
   
   'Get the seconds and minutes from the server time.
   intSeconds_FromSeconds = CInt(right(serverTime,2))
   intMinutes = CInt(Split(serverTime,":")(1))
   
   'How many five minute chunks.
   dblFiveMinutes = CDbl(intMinutes)/5.0
   
   'Take the fractional part of this and convert to seconds.
   intSeconds_FromMinutes = CInt(round(300*(dblFiveMinutes - Fix(dblFiveMinutes)),0))
   
   'Subtract both of these values from 300 to get the proper delay for the client.
   'Then add 9 to keep it tracking at 10 seconds after the 5-minute mark.
   intDelay_to_5min = 300 - intSeconds_FromMinutes - intSeconds_FromSeconds + 9
   strInitializeTimer = "initializeTimer(" & CStr(intDelay_to_5min) & ");"
   
Else
   strInitializeTimer = ""
End If

blnPostedDate_default = False
If (Request.QueryString("EndDate") = "") Then 
   ' Use the current date for a default. 
   dtePostedDate = CStr(Date())
   blnPostedDate_default = True
Else
   ' Split to just get the DATE part of this post.
   dtePostedDate = split(Request.QueryString("EndDate")," ")(0)
End If

If (Request.QueryString("Days") = "") Then 
   intDays = 1
Else
   intDays = Request.QueryString("Days")
End If

If (Request.QueryString("Sensor") = "") Then 
   strSensor = "Wind40"
Else
   strSensor = Request.QueryString("Sensor")
   ' Don't allow request for Delta-P from any region but CR.
   If (strRegion <> "CR") And (strSensor = "DeltaP") Then
         strSensor = "Wind40"
   End If
End If

' Set the normalization factor for the wind direction data
If (strSensor = "Wind40") Then 
   dblWindNormFactor = 40.0 / 360.0
Else
   dblWindNormFactor = 1.0 / 10.0
End If

' Set a default value for the location if the first time in or if the user changes
' the region.
If ((Request.QueryString("Location") = "") or (strRegionState = "new")) Then 
   If (strRegion = "CR") Then
      strLocation = "PASC"
   ElseIf (strRegion = "MN") Then
      strLocation = "KMKT"   
   ElseIf (strRegion = "Misc") Then
      strLocation = "KCQX"    
   Else
      strLocation = ""
      RWBR "No match in region branch..."
   End If
Else
   strLocation = Request.QueryString("Location")
End If


If ((strSensor = "Wind40") OR (strSensor = "Wind36")) Then
   strShowImages_command = "showImage();showDirections();"
Else
   strShowImages_command = "showImage();"
End If


strTimeZone = TimeZone( strLocation)


RC "<body onLoad='testJS();" & strShowImages_command & strInitializeTimer & _
      "' bgcolor=#FFCC99 link='#008080' vlink='#008080' topmargin='2' style='font-family: Arial;'>"

RC "<div class='pageblock'>"
    

' If the region is specified, then make preparations for populating the table
' including getting the most recent values for all the sensor data.

If (Request.QueryString("Region") <> "") Then

   ' If the end date in the chart request is within daylight savings time, then
   ' set the DLS flag. Add 3 hours to make sure you evaluate the day after the
   ' 2am change over point.

   If (dayLightSavingsTime(dateadd("h",3,dtePostedDate))) Then blnDayLightSavingsTime = True

   ' Get a recordset for the most recent data (to put into the table on
   ' the charting page). For speed, start by querying in the most recent 24 hours of data.
   
   strSQL = "SELECT * FROM FifteenMinData " & _
            "WHERE ([StationName] = '" & strLocation & "') AND " & _
                  "([DateTimeStamp] >=     #" & dateAdd("h",-24,now()) & "#) " & _
            "ORDER BY TimeMDY DESC, TimeHr DESC, TimeMin DESC"
      
   PopulateStaticRecordset DBConnection, strSQL, rstMostRecent
   
   ' If there's no data within the last 24 hours, search the whole database and find the latest timestamp.
   If (rstMostRecent.BOF) Then
   
      ' Find the time of the most recent station record.
      strSQL = "SELECT MAX(DateTimeStamp) as maxDateTime FROM FifteenMinData " & _
               "WHERE ([StationName] = '" & strLocation & "')"
                     
      PopulateStaticRecordset DBConnection, strSQL, rstLatestDate
      dteMaxTimeStamp = rstLatestDate("maxDateTime")
      CloseRecordSet rstLatestDate
            
      ' Build a recordset for getting the most recent record to
      ' put into the table on the charting page.
      strSQL = "SELECT * FROM FifteenMinData " & _
               "WHERE ([StationName] = '" & strLocation & "') AND " & _
               "      ([DateTimeStamp] = #" & FormatDateTime(dteMaxTimeStamp, vbGeneralDate) & "#) "
               
      PopulateStaticRecordset DBConnection, strSQL, rstMostRecent
   
   End If
   
   ' If a default value was used for the posted date, correct it if the posted date
   ' is more recent than the most recent data.
   'RWBR "Default=" & dtePostedDate & ", MostRecent=" & rstMostRecent("TimeMDY")
   If blnPostedDate_default and (DateDiff("d", dtePostedDate, rstMostRecent("TimeMDY")) < 0) Then
      dtePostedDate = rstMostRecent("TimeMDY")
   End If
   
   ' Check to see if there are any records before applying the MoveFirst method
   If (Not rstMostRecent.BOF) Then
      
      rstMostRecent.MoveFirst
      
      'Warning: this variable changes type here.
      strMRTime = rstMostRecent("TimeMDY") & " " & rstMostRecent("TimeHr") & ":" & rstMostRecent("TimeMin")
      strMRTime = FormatDateTime(strMRTime, vbGeneralDate)
      
      If (rstMostRecent("WindDirection") = -10) then
         strMRWindDir = "Variable"
      Else
         If IsNull(rstMostRecent("WindDirection")) Then
            strMRWindDir = "-"
         Else
            strMRWindDir = rstMostRecent("WindDirection") & _
                           " deg. [" & DirectionLabel(rstMostRecent("WindDirection")) & "]" & _
                           " [" & FormatNumber(rstMostRecent("WindDirection") * dblWindNormFactor, 1) & "]"
         End If
      End If    
      If IsNull(rstMostRecent("WindSpeed")) Then
         strMRWindAvg = "-" 
         strMRWindMax = "-"
      Else
         strMRWindAvg = rstMostRecent("WindSpeed")
         strMRWindMax = rstMostRecent("WindGust")
      End If

      If IsNull(rstMostRecent("Pressure")) Then
         strMRPressure = "-"
      Else
         strMRPressure = round(rstMostRecent("Pressure"),2)
      End If 

      strMRTemp = rstMostRecent("TempAvg")
      If (IsNull(strMRTemp)) Then
         strMRTemp = "-"
      End If
      
      strMRDewPoint = rstMostRecent("DewPoint") 
      If (IsNull(strMRDewPoint)) Then
         strMRDewPoint = "-"
      End If
   
   Else
      strMRTime = "-"
      strMRWindDir = "-"
      strMRWindAvg = "-"
      strMRWindMax = "-"
      strMRTemp = "-"
      strMRPressure = "-"   
      strMRDewPoint = "-" 
   End If
   
   CloseRecordSet rstMostRecent

   strButtonLabel = "Update"
   
Else
   dtePostedDate = ""

   ' Before first post (first time in) just show these dashes in the table...
   strMRTime = "-"
   strMRWindDir = "-"
   strMRWindAvg = "-"
   strMRWindMax = "-"
   strMRTemp = "-"
   strMRPressure = "-"
   strMRDewPoint = "-" 

   strButtonLabel = "Chart"
   
End if

'IP message to a particular user.
'IPMessage
'RWBR "Debug Message = " & strDebugMessage

'===========================================================================
' The current data table and CONTROLS form...
'===========================================================================
RC "<table border='1'>"

' First row

RC "<tr>"

RC "<td class='data' width='37%' rowspan='3'>"
'RC "<p align='center'><a onmouseover=""changeRegionAnchorValue('" & strRegion & "')"" onmouseout=""changeRegionAnchorValue('" & strTitle & "')"" name='regionanchor' id='regionanchor' class='noline' href='" & strRegionURL & "'>" & strTitle  & "</a>&nbsp;<br>"
RC "<p align='center'><span class='regionstring'>" & RegionString( strRegion) & "</span><br>"
RC "<a target='_blank' href='http://waconia.timetocode.org/FAQ.htm'><font size='2' color='#FF0000'>Help</font>" & _
                     "<font size='2' color='#008080'>: FAQs</font></a>&nbsp;"

If (strRegion = "MN") Then
   RC "<a href='pictures/mn_sites.jpg'><font size='2' color='#008080'>Sites</font></a>&nbsp;"
End If
RC "<a href='default.htm'><font size='2'>(home)</font></a>"

' Create a object for working with the image files...
Set fsoObject = CreateObject("Scripting.FileSystemObject")
' Note: path to image directory is defined in include file.
Set fdrObject = fsoObject.GetFolder(strPathToImageDir)
         
' Clean out any old temp image files. This is a new approach that doesn't depend on script in the global ASA
intFileCount = 0
For Each filObject in fdrObject.Files
   ' Count files that are less than 1 day old.
   If (DateDiff("h", filObject.DateLastModified, Now()) <= 24) Then
      intFileCount = intFileCount + 1
   End If
   ' Delete files that are more than three days old.
   If (DateDiff("h", filObject.DateLastModified, Now()) > 72) Then   
      filObject.delete
   End If  
Next         

' Write out a count of image files in the directory (1 and 7 day counts).
' Put the serverTime in a span so can access it from the client (if needed, may not actually use this).          
RC "<font color='#008080'  size='1'>" & _
   "&nbsp;&nbsp;" & intFileCount & "-(1d)&nbsp;&nbsp;" & fdrObject.Files.Count & "-(3d)&nbsp;&nbsp;" & _
   "<span id='spServerTime' name='spServerTime'>" & serverTime & "</span>" & _
   " (" & AgeOfData(strMRTime) & ")" & _
   "</font>" & _
   "</p>"
RC "</td>"


' Rest of the table headers
RC "<td width='23%' align='center' rowspan='2'><b><font color='#FF0000'>Latest</font>"
RC "<font color='#008080'> Reading"
RC "</font></b>"
RC "</td>"

RC "<td width='26%' align='center' colspan='3'><font color='#008080'><b>Wind </b><font size='2'> (mph)</font></font></td>"

RC "<td nowrap width='6%' align='center' colspan='2' rowspan='1'><font color='#008080'><b>Temp</b><font size='2'> (<sup>o</sup>F)</font></font></td>"
RC "<td width='8%' align='center' rowspan='2'><font color='#008080'><b>Pressure<br></b><font size='2'> (in Hg" & strHGSL & ")</font></font></td>"
RC "</tr>"

' Second row

RC "<tr>"
RC "<td width='6%' align='center'><font color='#008080' size='2'>Avg</font></td>"
RC "<td width='5%' align='center'><font color='#008080' size='2'>Max</font></td>"
RC "<td width='18%' align='center'><font color='#008080' size='2'>Direction</font></td>"
RC "<td align='center'><font color='#008080' size='2'>DryBulb</font></td>"
RC "<td align='center'><font color='#008080' size='2'>DewPoint</font></td>"
RC "</tr>"

' Third row

RC "<tr>"
RC "<td class='data' width='20%' align='center'><font color='#000000' size='2'>"
If (strMRTime <> "-") Then
   If (dayLightSavingsTime(strMRTime) And (strTimeZone <> "H")) Then
      Response.Write DateAdd("h",1,strMRTime) & " (" & strTimeZone & "DT)"
   Else
      Response.Write               strMRTime  & " (" & strTimeZone & "ST)"
   End If
Else
   Response.Write strMRTime
End If
RC "</font></td>"
RC "<td class='data' width='6%' align='center'><font color='#000000' size='2'>" & strMRWindAvg & "</font></td>"
RC "<td class='data' width='5%' align='center'><font color='#000000' size='2'>" & strMRWindMax & "</font></td>"
RC "<td class='data' width='18%' align='center'><font color='#000000' size='2'>" & strMRWindDir & "</font></td>"
RC "<td class='data' width='6%' align='center'><font color='#000000' size='2'>" & strMRTemp & "</font></td>"
RC "<td class='data' width='6%' align='center'><font color='#000000' size='2'>" & strMRDewPoint & "</font></td>"
RC "<td class='data' width='8%' align='center'><font color='#000000' size='2'>" & strMRPressure & "</font></td>"
RC "</tr>"

RC "</table>"

'=============================================================================
' Build a line of controls
'=============================================================================   

RC "<br>"
' Note that the GET method invokes the QueryString approach and submits form data in the URL.
RC "<form method='GET' accept-charset='utf-8' action='rosy.asp' name='ChartingParameters' id='ChartingParameters'>"

' Removing the "name" parameter here avoids submitting this with the form.
' Another option is to use "button" instead of "input".


' The submit button.

'RC "<...........................................name='submit_button'>"
RC "<input type='button' title='Query the database and update the plot.' value='" & strButtonLabel & "' name='myButton' id='myButton' style='width: 90px' onclick='submitform()'>"


' Region

RC "<select title='Region' size='1' name='Region' id='Region' onChange='setRegionState()'>"
arrRegions = Array("MN","CR","Misc")
For each strRegionValue in arrRegions
   If (strRegionValue = strRegion) Then
      RC "   <option selected>" & strRegionValue
   Else
      RC "   <option>" & strRegionValue
   End If
Next
RC "</select>"

' A hidden field that serves to indicate whether a new region has been selected. This is needed
' for determining the default location if the region selection changes.
RC "<input type='hidden' name='Region_state' id= 'Region_state' value='old'>"


' Location
'RWBR "strRegion = " & strRegion & ", RS= " & Request.QueryString("Region_state") & ", " & "Request.QueryString('Location') = " & Request.QueryString("Location") & ", strLocation = " & strLocation 

RC "<select title='Location of weather station' size='1' name='Location' id='Location' onChange='submitform()'>"

strSQL = "SELECT StationNames.Priority, StationNames.StationName, StationNames.NickName FROM StationNames " & _
         "WHERE ([Region]='" & strRegion  & "') " & _
         "ORDER BY Priority, NickName"

PopulateStaticRecordset DBConnection, strSQL, rstStations
rstStations.movefirst

Do until rstStations.eof 
   ' Exclude inactive stations from the selection list (marked as "skip" in the database).
   If (InStr(rstStations("Priority"),"skip")=0) Then
   
      'Populate the list and set the selected station for the two regions.
      If (rstStations("StationName") =  strLocation) Then 
         strNameForPlot = rstStations("NickName")
         RC "   <option value='" & rstStations("StationName") & "' selected>" & rstStations("NickName") 
      Else
         RC "   <option value='" & rstStations("StationName") & "'>" & rstStations("NickName")
      End If
   
   End If
   
   rstStations.movenext
   
loop

CloseRecordSet rstStations
RC "</select>"


' Click for next location.

RC "<INPUT  title='Click to step through the list of locations.' type='button' style='WIDTH:18px; HEIGHT:23px; COLOR:black; padding-left:3px;' value='>' id='btnStepLocationForward' name='btnStepLocationForward' onClick='stepLocationForward()'>"


' Sensor type

RC "<select title='Sensor type' size='1' name='Sensor' id='Sensor' onChange='submitform()'>"

WeatherTypes =     Array("Wind (0-36)", "Wind (0-40)", "Temperature", "Pressure", "Delta-P1", "Delta-P2")
WeatherTypes_URL = Array("Wind36",      "Wind40",      "Temperature", "Pressure", "DeltaP1" , "DeltaP2") 
WeatherTypes_count = UBound(WeatherTypes)

' Don't offer the Delta-P plot anywhere but in the Columbia Basin.
If (strRegion <> "CR") then
   WeatherTypes_count = WeatherTypes_count - 2 
End If

For intJ = 0 to WeatherTypes_count 
   If ((WeatherTypes_URL(intJ)= strSensor) OR ((strSensor = "") AND (WeatherTypes_URL(intJ)= "Wind40"))) Then
      RC "   <option selected value=" & WeatherTypes_URL(intJ) & " >" & WeatherTypes(intJ)
   Else
      RC "   <option value=" & WeatherTypes_URL(intJ) & " >" & WeatherTypes(intJ)
   End If
Next
RC "</select>"


' Select the last day.

RC "<select title='Last day' size='1' name='EndDate' id='EndDate' onChange='submitform()'>"
strSQL = "SELECT DISTINCT DaysGleaned.TimeMDY FROM DaysGleaned ORDER BY DaysGleaned.TimeMDY DESC"
  
' See IIShelp for description of parameters: Open Method (Recordset - ADO).
' The AdCmdText just tells it that it is a SQL string in the first parameter.
' Alternatively you could tell it that the first parameter is a table name...

PopulateStaticRecordset DBConnection, strSQL, rstDate
         
rstDate.movefirst
do until rstDate.eof 
   ' Coerce the date object to a string by using the (& "")
   If ((dtePostedDate = (rstDate("TimeMDY") & "")) OR ((dtePostedDate = "") AND (rstDate("TimeMDY") = Date()))) then
      RC "   <option selected>" & rstDate("TimeMDY") & " " & weekdayname(weekday(rstDate("TimeMDY")),True)
   Else
      RC "   <option>" & rstDate("TimeMDY") & " " & weekdayname(weekday(rstDate("TimeMDY")),True)
   End If  
   rstDate.movenext
loop
CloseRecordSet rstDate
RC "</select>"


' Select the time range.
  
RC "&nbsp;&nbsp;&nbsp;<font color='#008080'>Days:</font>"

RC "<select title='Time range' size='1' name='Days' id='Days' onChange='submitform()'>"
DaysChoices = Array("1","2","3","4","5","6","7","8","9","10","14","25")
For each DayValue in DaysChoices
   If (DayValue = intDays) Then
      RC "   <option selected>" & DayValue
   Else
      RC "   <option>" & DayValue
   End If
Next
RC "</select>"


' Time steppers

RC "<INPUT title='Click to step back in time.' type='button' style='WIDTH: 18px; HEIGHT: 23px; COLOR: black; padding-left:3px;' value='<' id='btnStepBack' name='btnStepBack' onClick='stepBack()'>"
RC "<INPUT title='Click to step forward in time.' type='button' style='WIDTH: 18px; HEIGHT: 23px; COLOR: black; padding-left:3px;' value='>' id='btnStepForward' name='btnStepForward' onClick='stepForward()'>"


' The 24-Hour charting option.
RC "&nbsp;&nbsp;" & _
   "<input " & str24Hrs_state & " type='checkbox' name='chk24Hrs' " & _
   "title='Select to display 24 hours of the most recent data (including data from yesterday) on the 1-day chart. " & _
   "Please refer to the FAQ on the ""24h"" checkbox.' " & _
   "onClick='submitform()'/>" & _
   "<font size='2' color='#008080'>24h</font>"
   
' The Running-average option
RW "" & _
   "<input " & strRA_state & " type='checkbox' name='chkRA' " & _
   "title='Select to apply a running average to all the data.' " & _
   "onClick='submitform()'/>" & _
   "<font size='2' color='#008080'>RA</font>"
   
' The timer for auto-plots
RW "&nbsp;" & _
   "<input " & strTimer_state & " type='checkbox' name='chkTimer' " & _
   "title='Select to enable a repeating 5-minute countdown timer. This is synchronized with the server to trigger a chart update immediately after " & _
   "the database has been updated.' " & _
   "onClick='submitform()'/>"

If (strTimer_state = "checked") Then
   ' The space in the span is needed for an initial value. The client-sided JavaScript changes this value
   ' every second.
   strTimer_value = " "
Else
   strTimer_value = "Timer"
End If
RW "<span id='spTimerSec' name='spTimerSec' style='color:#008080; font-size:10pt;'>" & strTimer_value & "</span>"


' A hidden field that serves to test if the client has JavaScript enabled. Some script will
' try to change this value from F to T.
RC "<input type='hidden' name='jS' id='jS' value='F'>"

RC "</form>"

If (Request.QueryString("jS") = "F") Then
   RBC "JavaScript is needed to use the charting controls and view a chart image."
   RBC ""
   RBC "Please enable JavaScript in your web browser. If you enable JavaScript, this warning"
   RBC "will clear after your second click of the press-to-chart button."
   RBC ""
   RBC "Note that requesting a chart update before the previous chart has completed is another"
   RBC "possible cause for this error message. Please wait until the image returns from the"
   RBC "server."
Else
   '=================================================================================
   ' PLOT THE CHART...
   '
   ' If the region has been specified in the query, then plot the chart.
   '
   '=================================================================================
   If ((Request.QueryString("Region") <> "") and (strMRTime <> "-")) Then
      PlotTheChart
   Else
      RWBR ""
      RWBR "The query has returned no data for the selected sensor and location."
   End If
End If

' Close connection to the database
CloseDataConnection DBConnection

'RBC "Testing"
'RBC "Date = " & Request.QueryString("EndDate") 

%>


<SCRIPT LANGUAGE=javascript RUNAT=Server>

// Server Side Scripting in JavaScript

// Running average prototype (a class)
function RunningAverage( n_StackSize){
   this.queue = [];
   this.n_StackSize = n_StackSize;
   this.recordCount = 0;
   this.recordIndex = 0;
   
   this.reset = function( recordCount){
      this.queue = [];
      this.recordIndex = 0;
      this.recordCount = recordCount;
      //Response.write("////////////////////////////<br><br>");
   }
   
   this.update = function( newValue){
      var total = 0;
      var n_FromEnd = 0;
      var average = 0;
      this.recordIndex = this.recordIndex + 1;
      
      //Add one to the top.
      this.queue.push( newValue);
      
      //Scrape one off the bottom.
      if (this.queue.length > this.n_StackSize) {
         this.queue.shift();
         //Response.write("Normal: one from bottom.<br>");   
      } 
           
      // As the record index approaches the end of the recordset, gradually turn
      // off the running average (empty out the bottom of the queue). This causes
      // the last value in the running average to equal the latest reading.
      
      //Hmmmm, the need for this "+ 1" here is a nagging mystery.
      n_FromEnd = (this.recordCount + 1) - this.recordIndex;  
      if (n_FromEnd == this.n_StackSize-2) {
         // Take only one (additional) off.
         this.queue.shift();   
         //Response.write("Special: one from bottom.<br>");   
         
      //} else if ((n_FromEnd >= 0) && (n_FromEnd < this.n_StackSize-2)){
      } else if (n_FromEnd < this.n_StackSize-2){
      
         // Take two off the bottom (because the normal bottom scraping won't
         // be triggered as the queue size diminishes).
         this.queue.shift();
         this.queue.shift();
         //Response.write("Special: two from bottom.<br>");   
      }
      
      //Sum the values.
      for (var i in this.queue) {
         total += this.queue[i]; 
      }
      
      average = total / this.queue.length;
      
      // Debug statements.
      //Response.write("--New=" + newValue + "--T=" + total + "--L=" + this.queue.length + "--A=" + average + 
      //               "--n_FEnd=" + n_FromEnd + "--Index=" + this.recordIndex + "---RC=" + this.recordCount + "<br>\n");
    
      return average;
   }
}

// Running average prototype for direction data (using components);
function RunningAverage_Dir( n_StackSize){
   this.n_StackSize = n_StackSize;
   // Instantiate a running average for each of the components.
   this.RA_x = new RunningAverage( n_StackSize);
   this.RA_y = new RunningAverage( n_StackSize);
   
   this.reset = function( recordCount){
      this.RA_x.reset( recordCount);
      this.RA_y.reset( recordCount);
   }   
   
   this.update = function( newDir_deg){
      // Determine the components of a unit vector at the specified direction
      // in radians.
      var x = Math.cos( newDir_deg * (Math.PI/180.0) );
      var y = Math.sin( newDir_deg * (Math.PI/180.0) );
   
      // Add each component to a the running average.
      var x_avg = this.RA_x.update( x);
      var y_avg = this.RA_y.update( y);
      
      // Determine the average angle from the running averages of the components. 
      var averageDir_deg = Math.atan2( y_avg, x_avg) * (180.0/Math.PI);
      
      // Transform the output so that all directions are positive.
      if (averageDir_deg < 0) {
         var averageDir_deg_corrected = averageDir_deg + 360.0;
      } else {
         var averageDir_deg_corrected = averageDir_deg +   0.0;
      }
            
      return averageDir_deg_corrected;
   }
}

function instantiateRunningAverages( traceName){
   // Make two running average objects for the chart, each a 3-point average.   
   
   // Set the number of points in the running average.
   var nPoints = 3;
   
   // These instantiated objects have global scope if the "var" word is not used 
   // in the assignment.
   RA_x = new RunningAverage( nPoints);  
   
   // Use a special running average for the wind-direction data.
   if (traceName == 'WindDirection') {
      RA_y = new RunningAverage_Dir( nPoints);
   } else {
      RA_y = new RunningAverage( nPoints);
   }
}

// This function determines if the supplied date is within daylight savings time.
// It does this by comparing the difference between local time and GMT. This difference
// is 5 hours (in the central time zone) during daylight savings time.

function dayLightSavingsTime( dateToCheck ){
   var dateObjectToCheck = new Date( dateToCheck);
   // Return true/false
   return (dateObjectToCheck.getTimezoneOffset() == 5*60);
}

</SCRIPT>



<!--  Client side script -->
<SCRIPT LANGUAGE="javascript">
<!--

//Globals

var cP = document.getElementById('ChartingParameters');

var cmbEndDate = document.getElementById('EndDate');
var cmbDays = document.getElementById('Days');
var cmbLocation = document.getElementById('Location');

var stepIncrement = cmbDays.options[cmbDays.selectedIndex].text;

function testJS(){
   document.getElementById('jS').value = 'T';
}

function showDirections(){
   try {
      var imgDirections = document.getElementById('directions');
      imgDirections.style.visibility = 'visible';
   }
   catch(e){}
}

function showImage(){
   try {
      var imgChartImage = document.getElementById('chartimage');
      imgChartImage.style.visibility = 'visible';
   }
   catch(e){}
}

function changeColorSubmitButton(){
   document.getElementById('myButton').style.color='red';
}

function submitform(){
   //document.getElementById('Sensor').style.backgroundColor='#FFE4C4';
   document.getElementById('myButton').value = 'Please Wait';
   cP.submit();
}

function stepLocationForward(){
   var targetIndex = cmbLocation.selectedIndex;
   if (targetIndex < (cmbLocation.length - 1)){
      cmbLocation.selectedIndex = targetIndex + 1;
   } else {
      cmbLocation.selectedIndex = 0;
   }
   submitform();
}

function stepBack(){
   var targetIndex = cmbEndDate.selectedIndex + (stepIncrement * 1.0);
   if (targetIndex > (cmbEndDate.length - 1)){
      cmbEndDate.selectedIndex = cmbEndDate.selectedIndex;
   } else {
      cmbEndDate.selectedIndex = targetIndex;
   }
   submitform();   
}

function stepForward(){
   var targetIndex = cmbEndDate.selectedIndex - (stepIncrement * 1.0);
   if (targetIndex < 0){
      cmbEndDate.selectedIndex = 0;
   } else {
      cmbEndDate.selectedIndex = targetIndex;
   }
   submitform();   
}

//Timer functions

var secs;
var timerID = null;
var timerRunning = false;
var delay = 1000;

function initializeTimer(secsFromChart){

   // Set the length of the timer, in seconds
   if (secsFromChart == null){
      if (timerRunning){
         secs = secs - 5;
         if (secs < 0){ 
            secs = 3;
         }
      }else{
         if (secs == null){
            secs = 298;
         }
      }
   }else{
      secs = secsFromChart;   
   }
    
   stopTheTimer();
   startTheTimer();
}

function stopTheTimer(){

   if (timerRunning){
      clearTimeout(timerID);
      timerRunning = false; 
      // This color change was used when there was a pause mode.
      //document.getElementById('spTimerSec').style.color = 'red';
   }
}

function startTheTimer(){

   //Reset the color back to normal.
   //document.getElementById('spTimerSec').style.color = '#008080';

   if (secs==0){
      //stopTheTimer();
        
      // Here's where you put something useful that's
      // executes after the allotted time.
      submitform();
    
   }else{
      self.status = secs;
      if (secs < 10){
         secs = ' ' + secs;
      }
      document.getElementById('spTimerSec').firstChild.nodeValue = '' + secs + 's.';
      secs = secs - 1;

      timerRunning = true;
      timerID = self.setTimeout("startTheTimer()", delay);
   }
}

function changeRegionAnchorValue( theInputString){
   //window.alert( theInputString);
   if (theInputString=='MN') {
      document.getElementById('regionanchor').firstChild.nodeValue = 'Columbia Basin Weather';
   } else if (theInputString=='CR') {
      document.getElementById('regionanchor').firstChild.nodeValue = 'Minnesota Weather';
   } else {
      document.getElementById('regionanchor').firstChild.nodeValue = theInputString;
   }
}

function setRegionState(){
   document.getElementById('Region_state').value = 'new';
   submitform(); 
}

//-->
</SCRIPT>
</div>
</body>
</html>