Write an Array of Integers
- Writes an array of integers between 0 and the specified value in cell B1to a row range starting fromB2. Even numbers are written twice (one worksheet).
Initial Solution
- This is a slow solution meant to be educational in understanding object variables (workbook-worksheet-range), ranges (Resize,Offset), loops,...
Option Explicit
Sub WriteArrayOfIntegersRange()
    Const ProcTitle As String = "Write Array of Integers Range"
    
    Dim wb As Workbook: Set wb = ThisWorkbook ' workbook containing this code
    
    Dim ws As Worksheet: Set ws = wb.Worksheets("Sheet1")
    
    ' Create a reference to the source cell.
    Dim sCell As Range: Set sCell = ws.Range("B1")
    
    ' Write the value of the source cell to a variable.
    Dim sValue As Variant: sValue = sCell.Value
    
    Dim LastInteger As Long
    
    ' Validate the source cell value.
    If IsNumeric(sValue) Then ' is a number
        LastInteger = Abs(CLng(sValue)) ' positive ('Abs'), whole ('CLng')
    Else ' is not a number
        MsgBox "The value in cell '" & sCell.Address(0, 0) & "' ('" _
            & sValue & "' is not a number.", vbCritical, ProcTitle
        Exit Sub
    End If
    
    ' Create a reference to the first destination cell.
    Dim dCell As Range: Set dCell = ws.Range("B2"): dCell.Value = 0
    
    Dim Size As Long: Size = 1
    
    Dim n As Long
    
    ' Loop through the numbers and apply alternating row size (1 or 2)
    ' and column offset (2 or 1) before writing.
    For n = 1 To LastInteger
        Set dCell = dCell.Offset(, Size) ' define next first cell
        Size = 2 - n Mod 2 ' calculate the size (Odd = 1, Even = 2)
        dCell.Resize(, Size).Value = n ' write to the resized row range
    Next n
    
    ' Clear the range to the right of the last cell to remove any previous data.
    Dim crrg As Range
    With dCell.Offset(, Size) ' define next first cell
        ' Define the range from the next first to the last worksheet cell
        ' in the row.
        Set crrg = .Resize(, ws.Columns.Count - .Column + 1)
    End With
    crrg.Clear ' or crrg.ClearContents
    
    MsgBox "Array of numbers written.", vbInformation, ProcTitle
End Sub
Using Arrays
- This is a more advanced solution that utilizes the multi-purpose GetArrayOfIntegersfunction. By modifying the related constants (Function Parameters) in the following procedure, you can easily change the output.
- Note that it returns the results in another worksheet (Sheet2).
- The last procedure is created for anyone to quickly get a flavor of the GetArrayOfIntegersfunction. Just add a new workbook, add a new module and copy the codes to it. Modify the function parameters in the last procedure to get different results in theImmediate window(Ctrl+G).
Sub WriteArrayOfIntegers()
' Needs the 'GetArrayOfIntegers' function.
    Const ProcTitle As String = "Write Array of Numbers"
    ' Source
    Const sName As String = "Sheet1"
    Const sCellAddress As String = "B1"
    ' Destination
    Const dName As String = "Sheet2"
    Const dfCellAddress As String = "B2"
    ' Function Parameters ' experiment with these five parameters
    Const EvensCount As Long = 2
    Const OddsCount As Long = 1
    Const DoReturnRow As Boolean = True
    Const IncludeZero As Boolean = True
    Const IsZeroOdd As Boolean = True
    ' Workbook
    Dim wb As Workbook: Set wb = ThisWorkbook ' workbook containing this code
    
    ' Create a reference to the source cell.
    Dim sws As Worksheet: Set sws = wb.Worksheets(sName)
    Dim sCell As Range: Set sCell = sws.Range(sCellAddress)
    
    ' Write the value of the source cell to a variable.
    Dim sValue As Variant: sValue = sCell.Value
    
    Dim LastInteger As Long
    
    ' Validate the source cell value.
    If IsNumeric(sValue) Then ' is a number
        LastInteger = Abs(CLng(sValue)) ' positive ('Abs'), whole ('CLng')
    Else ' is not a number
        MsgBox "The value in cell '" & sCell.Address(0, 0) & "' ('" _
            & sValue & "' is not a number.", vbCritical, ProcTitle
        Exit Sub
    End If
    
    ' Return the result (an array) of the 'GetArrayOfIntegers' function.
    Dim Data As Variant: Data = GetArrayOfIntegers( _
        LastInteger, EvensCount, OddsCount, DoReturnRow, IncludeZero, IsZeroOdd)
    ' Without the constants it would be:
    'Data = GetArrayOfIntegers(LastInteger, 2, 1, True, True, True)
    If IsEmpty(Data) Then Exit Sub
    
    Dim drCount As Long: drCount = UBound(Data, 1)
    Dim dcCount As Long: dcCount = UBound(Data, 2)
    
    ' Create a reference to the first destination cell.
    Dim dws As Worksheet: Set dws = wb.Worksheets(dName)
    Dim dfCell As Range: Set dfCell = dws.Range(dfCellAddress)
    
    ' Clear all cells next to (to the right of) and below
    ' the first destination cell.
    Dim dcrg As Range: Set dcrg = dfCell.Resize( _
        dws.Rows.Count - dfCell.Row + 1, dws.Columns.Count - dfCell.Column + 1)
    dcrg.Clear ' or dcrg.ClearContents
    
    ' Create a reference to the destination range.
    Dim drg As Range: Set drg = dfCell.Resize(drCount, dcCount)
    
    ' Write the values from the array to the destination range.
    drg.Value = Data
    
    MsgBox "Array of numbers written.", vbInformation, ProcTitle
End Sub
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' Author:       VBasic2008
' Dates:        20211101
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' Purpose:      Returns an array of integers in a 2D one-based array.
' Remarks:      The first element is always 0 or 1.
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
Function GetArrayOfIntegers( _
    ByVal LastInteger As Long, _
    Optional ByVal EvensCount As Long = 1, _
    Optional ByVal OddsCount As Long = 1, _
    Optional ByVal DoReturnRow As Boolean = False, _
    Optional ByVal IncludeZero As Boolean = False, _
    Optional ByVal IsZeroOdd As Boolean = False) _
As Variant
    
    Dim eoArr() As Long: ReDim eoArr(0 To 1)
    eoArr(0) = EvensCount: eoArr(1) = OddsCount
    
    Dim zCount As Long
    If IncludeZero Then
        If IsZeroOdd Then zCount = OddsCount Else zCount = EvensCount
    End If
    
    Dim iMod As Long: iMod = LastInteger Mod 2
    Dim eCount As Long: eCount = Int(LastInteger / 2)
    Dim oCount As Long: oCount = Int(LastInteger / 2) + iMod
    
    Dim dtCount As Long
    dtCount = eCount * EvensCount + oCount * OddsCount + zCount
    
    Dim Data As Variant
    Dim dt As Long: dt = 1
    Dim n As Long
    Dim r As Long
    
    If DoReturnRow Then
        ReDim Data(1 To 1, 1 To dtCount)
        If zCount > 0 Then
            For dt = 1 To zCount: Data(1, dt) = 0: Next dt
        End If
        For n = 1 To LastInteger
            For r = 1 To eoArr(n Mod 2)
                Data(1, dt) = n
                dt = dt + 1
            Next r
        Next n
    Else
        ReDim Data(1 To dtCount, 1 To 1)
        If zCount > 0 Then
            For dt = 1 To zCount: Data(dt, 1) = 0: Next dt
        End If
        For n = 1 To LastInteger
            For r = 1 To eoArr(n Mod 2)
                Data(dt, 1) = n
                dt = dt + 1
            Next r
        Next n
    End If
    
    GetArrayOfIntegers = Data
End Function
' This is an unrelated example to play with.
' Note that changing the fourth parameter will make no difference since
' the results are written to the Immediate window (Ctrl+G).
Sub GetArrayOfIntegersTEST()
' Needs the 'GetArrayOfIntegers' function.
    Dim Data As Variant: Data = GetArrayOfIntegers(4, 3, 2, False, False, False)
    Dim r As Long, c As Long
    For r = 1 To UBound(Data, 1)
        For c = 1 To UBound(Data, 2)
            Debug.Print Data(r, c)
        Next c
    Next r
End Sub