Code for last Post

Code:
'10   '         I   J   K
'20   '
'30   '  22     A   -   1
'40   '  23     B   -   2
'50   '  24     C   -   3
'60   '
Sub EvalRep2()      '                                https://www.excelforum.com/development-testing-forum/1154829-collection-stuff-of-codes-for-other-threads-no-reply-needed-14.html#post4602295
70   Rem 1) Here I go again. Just getting First value.    http://listenonrepeat.com/watch/?v=WyF8RHM1OCg#Whitesnake_-_Here_I_Go_Again__87
80   Dim strEval As String
90    Let strEval = "=REPT({""A"";""B""},2)": Debug.Print strEval           '  Ctrl+g reveals   =REPT({"A";"B"},2)    in the Immediate Window" , which is as "seen" by VBA, which is how we would write it in a cell  -  Quotes:  http://www.excelforum.com/development-testing-forum/1154829-collection-stuff-of-codes-for-other-threads-no-reply-needed-11.html#post4555023
100  Dim vTemp As Variant 'Choose Variant as we may get a single value or Array from Evaluate
110   Let vTemp = Evaluate(strEval)                                         ' Returns "AA"
120   Let vTemp = Evaluate("=REPT({""A"";""B""},2)")                        ' Returns "AA"
130   Let strEval = "=REPT(I22:I23,2)": Debug.Print strEval                 '  Ctrl+g reveals   =REPT(I22:I23,2)   in the Immediate Window
140   Let vTemp = Evaluate(strEval)                                         ' Returns "AA"
150   Let vTemp = Evaluate("=REPT(I22:I23,2)")                              ' Returns "AA"
160   Let vTemp = Evaluate(strEval)                                         ' Returns "AA"
170  Rem 2) Trying to get both possible values out.
180  '2a) review Excel VBA multi value analysis
190   Let strEval = "=I22:I23": Debug.Print strEval                         '    =I22:I23
200  Dim RngTemp As Range
210   Set RngTemp = Evaluate(strEval)
220   Let vTemp = Evaluate(strEval).Value: Let vTemp = Evaluate(strEval)    '   Default of .Value for returned Range object returned for unspecific Declaration ( Dim ing )
230   Let strEval = "=I22:I23" & "&" & "I22:I23": Debug.Print strEval       '    =I22:I23&I22:I23
240   'Set RngTemp = Evaluate(strEval) ' Error '421 Object required. - Excel takes this as a formula and not a referrence, values are given for the two referrences
250   Let vTemp = Evaluate(strEval)                                         ' Returns {AA;BB}
260   Let strEval = "=I23:I24" & "&" & "I22:I23": Debug.Print strEval       '    =I23:I24&I22:I23
270   Let vTemp = Evaluate(strEval)                                         ' Returns {BA;CB}
'2a(ii) When there is a mismatch in Array sizes,
280   Let strEval = "=I22:I24" & "&" & "I22:I23": Debug.Print strEval       '    =I22:I24&I22:I23
290   Let vTemp = Evaluate(strEval)                                         ' Returns {AA;BB;error 2042}
'Interception Theory:   http://www.excelfox.com/forum/showthread.php/2145-Excel-VBA-Interception-and-Implicit-Intersection-and-VLookUp              https://www.excelforum.com/tips-and-tutorials/1172587-excel-vba-interception-and-implicit-intersection-and-vlookup.html
'_(ii) ' Single value
300   Let strEval = "=I22:I24" & "&" & "I22": Debug.Print strEval           '    =I22:I24&I22
310   Let vTemp = Evaluate(strEval)                                         ' Returns {AA;BA;CA}
320   Let strEval = "=I22:I24" & "&" & """A""": Debug.Print strEval         '    =I22:I24&"A"
330   Let vTemp = Evaluate(strEval)                                         ' Returns {AA;BA;CA}
'_(iii) ' Single breadth
340   Let strEval = "=I22:J24" & "&" & """A""": Debug.Print strEval         '    =I22:J24&"A"
350   Let vTemp = Evaluate(strEval)                                         ' Returns {AA,-A;BA,-A;CA,-A}
360   Let strEval = "=I22:J24" & "&" & "I22:I23": Debug.Print strEval       '    =I22:J24&I22:I23
370   Let vTemp = Evaluate(strEval)                                         ' Returns {AA,-A;BB,-B;error 2042,error 2042}
380   Let strEval = "=I22:J24" & "&" & "{""A"";""B""}": Debug.Print strEval '    =I22:J24&{"A";"B"}
390   Let vTemp = Evaluate(strEval)                                         ' Returns {AA,-A;BB,-B;error 2042,error 2042}
400 '
410  '2b)(i) Attempting concatenations
420   Let strEval = "=I22:I23" & "&" & "REPT(I22:I23,2)": Debug.Print strEval '    =I22:I23&REPT(I22:I23,2)
430   Let vTemp = Evaluate(strEval) '   String housed in Variant type --      ' Returns "AAA" which is A & AA , so first value again
440   Let strEval = "={" & """""" & ";" & """""" & "}" & "&" & "REPT(I22:I23,2)": Debug.Print strEval ' ={"";""}&REPT(I22:I23,2)
450   Let vTemp = Evaluate(strEval)                                           ' Just first value, "AA" returned  ' A null string is being concatenated.
460   Let strEval = "=M40:M41" & "&" & "REPT(I22:I23,2)": Debug.Print strEval       '    =M40:M41&REPT(I22:I23,2)  NOTE: M40:M41 are arbritrary empty cells
470   Let vTemp = Evaluate(strEval)                                           ' Just first value, AA returned    ' A null string is being concatenated.
480   Let strEval = "={""A"";""B""}" & "&" & "REPT(I22:I23,2)": Debug.Print strEval '    ={"A";"B"}&REPT(I22:I23,2)
490  '2b(ii) Killing Interception
500   Let vTemp = Evaluate(strEval) '   String housed in Variant type --      ' Returns "AAA" which is A & AA   First Value.   KILLED interception
510   Let strEval = "={""A"";""B""}" & "&" & "REPT({""A"";""B""},2)": Debug.Print strEval '    ={"A";"B"}&REPT({"A";"B"},2)
520   Let vTemp = Evaluate(strEval) '   String housed in Variant type --      ' Returns "AAA" which is A & AA   First Value.   KILLED interception
530   Let strEval = "={""A"";""B""}" & "&" & """AA""": Debug.Print strEval    '   ={"A";"B"}&"AA"
540   Let vTemp = Evaluate(strEval) '                                         ' Returns {"AAA";"BAA"}
550   Let strEval = "={""A"";""B""}" & "&" & "REPT(""A"",2)": Debug.Print strEval '    ={"A";"B"}&REPT("A",2)
560   Let vTemp = Evaluate(strEval) '                                         ' Returns {"AAA";"BAA"}
570   Let strEval = "=I22:I23" & "&" & "REPT({""A"";""B""},2)": Debug.Print strEval       '   =I22:I23&REPT({"A";"B"},2)
580   Let vTemp = Evaluate(strEval) '   String housed in Variant type --      ' Returns "AAA" which is A & AA   First Value.   KILLED interception
590   Let strEval = "=I22:J23" & "&" & "REPT({""A"";""B""},2)": Debug.Print strEval       '   =I22:J23&REPT({"A";"B"},2)
600   Let vTemp = Evaluate(strEval) '   String housed in Variant type --      ' Returns "AAA" which is A & AA   First Value.   KILLED interception
610 '
620  '2c) Multivalue from REPT({"A";"B"},2)        "to get Multivalue Wonks"
630  '2c)(i) Index Wonks
640   Let strEval = "=Index(REPT({""A"";""B""},2),0,0)": Debug.Print strEval  '=Index(REPT({"A";"B"},2),0,0)
650   Let strEval = "=Index(REPT({""A"";""B""},2),0)"
660   Let strEval = "=Index(REPT({""A"";""B""},2),0,1)"
670   Let strEval = "=Index(REPT({""A"";""B""},2),)"
680   Let strEval = "=Index(REPT({""A"";""B""},2),,)"
690   Let strEval = "=Index(REPT({""A"";""B""},2),,0)"
700   Let strEval = "=Index(REPT({""A"";""B""},2),,1)"
710   Let vTemp = Evaluate(strEval)      '    All above succesful             ' Returns {"AA";"BB"}                                              '
720
730   Let strEval = "=I22:J24" & "&" & "Index(REPT({""A"";""B""},2),0,0)"
740   Let vTemp = Evaluate(strEval)      '    Intersection well behaved       ' Returns {"AAA,"-AA";"BBB,"-BB";"error 2042,error 2042"}
750
760  '2c)(ii) Transpose Wonk
770   Let strEval = "=Transpose(REPT({""A"",""B""},2))"
780   Let vTemp = Evaluate(strEval)                                           ' Returns {"AA";"BB"}
790 '
800  '2c(iii) If(Row(), ) If(Column(), ) Wonks
810   Let strEval = "=If(Column(),REPT({""A"";""B""},2))"
820   Let vTemp = Evaluate(strEval)                                           ' Returns {"AA";"BB"}
830 '
840  '2c(iv) If(Row(j1:j2)xColumn(i1:i2), ) Wonks
850   Let strEval = "=If(Row(1:2),REPT({""A"";""B""},2))"
860   Let strEval = "=If(Row(45:46),REPT({""A"";""B""},2))"
870   Let strEval = "=If(Row(A4:A5),REPT({""A"";""B""},2))"
880   Let vTemp = Evaluate(strEval)                                           ' All above Returns {"AA";"BB"}
890
900   Let strEval = "=If(Row(1:3),REPT({""A"";""B""},2))"
910   Let vTemp = Evaluate(strEval)                                           ' Returns {"AA";"BB";error 2042}
920
921 '2c(v) Some background to Row( ) type stuff.
922   Let strEval = "=If({1;1},REPT({""A"";""B""},2))"
923   Let strEval = "=If({True;True},REPT({""A"";""B""},2))"
924   Let strEval = "=If({True;1},REPT({""A"";""B""},2))"
925   Let strEval = "=If({True;2},REPT({""A"";""B""},2))"                     ' NOTE: any other than 0 is taken as True or 1
926   Let vTemp = Evaluate(strEval)                                           ' All above Returns {"AA";"BB"}
927   Let strEval = "=If({True;0},REPT({""A"";""B""},2))"
928   Let vTemp = Evaluate(strEval)                                           ' Returns {"AA";False}
' Behaving itself once the Multivalues are obtained.
930   Let strEval = "=If(Row(1:3)*Column(A:B),REPT({""A"";""B""},2))"         ' First argument returns an Array size, Interception ( Implicit Intersection on single breadth Arrays ) giving Array ##
935   Let strEval = "=If(Row(3:5)*Column(AB:AC),REPT({""A"";""B""},2))"       ' First argument returns an Array size, Interception ( Implicit Intersection on single breadth Arrays ) giving Array ##
940   Let vTemp = Evaluate(strEval)                                           ' All above Returns {"AA","AA";"BB","BB";error 2042,error 2042}
950 '
960 Rem 3
970   Let vTemp = Evaluate("=Row(3:5)*Column(D:E)")                         ' Returns {12,15;16,20;20,25} = {2x4,3x5;4x4,4x5,5x4,5x5}
End Sub