Consulting

Results 1 to 6 of 6

Thread: Adding multiple images to a single slide with a VBA Macro

  1. #1

    Adding multiple images to a single slide with a VBA Macro

    Hi,

    I have been struggling for a couple of days to figure out how to add multiple images to a single slide with a VBA Macro. Other key points is that this task will repeat over multiple slides.

    I have successfully created a VBA Macro that will allow me add slides and 2 images (.PNG and .JPG) to multiple slides. This Macro pulls images from a folder specified by the user and creates slides based off of information from a .csv This macro works nicely and is very reliable.

    However, now I would like to add and resize multiple photos to a single slide based on a field in the csv. In essence the first line of the csv may indicate that there are 2 photos for a specific slide and the the second line of the csv may indicate 4 photos for the next slide. The images have specific naming conventions that make this part a non issue.

    Here is the code that I have written - there are probably easier ways to do much of what I did, so I welcome additional comments. But my main goal is to figure out how to get the "loop" to work.

    I've included the entire code: but I think the issue is my integration of the For - Next loop, or the Calls with in the loop.

    There are two lines specifically that give me an issue. One is commented out. Both result in different errors.

    This one results in an object reference issue:
    [VBA] osld.Shapes.AddPicture strPath + file.Name, False, True, imgLeftPos(i), imgTopPos(i), imgHorSize, imgVertSize
    [/VBA]


    This one results in a "With" issue
    [VBA] Set oPic0 = osld.Shapes.AddPicture(FileName:=strPath & strFileJPG, LinkToFile:=msoFalse, SaveWithDocument:=msoTrue, Left:=imgLeftPos(0), Top:=imgTopPos(0), Width:=imgHorSize, Height:=imgVertSize)
    [/VBA]


    [VBA]Sub addSlides()
    Dim Input_file As Variant
    Dim dlgOpen As FileDialog
    Dim InfoFile As String
    Dim FileNum As Integer
    Dim Buffer As String
    Dim osld As Slide
    Dim oshp As Shape
    Dim x As Integer
    Dim y As Integer
    Dim xPos As Integer
    Dim yPos As Integer
    Dim strInput As String
    Dim JPG_found As Boolean
    Dim oText1 As Shape
    Dim oText2 As Shape
    Dim oText3 As Shape
    Dim columCount As Integer
    Dim PedNum As String
    Dim WID As String
    Dim Use As Integer
    Dim PedType As String
    Dim Results As String
    Dim Lamina As String
    Dim oPic0 As Shape
    Dim oPic1 As Shape
    Dim oPic2 As Shape
    Dim strPath As String
    Dim strFilePNG As String
    Dim strFileJPG As String
    Dim checkforFile As String
    Dim TotalSlids As Integer
    Dim imgLeftPos(10) As Integer
    Dim imgTopPos(10) As Integer
    Dim imgHorSize As Integer
    Dim imgVertSize As Integer
    Dim i As Integer, thisUse As String


    MsgBox ("The first thing you'll" & Chr(13) & "need to do is navigate to" & Chr(13) & "the csv with WID, Ped info, etc." & Chr(13) & "The next window is an 'open'" & Chr(13) & "window where you navigate and" & Chr(13) & "select the .csv")

    Set dlgOpen = Application.FileDialog(Type:=msoFileDialogOpen)
    dlgOpen.AllowMultiSelect = False
    If dlgOpen.Show = -1 Then
    Input_file = dlgOpen.SelectedItems.Item(1)
    End If

    EnterPath.Show

    strPath = EnterPath.EnterImagePathTextBox
    MsgBox ("Image Path = " + strPath)

    FileNum = FreeFile()
    Open Input_file For Input As FreeFile
    columCount = 0
    TotalSlides = 0
    While Not EOF(FileNum)
    columCount = columCount + 1
    Input #FileNum, Buffer
    If columCount = 1 Then
    WID = Buffer
    End If
    If columCount = 2 Then
    Use = Buffer
    If Use = 1 Then
    imgHorSize = 340
    imgVertSize = 340
    imgLeftPos(0) = 18
    imgTopPos(0) = 60
    imgLeftPos(1) = 360
    imgTopPos(1) = 60
    End If
    If Use = 2 Then
    imgHorSize = 234
    imgVertSize = 234
    imgLeftPos(0) = 6
    imgTopPos(0) = 102
    imgLeftPos(1) = 240
    imgTopPos(1) = 102
    imgLeftPos(2) = 474
    imgTopPos(2) = 102
    End If
    End If
    If columCount = 3 Then
    PedNum = Buffer
    End If
    If columCount = 4 Then
    PedType = Buffer
    End If
    If columCount = 5 Then
    Results = Buffer
    End If
    If columCount = 6 Then
    Lamina = Buffer
    Set osld = ActivePresentation.Slides.Add(ActivePresentation.Slides.Count + 1, ppLayoutBlank)
    Set oText1 = osld.Shapes.AddTextbox(msoTextOrientationHorizontal, Left:=260, Top:=10, Width:=648, Height:=42)
    With oText1.TextFrame
    .WordWrap = msoFalse
    .AutoSize = ppAutoSizeShapeToFitText
    .HorizontalAnchor = msoAnchorCenter
    With .TextRange
    .Text = WID + ", " + Use
    With .Font
    .Name = "Calibri"
    .Size = 40
    .Bold = msoFalse
    .Color.RGB = RGB(0, 0, 0)
    End With
    End With
    End With
    Set oText2 = osld.Shapes.AddTextbox(msoTextOrientationHorizontal, Left:=30, Top:=360, Width:=276, Height:=51)
    With oText2.TextFrame
    .WordWrap = msoTrue
    .AutoSize = ppAutoSizeShapeToFitText
    .HorizontalAnchor = msoAnchorNone
    With .TextRange
    .Text = "Ped " + PedNum + " - " + PedType & Chr(13) & "Results: " + Results & Chr(13) & "Lamina :" + Lamina
    With .Font
    .Name = "Calibri"
    .Size = 12
    .Bold = msoFalse
    .Color.RGB = RGB(0, 0, 0)
    End With
    End With
    End With
    Set oText3 = osld.Shapes.AddTextbox(msoTextOrientationHorizontal, Left:=402, Top:=438, Width:=210, Height:=24)
    With oText3.TextFrame
    .WordWrap = msoFalse
    .AutoSize = ppAutoSizeShapeToFitText
    .HorizontalAnchor = msoAnchorNone
    With .TextRange
    .Text = "IR Image of Process Wafer"
    With .Font
    .Name = "Calibri"
    .Size = 14
    .Bold = msoFalse
    .Color.RGB = RGB(0, 0, 0)
    End With
    End With
    End With
    For i = 0 To Use
    thisUse = CStr(i)
    strFileJPG = "orig." + WID + "gu" + thisUse + "sPSQ-donorr1200EXFO.jpg"
    checkforFile = strPath & strFileJPG
    If Dir(checkforFile) <> "" Then
    osld.Shapes.AddPicture strPath + file.Name, False, True, imgLeftPos(i), imgTopPos(i), imgHorSize, imgVertSize
    ' Set oPic0 = osld.Shapes.AddPicture(FileName:=strPath & strFileJPG, LinkToFile:=msoFalse, SaveWithDocument:=msoTrue, Left:=imgLeftPos(0), Top:=imgTopPos(0), Width:=imgHorSize, Height:=imgVertSize)
    Else
    MsgBox "Donor Image for " + WID + " Use " + thisUse + " was not found."
    End If
    Next
    TotalSlides = TotalSlides + 1
    columCount = 0
    End If
    Wend
    MsgBox ("Total Slides Added = " & TotalSlides)
    End Sub
    [/VBA]

    Thanks, I look forward to any help that can be offered

  2. #2
    VBAX Master
    Joined
    Feb 2007
    Posts
    2,093
    Location
    In the first problem line or code
    What is file.Name?? file looks like an unspecified object

    Also will strFileJPG = "orig." + WID + "gu" + thisUse + "sPSQ-donorr1200EXFO.jpg"
    create a valid file name? The "." looks suspect to me.

    There must be easier ways of coding this too. What does the csv look like and what exactly do you want the slide to look like?
    Last edited by John Wilson; 05-18-2012 at 02:09 AM.
    John Wilson
    Microsoft PowerPoint MVP
    Amazing Free PowerPoint Tutorials
    http://www.pptalchemy.co.uk/powerpoi...tutorials.html

  3. #3
    Thanks John! I dont know what I was thinking when I used file.Name I changed "strPath + file.Name" to "checkforFile" which I used a couple of lines before, and everything works beautifully.

    I would like any recommendations on the code, I too think it is complex as written, so any ideas for improvement is appreciated.

    The csv is used for two different spreadsheets that report two different details and summaries of experiments.

    Similar to a spreadsheet, the csv has an infinite number of rows with 6 columns. A single column would look like this:

    180111,2,39,Alum,Description of results from an experiment,Additional Notes about the experiment.

    For the presentation you helped with, he slide layout is: 180111 is the title at the top of the slide, then an array of images laid out horizontally with text underneath indicating Use#. In the example row this would be 2. So, so this slide would have three images Uses 0 - 3.

    In the other presentation, which works fine, the slide lay out is: 180111,2 is the title at the top of the slide, then two images are laid out underneath (one is a PNG and one is a JPG - this made life really easy). Under one image I list a Number and Type (in this example 39 and Alum), under that, the description of results and additional notes.

    I was going to start looking into importing info from excel instead of a csv, but for now this works.

    Thanks!

  4. #4
    VBAX Master
    Joined
    Feb 2007
    Posts
    2,093
    Location
    One way to get the data from each line is to use Line Input instead of Input to get the whole line and then use split to load into an array

    Dim data() As String

    Line Input #FileNum, buffer
    data() = Split(buffer, ",") 'split text at ","

    data(0) will be the first part of the line, data(1) the next etc up to data(4) in your case
    John Wilson
    Microsoft PowerPoint MVP
    Amazing Free PowerPoint Tutorials
    http://www.pptalchemy.co.uk/powerpoi...tutorials.html

  5. #5
    Thanks John! I implemented your suggestion and it cleaned up the code quite nicely.

    Here is how implemented it:
    [VBA]
    Dim Input_file As Variant
    Dim FileNum As Integer
    Dim jobData() As String
    FileNum = FreeFile()
    Open Input_file For Input As FreeFile
    While Not EOF(FileNum)
    Line Input #FileNum, Buffer
    jobData() = Split(Buffer, ",")
    [/VBA]

    But I tried to implement this same approach on another presentation and it fails.
    Here is how it is implemented in the other presentation:
    [VBA]
    Dim Input_file As Variant
    Dim PedUsage_file As Variant
    Dim FileNum As Integer
    Dim PedFileNum As Integer
    Dim pedInfo(4) As Integer
    Dim logData(20) As String
    FileNum = FreeFile()
    PedFileNum = FreeFile()
    Open Input_file For Input As FreeFile
    Open PedUsage_file For Input As FreeFile
    While Not EOF(PedFileNum)
    Line Input #PedFileNum, Buffer
    pedInfo() = Split(Buffer, ",")
    For i = 0 To MaxImage
    Line Input #FileNum, Buffer
    logData() = Split(Buffer, ",")
    [/VBA]

    When I run the Macro it fails @
    [VBA]pedInfo() = Split(Buffer, ",")[/VBA] With a compile error "can't assign to array"

    If I comment out like this:
    [VBA]
    FileNum = FreeFile()
    ' PedFileNum = FreeFile()
    Open Input_file For Input As FreeFile
    ' Open PedUsage_file For Input As FreeFile
    ' While Not EOF(PedFileNum)
    ' Line Input #PedFileNum, Buffer
    ' pedInfo() = Split(Buffer, ",")
    For i = 0 To MaxImage
    Line Input #FileNum, Buffer
    logData() = Split(Buffer, ",")
    [/VBA]

    I would expect it to pretty much be the same as the first code. Yet, @
    [VBA]logData() = Split(Buffer, ",")
    [/VBA]
    I get the same compile error "can't assign to array"

    Any ideas?

  6. #6
    VBAX Master
    Joined
    Feb 2007
    Posts
    2,093
    Location
    You must declare a dynamic array to use split

    ie Dim pedinfo() as string
    NOT
    Dim pedinfo(4) as string
    John Wilson
    Microsoft PowerPoint MVP
    Amazing Free PowerPoint Tutorials
    http://www.pptalchemy.co.uk/powerpoi...tutorials.html

Posting Permissions

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