• Hi All

    Please note that at the Chandoo.org Forums there is Zero Tolerance to Spam

    Post Spam and you Will Be Deleted as a User

    Hui...

  • When starting a new post, to receive a quicker and more targeted answer, Please include a sample file in the initial post.

MS Basic to VBA

NicGreen

Member
Hi All,

Currently i am trying to convert an old MS BASIC code into VBA for use with an Excel Spreadsheet. The MS BASIC Code is as per below.

Code:
10 REM TIME OF CONCENTRATION PROGRAM FOR OVERLAND FLOWS
20 REM USING KINEMATIC WAVE EQUATION
30 REM (IN MICROSOFT BASIC)
40 REM
50 DIM L(20),N(20),S(20)
60 REM CONSTANTS FOR 2 YEAR ARI INTENSITIES AT PENRITH, NSW
70 A = 3.382
80 B = -.579
90 C = -.0208
100 D = .00914
110 E = -.001066
120 F = -.0004188
130 G = .0000614
140 REM
150 PRINT
160 PRINT "TIME OF CONCENTRATION FOR OVERLAND FLOWS"
170 PRINT
180 INPUT "PROPERTY DRAINAGE + GUTTER FLOW TIME (MIN)?", CTIME
190 PRINT
200 PRINT "NUMBER OF OVERLAND FLOW SEGMENTS?"
210 INPUT NS
220 FOR J = 1 TO NS
230 PRINT "LENGTH (m), SLOPE (m/m) AND ROUGHNESS FOR SEGMENT" ;J
240 INPUT L(J),S(J),N(J)
250 NEXT J
260 TI = 5
270 CC = 1
280 PRINT "ITERATION  INTENSITY  ESTIMATED AND CALCULATED TIMES"
290 PRINT"    NO.      (mm/h)        (min)          (min)"
300 PRINT
310 REM START OF ITERATIONS
320 T = CTIME
330 TL = 0
340 REM CALCULATE INTENSITY FOR GIVEM TIME 'TI'
350 LT = LOG(TI / 60)
360 I = EXP(A + B*LT + C*LT^2 + D*LT^3 + E*LT^4 + F*LT^5 + G*LT^6)
370 FOR J = 1 TO NS
380 FL = TL
390 TL = TL + L(J)
400 T = T + 6.94 * (TL*N(J))^.6 / (I^.4 * S(J)^.3)
410 IF J = 1 THEN GOTO 430
420 T = T - 6.94 * (FL*N(J))^.6 / (I^.4 * S(J)^.3)
430 NEXT J
440 PRINT USING "  ###,  ####.#,  ####.##,  ####.##";CC,I,TI,T
450 IF ABS(T-TI) < 0.01 THEN GOTO 490
460 CC = CC + 1
470 TI = T
480 GOTO 320
490 PRINT
500 IF T > 5 THEN GOTO 520
510 PRINT "TIME IS LESS THAN 5 minutes - VALUE BELOW IS NOT EXACT"
520 PRINT USING "TIME IS ####.# minutes FOR INTENSITY ####.# mm/h";T,I
530 END

As you can see at Line 370 the For J = 1 to NS is initiated and completes it loop at like 430. However at line 480 it seems to jump back into the loop. Is there a way i can achieve this in VBA?

Currently my VBA code (apologies for the untidiness, i haven't cleaned it up) is as follows.

Code:
Private Sub CommandButton2_Click()
Dim ctime As String, NS As Double, tbl As ListObject, FSTable As Range, L As Range, Results As Range, R As Double, T As Double, S As Double
Set tbl = ActiveSheet.ListObjects("FS")
Set Res = ActiveSheet.ListObjects("Table2")
Set FSTable = ActiveSheet.Range("FS")
NS = tbl.Range.Rows.Count - 1
A = Range("CoefA").Value
B = Range("CoefB").Value
C = Range("CoefC").Value
D = Range("CoefD").Value
E = Range("CoefE").Value
F = Range("CoefF").Value
G = Range("CoefG").Value
TI = 5
CC = 1
ctime = Range("Ctime").Value
TL = 0
T = 0
Iteration = 1


For Each L In FSTable.Columns(2).Cells
If Iteration > 1 Then
T = ctime
TL = 0
Else
End If
LT = Log((TI / 60))
INTENSITY = Exp(A + (B * LT) + (C * LT ^ 2) + (D * LT ^ 3) + (E * LT ^ 4) + (F * LT ^ 5) + (G * LT ^ 6))


S = FSTable.Cells(Iteration, 3)
R = FSTable.Cells(Iteration, 4)


FL = TL
TL = TL + L

T = T + (6.94 * (((TL * R) ^ 0.6) / ((INTENSITY ^ 0.4) * (S ^ 0.3))))

If Iteration = 1 Then
GoTo Skip
Else
T = T - (6.94 * (((FL * R) ^ 0.6) / ((INTENSITY ^ 0.4) * (S ^ 0.3))))
End If

If Abs(T - TI) < 0.01 Then
GoTo Display
Else



End If

Display:
Res.DataBodyRange(Iteration, 3).Value = TI
Skip:
Res.DataBodyRange(Iteration, 1).Value = Iteration
Res.DataBodyRange(Iteration, 2).Value = INTENSITY
Res.DataBodyRange(Iteration, 3).Value = TI
Res.DataBodyRange(Iteration, 4).Value = T
TI = T
Iteration = Iteration + 1
Next
End Sub

This however doesn't produce the same results when compared with the BASIC program using the following inputs

Segment 1 Length 68 Slope 0.13 Roughness 0.04
Segment 2 Length 30 Slope 0.01 Roughness 0.035
Segment 3 Length 15 Slope 0.11 Roughness 0.04
Appreciate any direction on this one
 
Hi ,

I tried out the following code as it is , and it runs to completion :
Code:
Public Sub temp()
10 Rem TIME OF CONCENTRATION PROGRAM FOR OVERLAND FLOWS
20 Rem USING KINEMATIC WAVE EQUATION
30 Rem (IN MICROSOFT BASIC)
40 Rem
50 Dim L(20), N(20), S(20), T As Double, NS As Integer, CTIME As Double, J As Integer
60 Rem CONSTANTS FOR 2 YEAR ARI INTENSITIES AT PENRITH, NSW
70 A = 3.382
80 B = -0.579
90 C = -0.0208
100 D = 0.00914
110 E = -0.001066
120 F = -0.0004188
130 G = 0.0000614
140 Rem
150 Debug.Print
160 Debug.Print "TIME OF CONCENTRATION FOR OVERLAND FLOWS"
170 Debug.Print
180 CTIME = Val(InputBox("PROPERTY DRAINAGE + GUTTER FLOW TIME (MIN)?"))
190 Debug.Print
200 Debug.Print "NUMBER OF OVERLAND FLOW SEGMENTS?"
210 NS = Val(InputBox(""))
220 For J = 1 To NS
230 Debug.Print "LENGTH (m), SLOPE (m/m) AND ROUGHNESS FOR SEGMENT"; J
240 L(J) = Val(InputBox("LENGTH (m)")) : S(J) = Val(InputBox("SLOPE (m/m)")) : N(J) = Val(InputBox("ROUGHNESS FOR SEGMENT"))
250 Next J
260 TI = 5
270 CC = 1
280 Debug.Print "ITERATION  INTENSITY  ESTIMATED AND CALCULATED TIMES"
290 Debug.Print "    NO.      (mm/h)        (min)          (min)"
300 Debug.Print
310 Rem START OF ITERATIONS
320 T = CTIME
330 TL = 0
340 Rem CALCULATE INTENSITY FOR GIVEN TIME 'TI'
350 LT = Log(TI / 60)
360 I = Exp(A + B * LT + C * LT ^ 2 + D * LT ^ 3 + E * LT ^ 4 + F * LT ^ 5 + G * LT ^ 6)
370 For J = 1 To NS
380 FL = TL
390 TL = TL + L(J)
400 T = T + 6.94 * (TL * N(J)) ^ 0.6 / (I ^ 0.4 * S(J) ^ 0.3)
410 If J = 1 Then GoTo 430
420 T = T - 6.94 * (FL * N(J)) ^ 0.6 / (I ^ 0.4 * S(J) ^ 0.3)
430 Next J
440 Debug.Print USING; "  ###,  ####.#,  ####.##,  ####.##"; CC, I, TI, T
450 If Abs(T - TI) < 0.01 Then GoTo 490
460 CC = CC + 1
470 TI = T
480 GoTo 320
490 Debug.Print
500 If T > 5 Then GoTo 520
510 Debug.Print "TIME IS LESS THAN 5 minutes - VALUE BELOW IS NOT EXACT"
520 Debug.Print USING; "TIME IS ####.# minutes FOR INTENSITY ####.# mm/h"; T, I
End Sub
I did the following replacements :

Print ------------------- Debug.Print

Input ------------------- InputBox

VBA accepts the line numbering and respects it for the GoTo statements.

Narayan
 
Can you provide us the file you are using as well as what inputs and outputs you use and expect from the original code and the new code
 
Thanks Guys,

Hui,

Attached is the sheet i have setup. The overland flow segments have been prefilled with sample data but the results are wrong. The results should be as follows.

Iteration Intensity Estimated Time Calculated time
1 96.1 5 6.53
2 87.2 6.53 6.77
3 86 6.77 6.80
4 85.8 6.80 6.81

The idea is that the estimated time and the calculated time should converge to be within 0.01
 

Attachments

  • Kinematic Wave.xlsm
    29.4 KB · Views: 2
How is this?

Code:
Private Sub CommandButton2_Click()
 '  TIME OF CONCENTRATION PROGRAM FOR OVERLAND FLOWS
 '  USING KINEMATIC WAVE EQUATION
 '  (IN MICROSOFT BASIC)
 '
Dim L(20) As Variant, N(20) As Variant, S(20) As Variant
Dim T As Double, NS As Integer, J As Integer
Dim A As Double, B As Double, C As Double, D As Double, E As Double, F As Double, G As Double
Dim CTIME As Double

'  CONSTANTS FOR 2 YEAR ARI INTENSITIES AT PENRITH, NSW
Worksheets("Sheet1").Select
'Clear Report area
Range("K7").Select
Range(Selection, Selection.End(xlToRight)).Select
Range(Selection, Selection.End(xlDown)).Select
Selection.ClearContents
Range("F3").Select
A = [C6] '3.382
B = [C7] '-0.579
C = [C8] '-0.0208
D = [C9] ' 0.00914
E = [C10] '-0.001066
F = [C11] '-0.0004188
G = [C12] '0.0000614


Debug.Print "Time of Concentration for overland flows"

CTIME = [D3] 'PROPERTY DRAINAGE + GUTTER FLOW TIME (MIN)

NS = Range("F" & Rows.Count).End(xlUp).Row - 6

For J = 1 To NS
  L(J) = Cells(6 + J, 7).Value 'Length
  S(J) = Cells(6 + J, 8).Value 'Slope
  N(J) = Cells(6 + J, 9).Value 'Roughness
Next J
TI = 5
CC = 1
Debug.Print
Debug.Print "ITERATION  INTENSITY  ESTIMATED AND CALCULATED TIMES"
Debug.Print "  No.  (mm/h)  (min)  (min)"
Debug.Print

'  START OF ITERATIONS
100:
T = CTIME
TL = 0
 '  CALCULATE INTENSITY FOR GIVEN TIME 'TI'
LT = Log(TI / 60)
I = Exp(A + B * LT + C * LT ^ 2 + D * LT ^ 3 + E * LT ^ 4 + F * LT ^ 5 + G * LT ^ 6)
For J = 1 To NS
  FL = TL
  TL = TL + L(J)
  T = T + 6.94 * (TL * N(J)) ^ 0.6 / (I ^ 0.4 * S(J) ^ 0.3)
  If J = 1 Then GoTo 200
  T = T - 6.94 * (FL * N(J)) ^ 0.6 / (I ^ 0.4 * S(J) ^ 0.3)
200: Next J
 Debug.Print "  "; CC, Round(I, 2), Round(TI, 2), Round(T, 2)
 Cells(6 + CC, 11).Value = CC
 Cells(6 + CC, 12).Value = I
 Cells(6 + CC, 13).Value = TI
 Cells(6 + CC, 14).Value = T
 If Abs(T - TI) < 0.01 Then GoTo 300
 CC = CC + 1
 TI = T
GoTo 100

300:
Debug.Print
If T > 5 Then GoTo 400

Debug.Print "Time is less than 5 Minutes - Value below is not exact"
400: Debug.Print "Time is "; CStr(Round(T, 2)); " minutes for Intensity"; CStr(Round(I, 1)); " mm/h"

End Sub

It takes and returns all input/output from the worksheet

see attached file:
 

Attachments

  • Kinematic Wave.xlsm
    31.6 KB · Views: 4
Back
Top