Illegal Error

  • Thread starter Thread starter Guest
  • Start date Start date
G

Guest

When this procedure is ran on a Windows 98 (255 ram) machine and Access 2000
ver 9.0.0.2719 the computer locks up and I get all sorts of errors.
(Kernal32, Explorer, and Blue Screens of DEATH) I don't have any poblems on
my Computer that has less ram, but is Windows 2000. The API calls work and
were originally made for Access 2000. Is this because of a Service Pack
issue or could it be something else? (I can't install the service packs
because we lost the CD for this version of office.)

Is there a way to run this procedure with a pause between:
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
--PAUSE--
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
--PAUSE--
SetDefaultPrinter strCurrentPtr


---------Start Form Code--------
Private Sub Form_AfterUpdate()
On Error GoTo Err_cmdDuplicate

If Me.Dirty Then 'Save any edits.
Me.Dirty = False
End If

If Me.NewRecord Then 'Check there is a record to print
MsgBox "You must complete package information before printing a
label.", , "PackageLog 2005"
Else

Dim strCurrentPtr As String
Dim strSlipPrinter As String

strSlipPrinter = DLookup("[Printer]", "[DefaultLabelPrinter]", "[ID]
= 1")
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
SetDefaultPrinter strCurrentPtr
End If

Exit_cmdDuplicate:
Exit Sub

Err_cmdDuplicate:
If Err = 2212 Then
Else
MsgBox "Error " & Err.Number & " " & Err.Description
End If

Resume Exit_cmdDuplicate

End Sub
-------------end of code------------
 
They are API calls and they came from a link on allenbrowne.com. I did not
look at that website until now, and that looks way to complicated for my
level of experience. Would I just replace some code with PrtDevNames and
PrtDevMode properties

Rob Oldfield said:
Where do getcurrentptr and setdefaultprinter come from? I'd guess that
they're your problem.

Have you looked at this.... http://www.mvps.org/access/reports/rpt0009.htm



James said:
When this procedure is ran on a Windows 98 (255 ram) machine and Access 2000
ver 9.0.0.2719 the computer locks up and I get all sorts of errors.
(Kernal32, Explorer, and Blue Screens of DEATH) I don't have any poblems on
my Computer that has less ram, but is Windows 2000. The API calls work and
were originally made for Access 2000. Is this because of a Service Pack
issue or could it be something else? (I can't install the service packs
because we lost the CD for this version of office.)

Is there a way to run this procedure with a pause between:
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
--PAUSE--
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
--PAUSE--
SetDefaultPrinter strCurrentPtr


---------Start Form Code--------
Private Sub Form_AfterUpdate()
On Error GoTo Err_cmdDuplicate

If Me.Dirty Then 'Save any edits.
Me.Dirty = False
End If

If Me.NewRecord Then 'Check there is a record to print
MsgBox "You must complete package information before printing a
label.", , "PackageLog 2005"
Else

Dim strCurrentPtr As String
Dim strSlipPrinter As String

strSlipPrinter = DLookup("[Printer]", "[DefaultLabelPrinter]", "[ID]
= 1")
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
SetDefaultPrinter strCurrentPtr
End If

Exit_cmdDuplicate:
Exit Sub

Err_cmdDuplicate:
If Err = 2212 Then
Else
MsgBox "Error " & Err.Number & " " & Err.Description
End If

Resume Exit_cmdDuplicate

End Sub
-------------end of code------------
 
Hmm. Which link?

....and there again... how about this? (...stolen from an old post by Albert
D. Kallal...)


While you can't change the printer settings in a MDE, you actually don't
want to store the printer with report anyway. In other words, you should NOT
be storing the printer name with the report.

If you leave all reports with NO printer name, then simple solution becomes
to change the current windows default printer. The following code will do
just that. This code is minimal, and is smaller than the daily FAQ posted in
this newsgroup. Just paste the following into a module.


Option Compare Database
Option Explicit

'************************
' Printer setup module
' Set/retrieves the default printer - originaly for VB6
' Works for A97/a2000
' This is minimal code.
' Albert D.Kallal - 01/13/2002, (e-mail address removed)
' Rev history: Date Who notes
' 01/13/2002 Albert D. kallal
'
' I wrote this after looking at some the code on the net. Some of the
routines
' to change a printer were approaching 500 + of lines of code. Just the
printer
' constant defs was over 100 lines of code! Yikes! (not mention the whole
thing being
' 4 or more modules! How in heck is one supposed to add a simple printer
change to
' ones app? The solution is below!

' In addition the code on dev's site has some bugs, and will cause windows
to show
' *more* than one printer as the default. This is especially noticeable on
windows ME. The
' code here does NOT have this problem.
' I have not had time to clean this code up...it is "as is"

' I use only TWO API's (the 3rd one is optional). There is a total of only 4
functions!
' KISS is the word. Keep it simple stupid. I don't care about device
drivers, or the
' port number. All these routines just work with the simple printer name. If
you do
' actually care about the device driver and port stuff..then use the one of
many
' examples available on the net. Those other examples also deal with margins
, orientation
' etc.
'
' You can paste this code into a module..and away you go
'
'************************
' How to use
' To get the default printer
' debug.print GetDefaultPrinter
' To set the default printer
' debug.print SetDefaultPrinter("HP Laser JET")
' above returns true if success.
' To get a list of printers suitable for a listbox, or combo
' debug.print GetPrinters (in forms on-load event you
' would use:
' Me.Combo0.RowSource = GetPrinters
' Me.Combo0 = GetDefaultPrinter
' the first line loads up the combo box, the 2nd sets
' the combo to the default.
'
' that is all there folks!
'
' Thus, when printing a report, you can:
'
' 1) save the default printer into a string
' strCurrentPtr = GetDefaultPrinter
' 2) switch to your report printer
' SetDefaultPrinter strReportsPtr
' 3) print report
' 4) switch back to the default printer
' SetDefaultPrinter strCurrentPtr
'

Private Const HWND_BROADCAST As Long = &HFFFF&
Private Const WM_WININICHANGE As Long = &H1A

' The following code allows one to read, and write to the WIN.INI files
' In win 2000 the printer settings are actually in the registry. However,
windows
' handles this correctly
'
Private Declare Function GetProfileString Lib "kernel32" _
Alias "GetProfileStringA" _
(ByVal lpAppName As String, _
ByVal lpKeyName As String, _
ByVal lpDefault As String, _
ByVal lpReturnedString As String, _
ByVal nSize As Long) As Long

Private Declare Function WriteProfileString Lib "kernel32" _
Alias "WriteProfileStringA" _
(ByVal lpszSection As String, _
ByVal lpszKeyName As String, _
ByVal lpszString As String) As Long

Private Declare Function SendMessage Lib "user32" _
Alias "SendMessageA" _
(ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
lparam As Any) As Long



Private Function fstrDField(mytext As String, delim As String, groupnum As
Integer) As String

' this is a standard delimiter routine that every developer I know has.
' This routine has a million uses. This routine is great for splitting up
' data fields, or sending multiple parms to a openargs of a form
'
' Parms are
' mytext - a delimited string
' delim - our delimiter (usually a , or / or a space)
' groupnum - which of the delimited values to return
'

Dim startpos As Integer, endpos As Integer
Dim groupptr As Integer, chptr As Integer

chptr = 1
startpos = 0
For groupptr = 1 To groupnum - 1
chptr = InStr(chptr, mytext, delim)
If chptr = 0 Then
fstrDField = ""
Exit Function
Else
chptr = chptr + 1
End If
Next groupptr
startpos = chptr
endpos = InStr(startpos + 1, mytext, delim)
If endpos = 0 Then
endpos = Len(mytext) + 1
End If

fstrDField = Mid$(mytext, startpos, endpos - startpos)

End Function

Function SetDefaultPrinter(strPrinterName As String) As Boolean

Dim strDeviceLine As String
Dim strBuffer As String
Dim lngbuf As Long

' get the full device string
'
strBuffer = Space(1024)
lngbuf = GetProfileString("PrinterPorts", strPrinterName, "", strBuffer,
Len(strBuffer))

'Write out this new printer information in
' WIN.INI file for DEVICE item
If lngbuf > 0 Then

strDeviceLine = strPrinterName & "," & _
fstrDField(strBuffer, Chr(0), 1) & "," & _
fstrDField(strBuffer, Chr(0), 2)

Call WriteProfileString("windows", "Device", strDeviceLine)
SetDefaultPrinter = True

' Below is optional, and should be done. It updates the existing
windows
' so the "default" printer icon changes. If you don't do the
below..then
' you will often see more than one printer as the default! The reason
*not*
' to do the SendMessage is that many open applications will now sense
the change
' in printer. I vote to leave it in..but your case you might not want
this.
'

Call SendMessage(HWND_BROADCAST, WM_WININICHANGE, 0, ByVal "windows")

Else
SetDefaultPrinter = False
End If

End Function

Function GetDefaultPrinter() As String

Dim strDefault As String
Dim lngbuf As Long

strDefault = String(255, Chr(0))
lngbuf = GetProfileString("Windows", "Device", "", strDefault,
Len(strDefault))
If lngbuf > 0 Then
GetDefaultPrinter = fstrDField(strDefault, ",", 1)
Else
GetDefaultPrinter = ""
End If

End Function


Function GetPrinters() As String

' this routine returns a list of printers, separated by
' a ";", and thus the results are suitable for stuffing into a combo box

Dim strBuffer As String
Dim strOnePtr As String
Dim intPos As Integer
Dim lngChars As Long

strBuffer = Space(2048)
lngChars = GetProfileString("PrinterPorts", vbNullString, "", strBuffer,
Len(strBuffer))

If lngChars > 0 Then
intPos = InStr(strBuffer, Chr(0))
Do While intPos > 1
strOnePtr = Left(strBuffer, intPos - 1)
strBuffer = Mid(strBuffer, intPos + 1)
If GetPrinters <> "" Then GetPrinters = GetPrinters & ";"
GetPrinters = GetPrinters & strOnePtr
intPos = InStr(strBuffer, Chr(0))
Loop
Else
GetPrinters = ""
End If

End Function

Public Function testPrintersGet()

Debug.Print GetDefaultPrinter
Debug.Print GetPrinters


End Function

James said:
They are API calls and they came from a link on allenbrowne.com. I did not
look at that website until now, and that looks way to complicated for my
level of experience. Would I just replace some code with PrtDevNames and
PrtDevMode properties

Rob Oldfield said:
Where do getcurrentptr and setdefaultprinter come from? I'd guess that
they're your problem.

Have you looked at this.... http://www.mvps.org/access/reports/rpt0009.htm



James said:
When this procedure is ran on a Windows 98 (255 ram) machine and
Access
2000
ver 9.0.0.2719 the computer locks up and I get all sorts of errors.
(Kernal32, Explorer, and Blue Screens of DEATH) I don't have any
poblems
on
my Computer that has less ram, but is Windows 2000. The API calls
work
and
were originally made for Access 2000. Is this because of a Service Pack
issue or could it be something else? (I can't install the service packs
because we lost the CD for this version of office.)

Is there a way to run this procedure with a pause between:
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
--PAUSE--
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
--PAUSE--
SetDefaultPrinter strCurrentPtr


---------Start Form Code--------
Private Sub Form_AfterUpdate()
On Error GoTo Err_cmdDuplicate

If Me.Dirty Then 'Save any edits.
Me.Dirty = False
End If

If Me.NewRecord Then 'Check there is a record to print
MsgBox "You must complete package information before printing a
label.", , "PackageLog 2005"
Else

Dim strCurrentPtr As String
Dim strSlipPrinter As String

strSlipPrinter = DLookup("[Printer]", "[DefaultLabelPrinter]", "[ID]
= 1")
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
SetDefaultPrinter strCurrentPtr
End If

Exit_cmdDuplicate:
Exit Sub

Err_cmdDuplicate:
If Err = 2212 Then
Else
MsgBox "Error " & Err.Number & " " & Err.Description
End If

Resume Exit_cmdDuplicate

End Sub
-------------end of code------------
 
Thank you again. That is the code I am already using. I installed the
service packs on the machine that I was having trouble with, and so far no
problems.

Rob Oldfield said:
Hmm. Which link?

....and there again... how about this? (...stolen from an old post by Albert
D. Kallal...)


While you can't change the printer settings in a MDE, you actually don't
want to store the printer with report anyway. In other words, you should NOT
be storing the printer name with the report.

If you leave all reports with NO printer name, then simple solution becomes
to change the current windows default printer. The following code will do
just that. This code is minimal, and is smaller than the daily FAQ posted in
this newsgroup. Just paste the following into a module.


Option Compare Database
Option Explicit

'************************
' Printer setup module
' Set/retrieves the default printer - originaly for VB6
' Works for A97/a2000
' This is minimal code.
' Albert D.Kallal - 01/13/2002, (e-mail address removed)
' Rev history: Date Who notes
' 01/13/2002 Albert D. kallal
'
' I wrote this after looking at some the code on the net. Some of the
routines
' to change a printer were approaching 500 + of lines of code. Just the
printer
' constant defs was over 100 lines of code! Yikes! (not mention the whole
thing being
' 4 or more modules! How in heck is one supposed to add a simple printer
change to
' ones app? The solution is below!

' In addition the code on dev's site has some bugs, and will cause windows
to show
' *more* than one printer as the default. This is especially noticeable on
windows ME. The
' code here does NOT have this problem.
' I have not had time to clean this code up...it is "as is"

' I use only TWO API's (the 3rd one is optional). There is a total of only 4
functions!
' KISS is the word. Keep it simple stupid. I don't care about device
drivers, or the
' port number. All these routines just work with the simple printer name. If
you do
' actually care about the device driver and port stuff..then use the one of
many
' examples available on the net. Those other examples also deal with margins
, orientation
' etc.
'
' You can paste this code into a module..and away you go
'
'************************
' How to use
' To get the default printer
' debug.print GetDefaultPrinter
' To set the default printer
' debug.print SetDefaultPrinter("HP Laser JET")
' above returns true if success.
' To get a list of printers suitable for a listbox, or combo
' debug.print GetPrinters (in forms on-load event you
' would use:
' Me.Combo0.RowSource = GetPrinters
' Me.Combo0 = GetDefaultPrinter
' the first line loads up the combo box, the 2nd sets
' the combo to the default.
'
' that is all there folks!
'
' Thus, when printing a report, you can:
'
' 1) save the default printer into a string
' strCurrentPtr = GetDefaultPrinter
' 2) switch to your report printer
' SetDefaultPrinter strReportsPtr
' 3) print report
' 4) switch back to the default printer
' SetDefaultPrinter strCurrentPtr
'

Private Const HWND_BROADCAST As Long = &HFFFF&
Private Const WM_WININICHANGE As Long = &H1A

' The following code allows one to read, and write to the WIN.INI files
' In win 2000 the printer settings are actually in the registry. However,
windows
' handles this correctly
'
Private Declare Function GetProfileString Lib "kernel32" _
Alias "GetProfileStringA" _
(ByVal lpAppName As String, _
ByVal lpKeyName As String, _
ByVal lpDefault As String, _
ByVal lpReturnedString As String, _
ByVal nSize As Long) As Long

Private Declare Function WriteProfileString Lib "kernel32" _
Alias "WriteProfileStringA" _
(ByVal lpszSection As String, _
ByVal lpszKeyName As String, _
ByVal lpszString As String) As Long

Private Declare Function SendMessage Lib "user32" _
Alias "SendMessageA" _
(ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
lparam As Any) As Long



Private Function fstrDField(mytext As String, delim As String, groupnum As
Integer) As String

' this is a standard delimiter routine that every developer I know has.
' This routine has a million uses. This routine is great for splitting up
' data fields, or sending multiple parms to a openargs of a form
'
' Parms are
' mytext - a delimited string
' delim - our delimiter (usually a , or / or a space)
' groupnum - which of the delimited values to return
'

Dim startpos As Integer, endpos As Integer
Dim groupptr As Integer, chptr As Integer

chptr = 1
startpos = 0
For groupptr = 1 To groupnum - 1
chptr = InStr(chptr, mytext, delim)
If chptr = 0 Then
fstrDField = ""
Exit Function
Else
chptr = chptr + 1
End If
Next groupptr
startpos = chptr
endpos = InStr(startpos + 1, mytext, delim)
If endpos = 0 Then
endpos = Len(mytext) + 1
End If

fstrDField = Mid$(mytext, startpos, endpos - startpos)

End Function

Function SetDefaultPrinter(strPrinterName As String) As Boolean

Dim strDeviceLine As String
Dim strBuffer As String
Dim lngbuf As Long

' get the full device string
'
strBuffer = Space(1024)
lngbuf = GetProfileString("PrinterPorts", strPrinterName, "", strBuffer,
Len(strBuffer))

'Write out this new printer information in
' WIN.INI file for DEVICE item
If lngbuf > 0 Then

strDeviceLine = strPrinterName & "," & _
fstrDField(strBuffer, Chr(0), 1) & "," & _
fstrDField(strBuffer, Chr(0), 2)

Call WriteProfileString("windows", "Device", strDeviceLine)
SetDefaultPrinter = True

' Below is optional, and should be done. It updates the existing
windows
' so the "default" printer icon changes. If you don't do the
below..then
' you will often see more than one printer as the default! The reason
*not*
' to do the SendMessage is that many open applications will now sense
the change
' in printer. I vote to leave it in..but your case you might not want
this.
'

Call SendMessage(HWND_BROADCAST, WM_WININICHANGE, 0, ByVal "windows")

Else
SetDefaultPrinter = False
End If

End Function

Function GetDefaultPrinter() As String

Dim strDefault As String
Dim lngbuf As Long

strDefault = String(255, Chr(0))
lngbuf = GetProfileString("Windows", "Device", "", strDefault,
Len(strDefault))
If lngbuf > 0 Then
GetDefaultPrinter = fstrDField(strDefault, ",", 1)
Else
GetDefaultPrinter = ""
End If

End Function


Function GetPrinters() As String

' this routine returns a list of printers, separated by
' a ";", and thus the results are suitable for stuffing into a combo box

Dim strBuffer As String
Dim strOnePtr As String
Dim intPos As Integer
Dim lngChars As Long

strBuffer = Space(2048)
lngChars = GetProfileString("PrinterPorts", vbNullString, "", strBuffer,
Len(strBuffer))

If lngChars > 0 Then
intPos = InStr(strBuffer, Chr(0))
Do While intPos > 1
strOnePtr = Left(strBuffer, intPos - 1)
strBuffer = Mid(strBuffer, intPos + 1)
If GetPrinters <> "" Then GetPrinters = GetPrinters & ";"
GetPrinters = GetPrinters & strOnePtr
intPos = InStr(strBuffer, Chr(0))
Loop
Else
GetPrinters = ""
End If

End Function

Public Function testPrintersGet()

Debug.Print GetDefaultPrinter
Debug.Print GetPrinters


End Function

James said:
They are API calls and they came from a link on allenbrowne.com. I did not
look at that website until now, and that looks way to complicated for my
level of experience. Would I just replace some code with PrtDevNames and
PrtDevMode properties

Rob Oldfield said:
Where do getcurrentptr and setdefaultprinter come from? I'd guess that
they're your problem.

Have you looked at this.... http://www.mvps.org/access/reports/rpt0009.htm



When this procedure is ran on a Windows 98 (255 ram) machine and Access
2000
ver 9.0.0.2719 the computer locks up and I get all sorts of errors.
(Kernal32, Explorer, and Blue Screens of DEATH) I don't have any poblems
on
my Computer that has less ram, but is Windows 2000. The API calls work
and
were originally made for Access 2000. Is this because of a Service Pack
issue or could it be something else? (I can't install the service packs
because we lost the CD for this version of office.)

Is there a way to run this procedure with a pause between:
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
--PAUSE--
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
--PAUSE--
SetDefaultPrinter strCurrentPtr


---------Start Form Code--------
Private Sub Form_AfterUpdate()
On Error GoTo Err_cmdDuplicate

If Me.Dirty Then 'Save any edits.
Me.Dirty = False
End If

If Me.NewRecord Then 'Check there is a record to print
MsgBox "You must complete package information before printing a
label.", , "PackageLog 2005"
Else

Dim strCurrentPtr As String
Dim strSlipPrinter As String

strSlipPrinter = DLookup("[Printer]", "[DefaultLabelPrinter]",
"[ID]
= 1")
strCurrentPtr = GetDefaultPrinter
SetDefaultPrinter strSlipPrinter
DoCmd.OpenReport "PackageSlip", acViewNormal
DoCmd.OpenReport "MailboxSlip", acViewNormal
SetDefaultPrinter strCurrentPtr
End If

Exit_cmdDuplicate:
Exit Sub

Err_cmdDuplicate:
If Err = 2212 Then
Else
MsgBox "Error " & Err.Number & " " & Err.Description
End If

Resume Exit_cmdDuplicate

End Sub
-------------end of code------------
 
Back
Top