
|
Using ExportEx and ExportBitmap methods in CorelDRAW 10
CorelDRAW 10 introduces a new way of exporting graphics into different
format. Along with the old method Document.Export there
are two new ones in the Document object - ExportEx and
ExportBitmap:
- Function ExportEx(ByVal
FileName As String, ByVal Filter As
cdrFilter, [ByVal Range As cdrExportRange =
cdrCurrentPage (1)], [ByVal Options As
StructExportOptions = 0], [ByVal PaletteOptions As
StructPaletteOptions]) As Object
- Function ExportBitmap(ByVal
FileName As String, ByVal Filter As
cdrFilter, [ByVal Range As cdrExportRange =
cdrCurrentPage (1)], [ByVal ImageType As cdrImageType
= cdrRGBColorImage (4)], [ByVal Width As Long = 0], [ByVal
Height As Long = 0], [ByVal ResolutionX
As Long = 72], [ByVal ResolutionY As Long = 72], [ByVal
AntiAliasingType As cdrAntiAliasingType =
cdrNormalAntiAliasing (1)], [ByVal Dithered As
Boolean = False], [ByVal Transparent As Boolean =
False], [ByVal UseColorProfile As Boolean = True], [ByVal
Compression As cdrCompressionType =
cdrCompressionNone (0)], [ByVal PaletteOptions As
StructPaletteOptions]) As Object
In fact, both are doing exactly the same and you can use
ExportEx to export bitmaps as well as ExportBitmap to export vector art,
however they differ in the way they accept export parameters. As with
old Export method, ExportEx uses StructExportOptions object
to pass all the parameters needed to do the export. Here is the StructExportOptions object:
Properties:
- Property AntiAliasingType
As cdrAntiAliasingType [r/w]
- Property Compression
As cdrCompressionType [r/w]
- Property Dithered
As Boolean [r/w]
- Property ImageType
As cdrImageType [r/w]
- Property Overwrite
As Boolean [r/w]
- Property ResolutionX
As Long [r/w]
- Property ResolutionY
As Long [r/w]
- Property SizeX As
Long [r/w]
- Property SizeY As
Long [r/w]
- Property Transparent
As Boolean [r/w]
- Property UseColorProfile
As Boolean [r/w]
|
As you might notice most of the parameters in this object
are used only for rasterizing vectors (i.e. for bitmap export only). So,
you can create this object and set all the parameters, then call
ExportEx or you can just call ExportBitmap and pass all the values
"in-line" without having to create the StructExportOptions
object. The choice is yours. Please note that there are some new parameters in the
object - Compression, Dithered, Transparent,
and UseColorProfile. Compression is used by a limited number
of export filters such as BMP and TIFF. Dithered is used mostly for converting
to Black and white because in Draw 10 there's a new mechanism of
converting images to Paletted mode. I'll explain it a little bit later. Transparent can be only used with filter
that support transparency (e.g. CPT, TIFF, PSD). And UseColorProfile lets you use color
correction when exporting to bitmap. Also note that: ResolutionX and ResolutionY specify
the image resolution in DPI. If not specified, 72 dpi is used. SizeX and SizeY specify
the image size in pixels. If any of these is omitted (set to 0), the
(respective) size is calculated based on the export image resolution and
the actual object size in CorelDRAW. So you don't have to calculate it
yourself using Shape.GetSize method and then multiplying the size by the
resolution... You can also notice that there is a new parameter in call
to ExportEx comparing to Export method (it's also in ExportBitmap) -
PaletteOptions. This parameter is used when exporting to paletted
bitmaps:
Properties:
- Property ColorSensitive
As Boolean [r/w]
- Property DitherIntensity
As Long [r/w]
- Property DitherType
As cdrDitherType [r/w]
- Property Importance
As Long [r/w]
- Property Lightness
As Long [r/w]
- Property NumColors
As Long [r/w]
- Property PaletteType
As cdrImagePaletteType [r/w]
- Property Smoothing
As Long [r/w]
- Property TargetColor
As Long [r/w]
- Property ToleranceA
As Long [r/w]
- Property ToleranceB
As Long [r/w]
|
The parameters in this object correspond to the same
values in Convert To Paletted dialog. I believe you can figure it out
quickly... If you omit PaletteOptions patameter, default values are
used (optimized palette, 256 colors, no smoothing, no dithering and no
color sensitivity).
Both ExportEx
and ExportBitmap return an object representing the export filter. The
methods themselves do not do the export - they just prepare the drawing
for export and then load the filter and you must use the returned object
to finish the export. The actual object returned depends on the filter you
use for exporting. About a dozen filters support COM interfaces now.
They expose an export object you can use to interact with the filter.
All export objects contain at least four methods and properties:
- Property HasDialog
As Boolean [r/o]
- Sub Finish()
- Sub Reset()
- Function ShowDialog()
As Boolean
HasDialog returns True if the filter has
dialog box. If this property returns True, you may call ShowDialog
method to show the dialog and let the user set any export
filter parameters. ShowDialog returns True if the user
clicked OK, otherwise it returns False. Use Reset method to set all filter
parameters to default values (acts like Reset button on some bitmap
export filter dialogs). Finish should be called in order to
finish the export and free any memory allocated by ExportEx/ExportBitmap.
If you destroy the filter object without calling Finish method,
the export is canceled and the memory is freed automatically. So, you can do something like this in order to export
your document using the new export methods:
Sub Test()
Dim Filter as Object
Dim Res as Boolean
Set Filter = ActiveDocument.ExportBitmap("C:\image.jpg", cdrJPEG, _
cdrSelection, cdrRGBColorImage, UseColorProfile:=False)
Res = True
If Filter.HasDialog Then Res = Filter.ShowDialog()
If Res Then Filter.Finish
Set Filter = Nothing
End Sub
This example exports the current selection to JPEG
showing the filter dialog.
The following filters support advanced export
parameters:
- AI
- BMP (OS/2)
- DXF/DWG
- WMF/EMF
- EPS
- FPX
- GEM
- GIF
- JPEG
- PNG
- TGA
- WPG
- WVL (WI)
You can use these parameters to control some of the
filter-specific export parameters such as JPEG compression or GIF
transparency color. For example:
Sub Test()
Dim Filter as Object
Dim Res as Boolean
Set Filter=ActiveDocument.ExportBitmap("C:\image.jpg", cdrJPEG, _
cdrSelection, cdrRGBColorImage, UseColorProfile:=False)
Filter.Compression=20
Filter.Optimized=True
Res=True
If Filter.HasDialog Then Res=Filter.ShowDialog()
If Res Then Filter.Finish
Set Filter=Nothing
End Sub
You can both read and write most filter parameters. For instance, you can set some values, show
the filter dialog and then inspect the changes
the user might have done and correct something if necessary (e.g. you
might not want to allow to create transparent GIFs... for some
reason... :-) If the filter doesn't have extended parameters (e.g. CMX
or CPT) or the filter doesn't support automation at all (3rd party or
old filters), a default export filter object is returned with those
basic 4 methods. For the complete object models of supported filters, see
the link below:
|