Subido por Zack Vincent

1

Anuncio
Option Explicit
Public imageArray As Variant
Public keyCol As Long, keyCol2
Function QSortedArray(ByVal inputRange As Variant, Optional keyColumn As Long, Optional keyColumn2 As Long, Optional Descending As Boolean) As Variant
Dim RowArray As Variant
Dim outRRay As Variant
Dim i As Long, j As Long, size As Long
If keyColumn = 0 Then keyColumn = 1
Rem Input array vs range handeling
On Error GoTo HaltFunction
Select Case TypeName(inputRange)
Case Is = "Range"
If inputRange.Columns.Count < keyColumn Then
QSortedArray = CVErr(xlErrRef): Exit Function
Else
Set inputRange = Application.Intersect(inputRange, inputRange.Parent.UsedRange)
If inputRange Is Nothing Then
QSortedArray = Array(vbNullString): Exit Function
Else
imageArray = inputRange.Value
End If
End If
Case Is = "Variant()", "String()", "Double()", "Long()"
If UBound(inputRange, 2) < keyColumn Then
QSortedArray = Array(CVErr(xlErrRef)): Exit Function
Else
imageArray = inputRange
End If
Case Else
QSortedArray = CVErr(xlErrNA): Exit Function
End Select
On Error GoTo 0
Rem pass arguments To Public variables
If keyColumn2 = 0 Then keyColumn2 = keyColumn
If UBound(imageArray, 2) < keyColumn Then QSortedArray = CVErr(xlErrRef): Exit Function
If UBound(imageArray, 2) < keyColumn2 Then QSortedArray = CVErr(xlErrRef): Exit Function
keyCol = keyColumn
keyCol2 = keyColumn2
Rem create array of row numbers {1,2,3,...,Rows.Count}
size = UBound(imageArray, 1)
ReDim RowArray(1 To size)
For i = 1 To size
RowArray(i) = i
Next i
Rem sort row numbers
Call sortQuickly(RowArray, Descending)
Rem read imageArray With row order per the sorted RowArray
ReDim outRRay(1 To size, 1 To UBound(imageArray, 2))
For i = 1 To size
For j = 1 To UBound(outRRay, 2)
outRRay(i, j) = imageArray(RowArray(i), j)
Next j
Next i
QSortedArray = outRRay
Erase imageArray
HaltFunction:
On Error GoTo 0
End Function
Sub sortQuickly(ByRef inRRay As Variant, Optional ByVal Descending As Boolean, Optional ByVal low As Long, Optional ByVal high As Long)
Dim pivot As Variant
Dim i As Long, pointer As Long
If low = 0 Then low = LBound(inRRay)
If high = 0 Then high = UBound(inRRay)
pointer = low
Call Swap(inRRay, (low + high) / 2, high)
pivot = inRRay(high)
For i = low To high - 1
If LT(inRRay(i), pivot) Xor Descending Then
Call Swap(inRRay, i, pointer)
pointer = pointer + 1
End If
Next i
Call Swap(inRRay, pointer, high)
If low < pointer - 1 Then
Call sortQuickly(inRRay, Descending, low, pointer - 1)
End If
If pointer + 1 <= high Then
Call sortQuickly(inRRay, Descending, pointer + 1, high)
End If
End Sub
Function LT(aRow As Variant, bRow As Variant, Optional Descending As Boolean) As Boolean
On Error GoTo HaltFtn
LT = Descending
If imageArray(aRow, keyCol) = imageArray(bRow, keyCol) Then
LT = imageArray(aRow, keyCol2) < imageArray(bRow, keyCol2)
Else
LT = (imageArray(aRow, keyCol) < imageArray(bRow, keyCol))
End If
HaltFtn:
On Error GoTo 0
End Function
Sub Swap(ByRef inRRay, a As Long, b As Long)
Dim temp As Variant
temp = inRRay(a)
inRRay(a) = inRRay(b)
inRRay(b) = temp
End Sub
Function Filter2DArray(ByVal sArray, ByVal ColIndex As Long, ByVal FindStr As String, ColtoOuput As Long, ColtoSort As Long, Angle1 As Double, Angle2 As Double, Angle3 As Double, Angle4 As Double, Order As Boolean, ByVal HasTitle As Boolean)
Dim tmpArr, i As Long, j As Long, Arr, RArr, ReArr, dic, TmpStr, Tmp, Chk As Boolean, TmpVal As Double
Dim k As Long, p As Long, s As Long
On Error Resume Next
Set dic = CreateObject("Scripting.Dictionary")
tmpArr = sArray
ColIndex = ColIndex + LBound(tmpArr, 2) - 1
Chk = (InStr("><=", Left(FindStr, 1)) > 0)
For i = LBound(tmpArr, 1) - HasTitle To UBound(tmpArr, 1)
If Chk Then
TmpVal = CDbl(tmpArr(i, ColIndex))
If Evaluate(TmpVal & FindStr) Then dic.Add i, ""
Else
If UCase(tmpArr(i, ColIndex)) Like UCase(FindStr) Then dic.Add i, ""
End If
Next
If dic.Count > 0 Then
Tmp = dic.Keys
ReDim Arr(LBound(tmpArr, 1) To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle, LBound(tmpArr, 2) To UBound(tmpArr, 2))
For i = LBound(tmpArr, 1) - HasTitle To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(i, j) = tmpArr(Tmp(i - LBound(tmpArr, 1) + HasTitle), j)
Next
Next
If HasTitle Then
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(LBound(tmpArr, 1), j) = tmpArr(LBound(tmpArr, 1), j)
Next
End If
End If
ReDim RArr(LBound(Arr) To UBound(Arr), 1 To 2)
p = 1
For k = LBound(Arr) To UBound(Arr)
If (Arr(k, ColtoSort) >= Angle1 And Arr(k, ColtoSort) <= Angle2) Or (Arr(k, ColtoSort) >= Angle3 And Arr(k, ColtoSort) <= Angle4) Then
RArr(p, 1) = Arr(k, 2)
RArr(p, 2) = Arr(k, ColtoSort)
p = p + 1
End If
Next
ReDim ReArr(1 To p - 1, 1 To 2)
For s = 1 To p - 1
ReArr(s, 1) = RArr(s, 1)
ReArr(s, 2) = RArr(s, 2)
Next
'Dim a As Long
'a = 1
Filter2DArray = Application.Index(QSortedArray(ReArr, 2, 1, Order), , ColtoOuput)
End Function
Function Filter2DArray_LT(ByVal sArray, ByVal ColIndex As Long, ByVal FindStr As String, ByVal HasTitle As Boolean)
Dim tmpArr, i As Long, j As Long, Arr, dic, TmpStr, Tmp, Chk As Boolean, TmpVal As Double
On Error Resume Next
Set dic = CreateObject("Scripting.Dictionary")
tmpArr = sArray
ColIndex = ColIndex + LBound(tmpArr, 2) - 1
Chk = (InStr("><=", Left(FindStr, 1)) > 0)
For i = LBound(tmpArr, 1) - HasTitle To UBound(tmpArr, 1)
If Chk Then
TmpVal = CDbl(tmpArr(i, ColIndex))
If Evaluate(TmpVal & FindStr) Then dic.Add i, ""
Else
If UCase(tmpArr(i, ColIndex)) Like UCase(FindStr) Then dic.Add i, ""
End If
Next
If dic.Count > 0 Then
Tmp = dic.Keys
ReDim Arr(LBound(tmpArr, 1) To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle, LBound(tmpArr, 2) To UBound(tmpArr, 2))
For i = LBound(tmpArr, 1) - HasTitle To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(i, j) = tmpArr(Tmp(i - LBound(tmpArr, 1) + HasTitle), j)
Next
Next
If HasTitle Then
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(LBound(tmpArr, 1), j) = tmpArr(LBound(tmpArr, 1), j)
Next
End If
End If
Filter2DArray_LT = Arr
End Function
Function Filter2DArray_LTA(ByVal sArray, ByVal ColIndex As Long, ByVal FindStr As String, ByVal ColIndex2 As Long, ByVal FindStr2 As String, ByVal HasTitle As Boolean)
Dim tmpArr, i As Long, j As Long, Arr, dic, TmpStr, Tmp
Dim Chk As Boolean, Chk2 As Boolean
Dim TmpVal As Double, TmpVal2 As Double
Dim FindStr_Temp As Long, FindStr2_Temp As Long
On Error Resume Next
Set dic = CreateObject("Scripting.Dictionary")
tmpArr = sArray
ColIndex = ColIndex + LBound(tmpArr, 2) - 1
ColIndex2 = ColIndex2 + LBound(tmpArr, 2) - 1
Chk = (InStr("><=", Left(FindStr, 1)) > 0)
Chk2 = (InStr("><=", Left(FindStr2, 1)) > 0)
FindStr_Temp = Right(FindStr, Len(FindStr) - 1)
FindStr2_Temp = Right(FindStr2, Len(FindStr2) - 1)
If FindStr2_Temp > FindStr_Temp Then
If FindStr_Temp = 0 Then
FindStr = "<360"
End If
If FindStr2_Temp = 0 Then
FindStr2 = "<360"
End If
Else:
If FindStr2_Temp = 0 Then
FindStr = "<360"
FindStr2 = "<360"
End If
End If
For i = LBound(tmpArr, 1) - HasTitle To UBound(tmpArr, 1)
If Chk Or Chk2 Then
TmpVal = CDbl(tmpArr(i, ColIndex))
TmpVal2 = CDbl(tmpArr(i, ColIndex2))
If Evaluate(TmpVal & FindStr) = True And Evaluate(TmpVal2 & FindStr2) = True Then dic.Add i, ""
Else
If UCase(tmpArr(i, ColIndex)) Like UCase(FindStr) And UCase(tmpArr(i, ColIndex2)) Like UCase(FindStr2) Then dic.Add i, ""
End If
Next
If dic.Count > 0 Then
Tmp = dic.Keys
ReDim Arr(LBound(tmpArr, 1) To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle, LBound(tmpArr, 2) To UBound(tmpArr, 2))
For i = LBound(tmpArr, 1) - HasTitle To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(i, j) = tmpArr(Tmp(i - LBound(tmpArr, 1) + HasTitle), j)
Next
Next
If HasTitle Then
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(LBound(tmpArr, 1), j) = tmpArr(LBound(tmpArr, 1), j)
Next
End If
End If
Filter2DArray_LTA = Application.Index(Arr, , 2)
End Function
Function Filter2DArray_LT2(ByVal sArray, ByVal ColIndex As Long, ByVal FindStr As String, ByVal ColIndexAxis As Long, ByVal FindStrAxis As String, ByVal ColIndex2 As Long, ByVal FindStr2 As String, ByVal ColIndex3 As Long, ByVal FindStr3 As String, ByVal FindStr4 As String, ByVal FindStr5 As String, _
ByVal FindStr6 As String, ColtoOuput As Long, Order As Boolean, ByVal HasTitle As Boolean)
Dim tmpArr, i As Long, j As Long, k As Long, s As Long, z As Long, Arr, dic, TmpStr, Tmp, NewArr
Dim Chk As Boolean, Chk2 As Boolean, Chk3 As Boolean, Chk4 As Boolean, Chk5 As Boolean, Chk6 As Boolean, Rot As Boolean, ChkAxis As Boolean
Dim TmpVal As Double, TmpVal2 As Double, TmpVal3 As Double
Dim FindStr3_Temp As Long, FindStr4_Temp As Long
Dim FindStr3_Temp1 As String, FindStr4_Temp1 As String, FindStr3_Temp2 As String, FindStr4_Temp2 As String
On Error Resume Next
Set dic = CreateObject("Scripting.Dictionary")
tmpArr = sArray
ColIndex = ColIndex + LBound(tmpArr, 2) - 1
ColIndex2 = ColIndex2 + LBound(tmpArr, 2) - 1
ColIndex3 = ColIndex3 + LBound(tmpArr, 2) - 1
ColIndexAxis = ColIndexAxis + LBound(tmpArr, 2) - 1
Chk = (InStr("><=", Left(FindStr, 1)) > 0)
Chk2 = (InStr("><=", Left(FindStr2, 1)) > 0)
Chk3 = (InStr("><=", Left(FindStr3, 1)) > 0)
Chk4 = (InStr("><=", Left(FindStr4, 1)) > 0)
Chk5 = (InStr("><=", Left(FindStr5, 1)) > 0)
Chk6 = (InStr("><=", Left(FindStr6, 1)) > 0)
ChkAxis = (InStr("><=", Left(FindStrAxis, 1)) > 0)
FindStr3_Temp = Right(FindStr3, Len(FindStr3) - 2)
FindStr4_Temp = Right(FindStr4, Len(FindStr4) - 2)
If FindStr3_Temp > FindStr4_Temp Then
FindStr4 = "<=" & 360
FindStr5 = ">=" & 0
Rot = True
Else
Rot = False
End If
For i = LBound(tmpArr, 1) - HasTitle To UBound(tmpArr, 1)
If Chk Or Chk2 Or Chk3 Or Chk4 Or Chk5 Or ChkAxis Then
TmpVal = CDbl(tmpArr(i, ColIndex))
TmpVal2 = CDbl(tmpArr(i, ColIndex2))
TmpVal3 = CDbl(tmpArr(i, ColIndex3))
If Evaluate(TmpVal & FindStr) = True And Evaluate(TmpVal2 & FindStr2) = True Then
If (Evaluate(TmpVal3 & FindStr3) = True And Evaluate(TmpVal3 & FindStr4) = True) Or (Evaluate(TmpVal3 & FindStr5) = True And Evaluate(TmpVal3 & FindStr6) = True) Then dic.Add i, ""
End If
Else
If UCase(tmpArr(i, ColIndex)) Like UCase(FindStr) And UCase(tmpArr(i, ColIndexAxis)) Like UCase(FindStrAxis) And UCase(tmpArr(i, ColIndex2)) Like UCase(FindStr2) And ((UCase(tmpArr(i, ColIndex3)) Like UCase(FindStr3) And UCase(tmpArr(i, ColIndex3)) Like UCase(FindStr4)) Or (UCase(tmpArr(i, ColIndex3)) Like UCase(FindStr5) _
And UCase(tmpArr(i, ColIndex3)) Like UCase(FindStr6))) Then dic.Add i, ""
End If
Next
If dic.Count > 0 Then
Tmp = dic.Keys
ReDim Arr(LBound(tmpArr, 1) To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle, LBound(tmpArr, 2) To UBound(tmpArr, 2))
For i = LBound(tmpArr, 1) - HasTitle To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(i, j) = tmpArr(Tmp(i - LBound(tmpArr, 1) + HasTitle), j)
Next
Next
If HasTitle Then
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(LBound(tmpArr, 1), j) = tmpArr(LBound(tmpArr, 1), j)
Next
End If
End If
For k = LBound(Arr) To UBound(Arr)
If Arr(k, 1) <> "" Then
z = z + 1
End If
Next k
ReDim NewArr(LBound(Arr) To z, 1 To 6)
For k = LBound(Arr) To z
If Arr(k, 1) <> "" Then
For s = 1 To 6
If Rot And s = 5 And Arr(k, 5) < FindStr3_Temp Then
NewArr(k, s) = Arr(k, s) + 360
Else
NewArr(k, s) = Arr(k, s)
End If
Next s
End If
Next k
Filter2DArray_LT2 = Application.Index(QSortedArray(NewArr, 5, , Order), , ColtoOuput)
'Filter2DArray_LT2 = Arr
End Function
Function Filter2DArray_LTS(ByVal sArray, ByVal ColIndex As Long, ByVal searchArray, ByVal ColIndex2 As Long, ByVal FindStr2 As String, ColtoOuput As Long, Order As Boolean, ByVal HasTitle As Boolean)
Dim tmpArr, i As Long, j As Long, Arr, dic, Dict, TmpStr, Tmp, shellarray
Dim Chk As Boolean, Chk2 As Boolean
Dim TmpVal As Double, TmpVal2 As Double
Dim s As Long, k As Long, n As Long
Dim FindStr As String
Dim e As Variant
On Error Resume Next
Set dic = CreateObject("Scripting.Dictionary")
tmpArr = sArray
shellarray = searchArray
ColIndex = ColIndex + LBound(tmpArr, 2) - 1
ColIndex2 = ColIndex2 + LBound(tmpArr, 2) - 1
Chk2 = (InStr("><=", Left(FindStr2, 1)) > 0)
For s = LBound(shellarray, 1) To UBound(shellarray, 1)
FindStr = "=" & shellarray(s, 1)
Chk = (InStr("><=", Left(FindStr, 1)) > 0)
For i = LBound(tmpArr, 1) - HasTitle To UBound(tmpArr, 1)
'For s = LBound(shellarray, 1) To UBound(shellarray, 1)
If Chk Or Chk2 Then
TmpVal = CDbl(tmpArr(i, ColIndex))
TmpVal2 = CDbl(tmpArr(i, ColIndex2))
If Evaluate(TmpVal & FindStr) = True And Evaluate(TmpVal2 & FindStr2) = True Then dic.Add i, ""
Else
If UCase(tmpArr(i, ColIndex)) Like UCase(FindStr) And UCase(tmpArr(i, ColIndex2)) Like UCase(FindStr2) Then dic.Add i, ""
End If
Next
Next
If dic.Count > 0 Then
Tmp = dic.Keys
ReDim Arr(LBound(tmpArr, 1) To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle, LBound(tmpArr, 2) To UBound(tmpArr, 2))
For i = LBound(tmpArr, 1) - HasTitle To UBound(Tmp) + LBound(tmpArr, 1) - HasTitle
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(i, j) = tmpArr(Tmp(i - LBound(tmpArr, 1) + HasTitle), j)
Next
Next
If HasTitle Then
For j = LBound(tmpArr, 2) To UBound(tmpArr, 2)
Arr(LBound(tmpArr, 1), j) = tmpArr(LBound(tmpArr, 1), j)
Next
End If
End If
'Set Dict = CreateObject("Scripting.Dictionary")
'Dict.CompareMode = 1
'n = 1
'For k = LBound(Arr) To UBound(Arr)
' If Not Dict.Exists(Arr(k, 1) & "|" & Arr(k, 2) & "|" & Arr(k, 3) & "|" & Arr(k, 4)) Then
' Dict.Add (Arr(k, 1) & "|" & Arr(k, 2) & "|" & Arr(k, 3) & "|" & Arr(k, 4)), n
' n = n + 1
' End If
'Next
'ReDim w(1 To n, 1 To 4)
' For Each e In Dict.Keys
' w(Dict.Item(e), 1) = Split(e, "|")(0)
' w(Dict.Item(e), 2) = Split(e, "|")(1)
' w(Dict.Item(e), 3) = Split(e, "|")(2)
' w(Dict.Item(e), 4) = Split(e, "|")(3)
'Next
Filter2DArray_LTS = Application.Index(Arr, , 2)
End Function
Sub ShellID()
'Dim startTime As Double
'Dim SecondsElapsed As Double
''Remember time when macro starts
Dim StartTime As Single, EndTime As Single
StartTime = Timer
' Turn off Excel functionality to improve performance.
Application.ScreenUpdating = False
Application.DisplayStatusBar = False
Application.Calculation = xlCalculationManual
Application.EnableEvents = False
' Note: this is a sheet-level setting.
ActiveSheet.DisplayPageBreaks = False
Dim LastR1 As Long, LastR2 As Long, i As Long, n As Long, k As Long, j As Long
Dim Rng As Range, Rng2 As Range, Rng3 As Range, Rng4 As Range, Rng5 As Range, TempRng As Range
Dim Cell As Range
Dim Angle1 As Double, Angle2 As Double, Angle3 As Double, Angle4 As Double, Angle5 As Double, Angle6 As Double, Angle7 As Double, Angle8 As Double
Dim e As Variant
Dim Axis As String
Dim w, Dict, Arr, Point
With Sheets("ShellResult")
LastR1 = .Range("F" & Rows.Count).End(xlUp).Row
Set Rng = .Range("B4:E" & LastR1)
Arr = Rng
Set Dict = CreateObject("Scripting.Dictionary")
Dict.CompareMode = 1
n = 1
For k = LBound(Arr) To UBound(Arr)
If Not Dict.Exists(Arr(k, 1) & "|" & Arr(k, 2) & "|" & Arr(k, 3) & "|" & Arr(k, 4)) Then
Dict.Add (Arr(k, 1) & "|" & Arr(k, 2) & "|" & Arr(k, 3) & "|" & Arr(k, 4)), n
n = n + 1
End If
Next
ReDim w(1 To n, 1 To 4)
For Each e In Dict.Keys
w(Dict.Item(e), 1) = Split(e, "|")(0)
w(Dict.Item(e), 2) = Split(e, "|")(1)
w(Dict.Item(e), 3) = Split(e, "|")(2)
w(Dict.Item(e), 4) = Split(e, "|")(3)
Next
End With
Axis = Sheets("Results - 0 to 180").Range("A3").Value
With Sheets("Point")
LastR2 = .Range("F" & Rows.Count).End(xlUp).Row
Set Rng2 = .Range("C4:H" & LastR2)
Set Rng3 = .Range("C4:C" & LastR2)
Set Rng4 = .Range("G4:G" & LastR2)
End With
With ActiveSheet
.Range("A8:E98").ClearContents
.Range("A208:E298").ClearContents
.Range("A408:E498").ClearContents
.Range("A608:E698").ClearContents
Point = Filter2DArray_LT(Rng2, 2, Axis, False)
.Range("A8:A98") = Filter2DArray_LT2(Point, 6, "=" & .Range("B3"), 2, Axis, 4, "=" & .Range("B2"), 5, ">=" & Sheets("Level").Range("I2").Value, "<=" & Sheets("Level").Range("J2").Value, ">=" & Sheets("Level").Range("I3").Value, "<=" & Sheets("Level").Range("J3").Value, 1, False, False)
.Range("A208:A298") = Filter2DArray_LT2(Point, 6, "=" & .Range("B203"), 2, Axis, 4, "=" & .Range("B202"), 5, ">=" & Sheets("Level").Range("I4").Value, "<=" & Sheets("Level").Range("J4").Value, ">=" & Sheets("Level").Range("I5").Value, "<=" & Sheets("Level").Range("J5").Value, 1, True, False)
.Range("A408:A498") = Filter2DArray_LT2(Point, 6, "=" & .Range("B403"), 2, Axis, 4, "=" & .Range("B402"), 5, ">=" & Sheets("Level").Range("I2").Value, "<=" & Sheets("Level").Range("J2").Value, ">=" & Sheets("Level").Range("I3").Value, "<=" & Sheets("Level").Range("J3").Value, 1, False, False)
.Range("A608:A698") = Filter2DArray_LT2(Point, 6, "=" & .Range("B603"), 2, Axis, 4, "=" & .Range("B602"), 5, ">=" & Sheets("Level").Range("I4").Value, "<=" & Sheets("Level").Range("J4").Value, ">=" & Sheets("Level").Range("I5").Value, "<=" & Sheets("Level").Range("J5").Value, 1, True, False)
LastR1 = .Range("B" & Cells.Rows.Count).End(xlUp).Row
'Set Rng5 = .Range("A8:A98")
'.Range("B8:B98").Value = LookupResults(Rng3, Rng4, Rng5)
'Set Rng5 = .Range("A208:A298")
'.Range("B208:B298").Value = LookupResults(Rng3, Rng4, Rng5)
'Set Rng5 = .Range("A408:A498")
'.Range("B408:B498").Value = LookupResults(Rng3, Rng4, Rng5)
'Set Rng5 = .Range("A608:A698")
'.Range("B608:B698").Value = LookupResults(Rng3, Rng4, Rng5)
EndTime = Timer
Debug.Print (EndTime - StartTime) & " seconds have passed [1]"
For i = 8 To 98
If IsError(.Range("A" & i)) = False Then
.Range("C" & i).Value = .Range("A" & i + 1).Value
.Range("B" & i).Value = Application.WorksheetFunction.VLookup(.Range("A" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
If IsError(.Range("C" & i)) = False Then
If IsEmpty(.Range("A" & i + 1).Value) = False Then
.Range("D" & i).Value = Application.WorksheetFunction.VLookup(.Range("C" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
End If
End If
End If
Next
For i = 208 To 298
If IsError(.Range("A" & i)) = False Then
.Range("C" & i).Value = .Range("A" & i + 1).Value
.Range("B" & i).Value = Application.WorksheetFunction.VLookup(.Range("A" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
If IsError(.Range("C" & i)) = False Then
If IsEmpty(.Range("A" & i + 1).Value) = False Then
.Range("D" & i).Value = Application.WorksheetFunction.VLookup(.Range("C" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
End If
End If
End If
Next
For i = 408 To 498
If IsError(.Range("A" & i)) = False Then
.Range("C" & i).Value = .Range("A" & i + 1).Value
.Range("B" & i).Value = Application.WorksheetFunction.VLookup(.Range("A" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
If IsError(.Range("C" & i)) = False Then
If IsEmpty(.Range("A" & i + 1).Value) = False Then
.Range("D" & i).Value = Application.WorksheetFunction.VLookup(.Range("C" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
End If
End If
End If
Next
For i = 608 To 698
If IsError(.Range("A" & i)) = False Then
.Range("C" & i).Value = .Range("A" & i + 1).Value
.Range("B" & i).Value = Application.WorksheetFunction.VLookup(.Range("A" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
If IsError(.Range("C" & i)) = False Then
If IsEmpty(.Range("A" & i + 1).Value) = False Then
.Range("D" & i).Value = Application.WorksheetFunction.VLookup(.Range("C" & i).Value & Axis, Sheets("Point").Range("S:T"), 2, False)
End If
End If
End If
Next
' Set Rng5 = .Range("C8:C98")
' .Range("D8:D98").Value = LookupResults(Rng3, Rng4, Rng5)
' Set Rng5 = .Range("C208:C298")
' .Range("D208:D298").Value = LookupResults(Rng3, Rng4, Rng5)
' Set Rng5 = .Range("C408:C498")
' .Range("D408:D498").Value = LookupResults(Rng3, Rng4, Rng5)
' Set Rng5 = .Range("C608:C698")
' .Range("D608:D698").Value = LookupResults(Rng3, Rng4, Rng5)
EndTime = Timer
Debug.Print (EndTime - StartTime) & " seconds have passed [2]"
For i = 8 To 98
If .Range("B" & i).Value <> vbNullString And .Range("D" & i).Value <> vbNullString Then
.Range("E" & i).Value = Filter2DArray_LTA(Filter2DArray_LT(Filter2DArray_LT(w, 1, .Range("A" & i).Value, False), 3, ">" & .Range("B3").Value, False), 4, ">" & .Range("B" & i).Value, 4, "<" & .Range("D" & i).Value, False)
End If
Next
For i = 208 To 298
If .Range("B" & i).Value <> vbNullString And .Range("D" & i).Value <> vbNullString Then
.Range("E" & i).Value = Filter2DArray_LTA(Filter2DArray_LT(Filter2DArray_LT(w, 1, .Range("A" & i).Value, False), 3, ">" & .Range("B203").Value, False), 4, "<" & .Range("B" & i).Value, 4, ">" & .Range("D" & i).Value, False)
End If
Next
For i = 408 To 498
If .Range("B" & i).Value <> vbNullString And .Range("D" & i).Value <> vbNullString Then
.Range("E" & i).Value = Filter2DArray_LTA(Filter2DArray_LT(Filter2DArray_LT(w, 1, .Range("A" & i).Value, False), 3, "<" & .Range("B403").Value, False), 4, ">" & .Range("B" & i).Value, 4, "<" & .Range("D" & i).Value, False)
End If
Next
For i = 608 To 698
If .Range("B" & i).Value <> vbNullString And .Range("D" & i).Value <> vbNullString Then
.Range("E" & i).Value = Filter2DArray_LTA(Filter2DArray_LT(Filter2DArray_LT(w, 1, .Range("A" & i).Value, False), 3, "<" & .Range("B603").Value, False), 4, "<" & .Range("B" & i).Value, 4, ">" & .Range("D" & i).Value, False)
End If
Next
End With
EndTime = Timer
Debug.Print (EndTime - StartTime) & " seconds have passed [VBA]"
' Turn off Excel functionality to improve performance.
'Application.ScreenUpdating = True
Application.DisplayStatusBar = True
'Application.Calculation = xlCalculationAutomatic
'Application.EnableEvents = True
' Note: this is a sheet-level setting.
'ActiveSheet.DisplayPageBreaks = True
'SecondsElapsed = Round(Timer - StartTime, 2)
End Sub
Sub Shell()
Dim sh As Worksheet
Dim shtName As String
Dim i As Long, LastR1 As Long
' Turn off Excel functionality to improve performance.
Application.ScreenUpdating = False
Application.DisplayStatusBar = False
Application.Calculation = xlCalculationManual
Application.EnableEvents = False
' Note: this is a sheet-level setting.
ActiveSheet.DisplayPageBreaks = False
For Each sh In Worksheets
With sh
If sh.Name <> "Area" And sh.Name <> "MASTER" _
And sh.Name <> "Design Force - 180 to 360" And sh.Name <> "Design Force - 0 to 180" And sh.Name <> "Results - 180 to 360" And sh.Name <> "Results - 0 to 180" _
And sh.Name <> "ShellResult" And sh.Name <> "Level" And sh.Name <> "Point" And sh.Name <> "Area" And sh.Name <> "Panel" And sh.Name <> "Area Property" Then
Debug.Print .Name
.Activate
Call ShellID
End If
End With
Next sh
' Turn off Excel functionality to improve performance.
Application.ScreenUpdating = True
Application.DisplayStatusBar = True
Application.Calculation = xlCalculationAutomatic
Application.EnableEvents = True
' Note: this is a sheet-level setting.
ActiveSheet.DisplayPageBreaks = True
End Sub
Sub ShellandPointID()
Dim sht As Worksheet
Dim shtName As String
Dim i As Long, LastR1 As Long
With Sheets("Level")
' Turn off Excel functionality to improve performance.
Application.ScreenUpdating = False
Application.DisplayStatusBar = False
Application.Calculation = xlCalculationManual
Application.EnableEvents = False
' Note: this is a sheet-level setting.
ActiveSheet.DisplayPageBreaks = False
LastR1 = .Range("F" & Rows.Count).End(xlUp).Row
Sheets("MASTER").Visible = True
For i = 1 To 2 'LastR1
Sheets("MASTER").Copy After:=ActiveWorkbook.Sheets("MASTER")
shtName = .Range("F" & i)
ActiveSheet.Name = shtName
Sheets(shtName).Activate
Debug.Print shtName
Sheets(shtName).Range("D3").Value = i
Call Module2.ShellID
Call Module2.ShellResult
Next
Sheets("MASTER").Visible = False
End With
' Turn off Excel functionality to improve performance.
Application.ScreenUpdating = True
Application.DisplayStatusBar = True
Application.Calculation = xlCalculationAutomatic
Application.EnableEvents = True
' Note: this is a sheet-level setting.
ActiveSheet.DisplayPageBreaks = True
'For Each sh In Worksheets
' With sh
' If sh.Name <> "Area" And sh.Name <> "Z = -2.57906" And sh.Name <> "Z = -2.68375" And sh.Name <> "Z = -2.78844" And sh.Name <> "Z = -2.89313" And sh.Name <> "Z = -2.99781" And sh.Name <> "Z = -3.1025" _
' And sh.Name <> "Design Force - 180 to 360" And sh.Name <> "Design Force - 0 to 180" And sh.Name <> "Results - 180 to 360" And sh.Name <> "Results - 0 to 180" _
' And sh.Name <> "ShellResult" And sh.Name <> "Level" And sh.Name <> "Point" And sh.Name <> "Area" And sh.Name <> "Panel" Then
' Debug.Print .Name
' .Activate
' Call ShellID
' End If
' End With
'Next sh
'Application.Calculation = xlCalculationAutomatic
End Sub
Sub ShellResult()
Dim Rng As Range, Dn As Range
Dim dic As Object
Dim i As Long, j As Long, k As Long, n As Long
Dim Ray As Variant
Dim Name As String, Name2 As String
Dim StartTime As Single, EndTime As Single
OptimizeVBA True
StartTime = Timer
With Sheets("ShellResult")
Ray = .Range("A4").CurrentRegion.Resize(, 27)
End With
Set dic = CreateObject("scripting.dictionary")
dic.CompareMode = vbTextCompare
For n = 1 To UBound(Ray, 1)
dic(Ray(n, 1)) = n
Next
With ActiveSheet
For j = 0 To 600 Step 40
For k = 0 To 3
For i = 8 + 200 * k To 98 + 200 * k
If Application.WorksheetFunction.IsError(.Range("E" & i).Value) = False Then
If .Range("E" & i).Value <> vbNullString Then
Name = "Area" & .Range("E" & i).Value & "Point" & .Range("A" & i).Value & .Range("I1").Offset(0, j).Value & .Range("D2").Value
Name2 = "Area" & .Range("E" & i).Value & "Point" & .Range("C" & i).Value & .Range("I1").Offset(0, j).Value & .Range("D2").Value
If dic.Exists(Name) Then
.Range("I" & i).Offset(0, j).Value = Ray(dic(Name), 13)
.Range("N" & i).Offset(0, j).Value = Ray(dic(Name), 14)
.Range("S" & i).Offset(0, j).Value = Ray(dic(Name), 15)
.Range("X" & i).Offset(0, j).Value = Ray(dic(Name), 20)
.Range("AC" & i).Offset(0, j).Value = Ray(dic(Name), 21)
.Range("AH" & i).Offset(0, j).Value = Ray(dic(Name), 22)
.Range("AM" & i).Offset(0, j).Value = Ray(dic(Name), 26)
.Range("AR" & i).Offset(0, j).Value = Ray(dic(Name), 27)
Else:
.Range("I" & i).Offset(0, j).Value = "--"
.Range("N" & i).Offset(0, j).Value = "--"
.Range("S" & i).Offset(0, j).Value = "--"
.Range("X" & i).Offset(0, j).Value = "--"
.Range("AC" & i).Offset(0, j).Value = "--"
.Range("AH" & i).Offset(0, j).Value = "--"
.Range("AM" & i).Offset(0, j).Value = "--"
.Range("AR" & i).Offset(0, j).Value = "--"
End If
If dic.Exists(Name2) Then
.Range("J" & i).Offset(0, j).Value = Ray(dic(Name2), 13)
.Range("O" & i).Offset(0, j).Value = Ray(dic(Name2), 14)
.Range("T" & i).Offset(0, j).Value = Ray(dic(Name2), 15)
.Range("Y" & i).Offset(0, j).Value = Ray(dic(Name2), 20)
.Range("AD" & i).Offset(0, j).Value = Ray(dic(Name2), 21)
.Range("AI" & i).Offset(0, j).Value = Ray(dic(Name2), 22)
.Range("AN" & i).Offset(0, j).Value = Ray(dic(Name2), 26)
.Range("AS" & i).Offset(0, j).Value = Ray(dic(Name2), 27)
Else
.Range("J" & i).Offset(0, j).Value = "--"
.Range("O" & i).Offset(0, j).Value = "--"
.Range("T" & i).Offset(0, j).Value = "--"
.Range("Y" & i).Offset(0, j).Value = "--"
.Range("AD" & i).Offset(0, j).Value = "--"
.Range("AI" & i).Offset(0, j).Value = "--"
.Range("AN" & i).Offset(0, j).Value = "--"
.Range("AS" & i).Offset(0, j).Value = "--"
End If
Else
.Range("I" & i).Offset(0, j).Value = "--"
.Range("N" & i).Offset(0, j).Value = "--"
.Range("S" & i).Offset(0, j).Value = "--"
.Range("X" & i).Offset(0, j).Value = "--"
.Range("AC" & i).Offset(0, j).Value = "--"
.Range("AH" & i).Offset(0, j).Value = "--"
.Range("AM" & i).Offset(0, j).Value = "--"
.Range("AR" & i).Offset(0, j).Value = "--"
.Range("J" & i).Offset(0, j).Value = "--"
.Range("O" & i).Offset(0, j).Value = "--"
.Range("T" & i).Offset(0, j).Value = "--"
.Range("Y" & i).Offset(0, j).Value = "--"
.Range("AD" & i).Offset(0, j).Value = "--"
.Range("AI" & i).Offset(0, j).Value = "--"
.Range("AN" & i).Offset(0, j).Value = "--"
.Range("AS" & i).Offset(0, j).Value = "--"
End If
End If
Next i
Next k
Next j
End With
EndTime = Timer
Debug.Print (EndTime - StartTime) & " Seconds"
'OptimizeVBA False
End Sub
Function BuildLookupCollection(categories As Range, values As Range)
Dim vlookupCol As Object, i As Long
Set vlookupCol = CreateObject("Scripting.Dictionary")
For i = 1 To categories.Rows.Count
Call vlookupCol.Add(CStr(categories(i)), values(i))
Next i
Set BuildLookupCollection = vlookupCol
End Function
Function VLookupValues(ByVal lookupCategory As Range, vlookupCol As Object)
'Function VLookupValues(ByVal lookupCategory As Range, ByVal lookupValues As Range, vlookupCol As Object)
Dim i As Long, resArr() As Variant
ReDim resArr(lookupCategory.Rows.Count, 1)
For i = 1 To lookupCategory.Rows.Count
resArr(i - 1, 0) = vlookupCol.Item(CStr(lookupCategory(i)))
Next i
'lookupValues = resArr
VLookupValues = resArr
End Function
Sub OptimizeVBA(isOn As Boolean)
Application.Calculation = IIf(isOn, xlCalculationManual, xlCalculationAutomatic)
Application.EnableEvents = Not (isOn)
Application.ScreenUpdating = Not (isOn)
ActiveSheet.DisplayPageBreaks = Not (isOn)
End Sub
Function LookupResults(ByVal DataName As Range, ByVal Result As Range, ByVal LookID As Range)
OptimizeVBA True
Dim StartTime As Single, EndTime As Single
'startTime = Timer
On Error Resume Next
Dim names As Range, ages As Range
Dim lookupNames As Range, lookupAges As Range
Dim vlookupCol As Object
'Build Collection
Set vlookupCol = BuildLookupCollection(DataName, Result)
'Lookup the values
'VLookupValues lookupNames, lookupAges, vlookupCol
LookupResults = VLookupValues(LookID, vlookupCol)
'endTime = Timer
'Debug.Print (endTime - startTime) & " seconds have passed [VBA]"
'OptimizeVBA False
Set vlookupCol = Nothing
End Function
Function LookID(ByVal Point As Range, ByVal Shell As Range, LCase As String, Case2 As String)
Dim PointArr, ShellArr, Arr
Dim i As Long, n As Long
PointArr = Point
ShellArr = Shell
For i = LBound(ShellArr) To UBound(ShellArr)
If ShellArr(i, 1) <> vbNullString Then
n = n + 1
End If
Next
ReDim Arr(1 To n)
For i = LBound(ShellArr) To n
Arr(i) = "Area" & ShellArr(i, 1) & "Point" & PointArr(i, 1) & Case2 & LCase
Next
LookID = Arr
End Function
Function RotY(ByRef PTRng, YAngle As Double)
Dim Rng As Variant
Dim ResultRng As Variant, Rng2 As Variant
Dim i As Long
Dim X As Double, Y As Double, z As Double, TX As Double, TY As Double, TZ As Double, RAngle As Double
Rng = Application.Transpose(PTRng)
RAngle = Application.WorksheetFunction.Radians(YAngle)
ReDim ResultRng(1 To 3)
If UBound(PTRng) <> 3 Then Exit Function
X = PTRng(1)
Y = PTRng(2)
z = PTRng(3)
ResultRng(1) = X * Cos(RAngle) + z * Sin(RAngle)
ResultRng(2) = Y
ResultRng(3) = X * -Sin(RAngle) + z * Cos(RAngle)
RotY = ResultRng
End Function
Function RotZ(ByRef PTRng, YAngle As Double)
Dim Rng As Variant
Dim ResultRng As Variant, Rng2 As Variant
Dim i As Long
Dim X As Double, Y As Double, z As Double, TX As Double, TY As Double, TZ As Double, RAngle As Double
Rng = Application.Transpose(PTRng)
RAngle = Application.WorksheetFunction.Radians(YAngle)
ReDim ResultRng(1 To 3)
If UBound(PTRng) <> 3 Then Exit Function
X = PTRng(1, 1)
Y = PTRng(2, 1)
z = PTRng(3, 1)
ResultRng(1) = X * Cos(RAngle) - Y * Sin(RAngle)
ResultRng(2) = X * Sin(RAngle) + Y * Cos(RAngle)
ResultRng(3) = z
RotZ = ResultRng
End Function
Sub Rotation()
Dim i As Long, LastR1 As Long
Dim Arr
OptimizeVBA True
With Sheets("Area")
LastR1 = .Range("F" & Rows.Count).End(xlUp).Row
ReDim Arr(1 To 3)
For i = 4 To LastR1
Arr = Application.Transpose(.Range(.Cells(i, 17), .Cells(i, 19)))
.Range(.Cells(i, 24), .Cells(i, 26)) = RotY(RotZ(Arr, .Range("U" & i).Value), .Range("V" & i).Value)
Next
End With
OptimizeVBA False
End Sub
Sub Combine()
Call Module2.ShellID
Call Module2.ShellResult
End Sub
Function Angle(ByRef Rng As Range, Axis As String)
Dim dic As Object
Set dic = CreateObject("scripting.dictionary")
End Function
Descargar