Consulting

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

Thread: VBA code to extract images from word.

  1. #1
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location

    Smile VBA code to extract images from word.

    Hi All,

    I have written a code to extract all the images from a word document and saves it in a seperate folder.

    But problem is that , i need to save the images with the same name as present in the document.

    I have attached my word file which have macro save_Images.

    Saving is proper but i need the text below the image to be the name of the image.

    Can any one guide me how to do this.
    Attached Files Attached Files

  2. #2
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    There is no macro named 'save_Images' in your attachment. Docx files cannot contain code modules.

    In any event, any code that extracts images from your attachment is going to have its work complicated by the fact you have numerous images in the document that don't have names below them (e.g. the 'Call' and 'End Call' buttons) and there is no practical way of extracting the names from the images themselves. Furthermore, it's not clear whether you want the entire caption as the image name, or just the part after the caption number.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  3. #3
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location

    Wink

    Hi Macropod,

    The doc file which i attached is having macro named "save_images".

    Go to view then macro -> View macro.

    Question i need to ask like is it possible to change the name of the images from "images001" to that which is just below the image.

    For example in my attached doc, the first image name is "Screen shot 20: Group call – Ready Page".

    Can it be possible to give the same name while storing.

    Please see my code. Guide me, i am very thankful.

  4. #4
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    As I have already stated, a docx file cannot contain macros and there is no macro in your attachment.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  5. #5
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location
    Hi Macropodo,

    I have again attached the doc file for you.

    I have tested that macro so many times, i dont know why its not showing to you.

    Go to view-macro-view macro-save_images-run.

    It will extract all the images of that doc into one folder.
    Attached Files Attached Files

  6. #6
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    See my previous replies. I don't doubt that you can see your macro. Wherever it is, though, it is not and is incapable of being in your attachment. By insisting otherwise, you plainly do not understand the fundamental difference between docx and docm files.

    In all likelihood your macro is in the document's template. For further information, see: http://www.addbalance.com/usersguide/templates.htm
    Last edited by macropod; 05-09-2013 at 03:24 PM.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  7. #7
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    I have tested that macro so many times, i dont know why its not showing to you.
    There is a very simple reason why it is not showing. It is because the attached file does NOT - as stated by macropod - have any macros in it. It can't - as also stated by macropod - because docX files can not have any macros.

    Your macro is in your Normal.dotm file. This is the default location for macros. If you do not explicitly tell Word to store macros in an appropriate file, it stores them in Normal.
    The doc file which i attached is having macro named "save_images".
    To repeat, your file does NOT have any macros in it.

    For example in my attached doc, the first image name is "Screen shot 20: Group call – Ready Page".

    Can it be possible to give the same name while storing.
    Probably. You are incorrect though in stating the image name is "Screen shot 20: Group call – Ready Page".

    That is the text of the next paragraph...that is all. There is NO actual association to the image. That is the text of the next paragraph. There is probably a way to grab each image (Shape) and also get the text of the next paragraph. Then use that text as the file name of the Shapes you ae saving.

  8. #8
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location

    Smile

    Hi All,

    I have attached now my word document which contains two macros, one is to resize the images and another to save images into one folder.

    What i need to do is to save the images in the folder with the same name as present in the document.

    Example. In my attached doc , below first image text "Screen shot 1: PTT key assignment" is there.

    This image should be saved by the same name. But i am not able to do that.

    Can someone guide me please.
    Attached Files Attached Files

  9. #9
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    Once again, there are no macros in your attachment. Simply saving a document in the docm format doesn't add macros from a template or whatever to it ...
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  10. #10
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,334
    Location
    After you figure out how to attach a file containing code in this forum, you might want to consider which of the four images in your sample document it is that you want to name "Screen shot 1: PTT key assignment." All four cannot have the same name.
    Greg

    Visit my website: http://gregmaxey.com

  11. #11
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location
    I dont know why macros are not showing to you, but when i download the same doc, in my laptop its showing.

    Ok i will paste the content of both the macros

    Resize image
    ==========
    Dim PecentSize As Integer
    Dim oIshp As InlineShape
    Dim oshp As Shape

    PercentSize = InputBox("Enter percent of full size", "Resize Picture", 100)

    For Each oIshp In ActiveDocument.InlineShapes
    With oIshp
    .ScaleHeight = PercentSize
    .ScaleWidth = PercentSize
    End With
    Next oIshp

    For Each oshp In ActiveDocument.Shapes
    With oshp
    .ScaleHeight Factor:=(PercentSize / 100), _
    RelativeToOriginalSize:=msoCTrue
    .ScaleWidth Factor:=(PercentSize / 100), _
    RelativeToOriginalSize:=msoCTrue
    End With
    Next oshp

    Save Image
    =========
    FileName = ActiveDocument.FullName


    prePendFileName = Left(ActiveDocument.Name, Len(ActiveDocument.Name) - 5)
    'prePendFileName = Right(prePendFileName, Len(prePendFileName) - 11)


    saveLocaton = "C:\Users\Mohit\Desktop\"


    TodayDateString = Year(Date) & "_"
    If Month(Date) < 10 Then
    TodayDateString = TodayDateString & "0"
    End If
    TodayDateString = TodayDateString & Month(Date) & "_"

    If Day(Date) < 10 Then
    TodayDateString = TodayDateString & "0"
    End If
    TodayDateString = TodayDateString & Day(Date)



    FolderName = TodayDateString & "_" & prePendFileName

    MsgBox "Saving Images to " & saveLocaton & FolderName & "_files"

    'Delete the folder if it exists
    On Error Resume Next
    Kill saveLocaton & FolderName & "_files\*" 'Delete all files
    RmDir saveLocation & FolderName & "_files" 'Delete folder

    'First Save the current document as is
    ActiveDocument.Save


    ActiveDocument.SaveAs2 FileName:=saveLocaton & FolderName & ".html", _
    FileFormat:=wdFormatHTML

    ActiveDocument.Close

    Kill saveLocaton & FolderName & ".html"
    Kill saveLocaton & FolderName & "_files\*.xml"
    Kill saveLocaton & FolderName & "_files\*.html"
    Kill saveLocaton & FolderName & "_files\*.thmx"

    'Rename image Files
    'This is written for files with 99 or fewer images
    For x = 1 To 9
    Name saveLocaton & FolderName & "_files\image00" _
    & x & ".png" As saveLocaton & FolderName & "_files\" _
    & prePendFileName & "_00" & x & ".png"
    Next

    ' For x = 10 To 99
    ' Name saveLocaton & FolderName & "_files\image0" _
    ' & x & ".png" As saveLocaton & FolderName _
    ' & "_files\" & prePendFileName & "_0" & x & ".png"
    ' Next


    Word.Documents.Open (FileName)


    Word.Application.Visible = True
    Word.Application.Activate




    Please help regarding this.

    if you run this code image will be saved in the folder by the name "image001" but i need the name to be like "Screen shot 1: PTT key assignment" .
    I dont know how to grep that text via vba which is written below the image.

    Please help.

  12. #12
    VBAX Wizard
    Joined
    May 2004
    Posts
    6,713
    Location
    Are you seriously saying that:

    [VBA]For x = 1 To 9
    Name saveLocaton & FolderName & "_files\image00" _
    & x & ".png" As saveLocaton & FolderName & "_files\" _
    & prePendFileName & "_00" & x & ".png"
    Next [/VBA]

    is going to save images from IN the file?

    Please use the VBA code tags when posting code.

  13. #13
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,334
    Location
    You still haven't answered the question "Which one of the four images in your example to you want named using the common caption? All four can't have the same name.

    You might consider putting your images and captions in a borderless table. then you can use the cell ranges as a reference. For example, if the image is in Cell(1,1) then you would want to name it Cell(3, 1).range.Text & Cell(2,1) .Range.Text etc.
    Greg

    Visit my website: http://gregmaxey.com

  14. #14
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location
    Quote Originally Posted by fumei
    Are you seriously saying that:

    [VBA]For x = 1 To 9
    Name saveLocaton & FolderName & "_files\image00" _
    & x & ".png" As saveLocaton & FolderName & "_files\" _
    & prePendFileName & "_00" & x & ".png"
    Next [/VBA]

    is going to save images from IN the file?

    Please use the VBA code tags when posting code.
    @Fumie,
    I already have this code to save the images in folder, but it will come as image o1, image02 and so on, but what i need to do is to give the name of my images acoording to the text written below each images in document.

  15. #15
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location
    Quote Originally Posted by gmaxey
    You still haven't answered the question "Which one of the four images in your example to you want named using the common caption? All four can't have the same name.

    You might consider putting your images and captions in a borderless table. then you can use the cell ranges as a reference. For example, if the image is in Cell(1,1) then you would want to name it Cell(3, 1).range.Text & Cell(2,1) .Range.Text etc.

    @gmaxey.

    simply please understand that whatever text is written below every images i need to save these images with that name.

    Like if below image text is "Fig 1 1000" then i need to save that image with the same name.

    Actually i need to get the logic or rule to grep the text written below the image.

    If you have any idea other than it let me know, Meanwhile i am searching the same.

  16. #16
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    Quote Originally Posted by mktmohit
    simply please understand that whatever text is written below every images i need to save these images with that name.
    Instead of treating Greg like a fool, you should look at the documents you've posted to this forum. The first one has numerous images that don't have names below them and the first four images in the last document you posted have only one line below the lot of them and they cannot all be given that as a name. With the unstructured mess you're posting you're asking for the impossible.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  17. #17
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location
    Quote Originally Posted by macropod
    Instead of treating Greg like a fool, you should look at the documents you've posted to this forum. The first one has numerous images that don't have names below them and the first four images in the last document you posted have only one line below the lot of them and they cannot all be given that as a name. With the unstructured mess you're posting you're asking for the impossible.

    @macropod,

    my intention was not that.

    I have attached my doc once again, in which every image has a name below it, i need that name while saving.

    Thanks Macropod for guiding me.
    Attached Files Attached Files

  18. #18
    Knowledge Base Approver VBAX Guru macropod's Avatar
    Joined
    Jul 2008
    Posts
    4,435
    Location
    Your latest document is better, but even that is inconsistently laid out. Your first image, for example, has a paragraph of space characters before it, and the 'caption' is in the paragraph after that. The other images have the caption paragraphs immediately after the images. Unless you have a consistent layout, don't expect anyone's code to provide the results you want.
    Cheers
    Paul Edstein
    [Fmr MS MVP - Word]

  19. #19
    VBAX Regular
    Joined
    May 2013
    Posts
    22
    Location
    Quote Originally Posted by macropod
    Your latest document is better, but even that is inconsistently laid out. Your first image, for example, has a paragraph of space characters before it, and the 'caption' is in the paragraph after that. The other images have the caption paragraphs immediately after the images. Unless you have a consistent layout, don't expect anyone's code to provide the results you want.
    Yes you are ryt its inconsistent, but see what i want, while saving the image, we have to grep the below text.

    Example :- For x = 1 To 9
    Name saveLocaton & FolderName & "_files\image00" _
    & x & ".png" As saveLocaton & FolderName & "_files\" _
    & prePendFileName & "_00" & x & ".png"
    Next

    in between this code we need to implement the logic of grepping that below text and will give that name.

    What i am thinking is when compiler is giving name to image it will search for the text starting with "Screen shot" and will print whole line followed by Screen shot and will be named as the name of that image.

    Like the first image in my doc should be save by the name "Screen shot 1: PTT key assignment".

    let me know if u need further explanation.

  20. #20
    Microsoft Word MVP 2003-2009 VBAX Guru gmaxey's Avatar
    Joined
    Sep 2005
    Posts
    3,334
    Location
    To be honest, I was seriously considering ignoring this thead due to lack of cooperation on your part. However the challenge was interesting so I stuck with it.

    Here are some things that you should consider before posting again.

    1. Answer the questions ask. Doing so may help you discover and resolve the confusion that peoople trying to help you are experiencing. Stamping your foot and endlessly repeating your same question does not help.

    2. Provide helpful attachements. Sending a file with two .jpg images and three .png images with code to rename all as .png is not helpful.

    3. Declare you're varialbes. I do, and I think most regulars here do, and getting your code with a bunch of undeclared variables is frustrating.

    [vba]Sub SaveImage()
    Dim strFullName As String, strFileName As String
    Dim strBasePath As String, strDate As String
    Dim strFolderName As String, strImageName As String
    Dim x As Long
    Dim oRng As Word.Range
    Dim arrCaptions() As String
    Dim strExt As String

    ReDim arrCaptions(ActiveDocument.InlineShapes.Count - 1)
    For x = 1 To ActiveDocument.InlineShapes.Count
    Set oRng = ActiveDocument.InlineShapes(x).Range
    oRng.Collapse wdCollapseEnd
    oRng.MoveEndUntil Cset:="Screen", Count:=wdForward
    oRng.Collapse wdCollapseEnd
    oRng.MoveEndUntil Cset:=Chr(13), Count:=wdForward
    arrCaptions(x - 1) = oRng.Text
    Next x

    strFullName = ActiveDocument.FullName
    strFileName = Left(ActiveDocument.Name, Len(ActiveDocument.Name) - 5)
    strBasePath = "C:\Users\Mohit\Desktop\"
    strDate = Format(Now, "yyyy-mm-dd")
    strFolderName = strDate & "_" & strFileName
    'Delete the folder if it exists
    On Error Resume Next
    Kill strBasePath & strFolderName & "_files\*" 'Delete all files
    RmDir strBasePath & strFolderName & "_files" 'Delete folder
    On Error GoTo 0
    'Save the current document.
    ActiveDocument.Save
    'Save in HTML format
    ActiveDocument.SaveAs2 FileName:=strBasePath & strFolderName & ".html", FileFormat:=wdFormatHTML
    ActiveDocument.Close
    On Error Resume Next
    Kill strBasePath & strFolderName & ".html"
    Kill strBasePath & strFolderName & "_files\*.xml"
    Kill strBasePath & strFolderName & "_files\*.html"
    Kill strBasePath & strFolderName & "_files\*.thmx"
    On Error GoTo 0
    'Rename image Files
    On Error GoTo Err_Ext
    For x = 0 To UBound(arrCaptions)
    strImageName = Replace(arrCaptions(x), ":", "-")
    strExt = ".png"
    Name strBasePath & strFolderName & "_files\image00" _
    & x + 1 & strExt As strBasePath & strFolderName & "_files\" _
    & strFileName & strImageName & strExt
    Next
    Word.Documents.Open (strFullName)
    Word.Application.Visible = True
    Word.Application.Activate
    Exit Sub
    Err_Ext:
    strExt = ".jpg"
    Resume
    End Sub[/vba]
    Greg

    Visit my website: http://gregmaxey.com

Posting Permissions

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