Consulting

Page 1 of 2 1 2 LastLast
Results 1 to 20 of 26

Thread: VBA code problem with random numbers generations

  1. #1
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location

    VBA code problem with random numbers generations

    I want to generate random numbers between (1 &10) in column B starting with B4 and generating ones based on the generated number in B4, for example: if number 5 was generated in B4 , generate 5 ones in range (C4 to C8), and in column A generate random numbers between (1 & 3) starting with A4. Every click the model should give random numbers.
    Would you please have a look at the attached example.
    I will be very grateful if you can assist me.
    Regards.
    Ali
    Attached Files Attached Files

  2. #2
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Should be easy enough. I guess you would want all the existing data in A:C to be deleted with each run. Could the random integers 1-3 be repeated? If random, you could get 1,1,1. The same thing for the 3 numbers in column B 1-10. Cold they be repeated.

    What about sort order for the random numbers? I see that column A numbers are sorted but that may be coincidence. Column B number are not sorted.

  3. #3
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Maybe something like this



    Option Explicit
    
    Const ciTotalNumberOfRandoms As Long = 10
    
    Sub GenerateSomeRandomNumbers()
        Dim N As Long, i As Long, iRow As Long, j As Long
        
        
        ActiveSheet.Columns("A:C").Clear
        
        iRow = 4
        
        For i = 1 To ciTotalNumberOfRandoms
            N = Application.WorksheetFunction.RandBetween(1, 10)
            
            ActiveSheet.Cells(iRow, 1).Value = i
            ActiveSheet.Cells(iRow, 2).Value = N
            
            For j = 1 To N
                ActiveSheet.Cells(iRow, 3).Value = 1
                iRow = iRow + 1
            Next j
        Next I
    
    End Sub
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  4. #4
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Thank you so much Paul for your promptly reply. the code you sent is very useful.

    Regards.
    Ali

  5. #5
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Dear Paul,


    Can you make the numbers that you generated between 1 & 10 randomly be sometimes 3 numbers or 8 numbers or nothing every time you click run?
    Thanks
    Ali

  6. #6
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    A random (0 - 10) number of random numbers (1 - number_of_randoms)?

    Like this??


    Option Explicit
     
    Sub GenerateSomeRandomNumbers()
        Dim iNumberOfRandoms As Long, iRandom As Long
        Dim i As Long, iRow As Long, j As Long
         
        ActiveSheet.Columns("A:C").Clear
        
        iNumberOfRandoms = Application.WorksheetFunction.RandBetween(0, 10)
         
        iRow = 4
              
        For i = 1 To iNumberOfRandoms
            iRandom = Application.WorksheetFunction.RandBetween(1, iNumberOfRandoms)
             
            ActiveSheet.Cells(iRow, 1).Value = i
            ActiveSheet.Cells(iRow, 2).Value = iRandom
             
            For j = 1 To iRandom
                ActiveSheet.Cells(iRow, 3).Value = 1
                iRow = iRow + 1
            Next j
        Next i
         
    End Sub
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  7. #7
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Thanks Paul for the code.

    Do you know how to generate random times between two times. For example: how to generate random times between (09:00 & 12:00) in VBA?

    Regards.
    Ali

  8. #8
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Since a 'Time' is the fractional part of a double counted from Jan 1 1990 something like this would work

    There might be cleverer ways to do it

     
    Option Explicit
    Sub RandomTime()
        Dim i As Long
        Dim dStart As Double, dEnd As Double, dRandom As Double
        
        
        dStart = CDbl(TimeSerial(6, 0, 0))
        dEnd = CDbl(TimeSerial(10, 0, 0))
    
        For i = 1 To 100
            dRandom = dStart + dEnd * Rnd
            ActiveSheet.Cells(i, 1).Value = CDate(dRandom)
            ActiveSheet.Cells(i, 2).Value = Format(ActiveSheet.Cells(i, 1).Value, "hh:mm:ss")
        Next I
    End Sub
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  9. #9
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Thanks Paul,

    I want to generate random times between two times. For example how to generate random times between (14:00 & 16:00) in VBA?
    the code you sent I did not get it, I think there something wrong with it. Please assist me.

    Regards.
    Ali

  10. #10
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location

    VBA code sorting numbers ascending without removing the empty cells

    Hi,

    I want to sort numbers ascending without removing the blank cells.
    Thanks
    Ali

  11. #11
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    I lost a term somehow when I was pasting it


    Option Explicit
    Sub RandomTime()
        Dim i As Long
        Dim dStart As Double, dEnd As Double, dRandom As Double
         
         
        dStart = CDbl(TimeSerial(14, 0, 0))
        dEnd = CDbl(TimeSerial(16, 0, 0))
         
        For i = 1 To 100
            dRandom = dStart + (dEnd - dStart) * Rnd
            ActiveSheet.Cells(i, 1).Value = CDate(dRandom)
            ActiveSheet.Cells(i, 2).Value = Format(ActiveSheet.Cells(i, 1).Value, "hh:mm:ss")
        Next i
    End Sub
    
    Function OneRandomTime(Earliest As Date, Latest As Date) As Date
        Dim dStart As Double, dEnd As Double, dRandom As Double
         
         
        dStart = CDbl(Earliest)
        dStart = dStart - Int(dStart)
        
        dEnd = CDbl(Latest)
        dEnd = dEnd - Int(dEnd)
        
        dRandom = dStart + (dEnd - dStart) * Rnd
            
        OneRandomTime = CDate(dRandom)
    End Function
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  12. #12
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Thank you so much Paul for the code.

    Do you know how to sort numbers ascending without removing blank cells?

    Regards.
    Ali

  13. #13
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Hi,

    Do you know how to sort numbers ascending with blank cells in VBA without removing blank cells?
    I will be very grateful if you assist me

    Regards.
    Ali

  14. #14
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    Probably

    Please provide an example
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  15. #15
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Hi Paul,

    Lets say, I want to sort the numbers which are in column(A) to sorted ascending without removing the blank cells as in the column (D) as shown in the attached file.
    Regards.
    Ali
    Attached Files Attached Files

  16. #16
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    I think I understand. The sheet 'Test' has a macro button to see


    Option Explicit
    Sub SortWithBlanks()
        Dim iSortCol As Long, iDataCol As Long
        Dim iSortColLast As Long, iDataColLast As Long, iLongestCol As Long
        Dim iLastCol As Long, iRow As Long
        Dim rSort As Range
        
        iSortCol = 1
        iDataCol = 4
        
        
        Application.ScreenUpdating = False
        
        With ActiveSheet
            iSortColLast = .Cells(.Rows.Count, iSortCol).End(xlUp).Row
            iDataColLast = .Cells(.Rows.Count, iDataCol).End(xlUp).Row
            If iSortColLast >= iDataColLast Then
                iLongestCol = iSortColLast
            Else
                iLongestCol = iDataColLast
            End If
            
            iLastCol = .Cells(1, .Columns.Count).End(xlToLeft).Column
            iLastCol = iLastCol + 1
            
            For iRow = 1 To iLongestCol
                .Cells(iRow, iLastCol).Value = .Cells(iRow, iSortCol).Value
                If Len(.Cells(iRow, iLastCol).Value) = 0 Then .Cells(iRow, iLastCol).Value = .Cells(iRow - 1, iLastCol).Value
            Next iRow
            Set rSort = .Cells(1, 1).Resize(iLongestCol, iLastCol)
                
            .Sort.SortFields.Clear
            .Sort.SortFields.Add Key:=.Columns(iLastCol), SortOn:=xlSortOnValues, Order:=xlAscending, DataOption:=xlSortNormal
            .Sort.SetRange rSort
            .Sort.Header = xlNo
            .Sort.MatchCase = False
            .Sort.Orientation = xlTopToBottom
            .Sort.SortMethod = xlPinYin
            .Sort.Apply
        
            .Columns(iLastCol).ClearContents
        End With
        Application.ScreenUpdating = True
    
    End Sub
    Attached Files Attached Files
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

  17. #17
    VBAX Regular
    Joined
    Jul 2015
    Posts
    66
    Location
    Hi,
    Does anyone know how to generate random numbers without repetition in VBA excel.
    Thanks
    Ali

  18. #18
    Mac Moderator VBAX Guru mikerickson's Avatar
    Joined
    May 2007
    Location
    Davis CA
    Posts
    2,778
    Yes.

    Sub test()
        Dim Numbers() As Long
        Dim LowPossible As Long, HighPossible As Long, Size As Long
        Dim randIndex As Long, temp As Long
        Dim i As Long
        
        LowPossible = 100: HighPossible = 120: Rem adjust
        
        ReDim Numbers(LowPossible To HighPossible)
        For i = LowPossible To HighPossible
            Numbers(i) = i
        Next i
        
        For i = LowPossible To HighPossible
            randIndex = WorksheetFunction.RandBetween(LowPossible, HighPossible)
            temp = Numbers(i)
            Numbers(i) = Numbers(randIndex)
            Numbers(randIndex) = temp
        Next i
    
        Do
            Size = Application.InputBox("How Many Numbers (no duplicates)", Default:=(HighPossible - LowPossible + 1), Type:=1)
            If Size <= 0 Then Exit Sub: Rem canceled
            If (HighPossible - LowPossible + 1) < Size Then
                MsgBox "The most you can enter is " & (HighPossible - LowPossible + 1)
                Size = 0
            End If
        Loop Until 0 < Size
        
        With Range("a1")
            .EntireRow.ClearContents
            .Resize(1, Size).Value = Numbers
        End With
        
    End Sub

  19. #19
    VBAX Guru Kenneth Hobs's Avatar
    Joined
    Nov 2005
    Location
    Tecumseh, OK
    Posts
    4,956
    Location
    Yes. If you had said so after I asked in post #2, it would have saved a lot of time.
    Sub Test_RndIntPick()  MsgBox Join(RndIntPick(1, 100, 3), vbLf)
      MsgBox Join(RndIntPick(1, 100, 3, True, True), vbLf)
      MsgBox Join(RndIntPick(1, 100, 3, True, False), vbLf)
    End Sub
     
    Function RndIntPick(first As Long, last As Long, _
        noPick As Long, Optional bSort As Boolean = False, _
        Optional bAscending As Boolean = True) As Variant
        Dim i As Long, r As Long, temp As Long, k As Long
        ReDim iArr(first To last) As Variant
        Dim a() As Variant
         
        For i = first To last
            iArr(i) = i
        Next i
         
        Randomize
        For i = 1 To noPick
            r = Int(Rnd() * (last - first + 1 - (i - 1))) + (first + (i - 1))
            temp = iArr(r)
            iArr(r) = iArr(first + i - 1)
            iArr(first + i - 1) = temp
        Next i
         
        ReDim Preserve iArr(first To first + noPick - 1)
        ReDim a(1 To noPick)
        For r = 1 To noPick
            a(r) = iArr(LBound(iArr) + r - 1)
        Next r
         
        If bSort = True Then
            RndIntPick = ArrayListSort(a(), bAscending)
        Else
            RndIntPick = a()
        End If
    End Function
     
    Function ArrayListSort(sn As Variant, Optional bAscending As Boolean = True)
        With CreateObject("System.Collections.ArrayList")
            Dim cl As Variant
            For Each cl In sn
                .Add cl
            Next
             
            .Sort 'Sort ascendending
            If bAscending = False Then .Reverse 'Sort and then Reverse to sort descending
            ArrayListSort = .toarray()
        End With
    End Function

  20. #20
    VBAX Sage
    Joined
    Apr 2007
    Location
    United States
    Posts
    8,729
    Location
    I'm confused


    Post #1 -- I want to generate random numbers between (1 &10) in column B starting with B4 and generating ones based on the generated number in B4, for example: if number 5 was generated in B4 , generate 5 ones in range (C4 to C8), and in column A generate random numbers between (1 & 3) starting with A4.

    Post #5 -- Can you make the numbers that you generated between 1 & 10 randomly be sometimes 3 numbers or 8 numbers or nothing every time you click run?

    Post #8 -- Do you know how to generate random times between two times. For example: how to generate random times between (09:00 & 12:00) in VBA?

    Post #12 -- I want to sort numbers ascending without removing the blank cells.

    Post #22 -- Does anyone know how to generate random numbers without repetition in VBA excel.
    ---------------------------------------------------------------------------------------------------------------------

    Paul


    Remember: Tell us WHAT you want to do, not HOW you think you want to do it

    1. Use [CODE] ....[/CODE ] Tags for readability
    [CODE]PasteYourCodeHere[/CODE ] -- (or paste your code, select it, click [#] button)
    2. Upload an example
    Go Advanced / Attachments - Manage Attachments / Add Files / Select Files / Select the file(s) / Upload Files / Done
    3. Mark the thread as [Solved] when you have an answer
    Thread Tools (on the top right corner, above the first message)
    4. Read the Forum FAQ, especially the part about cross-posting in other forums
    http://www.vbaexpress.com/forum/faq...._new_faq_item3

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •