Sunday, September 12, 2010

How to copy RichTextBox contents to Word document

How to insert Rich Text Box Content to Word document using VBA

Let us have a form with a RichTextBox and a Command Button as shown below



The following VBA code will copy the Contents of RichTextBox to the First Paragraph of the ActiveDocument

Private Sub cmdCopyRTFContent_Click()
    
    Dim oRange As Word.Range            ' Word Range
    Dim sPath As String                 ' Temp Path
    
    Set oRange = ActiveDocument.Paragraphs(1).Range
    
    sPath = "c:\shasurdata\Temp.rtf"
    
    Open sPath For Output As 1
        Print #1, RichTextBox1.TextRTF
    Close #1
    
    oRange.ImportFragment sPath
    
End Sub


The program Exports the contents of RichTextBox to a RTF file and then imports to the Word document

Wednesday, August 25, 2010

How to edit Linked Objects using Word VBA

How to open and edit Linked Excel files from Word using VBA

One can insert an object in word by either linking or embedding. We have already seen How to Read and Edit Embedded objects using VBA, The following code will throw light on accessing a linked object from Word (Excel sheet) and editing the same.

Sub Edit_Linked_Excel_Objects()




Dim oXL As Excel.Application ' Excel App Object

Dim oWB As Excel.Workbook ' Workbook Object

Dim sWB As String ' Linked String

Dim oIShape As InlineShape ' Inline Shape Object



On Error GoTo Err_Report



Set oXL = New Excel.Application



For Each oIShape In ActiveDocument.InlineShapes

If InStr(1, oIShape.OLEFormat.ProgID, "Excel") Then



' Check if the Object is Linked

If oIShape.Type = wdInlineShapeLinkedOLEObject Then



' Get the Source Name of Linked Workbook

sWB = oIShape.LinkFormat.SourceFullName



If Len(Dir(sWB)) <> 0 Then

Set oWB = oXL.Workbooks.Open(sWB, , False)

oWB.Sheets(1).Range("A1").Value = "ID"

oWB.Save

oWB.Close False

oIShape.LinkFormat.Update

Else

MsgBox "Linked file not found"

End If

End If

End If







Next oIShape



Finally:



oXL.Quit

If Not oXL Is Nothing Then Set oXL = Nothing

If Not oWB Is Nothing Then Set oWB = Nothing

If Not oIShape Is Nothing Then Set oIShape = Nothing



Exit Sub

Err_Report:

MsgBox Err.Description & " - " & Err.Number

Err.Clear

GoTo Finally



End Sub


Saturday, August 21, 2010

Hide Sheet Tabs using VBA / Hide Excel Sheet Tabs (2007/2010)

How to Hide Excel Sheet Names using VBA


If you want to hide the Sheet Tab (as shown below) you can do that using Excel Options


Uncheck the Show sheet tabs checkbox from Advanced Tab of Options Menu


You can do the same through Excel VBA

ActiveWindow.DisplayWorkbookTabs = False

Friday, August 06, 2010

How to Read Excel Sheet embedded in Word Document using VBA

How to edit Embedded Objects (Excel Workbook) using Word VBA

In our previous posts we have seen how to Embedd an Word Document in Excel Object . Now let us try to read Excel spreadsheet embedded in Word document.



You need to add a reference to the Excel Object Libary as shown above from Tools --> References from Visual Basic Editor (VBE)



The code loops through the available InlineShapes and activates them if they are Excel Spreadsheet. Then it is assigned to an Excel workbook object, which can be programatically handled.

Sub Edit_Embedded_Excel_Objects()

Dim oWB As Excel.Workbook
Dim oIShape As InlineShape


For Each oIShape In ActiveDocument.InlineShapes
    If InStr(1, oIShape.OLEFormat.ProgID, "Excel") Then
        oIShape.OLEFormat.Activate
        Set oWB = oIShape.OLEFormat.Object
        oWB.Sheets(1).Range("A1").Value = "ProdID"
    End If
Next oIShape

End Sub


The code edits the value of the cell as shown below:


See how other Embedded objects are programmed

How to Extract All Formula's in Excel Sheet using VBA

Highlight all cells containing Formulas using Excel VBA

The following snippet highlights all cells that contain formula

Sub HighLight_Formula_Cells()

Dim oWS As Worksheet
Dim oCell As Range

Set oWS = ActiveSheet

For Each oCell In oWS.Cells.SpecialCells(xlCellTypeFormulas)
    oCell.Interior.ColorIndex = 36
    MsgBox oCell.Formula
Next oCell


End Sub

Wednesday, August 04, 2010

How to Connect XLSX file (Excel Workbook) through ADO

Using Excel (Xlsx) file as a database using VBA (ActiveX Data Objects - ADO)

In the past we have already seen how to Connect to an Excel file using ADO and query its contents. That was using Microsoft Excel 2003 or earlier. With Office 2007 the file formats haver changed to XLSX, which might create the following problems





to solve that use the following Connection string:


cN.ConnectionString = "Provider=Microsoft.ACE.OLEDB.12.0;Data Source=C:\Users\comp\documents\visual studio 2010\Projects\ExcelWorkbookDocLevel\ExcelWorkbookDocLevel\ExcelWorkbook1.xlsx;Extended Properties=Excel 12.0;Persist Security Info=False"

Tuesday, July 27, 2010

Excel VBA Autofilter - Specify Multiple Criteria using Array

How to pass an Array as Criteria in Excel Autofilter - VBA

After long time let us revisit our good old Autofilter Fruits example. The following figure shows the data available


If you need to filter say Oranges and Apples alone, you can either pass both criteria (Yes! I have avoided using - Mutliple criteria) or can try using an Array where you can pass multiple values



Sub AutoFilter_Using_Arrays()

Dim oWS As Worksheet

On Error GoTo Err_Filter

Dim arCriteria(0 To 1) As String

Set oWS = ActiveSheet

arCriteria(0) = "Apple"
arCriteria(1) = "Orange"

oWS.UsedRange.AutoFilter Field:=2, Criteria1:=arCriteria, Operator:=xlFilterValues

Finally:

If Not oWS Is Nothing Then Set oWS = Nothing

Err_Filter:
If Err <> 0 Then
MsgBox Err.Description
Err.Clear
GoTo Finally
End If
End Sub


If you leave out the Operator in Excel VBA Autofilter- Only Last Value of the Array Will be displayed

You can also pass the values directly like:


oWS.UsedRange.AutoFilter Field:=2, Criteria1:=Array("Apples","Peaches","Grapes), Operator:=xlFilterValues

Sunday, July 25, 2010

Program/Macro to Highlight Editable Ranges in Protected Sheet

How to identify Editable ranges in a protected Excel sheet using VBA

My good friend Srikanth Srinivasan is a Project Manager whom Microsoft will definitely want to hire as evangelist. He uses the functionality of Excel to great extent and made it ubiquitous.

The following code was for him, which highlights the ranges that are not protected in Excel sheet


Sub HighLight_Editable_Ranges()


Dim oWS As Worksheet
Dim oRng As AllowEditRange

Set oWS = ActiveSheet

oWS.Unprotect

For Each oRng In oWS.Protection.AllowEditRanges
oRng.Range.Interior.ColorIndex = 35
Next oRng

oWS.Protect

End Sub

Friday, July 23, 2010

How to retrieve value from Content Controls using Word VBA

The following snippet validates the user selection using VBA. This code uses the content control created in previous example - (How to add Content Controls using VBA)

Sub Validate_ContentControl()

Dim oCC As ContentControl
Dim OCCEntry As ContentControlListEntry

Set oCC = ActiveDocument.ContentControls(1)

For i = 1 To oCC.DropdownListEntries.Count
     If oCC.DropdownListEntries.Item(i).Text = oCC.Range.Text Then
        Set OCCEntry = oCC.DropdownListEntries.Item(i)
        ' Check the text against value - can be checked directly with text
        If OCCEntry.Value = 1 Then
            MsgBox "Correct"
        Else
            MsgBox "Try Again"
            Exit Sub
        End If
     End If
    
Next i

Thursday, July 22, 2010

How to add Content Controls using VBA

Add Combobox to Word document using VBA

The following code would add a Combo Box control to the existing Word document:

Sub Add_A_ContentControl()

Dim oCC As ContentControl

Set oCC = ActiveDocument.ContentControls.Add(wdContentControlComboBox, Selection.Range)
oCC.SetPlaceholderText , , "Which Team Won the World Cup 2010"

oCC.Title = "World Cup Teams"
oCC.DropdownListEntries.Add "Spain", 1
oCC.DropdownListEntries.Add "Netherlands", 0
oCC.DropdownListEntries.Add "France", 2
oCC.DropdownListEntries.Add "Uruguay", 3

' Prevents the Control from being deleted
oCC.LockContentControl = True
End Sub


Lock the control by setting the LockContentControl attribute to prevent it getting accidentally deleted.

The content control gets added as shown below

Monday, July 05, 2010

GetObject Error with Internet Explorer

How to get active Internet Explorer Object using Getobject in VBA

Set IEBrowser = GetObject(, "InternetExplorer.Application")

Using GetObject for Internet Explorer in VBA throws Runtime error 429 - ActiveX can't create object. The  solution for this is to use ShellWindows


Public Function IENavigate(ByRef IEBrowser) As Boolean

Dim theSHD As SHDocVw.ShellWindows
Dim IE As SHDocVw.InternetExplorer
Dim i As Long
Dim bIEFound As Boolean

On Error GoTo Err_IE
    
    Set theSHD = New SHDocVw.ShellWindows
    For i = 0 To theSHD.Count - 1
        Set IE = theSHD.Item(i)
        If Not IE Is Nothing Then
            If InStr(1, IE.LocationURL, "file://", vbTextCompare) = 0 And Len(IE.LocationURL) <> 0 Then
                If IE.Visible = True Then bIEFound = True: Exit For
                
            End If
        End If
    Next

    If bIEFound = True Then
        Set IEBrowser = IE
        IENavigate = True
    Else
        IENavigate = False
    End If
      
' -------------------------------------
' Error Handling
' -------------------------------------
Err_IE:
    If Err <> 0 Then
        Err.Clear
        Resume Next
    End If
End Function


The above code uses Microsoft Internet controls reference:


without which the following error might occur

---------------------------
Microsoft Visual Basic for Applications
---------------------------
Compile error:

User-defined type not defined
---------------------------
OK Help
---------------------------


Once you get the Internet Explorer object, you can use it as shown below:


Sub GEt_IE()

  Dim IEBrowser As InternetExplorer
  IENavigate IEBrowser
  If Not IEBrowser Is Nothing Then
    MsgBox IEBrowser.Document.Title
  End If


Friday, July 02, 2010

How to extract file name from FullPath string using VBA

Extract Name of the File from Path / Fullname using VBA

There are many methods to extract the filename from a given string. You can use FileSystemObject's function GetFileName or can use Arrays to get the last element of the array split by path separator

Here we use even simpler functions like Dir and InStrRev to achieve the same

Dir function will retrieve the name only if the file exists:


strFilePath = "C:\Users\comp\Documents\sample.xlsx"

sFileName = Dir(strFilePath)


If the file doesn't exist, Dir function will return an empty string. The following would be a better option


strFilePath = "C:\Users\comp\Documents\sample.xlsx"

sFileName = Mid(strFilePath, InStrRev(strFilePath, "\") + 1, Len(strFilePath))


Try it out and post the options you use

Thursday, June 24, 2010

How to simulate speech Echo in VBA

The following snippet simulates ( a sort of ) the Echo effect in VBA. This uses Microsoft Speech Object Library


Sub Voice_It_Out()

Dim oVoice As SpVoice                               ' Voice Object

' --------------------------------------------------------------
' Code for http://vbadud.blogspot.com
' --------------------------------------------------------------

Set oVoice = New SpVoice


For iVol = 100 To 10 Step -10
    oVoice.Volume = iVol
    oVoice.Speak "Echo!"
Next iVol

End Sub

VBA : How to convert text file to speech (audio) using VBA

Text to Speech using Excel VBA : Audio/Speech from input file

If you want to spell out the content of text file using VBA you can do it as shown below:


Sub Speech_FromFile_Example()

Dim oVoice As SpVoice                               ' Voice Object
Dim oVoiceFile As SpFileStream                      ' File Stream Object
Dim sFile As String                                 ' File Name

Set oVoice = New SpVoice
Set oVoiceFile = New SpFileStream

' --------------------------------------------------------------
' Code for http://vbadud.blogspot.com
' --------------------------------------------------------------

oVoice.Speak "This is an example for reading out a file"

sFile = "C:\ShasurData\ForBlogger\SpeechSample.txt"

oVoiceFile.Open sFile

oVoice.SpeakStream oVoiceFile

End Sub

The above code creates a filestream and reads the text file and the Voice object speaks it out!

The code requires Microsoft Speech Object Library (see figure below)



See also:

Voice Messages in VBA

How to get Author details from Track Changes using VBA

Word VBA - extract Revision Author information

If you want to know the details of track revisions, for example, Author name etc the following code will help you:

Sub Get_TrackRevision_Author()

Dim oRev As Revision
Dim oRange As Range

' -----------------------------------------------------------
' Change the line below to suit your needs
' -----------------------------------------------------------
Set oRange = Selection.Range

' -----------------------------------------------------------
' Coded by Shasur for http://vbadud.blogspot.com
' -----------------------------------------------------------

For Each oRev In oRange.Revisions
    MsgBox oRev.Range.Text & " " & oRev.Author
Next oRev


End Sub


The following code provides you more information (like if the comment is inserted / deleted)

If oRev.Type = wdRevisionDelete Then
        MsgBox oRev.Range.Text & " deleted by " & oRev.Author
    ElseIf oRev.Type = wdRevisionInsert Then
        MsgBox oRev.Range.Text & " added by " & oRev.Author
    Else
        MsgBox oRev.Range.Text & " " & oRev.Author
    End If

If you want to know Date of Revision using VBA then the following can be added

MsgBox oRev.Range.Text & " " & oRev.Author & " " & oRev.Date

Sunday, June 13, 2010

How to Save Excel Range as Image using VBA

How to copy Excel Range as Image using VBA / How to export Excel Range as Image

The following code saves the Excel Range (A1:B2) as an image.

It uses the Export function of the Chart object (Refer :How to Save a Chart as Image using Excel VBA)
to save as Image

Sub Export_Range_Images()

' =========================================
' Code to save selected Excel Range as Image
' =========================================

Dim oRange As Range
Dim oCht As Chart
Dim oImg As Picture



Set oRange = Range("A1:B2")
Set oCht = Charts.Add


oRange.CopyPicture xlScreen, xlPicture


oCht.Paste

oCht.Export FileName:="C:\temp\SavedRange.jpg", Filtername:="JPG"

End Sub

Thursday, May 27, 2010

How to Compress Pictures in Excel using VBA

How to Programatically Compress Pictures/Images in Excel using VBA

If you are trying to compress pictures, you will normally be doing using the following dialog:



Compress Pictures Excel Dialog



The same dialog can be automated using Excel VBA and SendKeys as shown below:


Sub Compress_PIX()

Dim octl As CommandBarControl

With Selection
    Set octl = Application.CommandBars.FindControl(ID:=6382)
    Application.SendKeys "%e~"
    Application.SendKeys "%a~"
     octl.Execute
End With

End Sub 

Supressing "Compressing Pictures May reduce the quality of your images.." dialog is also taken care by SendKeys

The code uses CommandBarControl to find the Command and then execute the dialog

See also: How to Increase / Decrease Size of Images in Word Document using VBA

How to add description to Macro Functions in Excel VBA

How to add argument description to Macros/User Defined Functions in Excel VBA

User-defined functions are created in Excel for helping the Excel users. It would be good to add descriptions of the arguments used in the functions. This can be done using Application.Macrooptions method

Let us assume a small User Defined Function that takes an argument:

Function A_Sample_UDF(ByVal sArg)

MsgBox "Sample UDF " & sArg

End Function



The following code will add the UDF to information category
Sub Add_UDF()

Dim ArgDes As Variant

ArgDes = Array("First Arg")

Application.MacroOptions Macro:="Personal.XLSB!A_Sample_UDF", Description:="Sample Function", Category:="Information", ArgumentDescriptions:=ArgDes

End Sub

How to Extract TextBox Contents from All Slides using Powerpoint VBA

Extract Text from Textboxes in Powerpoint slides using VBA

Dedicated to good blogger friend Rahul. This code snippet loops through the slides and extracts the contents of the Textboxes

Sub Extract_TextBox_Text_FromSlides()

Dim oPres As Presentation
Dim oSlide As Slide
Dim oShapes As Shapes
Dim oShape As Shape

Set oPres = ActivePresentation

' --------------------------------------------------
' coded by Shasur for http://vbadud.blogspot.com
' --------------------------------------------------

For Each oSlide In oPres.Slides
    Set oShapes = oSlide.Shapes
    For Each oShape In oShapes
        If oShape.Type = msoTextBox Then
        
            Debug.Print oSlide.Name & vbTab & oShape.TextFrame.TextRange.Text
            
        End If
    Next oShape
Next oSlide



End Sub

Wednesday, May 26, 2010

How to get OS Version using VBA

How to retrieve Operating System Information using Excel/Word VBA

The version information of OS can be retrieved using the WIN API functions given below

Private Type OSVERSIONINFO
    dwOSVersionInfoSize As Long
    dwMajorVersion As Long
    dwMinorVersion As Long
    dwBuildNumber As Long
    dwPlatformId As Long
    szCSDVersion As String * 128
End Type

Private Declare Function GetVersionEx Lib "kernel32" _
      Alias "GetVersionExA" (lpVersionInformation As _
      OSVERSIONINFO) As Long


The following sub uses GetVersionEx function to get the Major and Minor version of OS

Sub Get_OS_Version_VBA()

' -------------------------------------------------------------
' Code to Get Version of Operating System through VBA
' -------------------------------------------------------------

Dim oOSInfo As OSVERSIONINFO
oOSInfo.dwOSVersionInfoSize = Len(oOSInfo)


GetVersionEx oOSInfo

' -------------------------------------------------------------
' Coded for http://vbadud.blogspot.com
' -------------------------------------------------------------

MsgBox "Version of Current OS is " & oOSInfo.dwMajorVersion & "." & oOSInfo.dwMinorVersion

End Sub

Saturday, May 22, 2010

How to iterate through all Subdirectories till the last directory in VBA

List all Level SubDirectories using VBA

The following code lists all the directories under c:\Temp

Function GetSubDir(ByVal sDir)

    Dim oFS As New FileSystemObject
    Dim oDir
    
    Set oDir = oFS.GetFolder(sDir)
    For Each oSub In oDir.SubFolders
        MsgBox oSub.Path
        GetSubDir oSub.Path
    Next oSub
End Function


You can call the function like shown below

GetSubDir "C:\Temp\"


The code uses FileSystemObject from Microsoft Scripting RunTime. You need to add reference to this library (see figure below)



See also VBA Dir Function to Get Sub Directories

How to retrieve images of the Word document using VBA / Extract images in

How to Save Word Document as WebPage using VBA

I have some lazy friends who come up with strange requirements. One such guy wanted me to extract images from Word document into a separate folder, which he want to use later. I found that saving the Webpage creates the images in a folder and that would be enough for the sloth friend. Here is the code snippet of that.

This code Saves the given document in Temporary folder (See How to get Temp folder using VBA)

Then it deletes the file and folder from the location (See Different Ways to Delete Files in VBA) to be sure there is no clash.

It then saves the document and loops through the Images folder using Dir function (See Dir Function in VBA) and stores them in an array

Function Save_As_HTML(ByRef oTempWd As Document) As Boolean


Dim sDir
Dim iDir As Integer
Dim oShp As Word.Shape                      ' Word Shape Object

On Error GoTo Err_Save_As_HTML

sTempFolder = GetTempFolder()
sImageFolder = sTempFolder & "Save_As_HTML_files\"

Delete_File sTempFolder & "Save_As_HTML.html"
Delete_File sImageFolder & "*.*"
RmDir sImageFolder


oTempWd.SaveAs sTempFolder & "Save_As_HTML.html", FileFormat:= _
        wdFormatHTML, LockComments:=False, Password:="", AddToRecentFiles:=True, _
        WritePassword:="", ReadOnlyRecommended:=False, EmbedTrueTypeFonts:=False, _
         SaveNativePictureFormat:=False, SaveFormsData:=False, SaveAsAOCELetter:= _
        False


oTempWd.Close (False)
Erase arImageFiles

sDir = Dir(sImageFolder & "*.gif") ' You can also use PNG format
Do Until Len(sDir) = 0
    iDir = iDir + 1
    arImageFiles(iDir) = sDir
    sDir = Dir
Loop

Err_Save_As_HTML:
If Err <> 0 Then
   Debug.Assert Err = 0
   Debug.Print Err.Description
   Err.Clear
   Resume Next
End If

End Function 

How to Increase / Decrease Size of Images in Word Document using VBA

Scaling of Pictures / Images using Word VBA

The following code scales all the pictures of the Word document

Function Scale_Pictures(ByRef oTempWd As Document) As Boolean


Dim oShp As Word.Shape                      ' Word Shape Object


' -------------------------------------
' Scale Shapes Height and Weight
' -------------------------------------
For Each oShp In oTempWd.Shapes
    oShp.ScaleHeight 0.6, msoFalse
    oShp.ScaleWidth 0.6, msoFalse
Next oShp

End Function 

How to insert field in Word 2007/2010



To insert Field in a Word document, select the Quick Parts option from Insert tab



Click on the Field, which will throw the following dialog box

Select appropriate field and enter the values

How to Select a Web Page from Excel / Word using VBA

How to Select a Web Page from using Excel / Word VBA

The following code uses GetOpenFilename method to select the Webpage (HTML here)

Sub Select_A_HTMLPAGE()
Dim fHTML As Variant
fHTML = Application.GetOpenFilename("Webpage (*.htm*), *.htm*", _
  , "Select a HTML page:")
 If fHTML <> False Then
      MsgBox "Selected file is" & CStr(fHTML)
 End If
End Sub

How to Check Internet Connectivity using VBA

The following code snippet uses API functions to check Internet connectivity and also the type of connection
:
Public Declare Function InternetGetConnectedState _
                         Lib "wininet.dll" (lpdwFlags As Long, _
                                            ByVal dwReserved As Long) As Boolean

Private Declare Function InternetGetConnectedStateEx Lib "wininet.dll" Alias "InternetGetConnectedStateExA" ( _
ByRef lpdwFlags As Long, _
ByVal lpszConnectionName As String, _
ByVal dwNameLen As Long, _
ByVal dwReserved As Long) As Long


'Local system uses a modem to connect to the Internet.
Private Const INTERNET_CONNECTION_MODEM As Long = &H1

'Local system uses a LAN to connect to the Internet.
Private Const INTERNET_CONNECTION_LAN As Long = &H2

'Local system uses a proxy server to connect to the Internet.
Private Const INTERNET_CONNECTION_PROXY As Long = &H4

The following API functions are used

Function IsConnected() As Boolean
    
    Dim Stat As Long
    
    IsConnected = (InternetGetConnectedState(Stat, 0&) <> 0)
    
    If IsConnected And INTERNET_CONNECTION_LAN Then
        MsgBox "Lan Connection"
    ElseIf IsConnected And INTERNET_CONNECTION_MODEM Then
        MsgBox "Modem Connection"
    ElseIf IsConnected And INTERNET_CONNECTION_PROXY Then
        MsgBox "Proxy"
    End If
End Function

If you want to know just if it is connected or not you can use the following:

CBool(InternetGetConnectedStateEx(0, vbNullString, 512, 0&))

Saturday, May 08, 2010

How to Dynamically Change Userform's Control properties from Excel Sheet using Excel VBA

How to Draw Rectangle in VBA using Excel Data

This is an exclusive request from Phil. If you find it interesting, I am more glad. The idea is to draw/resize a rectangle in userform based on values from Excel sheet.

I am using a label control for rectangle. Let us add a label control to userform and name it as LabelRect



To the WorkSheet_Change event of the required sheet add the following event

Private Sub Worksheet_Change(ByVal Target As Range)

Dim oLbl As MSForms.Label

Set oLbl = UserForm1.LabelRect

If Target.Address = "$B$1" Or Target.Address = "$B$2" Then

    If IsNumeric(Range("B1").Value) = True Then oLbl.Height = Range("B1").Value
    If IsNumeric(Range("B2").Value) = True Then oLbl.Width = Range("B2").Value
    oLbl.BackColor = vbGreen
    
    UserForm1.Show (False)
    
End If

End Sub


The code will get executed when there is a change in Value in column B1 and B2. Hence the label in the userform will be adjusted accordingly as shown below:

Saturday, April 24, 2010

How to Save Powerpoint Presentation with Password using VBA

How to Specify the Password in SaveAs option in PowerPoint VBA

Unlike SaveAs in Word/Excel, which takes the Password as part of the argument, Powerpoint SaveAs function doesn't specify it.

Here is a way to do it through VBA

Sub Save_Presentation_With_Password()

Dim oPS As PowerPoint.Presentation
Dim sTempPath As String

Set oPS = Presentations.Add
oPS.Slides.Add 1, ppLayoutTitle

' ----------------------------
' Coded by Shasur for VBADUD.Blogspot.com
' ----------------------------

sTempPath = Environ("Temp") & "\"

oPS.Password = "PPTPWD"


oPS.SaveAs FileName:=sTempPath & "PPTSample1.pptx", FileFormat:=ppSaveAsDefault
oPS.Close


End Sub 
 

See also


Run Excel Macro from Powerpoint VBA

Save Powerpoint Slides as Images using VBA

Add Controls Popup Menu using Powerpoint VBA

VBA - Creating PowerPoint Presentation

 

 

 

 

How to Convert Automatic Hyphens to Manual Hyphens using Word VBA

Word does automatic hyphenation at the end of line when the AutomaticHyphenation feature is turned on

ActiveDocument.AutoHyphenation = True 

For example, in the pic below, the word has hyphenated non-breaking automatically



You can test it by try selecting the Hyphen (which is not there physically)

The following code converts all automatic hyphens to manual ones

ActiveDocument.ConvertAutoHyphens

Friday, April 23, 2010

Unprotect and Protect Sheet using VBA code

How to write to protected Excel file using VBA

Here is a sample to unprotect a sheet and write some values and then protect the sheet again


Sub Unprotect_And_ThenProtect()
    
    ActiveSheet.Unprotect
    Range("A2").Value = Now()
    ActiveSheet.Protect DrawingObjects:=True, Contents:=True, Scenarios:=True

End Sub

Monday, March 29, 2010

How to clean Office Solution - .NET

How to clean Office Solution from Visual Studio / How to unistall Excel/Word addins using Visual Studio

Use the clean option in Build Menu to remove the Addin



Tuesday, February 16, 2010

Enable Developer Tab in Office 2010

How to enable Developer Tab in Office 2010

If the developer tab is not showing on your Ribbon UI, you can enable it from Application Options-->Customize Ribbon

Monday, February 15, 2010

Run Excel Macro from Powerpoint VBA





How to Run an Excel Macro from PowerPoint

Before writing code for doing it you need to add Excel Library to the PowerPoint VBE Project

Excel VBA and Power Point VBAPowerpoint VBE Screen

EXcel VBA and Powerpoint VBAExcel Library in the References

This can be done from Powerpoint VBE-->Tools-->References -->Browse for the particular reference and add them.

We have the Excel macros embedded in a workbook (CanBeDeleted.xlsm)



Sub AnotherWrkBook_Macro()

MsgBox "I have Run!"


End Sub



Above code is a simple message box. The code below, however, accepts an argument and stores the same in the workbook


Function Store_Value(ByVal sPPTName As String)

Sheet1.Range("A2").Value = sPPTName


End Function



The following Powerpoint VBA code uses Application.Run method of Excel VBA to execute a particular macro.

Multiple arguments can be passed to Application.Run method


Sub Run_Excel_Macro_From_PPT()

Dim oXL As Excel.Application ' Excel Application Object
Dim oWB As Excel.Workbook ' Excel Workbook Object
Dim sPName As String ' Variable - Active Presentation Name

On Error GoTo Err_PPXL

' -----------------------------------------------------------
' coded by Shasur for http://vbadud.blogspot.com
' -----------------------------------------------------------

Set oXL = New Excel.Application
Set oWB = oXL.Workbooks.Open("C:\Users\comp\Documents\CanBeDeleted.xlsm")

' Set Excel as Visibile - Turn Off if not needed
oXL.Visible = True

' Pass and Argument
sPName = ActivePresentation.Name

' Run the Macro without Argument
oXL.Application.Run "'CanBeDeleted.xlsm'!AnotherWrkBook_Macro"

' Run the Macro without Argument
oXL.Application.Run "'CanBeDeleted.xlsm'!Store_Value", sPName

' Save and Close the Workbook
oWB.Save
oWB.Close (False)


' Quit the Excel
oXL.Quit


' Release Objects - Good Practive
If Not oWB Is Nothing Then Set oWB = Nothing
If Not oXL Is Nothing Then Set oXL = Nothing


Err_PPXL:
If Err <> 0 Then
MsgBox Err.Description
Err.Clear
End If
End Sub




The macro saves and closes the workbook and quits Excel

See also:


Execute a macro in a different workbook

Run a Automatic Macro in Word Document

Saturday, February 13, 2010

Office 2010 - Application.FileSearch Error

Application.FileSearch doesn't work in Excel 2010 (Office 2010)

Application.FileSearch didn't work in Office 2007 (It has been deprecated from Office 2007) and hence it doesn't work in Office 2010 either. It will throw Run-time Errror 445 Object doesn't support this action

Office 2010 - Application.FileSearch ErrorRun-time Errror 445 Object doesn't support this action

There are some good work-arounds for this:

1. FileSystemObject

2. Dir Function


For a lively discussion please have a look at http://social.msdn.microsoft.com/Forums/en/isvvba/thread/a450830d-4fc3-4f4e-aee2-03f7994369d6



Excel 2010 Application.FileSearch Error, Excel 2007 Application.FileSearch Error

Saturday, February 06, 2010

How to check compatibility issues in a Word Document

How to check compatibility issues in an Office Document

Microsoft Office is getting polished rapidly. Upgrades from 2003 to 2010 saw sea change in functionality. If you are using 2010 and sending it to your friend who hasn’t upgraded, It is better to do a compatibility check


A check mark appears next to the name of the mode that the document is in.

1. Click the File tab.

2. Click Info.

3. In the Prepare for Sharing section, click Check for Issues, and then click Check Compatibility.

4. Click Select versions to show.









Show All Comments using Excel VBA / Hide All Comments using Excel VBA

The following code is a easier way to show all comments in the Excel Spreadsheet. This comes handy when you want to view all the comments to make some decisions.


Application.DisplayCommentIndicator = xlCommentAndIndicator




Just in case you feel the sheet is littered with comments you can turn it off by using


Application.DisplayCommentIndicator = xlCommentIndicatorOnly

Maximum Limit of Rows, Columns etc in Excel

How BIG is Excel 2007 and 2010

If you have worked on a large set of data from a non-Excel data source, for example, MS ACCESS, there are chances that you would have stored that in multiple sheets.

This riducules the data management. Now in Excel 2007 and above you have a big Excel workbook with 16384 columns and 10,48,576 rows

Following table gives you how big Excel has grown :)

Excel 2003

Excel 2007 and above

Maximum No of Rows

65,536

10,48,576

Maximum No of Columns

256

16,384

Related Posts Plugin for WordPress, Blogger...
Download Windows Live Toolbar and personalize your Web experience! Add custom buttons to get the information you care about most.