SHBrowseForFolder и lpfnCallback

Программирование на Visual Basic for Applications
YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 04.08.2009 (Вт) 15:00

Не получается использовать процедуру обратного вызова, ошибку выдает уже при объявлении dlgBrowseFolder(OwnerForm As Form.....
а также ей не нравится FnPtr(AddressOf BrowseCallbackProc) в чем дело, кто подскажет.
Код нашел где-то здесь на форуме.
Код: Выделить всё
   Option Explicit

    Public 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 Enum BrowseFlagsEnum
      bifBrowseForComputer = &H1000&
      bifBrowseForPrinter = &H2000&
      bifBrowseIncludeFiles = &H4000&
      bifBrowseIncludeURLs = &H80&
      bifShareable = &H8000&
      bifDontGoBelowDomain = &H2&
      bifEditBox = &H10&
      bifReturnFSAncestors = &H8&
      bifReturnOnlyFSDirs = &H1&
      bifStatusText = &H4&
      bifUseNewUI = &H40&
      bifValidate = &H20&
    End Enum
    Private Enum BrowseMessages
      'Messages from browser
      bffmInitialized = 1
      bffmSelChanged = 2
      bffmValidateFailedA = 3 'lParam:szPath ret:1(cont),0(EndDialog)
      bffmValidateFailedW = 4 'lParam:szPath ret:1(cont),0(EndDialog)
      'Messages to browser
      bffmSetStatusTextA = (WM_USER + 100)
      bffmEnableOk = (WM_USER + 101)
      bffmSetSelectionA = (WM_USER + 102)
      bffmSetSelectionW = (WM_USER + 103)
      bffmSetStatusTextW = (WM_USER + 104)
    #If Win32 Then
      bffmSetStatusText = bffmSetStatusTextW
      bffmSetSelection = bffmSetSelectionW
      bffmValidateFailed = bffmValidateFailedW
    #Else
      bffmSetStatusText = bffmSetStatusTextA
      bffmSetSelection = bffmSetSelectionA
      bffmValidateFailed = bffmValidateFailedA
    #End If
    End Enum
    Private Type BrowseInfo
      hWndOwner As Long
      pIDLRoot As Long
      pszDisplayName As Long
      lpszTitle As Long
      ulFlags As BrowseFlagsEnum
      lpfnCallback As Long
      lParam As Long
      iImage As Long
    End Type
    Private BrowsePath As String
    Private Declare Function SHBrowseForFolder Lib "shell32" (lpBI As BrowseInfo) As Long
    Private Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As Long, ByVal lpBuffer As String) As Long
    Private Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)


    Function FnPtr(ByVal lp As Long) As Long
    FnPtr = lp
    End Function

    Private Sub RemoveNullChar(ByRef Text As String)
    Dim I As Long
    I = InStr(Text, vbNullChar)
    If I > 0 Then Text = Left$(Text, I - 1)
    End Sub

    Public Function BrowseCallbackProc(ByVal hWnd As Long, ByVal uMsg As Long, ByVal lParam As Long, ByVal lpData As Long) As Long
    Select Case uMsg
      Case BrowseMessages.bffmInitialized
        SendMessage hWnd, BrowseMessages.bffmSetSelectionA, True, ByVal BrowsePath
    End Select
    BrowseCallbackProc = 0&
    End Function

    Public Function dlgBrowseFolder(OwnerForm As Form, ByRef Path As String, Optional ByVal Title As String, Optional ByVal AllowExtStyle As Boolean = False, Optional ByVal AllowManualEnter As Boolean = False) As Boolean
    Dim BI As BrowseInfo, lpIDList As Long
    Const MaxPath As Long = 1024&
    BrowsePath = Path
    Title = StrConv(Title, vbFromUnicode)
    With BI
      If OwnerForm Is Nothing Then
        .hWndOwner = 0&
      Else
        .hWndOwner = OwnerForm.hWnd
      End If
      .pIDLRoot = 0&
      .pszDisplayName = 0&
      .lpszTitle = StrPtr(Title)
      .ulFlags = bifReturnOnlyFSDirs Or IIf(AllowExtStyle, bifUseNewUI, 0&) Or IIf(AllowManualEnter, bifEditBox, 0&)
      .lpfnCallback = FnPtr(AddressOf BrowseCallbackProc)
      .lParam = 0&
      .iImage = 0&
    End With
    lpIDList = SHBrowseForFolder(BI)
    If lpIDList <> 0 Then
      Path = String$(MaxPath, 0)
      SHGetPathFromIDList lpIDList, Path
      CoTaskMemFree lpIDList
      RemoveNullChar Path
      dlgBrowseFolder = True
    End If
    End Function



Использование (в форме)

    Dim S As String
    S = "C:\MyFolder"
    If dlgBrowseFolder(Me, S, "Select folder") Then
      MsgBox S
    End If

YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

Re: SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 05.08.2009 (Ср) 11:27

Неужели никто не знает как использовать процедуру обратного вызова

dormouse
Продвинутый пользователь
Продвинутый пользователь
Аватара пользователя
 
Сообщения: 140
Зарегистрирован: 10.01.2007 (Ср) 21:58
Откуда: Волжский

Re: SHBrowseForFolder и lpfnCallback

Сообщение dormouse » 05.08.2009 (Ср) 13:32

Код: Выделить всё
Private Type BrowseInfo
     hwndOwner As Long
     pIDLRoot As Long
     pszDisplayName As Long
     lpszTitle As String
     ulFlags As Long
     lpfnCallback As Long
     lParam As String
     iImage As Long
End Type

Private Declare Function SHBrowseForFolder Lib "shell32.dll" (lpbi As BrowseInfo) As Long
Private Declare Function SHGetPathFromIDList Lib "shell32.dll" (ByVal pidList As Long, ByVal lpBuffer As String) As Long
Private Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)
Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Any) As Long


Public Function BrowseForFolder(ByVal hwnd As Long, ByVal strPrompt As String, ByVal strDefaultPath As String) As String

Dim pIdl As Long
Dim strPath As String * 260, udtBI As BrowseInfo

'Const BIF_RETURNONLYFSDIRS = 1  ' Return only file system directories (physical locations).
'                            ' If a user selects folders that are not part of the file system, the OK button is grayed.
'Const BIF_DONTGOBELOWDOMAIN = 2  ' Do not include network folders below the domain level in the tree view control
'                            ' (For example, My Computer and My Networks).
'Const BIF_RETURNFSANCESTORS = 8  ' Return only file system ancestors. If a user selects anything other
'                            ' than a file system ancestor, the OK button is grayed.
'Const BIF_EDITBOX = 16  ' The browse dialog includes an edit control in which the user can type the name of an item.
'                            ' Available on Windows 98 and above, or with Internet Explorer 4.0 or higher (assuming shell integration
'                            ' option selected). Requires version 4.71 of shell32.dll.
'Const BIF_USENEWUI = 64  ' Use the new user-interface. Setting this flag provides the user with a larger, resizable dialog box.
'                            ' Additional functionality includes: drag and drop capability within the dialog box, reordering, context menus,
'                            ' new folders, delete, and other context menu commands. Support in Windows 2000 and above.
'                            ' Requires version 5.00 of shell32.dll.
'Const BIF_BROWSEINCLUDEFILES = 16384  ' The browse dialog will display files as well as folders.
'                            ' Available on Windows 98 and above, or with Internet Explorer 4.0 or higher
'                            ' (assuming shell integration option selected). Requires version 4.71 of shell32.dll.
'Const BIF_BROWSEFORCOMPUTER = &H1000&  ' Only returns computers. If the user selects anything other than a computer,
'                            ' the OK button is grayed.
'Const BIF_BROWSEFORPRINTER = &H2000&  ' Only returns printers. If the user selects anything other than a printer,
'                            ' the OK button is grayed.
'Const BIF_STATUSTEXT = &H4&  ' Includes a status area in the dialog box. The callback function can set the status text
'                            ' by sending messages to the dialog box. Use of this flag is beyond the scope of this article.
'Const BIF_BROWSEINCLUDEURLS = &H80& ' Version 5.0. The browse dialog box can display URLs.
'                            ' The BIF_USENEWUI and BIF_BROWSEINCLUDEFILES flags must also be set. If these three flags are not set,
'                            ' the browser dialog box will reject URLs. Even when these flags are set, the browse dialog box will only
'                            ' display URLs if the folder that contains the selected item supports them.
'                            ' When the folder's IShellFolder::GetAttributesOf method is called to request the selected item's attributes,
'                            ' the folder must set the SFGAO_FOLDER attribute flag. Otherwise, the browse dialog box will not display the URL.
'Const BIF_NEWDIALOGSTYLE = &H40&  ' Version 5.0. Use the new user interface. Setting this flag provides the user with
'                            ' a larger dialog box that can be resized. The dialog box has several new capabilities including:
'                            ' drag and drop capability within the dialog box, reordering, shortcut menus, new folders, delete,
'                            ' and other shortcut menu commands. To use this flag, you must call OleInitialize or CoInitialize
'                            ' before calling SHBrowseForFolder.
'Const BIF_NONEWFOLDERBUTTON = &H200&  ' Do not include the "New Folder" button in the browse dialog box.
'Const BIF_SHAREABLE = &H8000&  ' Version 5.0. The browse dialog box can display shareable resources on remote systems.
'                            ' It is intended for applications that want to expose remote shares on a local system.
'                            ' The BIF_USENEWUI flag must also be set.
'Const BIF_UAHINT = &H100&  ' When combined with BIF_NEWDIALOGSTYLE, adds a usage hint to the dialog box
'                            ' in place of the edit box. BIF_EDITBOX overrides this flag.
'Const BIF_VALIDATE = &H20&  ' Version 4.71. If the user types an invalid name into the edit box,
'                            ' the browse dialog box will call the application's BrowseCallbackProc with the BFFM_VALIDATEFAILED message.
'                            ' This flag is ignored if BIF_EDITBOX is not specified.

With udtBI
    ' ownner of the dialog. Pass 0 for the desktop.
    .hwndOwner = hwnd
    ' The desktop folder will be the dialog's root folder.
    .pIDLRoot = 0
'    .ulFlags =
    ' Set the dialog's prompt string
    .lpszTitle = strPrompt
    ' Obtain and set the address of the callback function
    .lpfnCallback = FARPROC(AddressOf BrowseCallbackProcStr)
    .lParam = strDefaultPath
End With

pIdl = SHBrowseForFolder(udtBI)

If pIdl Then
    ' Get the path from the selected folder's pidl returned
    ' from the SHBrowseForFolder call (rtns True on success,
    ' sPath must be pre-allocated!)
    If SHGetPathFromIDList(pIdl, strPath) Then
        ' Return the path
        BrowseForFolder = Left$(strPath, InStr(strPath, vbNullChar) - 1)
        If BrowseForFolder <> "" Then
            If Right$(BrowseForFolder, 1) <> "\" Then
                BrowseForFolder = BrowseForFolder & "\"
            End If
        End If
    End If
    ' Free the memory the shell allocated for the pidl.
    CoTaskMemFree pIdl
End If

End Function


Private Function FARPROC(ByVal pfn As Long) As Long
    FARPROC = pfn
End Function


Private Function BrowseCallbackProcStr(ByVal hwnd As Long, ByVal uMsg As Long, ByVal lParam As Long, ByVal lpData As Long) As Long

Const BFFM_INITIALIZED = 1
Const BFFM_SETSELECTIONA As Long = &H466

' Callback for the Browse STRING method. On initialization, set the Dialog 's
' pre-selected folder from the pointer to the path allocated as bi.lParam,
' passed back to the callback as lpData param.

If uMsg = BFFM_INITIALIZED Then
    SendMessage hwnd, BFFM_SETSELECTIONA, True, lpData
End If

End Function

Sub Sample()
Debug.Print BrowseForFolder(0, "А нука выбери папку!", "C:\")
End Sub

VBA, MSA97

YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

Re: SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 05.08.2009 (Ср) 15:58

Ругается на строке FARPROC(AddressOf BrowseCallbackProcStr)

Ошибка --- Compile error: Invalid use of AddressOf operator

YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

Re: SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 06.08.2009 (Чт) 17:24

Господа так как, запустить этот код, неужели у всех нормально работает :?

Debugger
Продвинутый гуру
Продвинутый гуру
Аватара пользователя
 
Сообщения: 1667
Зарегистрирован: 17.06.2006 (Сб) 15:11

Re: SHBrowseForFolder и lpfnCallback

Сообщение Debugger » 06.08.2009 (Чт) 18:01

BrowseCallbackProcStr надо разместить в отдельном модуле вроде.

YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

Re: SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 07.08.2009 (Пт) 12:49

Господа, не получается.
Надо установить на какой папке будет открываться диалог.
Помогите, плиз, - горит проект. :oops:

Template
Обычный пользователь
Обычный пользователь
 
Сообщения: 73
Зарегистрирован: 09.09.2006 (Сб) 18:03

Re: SHBrowseForFolder и lpfnCallback

Сообщение Template » 09.08.2009 (Вс) 17:48

2 YanMinsk в 97 офисе нет оператора addressoff

YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

Re: SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 10.08.2009 (Пн) 12:59

Вообще-то у меня MSO 2003.
Может выложить исходник, кто-нибудь найдет в чем проблема :(

Template
Обычный пользователь
Обычный пользователь
 
Сообщения: 73
Зарегистрирован: 09.09.2006 (Сб) 18:03

Re: SHBrowseForFolder и lpfnCallback

Сообщение Template » 10.08.2009 (Пн) 20:52

2 YanMinsk вообще-то у меня когда-то был 97 офис, и там действительно нет оператора addressoff, а по теме,

Код: Выделить всё
Sub DialogFolder()

    Dim Folder As String

    With Application.FileDialog(msoFileDialogFolderPicker)
         .Title = "Надо выбрать папку"
         .ButtonName = "Кликни меня ..."
         If .Show = -1 Then
            Folder = .SelectedItems(1)
            MsgBox Folder
         Else
            MsgBox "Не, ну зря это"
         End If
    End With

End Sub

YanMinsk
Начинающий
Начинающий
 
Сообщения: 24
Зарегистрирован: 02.06.2009 (Вт) 1:09

Re: SHBrowseForFolder и lpfnCallback

Сообщение YanMinsk » 11.08.2009 (Вт) 18:40

Через FileDialog я знаю, но мне такой путь не нравиться т.к. открывается папка внутри которой папок уже нет, плюс надо древовидная структура. Самым оптимальным вижу использование SHBrowseForFolder, но не могу установить отличную от "Мой компьютер" папку.

Template
Обычный пользователь
Обычный пользователь
 
Сообщения: 73
Зарегистрирован: 09.09.2006 (Сб) 18:03

Re: SHBrowseForFolder и lpfnCallback

Сообщение Template » 11.08.2009 (Вт) 19:21



Вернуться в VBA

Кто сейчас на конференции

Сейчас этот форум просматривают: нет зарегистрированных пользователей и гости: 14

    TopList