Page 9 of 11 FirstFirst ... 7891011 LastLast
Results 81 to 90 of 102

Thread: VBA Copy Rows From One Workbook To text csv File Based On Count In Different Workbook. Cross Posted Chaos

  1. #81
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Problem Solved Doc Sir & Sandy Sir
    Thnx Alot for ur Great Support
    I got the macro that does the same

  2. #82
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    Please can you post us the working macro, ( and could you please give us test data files*** which work with that macro )
    Please explain to us what the issues were, and please explain to us how those issues have been solved
    ( Remember to include URL links to anywhere else where you have posted the same question. )
    Providing us that infomation will help all of us in the future.

    Thanks

    Alan

    *** Please use Google drive or similar for the .csv file.
    It is important that we are given the actual .csv file and not an Excel File which we must convert to a .csv file
    Last edited by DocAElstein; 05-16-2020 at 01:45 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  3. #83
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Code:
    Sub STEP10()
    Dim Wb1 As Workbook, Wb2 As Workbook, WB3 As Workbook
    Dim Ws1 As Worksheet, Ws2 As Worksheet, WS3 As Worksheet
    Dim WSM As Worksheet
    Dim MaxData1 As Long, MaxCol3 As Long, I As Long
    Dim FPath As String, sFile1 As String
    Dim Rng As Range
    Dim bCloseExit As Boolean
    
    
    With Application
        .EnableEvents = False
        .ScreenUpdating = False
        .DisplayAlerts = False
    End With
    
    
    For I = 1 To 3
        
        Select Case I
            Case 1
                On Error Resume Next
                Set Wb1 = Workbooks.Open("C:UsersWolfieeeStyleDesktop1.xls")
                If Err  0 Then
                   
                    bCloseExit = True
                Else
                    On Error GoTo 0
                    Set Ws1 = Wb1.ActiveSheet
                    sFile1 = Wb1.FullName
                End If
            Case 2
                On Error Resume Next
                Set Wb2 = Workbooks.Open("C:UsersWolfieeeStyleDesktopAlert..csv")
                If Err  0 Then
                    
                    bCloseExit = True
                Else
                    On Error GoTo 0
                    Set Ws2 = Wb2.ActiveSheet
                End If
            Case 3
                On Error Resume Next
                Set WB3 = Workbooks.Open("C:UsersWolfieeeStyleDesktopFilesAlertCodes.xlsx")
                If Err  0 Then
                    
                    bCloseExit = True
                Else
                    On Error GoTo 0
                    Set WS3 = WB3.Worksheets.Item(3)
                End If
        End Select
        
        If bCloseExit Then
            Wb1.Close savechanges:=False
            Wb2.Close savechanges:=False
            WB3.Close savechanges:=False
            Exit Sub
        End If
    Next I
    
    MaxData1 = Ws1.Range("A" & Ws1.Rows.Count).End(xlUp).Row - 1
    MaxCol3 = WS3.Cells(1, WS3.Columns.Count).End(xlToLeft).Column
    Set Rng = WS3.Range(WS3.Range("A1"), WS3.Cells(1, MaxCol3))
    Rng.COPY Ws2.Range("A1")
    Ws2.Range(Ws2.Range("A1"), Ws2.Cells(MaxData1, MaxCol3)).FillDown
    
    
    Wb1.Close savechanges:=False
    WB3.Close savechanges:=False
    Wb2.SaveAs FileName:=Wb2.FullName, FileFormat:=xlCSV
    Wb2.Close
    Set Ws1 = Nothing
    Set Ws2 = Nothing
    Set WS3 = Nothing
    Set Wb1 = Nothing
    Set Wb2 = Nothing
    Set WB3 = Nothing
    
    
    With Application
        .EnableEvents = True
        .ScreenUpdating = True
        .DisplayAlerts = True
    End With
    
    
    
    
    
    End Sub
    This was the Macro Doc Sir

  4. #84

  5. #85
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    I have no idea what that macro is supposed to be doing.
    In any case it errors in three places
    MacroError.JPG : : https://imgur.com/TT9h9fz
    MacroError.JPG

    The file names uploaded and the file names in the macro are inconsistent.

    You appear to have hurriedly uploaded a few files and some coding.

    Please read again : https://excelfox.com/forum/showthrea...ll=1#post13354
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  6. #86
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    in the path( / )is not mentioned,it was my mistake .
    Actually this problem was solved, so i deleted the sample file,& since i deleted the sample file, i made a new one & shared with u Doc Sir
    Last edited by fixer; 05-16-2020 at 11:33 PM.

  7. #87
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    https://www.experts-exchange.com/que...-the-file.html
    I got help from experts exchange for this problem Doc Sir

  8. #88
    Fuhrer, Vierte Reich DocAElstein's Avatar
    Join Date
    Aug 2014
    Posts
    9,313
    Rep Power
    10
    My first answer here was almost perfect. https://excelfox.com/forum/showthrea...ll=1#post13185
    https://excelfox.com/forum/showthrea...ll=1#post13184


    This was your question:
    i have three files 1.xls & 2.csv & 3.xlsx
    1.xls first row has headers so dont count that
    In 1.xls count the total number of rows that has data and copy the 3.xlsx sheet3 first row(first complete row copy) and paste that much time of 3.xlsx first row of sheet3 to 2.csv
    suppose 1.xls has data in 5 rows then copy 3.xlsx first row of sheet3 and paste it to 2.csv 5 times
    all files are located in a different path
    sheet name can be anything


    This question should have been you question:
    VBA To Copy Rows From One Workbook To text csv File, Based On Count In A Different Workbook
    I have three files: 2 Excel Files,1.xls & 3.xlsx , and a text file, 2.csv
    1.xls first row has headers so don't count that
    In 1.xls count the total number of rows that has data and copy the 3.xlsx sheet3 first row(first complete row copy) and paste that many rows of 3.xlsx first row of sheet3 to 2.csv
    suppose 1.xls has data in 5 rows then copy 3.xlsx first row of sheet3 and paste it to 2.csv 5 times
    all files are located in a different path
    sheet name can be anything

    The final result should be a comma separated values text file , 2.csv.
    For example, in Notepad, it looks like this:

    2csv is a comma seperated text file.JPG : https://imgur.com/FEjKVMs
    2csv is a comma seperated text file.jpg

    That is the final result that I want


    Here is the new answer from me : https://excelfox.com/forum/showthrea...ll=1#post13346

    Only a very small change was required:
    Code:
    ' 3b
     w2.SaveAs Filename:=ThisWorkbook.Path & "\2.csv", FileFormat:=xlCSV
     Let Application.DisplayAlerts = True
     w2.Close



    Avinash
    Read this, and try to understand at least a little of it.

    2.csv is a text file. It is not an Excel file.
    For example, in Notepad, it looks like this:
    2csv is a comma seperated text file.JPG : https://imgur.com/FEjKVMs
    2csv is a comma seperated text file.jpg

    2.csv is a text file. It is not an Excel file.
    You can open a .csv file in Excel, and Excel will do its best to display the data in columns


    Sometimes Excel will do this:

    _____ Workbook: 2.csv ( Using Excel 2007 32 bit )
    Row\Col
    A
    B
    C
    D
    E
    F
    G
    H
    I
    J
    K
    L
    1
    NSE
    6
    A GTT
    2
    NSE
    6
    A GTT
    3
    NSE
    6
    A GTT
    4
    NSE
    6
    A GTT
    5
    NSE
    6
    A GTT
    6
    Worksheet: 2


    Sometimes Excel will do this:

    _____ Workbook: 2.csv ( Using Excel 2007 32 bit )
    Row\Col
    A
    B
    C
    1
    NSE,,6,,,A,,,,,GTT
    2
    NSE,,6,,,A,,,,,GTT
    3
    NSE,,6,,,A,,,,,GTT
    4
    NSE,,6,,,A,,,,,GTT
    5
    NSE,,6,,,A,,,,,GTT
    6
    Worksheet: 2


    Alan
    Last edited by DocAElstein; 05-17-2020 at 08:05 PM.
    ….If you are my competitor, I will try all I can to beat you. But if I do, I will not belittle you. I will Salute you, because without you, I am nothing.
    If you are my enemy, we will try to kick the fucking shit out of you…..
    Winston Churchill, 1939
    Save your Forum..._
    _...KILL A MODERATOR!!

  9. #89
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    Correct Doc Sir, Thats what i wanted to say u at that time,only minor changes is required, Thnx Alot for helping me in solving the same Doc Sir

  10. #90
    Senior Member
    Join Date
    Jul 2019
    Posts
    382
    Rep Power
    0
    The code given by u Doc Sir No Doubt its perfect, But it requires a little change
    it requires a little change bcoz i changed something in the macro, I am providing all the details below
    Code:
    Sub Step14() '     https://excelfox.com/forum/showthread.php/2467-VBA-To-Copy-Rows-From-One-Workbook-To-text-csv-File-Based-On-Count-In-A-Different-Workbook?p=13367&viewfull=1#post13367        '    http://www.eileenslounge.com/viewtopic.php?f=30&t=34508 (zyxw123)     https://excelfox.com/forum/showthread.php/2467-COPY-AND-PASTE?p=13182#post13182
    Rem 1 Worksheets info
    Dim w1 As Workbook, w2 As Workbook, w3 As Workbook
     Set w1 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\1.xls")  ' Workbooks("1.xls")                         ' Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\1.xlsx")
     Set w2 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Hot Stocks\Alert..csv") ' Workbooks("2.csv")                         ' Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\document\2.csv")
     Set w3 = Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\Files\AlertCodes.xlsx")  ' Workbooks("3.xlsx")                        ' Workbooks.Open("C:\Users\WolfieeeStyle\Desktop\files\3.xlsx")
    Dim WS1 As Worksheet, WS2 As Worksheet, WS3 As Worksheet
     Set WS1 = w1.Worksheets.Item(1)
     Set WS2 = w2.Worksheets.Item(1)
     Set WS3 = w3.Worksheets.Item(3)
    Dim Lc3 As Long, Lenf1 As Long, Lr1 As Long
     Let Lr1 = WS1.Range("A" & WS1.Rows.Count & "").End(xlUp).Row       '   http://www.excelfox.com/forum/showthread.php/2345-Appendix-Thread-(-Codes-for-other-Threads-HTML-Tables-etc-)?p=11466&viewfull=1#post11466      Making Lr dynamic ( using rng.End(XlUp) for a single column. )
     Let Lc3 = WS3.Cells.Item(1, WS3.Columns.Count).End(xlToLeft).Column
    Dim Lc3Ltr As String
     Let Lc3Ltr = CL(Lc3)
    Rem 2  ' In 1.xls count the total number of rows that has data and copy the 3.xlsx sheet3 first row(first complete row copy) and paste that much time of 3.xlsx first row of sheet3 to 2.csv
     Let Lenf1 = Lr1 - 1                                                ' 1.xls first row has headers so dont count that
    ' 2a)
    Dim rngOut As Range: Set rngOut = WS2.Range("A1:" & Lc3Ltr & Lenf1 & "")
    '' 2b)(i)  Relative formula referrences  ... https://teylyn.com/2017/03/21/dollarsigns/#comment-191
    ' WS2.Cells.NumberFormat = "General"                          ' May be needed to prevent formulas coming out as test     =[3.xlsx]Sheet1!$A$1
    ' Let rngOut.Value = "='[3.xlsx]" & WS3.Name & "'!A$1"
    ' Let rngOut.Value = rngOut.Value  '  Change Formulas to values
    ' Let rngOut.Value = Evaluate("If({1},SUBSTITUTE(" & rngOut.Address & ", ""0"", """"))")      '                              https://excelribbon.tips.net/T010741_Removing_Spaces
    ' Or
    ' 2b)(ii) Copy Paste
    Dim rngIn As Range
     Set rngIn = WS3.Range("A1:" & Lc3Ltr & "1")
     rngIn.Copy
     rngOut.PasteSpecial Paste:=xlPasteValues  '   understanding  Paste  across ranges of different size to  Copy  range : https://excelfox.com/forum/showthread.php/2221-VBA-Range-Insert-Method-Code-line-makes-a-space-to-put-new-range-in?p=10441&viewfull=1#post10441
    
    Rem 3
    ' 3a
     w1.Close
     w3.Close
    ' 3b
    w2.SaveAs Filename:=w2.FullName, FileFormat:=xlCSV
     Let Application.DisplayAlerts = False
     w2.Close
     Let Application.DisplayAlerts = True
     
    End Sub
    
    Public Function CL(ByVal lclm As Long) As String '         http://www.excelforum.com/development-testing-forum/1101544-thread-post-appendix-no-reply-needed-please-do-not-delete-thanks-4.html#post4213980
        Do: Let CL = Chr(65 + (((lclm - 1) Mod 26))) & CL: Let lclm = (lclm - (1)) \ 26: Loop While lclm > 0
    End Function


    I used this code & i am getting perfect output
    i changed this line plz see
    Code:
    w2.SaveAs Filename:=ThisWorkbook.Path & "\2.csv", FileFormat:=xlCSV

    to
    this

    Code:
    w2.SaveAs Filename:=w2.FullName, FileFormat:=xlCSV
    and i am getting this popup which i have attached plz see (If i click on Yes then i am getting the desired output & i want that to be done by vba )
    Attached Images Attached Images

Similar Threads

  1. Replies: 4
    Last Post: 04-10-2014, 10:58 PM
  2. Replies: 2
    Last Post: 09-18-2013, 12:30 AM
  3. TO convert Excel entire workbook in csv format
    By pritee in forum Excel Help
    Replies: 11
    Last Post: 08-16-2013, 11:28 AM
  4. Replies: 4
    Last Post: 06-20-2013, 04:25 PM
  5. Replies: 9
    Last Post: 09-09-2011, 02:30 AM

Tags for this Thread

Posting Permissions

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