Hi Guys,

I'm completely new to excel macros. I found this code on a site and tried to create a macro from it, however I keep getting the following error:

Compile error: Type mismatch.

This is what the code looks like so far. The machine is a 64-bit Windows 7 machine.

Any help would be seriously appreciated.

 Option Explicit
 
   Public Type PRINTER_DEFAULTS
       pDatatype As Long
       pDevMode As Long
       DesiredAccess As Long
   End Type

   Public Type PRINTER_INFO_2
       pServerName As Long
       pPrinterName As Long
       pShareName As Long
       pPortName As Long
       pDriverName As Long
       pComment As Long
       pLocation As Long
       pDevMode As Long               '<<Pointer to DEVMODE structure
       pSepFile As Long
       pPrintProcessor As Long
       pDatatype As Long
       pParameters As Long
       pSecurityDescriptor As Long    '<<Pointer to SECURITY_DESCRIPTOR structure
       Attributes As Long
       Priority As Long
       DefaultPriority As Long
       StartTime As Long
       UntilTime As Long
       Status As Long
       cJobs As Long
       AveragePPM As Long
   End Type

   Public Type DEVMODE
       dmDeviceName As String * 32
       dmSpecVersion As Integer
       dmDriverVersion As Integer
       dmSize As Integer
       dmDriverExtra As Integer
       dmFields As Long
       dmOrientation As Integer
       dmPaperSize As Integer
       dmPaperLength As Integer
       dmPaperWidth As Integer
       dmScale As Integer
       dmCopies As Integer
       dmDefaultSource As Integer
       dmPrintQuality As Integer
       dmColor As Integer
       dmDuplex As Integer
       dmYResolution As Integer
       dmTTOption As Integer
       dmCollate As Integer
       dmFormName As String * 32
       dmUnusedPadding As Integer
       dmBitsPerPel As Integer
       dmPelsWidth As Long
       dmPelsHeight As Long
       dmDisplayFlags As Long
       dmDisplayFrequency As Long
       dmICMMethod As Long
       dmICMIntent As Long
       dmMediaType As Long
       dmDitherType As Long
       dmReserved1 As Long
       dmReserved2 As Long
   End Type

   Public Const DM_DUPLEX = &H1000&
   Public Const DM_IN_BUFFER = 8

   Public Const DM_OUT_BUFFER = 2
   Public Const PRINTER_ACCESS_ADMINISTER = &H4
   Public Const PRINTER_ACCESS_USE = &H8
   Public Const STANDARD_RIGHTS_REQUIRED = &HF0000
   Public Const PRINTER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or _
             PRINTER_ACCESS_ADMINISTER Or PRINTER_ACCESS_USE)
   
   Public Declare PtrSafe Function ClosePrinter _
     Lib "winspool.drv" _
       (ByVal hPrinter As Long) As Long
    
   Public Declare PtrSafe Function DocumentProperties _
     Lib "winspool.drv" _
       Alias "DocumentPropertiesA" _
         (ByVal hWnd As Long, _
          ByVal hPrinter As Long, _
          ByVal pDeviceName As String, _
          ByVal pDevModeOutput As Long, _
          ByVal pDevModeInput As Long, _
          ByVal fMode As Long) As Long
     
   Public Declare PtrSafe Function GetPrinter _
     Lib "winspool.drv" _
       Alias "GetPrinterA" _
         (ByVal hPrinter As Long, _
          ByVal Level As Long, _
          pPrinter As Byte, _
          ByVal cbBuf As Long, _
          pcbNeeded As Long) As Long
     
   Public Declare PtrSafe Function OpenPrinter _
     Lib "winspool.drv" _
       Alias "OpenPrinterA" _
         (ByVal pPrinterName As String, _
          phPrinter As Long, _
          pDefault As PRINTER_DEFAULTS) As Long
     
   Public Declare PtrSafe Function SetPrinter _
     Lib "winspool.drv" _
     Alias "SetPrinterA" _
       (ByVal hPrinter As Long, _
         ByVal Level As Long, _
         pPrinter As Byte, _
         ByVal Command As Long) As Long

   Public Declare PtrSafe Sub CopyMemory _
     Lib "kernel32" _
       Alias "RtlMoveMemory" _
         (pDest As Any, _
          pSource As Any, _
          ByVal cbLength As Long)
 
   Private Declare PtrSafe Function StrLen _
     Lib "kernel32" _
       Alias "lstrlenA" _
         (ByVal lpString As Long) As Long
 
   ' ==================================================================
   ' SetPrinterDuplex.
   '
   '  Set the Duplex flag for the specified default properties
   '  of the printer driver.
   '
   '  Returns: True on success and False on error. An error also

   '  displays a message box. This message box is displayed for information
   '  only. You must modify the code to support better error
   '  handling in your production application.
   '
   '  Parameters:
   '    sPrinterName - The name of the printer to be used.
   '
   '    nDuplexSetting - One of the following standard settings:
   '       1 = None
   '       2 = Duplex on long edge (book)
   '       3 = Duplex on short edge (legal)
   '
   ' ==================================================================
   Public Function SetPrinterDuplex(ByVal sPrinterName As String, _
                                    ByVal nDuplexSetting As Long) As Boolean

      Dim hPrinter As Long
      Dim pd As PRINTER_DEFAULTS
      Dim pinfo As PRINTER_INFO_2
      Dim dm As DEVMODE
   
      Dim yDevModeData() As Byte
      Dim yPInfoMemory() As Byte
      Dim nBytesNeeded As Long
      Dim nRet As Long, nJunk As Long
   
      On Error GoTo cleanup
   
      If (nDuplexSetting < 1) Or (nDuplexSetting > 3) Then
         MsgBox "Error: dwDuplexSetting is incorrect."
         Exit Function
      End If
      
      pd.DesiredAccess = PRINTER_ALL_ACCESS
      nRet = OpenPrinter(sPrinterName, hPrinter, pd)
      If (nRet = 0) Or (hPrinter = 0) Then
         If Err.LastDllError = 5 Then
            MsgBox "Access denied -- See the article for more info."
         Else
            MsgBox "Cannot open the printer specified " & _
              "(make sure the printer name is correct)."
         End If
         Exit Function
      End If
   
      nRet = DocumentProperties(0, hPrinter, sPrinterName, 0, 0, 0)
      If (nRet < 0) Then
         MsgBox "Cannot get the size of the DEVMODE structure."
         GoTo cleanup
      End If
   
      ReDim yDevModeData(nRet + 100) As Byte
      nRet = DocumentProperties(0, hPrinter, sPrinterName, _
                  VarPtr(yDevModeData(0)), 0, DM_OUT_BUFFER)
      If (nRet < 0) Then
         MsgBox "Cannot get the DEVMODE structure."
         GoTo cleanup
      End If
   
      Call CopyMemory(dm, yDevModeData(0), Len(dm))
   
      If Not CBool(dm.dmFields And DM_DUPLEX) Then
        MsgBox "You cannot modify the duplex flag for this printer " & _
               "because it does not support duplex or the driver " & _
               "does not support setting it from the Windows API."
         GoTo cleanup
      End If
   
      dm.dmDuplex = nDuplexSetting
      Call CopyMemory(yDevModeData(0), dm, Len(dm))
   
      nRet = DocumentProperties(0, hPrinter, sPrinterName, _
        VarPtr(yDevModeData(0)), VarPtr(yDevModeData(0)), _
        DM_IN_BUFFER Or DM_OUT_BUFFER)

      If (nRet < 0) Then
        MsgBox "Unable to set duplex setting to this printer."
        GoTo cleanup
      End If
   
      Call GetPrinter(hPrinter, 2, 0, 0, nBytesNeeded)
      If (nBytesNeeded = 0) Then GoTo cleanup
   
      ReDim yPInfoMemory(nBytesNeeded + 100) As Byte

      nRet = GetPrinter(hPrinter, 2, yPInfoMemory(0), nBytesNeeded, nJunk)
      If (nRet = 0) Then
         MsgBox "Unable to get shared printer settings."
         GoTo cleanup
      End If
   
      Call CopyMemory(pinfo, yPInfoMemory(0), Len(pinfo))
      pinfo.pDevMode = VarPtr(yDevModeData(0))
      pinfo.pSecurityDescriptor = 0
      Call CopyMemory(yPInfoMemory(0), pinfo, Len(pinfo))
   
      nRet = SetPrinter(hPrinter, 2, yPInfoMemory(0), 0)
      If (nRet = 0) Then
         MsgBox "Unable to set shared printer settings."
      End If
   
      SetPrinterDuplex = CBool(nRet)

cleanup:
      If (hPrinter <> 0) Then Call ClosePrinter(hPrinter)

   End Function

Public Sub PrintSingleSided()

  Dim I As Long
  Dim PrinterName As String
  Dim RetVal As Variant
  
    PrinterName = Application.ActivePrinter
    I = InStr(1, PrinterName, " on")
      If I > 0 Then PrinterName = Left(PrinterName, I - 1)
      
      
    RetVal = SetPrinterDuplex(PrinterName, 1)
    
End Sub

Public Sub PrintTwoSidedBookStyle()
  
  Dim I As Long
  Dim PrinterName As String
  Dim RetVal As Variant
  
    PrinterName = Application.ActivePrinter
    I = InStr(1, PrinterName, " on")
      If I > 0 Then PrinterName = Left(PrinterName, I - 1)
      
      
    RetVal = SetPrinterDuplex(PrinterName, 2)

End Sub

Public Sub PrintTwoSidedTabletStyle()

  Dim I As Long
  Dim PrinterName As String
  Dim RetVal As Variant
  
    PrinterName = Application.ActivePrinter
    I = InStr(1, PrinterName, " on")
      If I > 0 Then PrinterName = Left(PrinterName, I - 1)
      
      
    RetVal = SetPrinterDuplex(PrinterName, 3)

End Sub