Win32FileDialog.st
author Claus Gittinger <cg@exept.de>
Mon, 31 Mar 2008 18:14:43 +0200
changeset 8037 04b0b1939a14
parent 8015 4e27ebbd5d79
child 8260 bd2f4ccb4fec
permissions -rw-r--r--
double*AtOffset -> double*

"{ Package: 'stx:libtool' }"

Object subclass:#Win32FileDialog
	instanceVariableNames:'fileName openFileNameStruct filters lpstrFilter lpstrFile
		lpstrInitialDir lpstrTitle lpstrDefExt defFilter defExtension
		style title smalltalkFileFilters defFilterIndex parent'
	classVariableNames:'InitialDirectory CommonDialogConstants FilterPatternDescriptions'
	poolDictionaries:''
	category:'Interface-Tools-File'
!

ByteArray variableByteSubclass:#OpenFilenameStructure
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:Win32FileDialog
!


!Win32FileDialog class methodsFor:'instance creation'!

new

    ^ super new initialize
! !

!Win32FileDialog class methodsFor:'accessing'!

getInitialDirectory

     ^ InitialDirectory
!

setInitialDirectory: aName

     InitialDirectory := Directory pathName: aName
! !

!Win32FileDialog class methodsFor:'constants'!

commonDialogConstantAt: aString

    ^ self commonDialogConstants at: aString ifAbsent:[Transcript showCR: 'Common Dialog Constant ', aString, ' notfound!!']
!

commonDialogConstants

    CommonDialogConstants isNil ifTrue:[CommonDialogConstants := self generateCommonDialogConstants ].
    ^ CommonDialogConstants
!

generateCommonDialogConstants

    |dictionary|

    dictionary := Dictionary new.
    dictionary
    at: 'CcPreventfullopen' put: 4;
    at: 'FrShowhelp' put: 128;
    at: 'PdEnablesetuptemplate' put: 32768;
    at: 'FrNoupdown' put: 1024;
    at: 'CfNosimulations' put: 4096;
    at: 'OfnPathmustexist' put: 2048;
    at: 'CfWysiwyg' put: 32768;
    at: 'PdReturndc' put: 256;
    at: 'PdEnableprinthook' put: 4096;
    at: 'CfInittologfontstruct' put: 64;
    at: 'CfScalableonly' put: 131072;
    at: 'PdPrinttofile' put: 32;
    at: 'CfEffects' put: 256;
    at: 'PdShowhelp' put: 2048;
    at: 'OfnEnabletemplatehandle' put: 128;
    at: 'CfBoth' put: 3;
    at: 'OfnReadonly' put: 1;
    at: 'PdNopagenums' put: 8;
    at: 'PdDisableprinttofile' put: 524288;
    at: 'PdHideprinttofile' put: 1048576;
    at: 'OfnAllowmultiselect' put: 512;
    at: 'CfPrinterfonts' put: 2;
    at: 'CfEnabletemplatehandle' put: 32;
    at: 'PdSelection' put: 1;
    at: 'OfnHidereadonly' put: 4;
    at: 'PdPrintsetup' put: 64;
    at: 'OfnExtentiondifferent' put: 1024;
    at: 'FrReplaceall' put: 32;
    at: 'FrMatchcase' put: 4;
    at: 'OfnFilemustexist' put: 4096;
    at: 'PdCollate' put: 16;
    at: 'CfFixedpitchonly' put: 16384;
    at: 'PdEnablesetuphook' put: 8192;
    at: 'OfnShareaware' put: 16384;
    at: 'CcEnablehook' put: 16;
    at: 'CfEnabletemplate' put: 16;
    at: 'Findmsgstring' put: 'commdlgFindreplace';
    at: 'CfLimitsize' put: 8192;
    at: 'OfnNochangedir' put: 8;
    at: 'OfnCreateprompt' put: 8192;
    at: 'ScreenFonttype' put: 8192;
    at: 'PdUsedevmodecopies' put: 262144;
    at: 'CcRgbinit' put: 1;
    at: 'FrFindnext' put: 8;
    at: 'CfUsestyle' put: 128;
    at: 'FrEnablehook' put: 256;
    at: 'PdEnableprinttemplatehandle' put: 65536;
    at: 'CfShowhelp' put: 4;
    at: 'FrNowholeword' put: 4096.
    dictionary
    at: 'ShareExist' put: 16448;
    at: 'OfnOverwriteprompt' put: 2;
    at: 'OfnEnablehook' put: 32;
    at: 'OfnShowhelp' put: 16;
    at: 'CcEnabletemplatehandle' put: 64;
    at: 'SimulatedFonttype' put: 32768;
    at: 'FrDown' put: 1;
    at: 'PdEnableprinttemplate' put: 16384;
    at: 'CfNovectorfonts' put: 2048;
    at: 'PdNoselection' put: 4;
    at: 'CfAnsionly' put: 1024;
    at: 'OfnNovalidate' put: 256;
    at: 'CfScreenfonts' put: 1;
    at: 'FrWholeword' put: 2;
    at: 'FrEnabletemplatehandle' put: 8192;
    at: 'PdAllpages' put: 0;
    at: 'CfForcefontexist' put: 65536;
    at: 'CcEnabletemplate' put: 32;
    at: 'PdPagenums' put: 2;
    at: 'FrReplace' put: 16;
    at: 'PdEnablesetuptemplatehandle' put: 131072;
    at: 'CfApply' put: 512;
    at: 'OfnEnabletemplate' put: 64;
    at: 'DnDefaultprn' put: 1;
    at: 'PdNowarning' put: 128;
    at: 'CfTtonly' put: 262144;
    at: 'PrinterFonttype' put: 16384;
    at: 'CcShowhelp' put: 8;
    at: 'CcFullopen' put: 2;
    at: 'PdReturnic' put: 512;
    at: 'FrEnabletemplate' put: 512;
    at: 'FrDialogterm' put: 64;
    at: 'Helpmsgstring' put: 'commdlgHelp';
    at: 'PdReturndefault' put: 1024;
    at: 'FrNomatchcase' put: 2048;
    at: 'CfEnablehook' put: 8.
    ^ dictionary
! !

!Win32FileDialog class methodsFor:'examples'!

openFile

    "
        self openFile
    "

    ^ (FileDialogWin new openFile: 'c:\untitled.txt') file.
!

saveFile

    "
        self saveFile
    "

    ^ (FileDialogWin new saveFile: 'C:\vsw311\untitled.txt') file.
! !

!Win32FileDialog class methodsFor:'filters'!

filterPatternDescription: filterPattern

    ^ self filterPatternDescriptions at: filterPattern ifAbsent: ''
!

filterPatternDescriptions

    FilterPatternDescriptions isNil ifTrue:[ FilterPatternDescriptions := self generateFilterPatternDescriptions ].
    ^ FilterPatternDescriptions
!

filtersFor: pattern

    |filters filterPatterns|

    pattern isEmptyOrNil ifTrue:[^ nil].

    filters := OrderedCollection new.
    filterPatterns := pattern subStrings: $;.
    filterPatterns do:[:filterPattern | 
        filterPattern notEmpty ifTrue:[
            filters add: (Array with: (self filterPatternDescription: filterPattern) 
                                with:filterPattern)
        ].
    ].
    ^ filters asArray
!

generateFilterPatternDescriptions

    ^ Dictionary new
        at: '*.txt' put: 'Text files (*.txt)';
        at: '*.st'  put: 'Smalltalk files (*.st)';
        at: '*.csv' put: 'CSV files (*.csv)';
        at: '*.xml' put: 'XML files (*.xml)';
        at: '*.zip' put: 'ZIP files (*.zip)';   
        at: '*.xls' put: 'Excel files (*.xls)'; 
        at: '*.ent' put: 'SGML Entity files (*.ent)'; 
        at: '*.ccs' put: 'CCS files (*.ccs)';             
        at: '*.ini' put: 'Configuration files (*.ini)';    
        at: '*.prn' put: 'Printer Text files (*.prn)'; 
        at: '*.dir' put: 'DapasX Database files (*.dir)';
        at: '*.dat' put: 'DapasX Database files (*.dat)'; 
        at: '*.prg' put: 'DapasX Program files (*.prg)';      
        at: '*.dcf' put: 'DapasX Options files (*.dcf)';  
        at: '*.ext' put: 'DapasX Backup files (*.ext)';  
        at: '*.mpl' put: 'DapasX Project files (*.mpl)';    
        yourself
! !

!Win32FileDialog class methodsFor:'initialize'!

startUp

        "Private - Initialize the class variables.  This is called
         during startup."

    InitialDirectory := Directory pathName: Disk drivePathName.
! !

!Win32FileDialog class methodsFor:'opening'!

fileDialogFor:ownerWindow 
         save:isSaveDialog 
        title:titleOrNil 
  inDirectory:dirPathOrNil
initialAnswer:initialOrNil
       filter:pattern
    extension:extensionOrNil


    "start a native open-file dialog.
     If not cancelled, the selected fileName is returned; nil otherwise.
     Of course, this one looks like the
     Windows file dialog - no matter which viewStyle settings are active.
     Notice: if no ownerWindow is given, the dialog pops up at 0@0.

     EXPERIMENTAL & non-portable: use with caution"

    |filePath filterArrayOrNil|

    filterArrayOrNil := self filtersFor: pattern.

    filePath := self new
        openFor:ownerWindow
           save:isSaveDialog
          title:titleOrNil
    inDirectory:dirPathOrNil
  initialAnswer:initialOrNil
         filter:filterArrayOrNil
      extension:extensionOrNil.

    ^ filePath
! !

!Win32FileDialog methodsFor:'accessing'!

addAllFilesFilter

    self addFilter: '*.*' description: 'All Files (*.*)'.
!

addFilter: aFilter description: aDescription
        "Add aFilter and aDescription to the list of File dialog
        filters."

    filters add: ( Association key: aFilter value: aDescription ).
!

addSmalltalkFileFilters

    ^ smalltalkFileFilters
!

defExtension: aDefExtension
        "Specifies the default extension of File dialog."

    defExtension := aDefExtension.
!

defFilter
        "Answers the aDefFilterString as the default filter of File dialog."

    ^ defFilter
!

defFilter: aDefFilterString
        "Specifies the aDefFilterString as the default filter of File dialog."

    defFilter := aDefFilterString
!

defFilterIndex: defaultFilterIndex 

    defFilterIndex := defaultFilterIndex.
!

directory
        "Answer the selected directory."
    InitialDirectory isNil ifTrue:[
        ^ Filename currentDirectory pathName asFilename
    ].
    ^ InitialDirectory "? OperatingSystem getCurrentDirectory asFilename"
!

directory: directory
        "Sets the initial directory."

    | aFilename |

    directory isNil ifTrue:[^ self.].
    aFilename := directory asFilename.
    aFilename exists ifTrue: [ InitialDirectory := aFilename ].      
!

file
        "Answer the selected file."

    ^fileName
!

fileSpec: aFileSpec
        "Sets the initial fileName and directory in the File Dialog."

   | array dir |

    "SHOULD assign initial fileName and directory separately using #fileName: and #directory"

    self halt.
    fileName := aFileSpec.
"/    array := Filename splitPath: aFileSpec in: self directory .
"/    dir := 
"/        (( String with: ( array at: 1 ) with: $: ),
"/        ( ( array at: 2 ) isEmpty ifTrue: [ '\' ] ifFalse: [ array at: 2 ] )) asFilename.
"/    dir exists ifFalse: [ dir := OperatingSystem getCurrentDirectory asFilename ].
"/
"/    self directory: dir.
"/    fileName := array at: 3
!

filters
        "Private - answers  a string containing all filters and sets up
        the defFilterIndex property"

    | filterString count defaultFilterIndex defaultFilter|

    smalltalkFileFilters notNil ifTrue: [
        self
            addFilter: '*.cls' description: 'Class Files (*.CLS)';
            addFilter: '*.mth' description: 'Method Files (*.MTH)';
            addFilter: '*.st' description: 'Smalltalk Files (*.ST)';
            addFilter: '*.bnd' description: 'Library Bind Files (*.BND)';
            addFilter: '*.map' description: 'Library Map Files (*.MAP)';
            addFilter: '*.ini' description: 'Initialization Files (*.INI)';
            addFilter: '*.obj' description: 'Object Files (*.OBJ)';
            addFilter: '*.log' description: 'Log Files (*.LOG)' 
    ].

    defaultFilter := self defFilter.
    (fileName notEmptyOrNil and:[defaultFilter isNil]) ifTrue:[
        |initialFilenameSuffix|
        initialFilenameSuffix := fileName asFilename suffix.
        initialFilenameSuffix notEmptyOrNil ifTrue:[
            defaultFilter := '*.', initialFilenameSuffix.
        ].
    ].

    filterString := String new.
    count := 0.
    defaultFilterIndex := 0.
    filters do: [:assoc |
        count := count + 1.
        assoc key = defaultFilter ifTrue: [ defaultFilterIndex := count ].
        filterString := filterString, assoc value, #[0] asString, assoc key , #[0] asString. 
    ].

    self defFilterIndex: defaultFilterIndex.
    ^filterString
!

flags
        "Private - Answers the dialog box current flags.
        For compatibility reasons -> use style instead"

    ^openFileNameStruct flags
!

flags: flags

        "Private - Specifies the dialog box creation flags.
        Kept for compatibility reasons. Use style: instead"

    self style: flags
!

hideReadonly

        "Hides the file dialog's Readonly check box. "

    self style: self style | (self class commonDialogConstantAt: 'OfnHidereadonly')
!

initialFileName: filename
        "Sets the initial fileName string in the File Dialog."

    | aString |
    filename isNil ifTrue:[^ self.].
    aString := filename.
    filename isFilename ifTrue:[ aString := filename baseName].
    fileName := aString.
!

overwritePrompt

        "Prompt if the user attempts to overwrite a file"

    self style: self style | (self class commonDialogConstantAt: 'OfnOverwriteprompt')
!

owner: ownerWindow

        "Sets the owner of the Dialog box."

    |mainView handle|

    ownerWindow isNil ifTrue:[^ self].
    mainView := ownerWindow windowGroup mainView.
    mainView notNil ifTrue:[
        handle := mainView id.
        handle notNil ifTrue:[
            parent := handle address
        ].
    ].

"/    super owner: anOwner.
"/    owner isWindow
"/        ifTrue: [ parent := owner ]
"/        ifFalse: [ parent := owner mainView.
"/                       parent isWindow ifFalse: [
"/                            parent := Notifier findWindow: WindowHandle queryActive ]].
!

pathMustExist

       "Private & DEFAULT!!."
       "Changed by K3/EES5-Mg, 29.01.97"

    self style: self style | 16r800.
!

shareAware

        "Allows a previously opened file to be opened
         (e.g. change.log)"

    self style: self style | (self class commonDialogConstantAt: 'OfnShareaware')
!

style
    ^ style ? 8
!

style:something
    style := something.
!

title: aTitle

        "Specifies the string to be placed in the title bar of the
        File dialog."

    title := aTitle
! !

!Win32FileDialog methodsFor:'dapas'!

dapasOpenFile

        "Brings up the default open file dialog "
       "Changed by K3/EES5-Mg, 28.02.96"

    self hideReadonly;
         shareAware;
         addFilter: '*.*' description: 'All Files (*.*)'.

    self defFilter isNil ifTrue:[ self defFilter: '*.*'].

    self open.
!

dapasSaveFile

        "Brings up the file save dialog."
       "Changed by K3/EES5-Mg, 28.02.96"

    self hideReadonly;
         overwritePrompt;
         addFilter: '*.*' description: 'All Files (*.*)'.

    self save.
!

openFileXml

        "Brings up the default open file dialog "
       "Changed by K3/EES5-Mg, 28.02.96"
       "Changed by GS-EC/EES3 - Bernd Eisenmann, 14.08.03"

    self hideReadonly;
         shareAware;
         addFilter: '*.xml' description: 'XML-Datei'.

    self defFilter isNil ifTrue:[ self defFilter: '*.*'].

    self open.
!

openFileXmlZip

        "Brings up the default open file dialog "
       "Changed by K3/EES5-Mg, 28.02.96"
       "Changed by GS-EC/EES3 - Bernd Eisenmann, 14.08.03"

    self hideReadonly;
         shareAware;
         addFilter: '*.xml' description: 'XML-Datei';
         addFilter: '*.zip' description: 'ZIP-Datei'.

    self defFilter isNil ifTrue:[ self defFilter: '*.*'].

    self open.
! !

!Win32FileDialog methodsFor:'initialize & release'!

cleanUp
        "Private - Free openFileNameStruct."

    self style: self flags.
    lpstrFilter notNil ifTrue: [lpstrFilter free].
    lpstrFile notNil ifTrue: [lpstrFile free].
    lpstrInitialDir notNil ifTrue: [lpstrInitialDir free].
    lpstrTitle notNil ifTrue: [ lpstrTitle free ].
    lpstrDefExt notNil ifTrue: [ lpstrDefExt free ].

    openFileNameStruct := nil
!

initialize

        "Private - Initialize openFileNameStruct"

    super initialize.
    openFileNameStruct :=  OpenFilenameStructure new.
    openFileNameStruct lStructSize: openFileNameStruct sizeInBytes.
    fileName := String new.
    filters := OrderedCollection new.
    self style: (self class commonDialogConstantAt: 'OfnNochangedir')
! !

!Win32FileDialog methodsFor:'opening'!

open
        "Brings up the open file dialog."

    | error rslt openFileNameStructExternalBytes |

    [
    self fillStruct.
    parent notNil ifTrue: [ openFileNameStruct hwndOwner: parent.].
    style notNil ifTrue: [ openFileNameStruct flags: style ].

    openFileNameStructExternalBytes := ExternalBytes from: openFileNameStruct asByteArray.
    rslt := OperatingSystem getOpenFilename: openFileNameStructExternalBytes address.
    rslt
        ifTrue: [ self getFileName ]
        ifFalse: [
            fileName := nil.
            error := OperatingSystem commDlgExtendedError.
        ].
    ] ensure:[
        openFileNameStructExternalBytes free.
        self cleanUp.
    ].

    (error notNil and:[error ~= 0]) ifTrue: [self error: error ]. 
!

openFile
        "Brings up the default open file dialog.  The title is set to 'Open File'
        and fileSpec is set to '*.*'. "

    self openFile: '*.*'.
!

openFile: initialFileName

        "Brings up the default open file dialog.  The title is set to 'Open File'
        and fileSpec is set to patternString. "  

    self title: 'Open'.
    initialFileName notNil ifTrue: [ self initialFileName: initialFileName ].
    self
        hideReadonly;
        shareAware;
        addAllFilesFilter;
        addFilter: '*.txt' description: 'Text Files (*.txt)'.
    Smalltalk isStandAloneApp ifFalse: [ self addSmalltalkFileFilters ].
    self defFilter isNil ifTrue:[ self defFilter: '*.*'].
    self open.
!

openFor:ownerWindow
        save:isSaveDialog
        title:titleOrNil
        inDirectory:dirPathOrNil
        initialAnswer:initialOrNil
        filter:filterArrayOrNil
     extension:extensionOrNil

    self 
        owner: ownerWindow;
        title: titleOrNil;
        initialFileName: initialOrNil;
        defFilter: extensionOrNil.

    filterArrayOrNil notNil ifTrue:[
        filterArrayOrNil do:[:each | self addFilter: each last description: each first].
    ].

    self addAllFilesFilter.
"/    self defFilter isNil ifTrue:[ self defFilter: '*.*'].

    isSaveDialog 
        ifTrue:[
            self hideReadonly;
                 overwritePrompt;
                 save.
        ] ifFalse:[
            self hideReadonly;
                 shareAware;
                 open.
    ].

    ^ self file
!

save
        "Brings up the save file dialog."

    | error rslt openFileNameStructExternalBytes |

    [
    self fillStruct.
    parent notNil ifTrue: [ openFileNameStruct hwndOwner: parent.].
    style notNil ifTrue: [ openFileNameStruct flags: style ].

    openFileNameStructExternalBytes := ExternalBytes from: openFileNameStruct asByteArray.
    rslt := OperatingSystem getSaveFilename: openFileNameStructExternalBytes address.
    rslt
        ifTrue: [ self getFileName ]
        ifFalse: [
            fileName := nil.
            error := OperatingSystem commDlgExtendedError.
        ].
    ] ensure:[
        openFileNameStructExternalBytes free.
        self cleanUp.
    ].

    (error notNil and:[error ~= 0]) ifTrue: [self error: error ]. 
!

saveFile: aString

        "Brings up the save file dialog with aString as the
         default name.  The title is set to 'Save File'. "

    self saveTitle: 'Save File' fileName: aString
!

saveTitle: aTitle fileName: initialFileName

        "Brings up the file save dialog with aTitle and aString
         as the default name."

    self title: aTitle;
            initialFileName: initialFileName;
            hideReadonly;
            overwritePrompt;
            addAllFilesFilter;
            addFilter: '*.txt' description: 'Text Files (*.txt)'.

    self save.
! !

!Win32FileDialog methodsFor:'private'!

fillStruct
        "Private - fills the openFileNameStruct"

    | temp |

    temp := fileName "asAsciiZ".
    lpstrFile := ExternalBytes new:512 withAll:0.
    lpstrFile 
        replaceBytesFrom:1 
        to:temp size 
        with:temp 
        startingAt:1.

    lpstrFilter := ExternalBytes newNullTerminatedFromString: self filters.

    lpstrInitialDir := ExternalBytes newNullTerminatedFromString: self directory pathName.

    openFileNameStruct
        lpstrFile: lpstrFile address ;
        nMaxFile: 512;
        lpstrFilter: lpstrFilter address ;
        nFilterIndex: defFilterIndex ;      "set by filters"
        lpstrInitialDir: lpstrInitialDir address.

    ( temp := defExtension) notNil ifTrue: [
        lpstrDefExt := ExternalBytes newNullTerminatedFromString: temp.
        openFileNameStruct lpstrDefExt: lpstrDefExt address].

    ( temp := title ) notNil ifTrue: [
        lpstrTitle := ExternalBytes newNullTerminatedFromString: temp.
        openFileNameStruct lpstrTitle: lpstrTitle address ].
!

getFileName
        "Private - get the filename"

    | directory |

    self style: self flags.
    fileName := lpstrFile stringAt: 1.
    directory := fileName copyFrom: 1 to: openFileNameStruct nFileOffset.
    self directory: directory asFilename.
! !

!Win32FileDialog::OpenFilenameStructure class methodsFor:'accessing'!

sizeInBytes

    ^ 76
! !

!Win32FileDialog::OpenFilenameStructure class methodsFor:'instance creation'!

new

    ^ super new: self sizeInBytes
! !

!Win32FileDialog::OpenFilenameStructure methodsFor:'accessing'!

flags
    "Answer the receiver's flags field as a Smalltalk object."

    ^ self doubleWordAt: 52+1
!

flags: anObject
    "Set the receiver's flags field as a Smalltalk object."

    ^ self doubleWordAt: 52+1 put: anObject
!

hInstance
    "Get the receiver's hInstance field."

    ^ self doubleWordAt: 8+1 
!

hInstance: anObject
    "Set the receiver's hInstance field to the value of anObject."

    self doubleWordAt: 8+1 put: anObject
!

hwndOwner
    "Get the receiver's hwndOwner field."

    ^ self doubleWordAt: 4+1 
!

hwndOwner: anObject
    "Set the receiver's hwndOwner field to the value of anObject."

    self doubleWordAt: 4+1 put: anObject
!

lCustData
    "Get the receiver's lCustData field."

    ^ self doubleWordAt: 64+1 
!

lCustData: anObject
    "Set the receiver's lCustData field as a Smalltalk object."

    ^ self doubleWordAt: 64+1 put: anObject
!

lStructSize
    "Get the receiver's lStructSize field."

    ^ self doubleWordAt: 0+1
!

lStructSize: anObject
    "Set the receiver's lStructSize field to the value of anObject."

    self doubleWordAt:0+1 put:anObject
!

lpfnHook
    "Get the receiver's lpfnHook field."

    ^ self doubleWordAt: 68+1 
!

lpfnHook: anObject
    "Set the receiver's lpfnHook field to the value of anObject."

    self doubleWordAt: 68+1 put: anObject
!

lpstrCustomFilter
    "Get the receiver's lpstrCustomFilter field."

    ^ self doubleWordAt: 16+1 
!

lpstrCustomFilter: anObject
    "Set the receiver's lpstrCustomFilter field to the value of anObject."

    self doubleWordAt: 16+1 put: anObject
!

lpstrDefExt
    "Get the receiver's lpstrDefExt field."

    ^ self doubleWordAt: 60+1 
!

lpstrDefExt: anObject
    "Set the receiver's lpstrDefExt field to the value of anObject."

    self doubleWordAt: 60+1 put: anObject
!

lpstrFile
    "Get the receiver's lpstrFile field."

    ^ self doubleWordAt: 28+1 
!

lpstrFile: anObject
    "Set the receiver's lpstrFile field to the value of anObject."

    self doubleWordAt: 28+1 put: anObject
!

lpstrFileTitle
    "Get the receiver's lpstrFileTitle field."

    ^ self doubleWordAt: 36+1 
!

lpstrFileTitle: anObject
    "Set the receiver's lpstrFileTitle field to the value of anObject."

    self doubleWordAt: 36+1 put: anObject
!

lpstrFilter
    "Get the receiver's lpstrFilter field."

    ^ self doubleWordAt: 12+1 
!

lpstrFilter: anObject
    "Set the receiver's lpstrFilter field to the value of anObject."

    self doubleWordAt: 12+1 put: anObject
!

lpstrInitialDir
    "Get the receiver's lpstrInitialDir field."

    ^ self doubleWordAt: 44+1 
!

lpstrInitialDir: anObject
    "Set the receiver's lpstrInitialDir field to the value of anObject."

    self doubleWordAt: 44+1 put: anObject
!

lpstrTemplateName
    "Get the receiver's lpstrTemplateName field."

    ^ self doubleWordAt: 72+1 
!

lpstrTemplateName: anObject
    "Set the receiver's lpstrTemplateName field to the value of anObject."

    self doubleWordAt: 72+1 put: anObject
!

lpstrTitle
    "Get the receiver's lpstrTitle field."

    ^ self doubleWordAt: 48+1
!

lpstrTitle: anObject
    "Set the receiver's lpstrTitle field to the value of anObject."

    self doubleWordAt: 48+1 put: anObject
!

nFileExtension
    "Get the receiver's nFileExtension field."

    ^ self unsignedShortAt: 58+1 
!

nFileExtension: anObject
    "Set the receiver's nFileExtension field to the value of anObject."

    self unsignedShortAt: 58+1 put: anObject
!

nFileOffset
    "Get the receiver's nFileOffset field."

    ^ self unsignedShortAt: 56+1 
!

nFileOffset: anObject
    "Set the receiver's nFileOffset field to the value of anObject."

    self unsignedShortAt: 56+1 put: anObject
!

nFilterIndex
    "Get the receiver's nFilterIndex field."

    ^ self doubleWordAt: 24+1 
!

nFilterIndex: anObject
    "Set the receiver's nFilterIndex field to the value of anObject."

    self doubleWordAt: 24+1 put: anObject
!

nMaxCustFilter
    "Get the receiver's nMaxCustFilter field."

    ^ self doubleWordAt: 20+1
!

nMaxCustFilter: anObject
    "Set the receiver's nMaxCustFilter field to the value of anObject."

    self doubleWordAt: 20+1 put: anObject
!

nMaxFile
    "Get the receiver's nMaxFile field."

    ^ self doubleWordAt: 32+1
!

nMaxFile: anObject
    "Set the receiver's nMaxFile field to the value of anObject."

    self doubleWordAt: 32+1 put: anObject
!

nMaxFileTitle
    "Get the receiver's nMaxFileTitle field."

    ^ self doubleWordAt: 40+1
!

nMaxFileTitle: anObject
    "Set the receiver's nMaxFileTitle field to the value of anObject."

    self doubleWordAt: 40+1 put: anObject
!

sizeInBytes

    ^ self class sizeInBytes
! !

!Win32FileDialog::OpenFilenameStructure methodsFor:'printing'!

printOn: aStream

    super printOn: aStream.
    aStream cr.
    aStream nextPutAll:'flags: ', self flags printString; cr.
    aStream nextPutAll:'hInstance: ', self hInstance printString; cr.
    aStream nextPutAll:'hwndOwner: ', self hwndOwner printString; cr.
    aStream nextPutAll:'lCustData: ', self lCustData printString; cr.
    aStream nextPutAll:'lpfnHook: ', self lpfnHook printString; cr.
    aStream nextPutAll:'lpstrCustomFilter: ', self lpstrCustomFilter printString; cr.
    aStream nextPutAll:'lpstrDefExt: ', self lpstrDefExt printString; cr.
    aStream nextPutAll:'lpstrFile: ', self lpstrFile printString; cr.
    aStream nextPutAll:'lpstrFileTitle: ', self lpstrFileTitle printString; cr.
    aStream nextPutAll:'lpstrFilter: ', self lpstrFilter printString; cr.
    aStream nextPutAll:'lpstrInitialDir: ', self lpstrInitialDir printString; cr.
    aStream nextPutAll:'lpstrTemplateName: ', self lpstrTemplateName printString; cr.
    aStream nextPutAll:'lStructSize: ', self lStructSize printString; cr.
    aStream nextPutAll:'nFileExtension: ', self nFileExtension printString; cr.    
    aStream nextPutAll:'nFileOffset: ', self nFileOffset printString; cr.    
    aStream nextPutAll:'nFilterIndex: ', self nFilterIndex printString; cr.    
    aStream nextPutAll:'nMaxCustFilter: ', self nMaxCustFilter printString; cr.    
    aStream nextPutAll:'nMaxFile: ', self nMaxFile printString; cr.    
    aStream nextPutAll:'nMaxFileTitle: ', self nMaxFileTitle printString; cr.    
! !

!Win32FileDialog class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Win32FileDialog.st,v 1.2 2008-03-31 16:14:43 cg Exp $'
! !