Announcement

Collapse

Forum Guidelines

This forum is for finished source code that is working properly. If you have questions about this or any other source code, please post it in one of the Discussion Forums, not here.
See more
See less

KeyNote PlugIn Kit for PBWin7 (with Spell-Checker Demo)

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Tony Burcham
    replied
    Save this as "FixPlugin.ini"
    Code:
    @Dlg     = 101	494	30
    $NonTxt  = 1005	
    $ResTxt  = 1006	
    $PathTxt = 1007
    ------------------
    Tony Burcham
    TheirCorp


    [This message has been edited by Tony Burcham (edited January 31, 2006).]

    Leave a comment:


  • Tony Burcham
    replied
    "FixPlugin.bas"
    Code:
    '**************************************
    '   "FixPlugin.bas"
    
    
    'Public domain by TheirWare Corporation, 2005
    '**************************************
    
    #PBForms Created V1.51
    #Compile Exe "FixPlugin.exe"
    #Dim All
    
    #PBForms Begin Includes
    #If Not %Def(%WINAPI)
        #Include "WIN32API.INC"
    #EndIf
    #PBForms End Includes
    
    #PBForms Begin Constants
    %Dlg     =  101
    %FindBtn = 1001
    %NonBtn  = 1002
    %ResBtn  = 1003
    %Txt     = 1004
    %NonTxt  = 1005
    %ResTxt  = 1006
    %PathTxt = 1007
    %PathLbl = 1008
    %NonLbl  = 1009
    %ResLbl  = 1010
    %MsgLbl  = 1011
    %NonFrm  = 1012
    %ResFrm  = 1013
    #PBForms End Constants
    
    Declare CallBack Function ShowDlgProc()
    Declare Function ShowDlg(ByVal hParent As Dword) As Long
    #PBForms Declarations
    
    '**************************************
    Global hDlg     As Dword
    Global es       As String
    Global os       As String   'original path
    Global ps       As String   'path
    Global s        As String   'for the DLL's contents
    Global t        As String
    
    %NonResident    = %NonTxt
    %Resident       = %ResTxt
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    '   settings related
    
    Macro Function GetCheck(ID)
    MacroTemp chk
    Dim chk&
        Control Get Check hDlg, ID To chk&
    End Macro = chk&
    
    Declare Sub LoadSettings(hDlg As Dword)
    Declare Sub SaveSettings(hDlg As Dword)
    Declare Sub GetSettings(hDlg As Dword)
    
    Global stg      As String
    Global tmp      As String
    
    $IniFile = "FixPlugin.ini"
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    
    Sub LoadSettings(hDlg As Dword)
    Local ff  As Long
    Local cx  As Long 'x coordinate
    Local cy  As Long 'y coordinate
    Local i   As Long 'control ID
    Local v   As Long 'value of numeric setting
    Local t   As Asciz * 2
    
        If Len(Dir$(os & $IniFile)) Then
            ff = FreeFile
            Open os & $IniFile For Input As #ff
    
            Do
                Line Input# ff, tmp
                t = Left$(tmp, 1)
                tmp = Parse$(tmp, "=", 2)
                i = Val(tmp)
    
                If t = "@" Then     'it's position coordinates
                    cx = Val(Parse$(tmp, $Tab, 2))
                    cy = Val(Parse$(tmp, $Tab, 3))
                    If i < 1000 Then
                        Dialog Set Loc hDlg, cx, cy
                    Else
                        Control Set Loc hDlg, i, cx, cy
                    End If
    
                ElseIf t = "$" Then         'it's a control text
                    Control Set Text hDlg, i, Parse$(tmp, $Tab, 2)  'apply setting
    
                ElseIf t = "%" Then         'it's a check state
                    Control Set Check hDlg, i, Val(Parse$(tmp, $Tab, 2))
    
                End If
    
            Loop Until Eof(ff)
            Close #ff
    
        End If
    
    End Sub 'LoadSettings
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    
    Sub SaveSettings(hDlg As Dword)
    Local ff  As Long
    Local n   As Long
    Local b   As Long
    Local i   As Long
    Local v   As Long
    Local cx  As Long
    Local cy  As Long
    Local s   As String
    Local t   As Asciz * 2
    
        If Len(Dir$(os & $IniFile)) Then
    
            ff = FreeFile
            Open os & $IniFile For Binary As #ff
                Get$ #ff, Lof(ff), stg
                stg = RTrim$(stg, Any $CrLf)
            Close #ff
    
            Open os & $IniFile For Output As #ff
            For n = 1 To ParseCount(stg, $CrLf)
                tmp = Trim$(Parse$(stg, $CrLf, n))
                t = Left$(tmp, 1)
                i = Val(Parse$(tmp, "=", 2))        'get control ID
    
                If t = "@" Then     'it's position coordinates
                    If i < 1000 Then
                        Dialog Get Loc hDlg To cx, cy
                    Else
                        Control Get Loc hDlg, i To cx, cy
                    End If
                    tmp = Parse$(tmp, $Tab, 1) & $Tab & Format$(cx) & $Tab & Format$(cy)
    
                ElseIf t = "$" Then     'it's text
                    Control Get Text hDlg, i To s   'get current setting
                    tmp = Parse$(tmp, $Tab, 1) & $Tab & s
    
                ElseIf t = "%" Then     'it's a check state
                    tmp = Parse$(tmp, $Tab, 1) & $Tab & Format$(GetCheck(i))
    
                Else
                    'do nothing
                End If
    
                    Print# ff, tmp
            Next n
    
            SetEof# ff
            Close# ff
    
        End If
    
    End Sub 'SaveSettings
    
    '**************************************
    
    Sub msg()
    Local n     As Long
    
        'a little something to show it's been busy
        Control Set Text hDlg, %Txt, ""
        For n = 1 To 5
            Control Set Text hDlg, %Txt, String$(n, "*") & Mid$("|/=\", (n Mod 4) + 1, 1)
            Dialog DoEvents
            Sleep 50
        Next n
    
        Control Set Text hDlg, %Txt, es
    
    End Sub
    
    '**************************************
    
    Function FindKeyNote() As String
    Local dr    As Dword
    Local k     As Long
    Local m     As Long     'limits the iterations
    Local n     As Long
    Local c     As Long     'ASCII value of drive letter
    
    Data "C:"
    Data "C:\Program Files"
    Data "C:\Programs"
    
        es = ""
        c = 66  '= Asc("B") --- it will actually start searching on drive C:
        dr = GetLogicalDrives() And &B0111111
        Shift Right dr, 1
        If dr = 0 Then
            es = "Couldn't find any drives"
            msg
            Exit Function
        End If
    
        Do  'go through all the drives on the system (if needed)
    
            Incr c
            Shift Right dr, 1 'go to next drive
            If dr = 0 Then Exit Do
    
            For n = 1 To DataCount 'go through a list of likely paths
    
                Try 'see if this is a valid path
                    s = Read$(n)
                    Mid$(s, 1, 1) = Chr$(c)    'set the drive letter
                    ChDrive Left$(s, 1)
                    ChDir IIf$(Len(s) < 3, "\", s)
                Catch
                    Iterate For
                End Try
    
                'check for "KeyNote" folder
                t = Dir$("keynote*", %SUBDIR)
                If Len(t) Then
    
                    s = s & "\" & t & "\plugins"
    
                    If Len(Dir$(s, %SUBDIR)) = 0 Then 'check for "plugins" folder
    
                        'ask to create the folder
                        es = "Create folder: """ & s & " ?"
                        If MsgBox(es, %MB_YESNO, "Plugins folder is missing") = %IDYES Then
    
                            Try     'add the "plugins" folder
                                es = ""
                                MkDir s
                            Catch
                                es = s & " could not be created, error: " & Format$(Err)
                            End Try '...add "plugins" folder
                            msg
                        End If
    
                    End If 'check for plugins folder
    
                    Function = s : Exit Function
    
                End If  'check for "KeyNote" folder
    
            Next n  'next likely path
    
        Loop    'loop through drives
    
    End Function 'FindKeyNote
    
    '**************************************
    'gets and cleans up path
    Function CheckPath(s As String) As Long
    
        s = RTrim$(s, Any $Spc & $Tab)
        If Right$(s, 1) <> "\" Then s = s & "\"
        If Len(Dir$(s, %SUBDIR)) = 0 Then s = FindKeyNote()
        If Len(Dir$(s, %SUBDIR)) = 0 Then Function = 1
    
    End Function
    
    '**************************************
    'gets and cleans up plugin name
    Function GetName(tp As Long) As String
    Local n     As Long
    Local p     As Long
    Local s     As String
    
        Control Get Text hDlg, tp To s
        s = Trim$(LCase$(s), Any " .\")
        n = InStr(-1, s, "\")
        p = InStr(n, s, ".")
        If (n * p) And (p > n) Then s = Left$(s, p - 1)
    
        Function = s
    
    End Function
    
    '**************************************
    
    Function FixPlugin(tp As Long) As Long
    Local ff    As Long
    Local m     As Long 'count of missing exports
    Local n     As Long
    
    '--------------------------------------
    'the properly capitalized export names
    Data KNTGetPluginName
    Data KNTGetPluginVersion
    Data KNTGetPluginDescription
    Data KNTConfigurePlugin
    Data KNTGetPluginFeatures
    Data KNTPluginExecute
    Data KNTPluginCleanup
    Data KNTSetPluginID     :'this is only used in resident plugins
    
    
        '----------------------------------
        'make sure the DLL exists
        t = GetName(tp)
        Control Get Text hDlg, %PathTxt To ps
        If CheckPath(ps) Then Exit Function
        If Len(Dir$(os & t & ".dll")) = 0 Then
            es = os & t & ".dll" & $CrLf & _
            "not found.  Make sure the path" & $CrLf & _
            "and the DLL's name DLL name are correct"
            msg
            Exit Function
        End If
    
    
        '----------------------------------
        'load the DLL into a string
        ff = FreeFile
        Open os & t & ".DLL" For Binary As #ff
        Get$ #ff, Lof(ff), s
        Close# ff
    
    
        '----------------------------------
        'fix the internal reference to the DLL...
        'This assumes all occurences of these strings
        'are in the export section of the DLL
        n = InStr(LCase$(s), t & ".dll" & $Nul)
        t = t & ".knl" & $Nul
        If n Then
            Mid$(s, n) = t
        Else
            es = "Internal reference to DLL """ & t & """ was not found" & $CrLf
        End If
    
    
        '----------------------------------
        'now check for the export names
        For n = 1 To DataCount - IIf&(tp = %Resident, 0, 1)
            t = Read$(n) & $Nul
            'collect names of any missing exports
            If InStr(s, t) = 0 Then es = es & t & $CrLf : Incr m
        Next n
    
    
        '----------------------------------
        'report any missing exports
        If m Then
            Replace $Nul With $Spc In es
            es = es & "The following export" & IIf$(m > 1, "s were", " was") & " not found:" & $CrLf & es
            msg
            Exit Function
        End If
    
        '----------------------------------
        'put the DLL's contents into the ".knl" file
        ff = FreeFile
        t = GetName(tp)
        Try
            'open ps & "\" & t & ".knl" for binary as #ff
            Open ps & t & ".knl" For Binary As #ff
            Put$ ff, s
            SetEof# ff
            Close# ff
        Catch
            es = "Failed to save the DLL's contents to the "".knl"" file"
            msg
            Exit Function
        End Try
    
    
        '----------------------------------
        es = "Done with "
        If tp = %NonResident Then es = es & "NON-"
        es = es & "resident plugin: " & t & ".knl"
        msg
    
    End Function
    
    '**************************************
    'f is a flag: bit zero = resident, bit 1 = non-resident
    'LoadLibrary will not load DLLs if it can't also find
    'all of its implicitly loaded dependencies
    Sub FindDlls()
    Local ff    As Long
    Local f     As Dword
    Local h     As Dword
    Local n     As Long
    Local a     As Asciz * %OFS_MAXPATHNAME + 1
    
        '----------------------------------
        'protect the saved names from being over-written
        Control Get Text hDlg, %ResTxt To s
        If Len(Trim$(s)) Then f = 1
        Control Get Text hDlg, %NonTxt To s
        If Len(Trim$(s)) Then f = f Or 2
    
        '----------------------------------
        'find all the plugin DLLs in the project's folder
        n = Len(es)
        s = Dir$(os & "*.DLL")
        Do
    
            If Len(s) Then 'found one
    
                ff = FreeFile
                Open os & s For Binary As #ff
                Get$ #ff, Lof(ff), t
                Close# ff
    
                If InStr(t, $Nul & "KNTGetPluginName" & $Nul) Then
                    s = Left$(s, Len(s) - 4)
                    If InStr(t, $Nul & "KNTSetPluginID" & $Nul) Then
                        es = es & "Resident plugin: "
                        If (f And 1) = 0 Then Control Set Text hDlg, %ResTxt, s
                    Else
                        es = es & "Non-resident plugin: "
                        If (f And 2) = 0 Then Control Set Text hDlg, %NonTxt, s
                    End If
                    es = es & s & $CrLf
    
                End If
    
            Else    'no more DLLs to be found
                Exit Do
    
            End If
    
            s = Dir$ 'find the next DLL
    
        Loop
    
        t = ""
    
        '----------------------------------
        'if any plugin DLLs were found, then insert an explanation
        If n < Len(es) Then es = "DLL(s) found: " & $CrLf & es
    
    End Sub
    
    '**************************************
    
    Sub Init()
    
        os = String$(%OFS_MAXPATHNAME, 32)
        os = Left$(os, GetModuleFileName(ByVal 0???, ByVal StrPtr(os), Len(os)))
        os = Left$(os, InStr(-1, os, "\"))
    
        LoadSettings hDlg
        Control Get Text hDlg, %PathTxt To s
        If Len(Dir$(s, %SUBDIR)) = 0 Then s = FindKeyNote()
        Control Set Text hDlg, %PathTxt, s
        FindDlls
        msg
    
    End Sub
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    
    CallBack Function ShowDlgProc()
    
        Select Case As Long CbMsg
    
            Case %WM_INITDIALOG
                Init
    
            Case %WM_DESTROY
                SaveSettings hDlg
    
            Case %WM_NCACTIVATE
                Static hWndSaveFocus As Dword
                If IsFalse CbWParam Then
                    hWndSaveFocus = GetFocus()
                ElseIf hWndSaveFocus Then
                    SetFocus(hWndSaveFocus)
                    hWndSaveFocus = 0
                End If
    
            Case %WM_COMMAND
                Select Case As Long CbCtl
    
                    Case %NonBtn
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            FixPlugin(%NonResident)
                        End If
    
                    Case %ResBtn
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            FixPlugin(%Resident)
                        End If
    
                    Case %FindBtn
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            Control Set Text hDlg, %PathTxt, FindKeyNote()
                            Control Set Text hDlg, %Txt, es
                        End If
    
                End Select
    
        End Select
    
    End Function
    
    '**************************************
    
    Function PBMain()
        Local lRslt As Long
    
    #PBForms Begin Dialog %Dlg->->
    
        Dialog New %HWND_DESKTOP, "KeyNote Plugin Fixer", , , 240, 160, %WS_POPUP _
            Or %WS_BORDER Or %WS_DLGFRAME Or %WS_CAPTION Or %WS_SYSMENU Or _
            %WS_MINIMIZEBOX Or %WS_CLIPSIBLINGS Or %WS_VISIBLE Or %DS_MODALFRAME _
            Or %DS_3DLOOK Or %DS_NOFAILCREATE Or %DS_SETFONT, %WS_EX_CONTROLPARENT _
            Or %WS_EX_LEFT Or %WS_EX_LTRREADING Or %WS_EX_RIGHTSCROLLBAR, To hDlg
    
        Control Add Label,   hDlg, %ResLbl, "Name", 4, 12, 98, 10
        Control Add TextBox, hDlg, %ResTxt, "", 4, 22, 98, 13
        Control Add Button,  hDlg, %ResBtn, "Fix &Res.", 78, 43, 34, 14
        Control Add Label,   hDlg, %NonLbl, "Name", 128, 12, 94, 10
        Control Add TextBox, hDlg, %NonTxt, "", 128, 22, 94, 13
        Control Add Button,  hDlg, %NonBtn, "Fix &Non.", 202, 43, 34, 14
        Control Add Label,   hDlg, %PathLbl, "KeyNote's ""plugins"" path:", 66, 67, 100, 10
        Control Add TextBox, hDlg, %PathTxt, "", 66, 76, 136, 13
        Control Add Button,  hDlg, %FindBtn, "&Find", 203, 76, 34, 13
        Control Add Label,   hDlg, %MsgLbl, "Messages...", 4, 83, 44, 10
    
        Control Add TextBox, hDlg, %Txt, "", 2, 93, 236, 64, %WS_CHILD Or _
            %WS_VISIBLE Or %WS_TABSTOP Or %ES_LEFT Or %ES_MULTILINE Or _
            %ES_AUTOHSCROLL Or %ES_WANTRETURN, %WS_EX_CLIENTEDGE Or %WS_EX_LEFT _
            Or %WS_EX_LTRREADING Or %WS_EX_RIGHTSCROLLBAR
        Control Add Frame,   hDlg, %ResFrm, "Resident Plugin", 0, 1, 116, 60
        Control Add Frame,   hDlg, %NonFrm, "Non-Resident Plugin", 124, 1, 116, 60
    #PBForms End Dialog
    
        Dialog Show Modal hDlg, Call ShowDlgProc To lRslt
    
    #PBForms Begin Cleanup %Dlg
    #PBForms End Cleanup
    
        Function = lRslt
    End Function
    
    '**************************************
    ------------------
    Tony Burcham
    TheirCorp


    [This message has been edited by Tony Burcham (edited January 31, 2006).]

    Leave a comment:


  • Tony Burcham
    replied
    "SpellChecker.bas"
    Code:
    '**************************************
    '   "SpellChecker.prj"
    '**************************************
    
    '**************************************
    'Procedures required to be present and exported for resident plugins:
    '   KNTConfigurePlugin
    '   KNTGetPluginDescription
    '   KNTGetPluginFeatures
    '   KNTGetPluginName
    '   KNTGetPluginVersion
    '   KNTSetPluginID
    '   KNTPluginExecute
    '   KNTPluginCleanup
    
    '**************************************
    'Notes:
    'All of the procedures listed above must be present and exported
    'or KeyNote won't run it. Some don't even have to do anything,
    'they just have to be there.
    'The capitalization must also be exactly as shown. This is why
    '"FixPlugin" was written. You will need to run it each time you
    'compile this DLL, to: properly capitalize the export names,
    'change the internal reference to the DLL to "DllName.KNL" and
    'change the extension to "KNL".
    
    'For the functions:
    '   KNTConfigurePlugin
    '   KNTGetPluginDescription
    '   KNTGetPluginName
    '   KNTPluginCleanup
    '...returning any value except zero, indicates an error.
    
    
    '**************************************
    'Other procedures:
    '    GetText
    '    SendText
    '    ShowDlgProc
    
    'Public domain by TheirWare Corporation 2005
    '**************************************
    
    'Set this path to KeyNote's "plugins"
    #Compile Dll "SpellChecker.dll"
    #Dim All
    #Register All
    '#Debug Error On
    '#Tools On
    
    '**************************************
    '   equates for dialog and controls
    %Dlg     =  101
    %ChkBtn  = 1001
    %SaveBtn = 1002
    %SndOpt  = 1003
    %MetaOpt = 1004
    %Txt     = 1005
    
    '**************************************
    'equates for plugin
    
    $Caption    = "Spell Checker for KeyNote"
    $PlugName   = "Spell-Checker (PowerSpell)"
    $Desc       = "TheirWare's Resident Spell-Checker PlugIn for KeyNote, Written in PowerBASIC"
    
    
    'plugin features bit-masks
    %plOK                = 1&
    %plGetsData          = 2&
    %plGetsRTF           = 4&
    %plGetsSelection     = 8&
    %plReturnsData       = 16&
    %plReturnsRTF        = 32&
    %plReturnsClipboard  = 64&
    %plNeedsSelection    = 128&
    %plWantsDlgBox       = 512&
    %plStaysResident     = 4096&
    
    
    %Features = %plGetsData Or %plGetsSelection
    
        '**************************************
    
    'arbitrary, maximum length of text that KeyNote will
    'display in a dialog box. If plugin wants KeyNote
    'to show its output in a dialog box, output will be
    'truncated to this length
    %MAX_DLGBOX_MSG_LEN = 512
    
    $KeyNote_WinMsgIDStr = "KeyNote1_WinMsgIdStr"
    
    ' Message IDs for resident plugins
    %KNT_MSG_INSERTTEXT         = 101   ' insert plain text in active note
    %KNT_MSG_INSERTRTFTEXT      = 102   ' not implemented (0.999)
    %KNT_MSG_PLUGIN_SHUTDOWN    = 1000  ' notify KeyNote that plugin is about to shut down
    
    $NO_FILENAME_TO_LOAD = "?"
    
    'custom structure for passing information with %WM_COPYDATA
    Type KeyNoteMsg Byte
        intData1    As Dword    'the KeyNote-message to send
        intData2    As Dword    'length of data being sent
        strData     As String * 256
    End Type
    
    '**************************************
    '   includes
    %USEMACROS      = 1
    #Include "WIN32API.INC"
    #Include "COMMCTRL.INC"
    #Include "RichEdit.inc"
    #Include "PBForms.INC"
    
    '**************************************
    '   Be sure "PwrSpell.DLL", "SQLite.DLL" and "words.db" are in the
    '   same folder as "KeyNote.EXE".
    '   PwrSpell can be obtained from ZCureIT Tech at:
    '   [url="http://www.zcureit.com/"]http://www.zcureit.com/[/url] 
    
    %Soundex        = 0   'Soundex
    %DoubleMeta     = 1   'Double Metaphone
    
    $BusyCaption    = "PowerSpell is busy, please wait..."
    $Class          = "PwrSpell"
    
    $PwrSpell   = "PwrSpell.DLL"
    $PwrWord    = "*.db"    '"words.db"
    $Sqlite     = "SQLITE.DLL"
    %FileAttr   = %NORMAL Or %READONLY Or %HIDDEN Or %SYSTEM Or %ARCHIVE
    
    #Include "PwrSpell.INC"
    
    Global hSpell   As Dword
    Global pCheck   As Dword
    Global hIcon    As Dword
    
    '**************************************
    '   globals
    Global hDlg     As Dword
    Global gID      As Long
    Global ghInst   As Dword
    Global ghApp    As Dword
    Global ghWnd    As Dword
    Global ghRichEd As Dword
    Global s        As String
    Global t        As String
    Global fs       As String   'file name
    Global ns       As String   'note name
    
    Global NotID    As Word
    Global cds      As COPYDATASTRUCT
    Global msg      As KeyNoteMsg
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    '   richedit
    'Global hREInst     As Dword   'Richedit instance
    'Global ChrRng       As CHARRANGE
    'Global TxtRng       As TEXTRANGE
    Global gt           As GETTEXTEX
    Global gtlx         As GETTEXTLENGTHEX
    Global edstr        As EDITSTREAM
    %GetFromRichEdit    = 0
    %SendToRichEdit     = 1
    %fCanUndo           = 1
    
    '**************************************
    '   declares
    Declare Function KNTGetPluginName Alias "KNTGetPluginName" (ByVal buf As Byte Ptr, ByVal sz As Long) As Long
    Declare Function KNTGetPluginVersion Alias "KNTGetPluginVersion" () As Long
    Declare Function KNTGetPluginDescription Alias "KNTGetPluginDescription" (ByVal buf As Byte Ptr, ByVal sz As Long) As Long
    Declare Function KNTConfigurePlugin Alias "KNTConfigurePlugin" (ByVal hWnd As Dword) As Long
    Declare Function KNTGetPluginFeatures Alias "KNTGetPluginFeatures" () As Long
    Declare Sub KNTSetPluginID Alias "KNTSetPluginID" (ByVal ID As Dword)
    Declare Function KNTPluginExecute Alias "KNTPluginExecute" (ByVal hApp As Dword, ByVal hWnd As Dword, ByVal hRichEd As Dword, ByRef FileName As Asciz, ByRef NoteName As Asciz, ByRef InText As Asciz, ByRef OutText As Dword) As Long
    Declare Function KNTPluginCleanup Alias "KNTPluginCleanup" () As Long
    Declare CallBack Function ShowDlgProc()
    Declare Sub GetText()
    Declare Sub SendText()
    
    '**************************************
    'Send KeyNote the name of the plugin
    'sz is the maximum length of the name
    Function KNTGetPluginName( _
        ByVal buf As Byte Ptr, _ 'pointer to asciiz string
        ByVal sz As Long _       'length of the asciiz string
        ) Export As Long
    
        'pass the plugin's name to KeyNote.
        Poke$ buf, Left$($PlugName, sz - 1)
    
        'Function = 0
    
    End Function 'KNTGetPluginName
    
    '**************************************
    'Send KeyNote the version of the plugin
    '(must be 1 for now)
    Function KNTGetPluginVersion() Export As Long
    
        Function = 1
    
    End Function
    
    '**************************************
    'Send KeyNote the description of the plugin
    'sz is the maximum length of the description
    Function KNTGetPluginDescription( _
        ByVal buf As Byte Ptr, _ 'pointer to asciiz string
        ByVal sz As Long _      'length of the asciiz string
        ) Export As Long
    
        'pass plugin description to KeyNote.
        Poke$ buf, Left$($Desc, sz - 1)
    
        'Function = 0
    
    End Function 'KNTGetPluginDescription
    
    '**************************************
    'Let the user configure the plugin
    Function KNTConfigurePlugin(ByVal hWnd As Dword) Export As Long
    
        If hWnd = 0 Then hWnd = FindWindow("GFKeyNote10", "")
        ghWnd = hWnd 'save a global copy
    
        'There's no configuration code yet,
        'so just show a messagebox.
        MessageBox(hWnd, "KeyNote 2.0 by General Frenetics", $Desc, _
        %MB_OK Or %MB_ICONASTERISK Or %MB_DEFBUTTON1 Or %MB_APPLMODAL)
    
        'Function = 0
    
    End Function ' KNTConfigurePlugin
    
    '**************************************
    'Returns a bit mask to tell KeyNote what
    'the plugin wants and what it does.
    Function KNTGetPluginFeatures() Export As Long
    
        Function = %Features Or %plOK Or %plStaysResident
    
    End Function ' KNTGetPluginFeatures
    
    '**************************************
    'Get ID for communicating with KeyNote
    'The plugin must record the ID which KeyNote
    'will pass to it, in order to identify itself
    'to KeyNote when it shuts down.
    Sub KNTSetPluginID(ByVal ID As Dword) Export
    
        gID = ID
    
    End Sub 'KNTSetPluginID
    
    '**************************************
    'Returns the length of the data placed at the
    'address referenced by the pointer named "OutText"
    
    'This performs the the plugin's primary function ---
    'it is the function KeyNote calls when you '"run"
    'the plugin
    
    'This function must change the value of OutText
    'to point to the data being returned.
    Function KNTPluginExecute( _
        ByVal hApp As Dword,  _
        ByVal hWnd As Dword,  _     'KeyNote's window handle
        ByVal hRichEd As Dword,  _  'current richedit control's handle
        ByRef FileName As Asciz,  _ 'name of the file currently open in KeyNote
        ByRef NoteName As Asciz,  _ 'name of the note currently open in KeyNote
        ByRef InText As Asciz,  _   'the text currently selected in KeyNote
        ByRef OutText As Dword _    'a pointer (ByRef) to the data you want to send back
        ) Export As Long
    
        Local lRslt As Long
    
        'save global copies of these
        ghApp    = hApp
        ghWnd    = hWnd
        ghRichEd = hRichEd
        fs = FileName
        ns = NoteName
    
        NotID = RegisterWindowMessage($KeyNote_WinMsgIDStr)
    
        s = ""
        t = String$(%OFS_MAXPATHNAME, $Nul)
        t = Left$(t, GetModuleFileName(ByVal 0, ByVal StrPtr(t), Len(t)))
        t = Left$(t, InStr(-1, t, "\"))
        If Len(Dir$(t & $PwrSpell, %FileAttr)) = 0 Then s = s & $PwrSpell & $CrLf
        If Len(Dir$(t & $PwrWord, %FileAttr)) = 0 Then s = s & $PwrWord & " (word database)" & $CrLf
        If Len(Dir$(t & $Sqlite, %FileAttr)) = 0 Then s = s & $Sqlite & $CrLf
        If Len(s) Then
            s = "Couldn't find the required file(s)" & $CrLf & _
            "in KeyNote's home directory:" & s & $CrLf & _
            "You may download them from ZCureIT Tech at:" & $CrLf _
            & "http://www.zcureit.com/"
        End If
    
        Dialog New ghWnd, $Caption, 289, 69, 213, 149, %WS_POPUP Or _
            %WS_BORDER Or %WS_DLGFRAME Or %WS_CAPTION Or %WS_SYSMENU Or _
            %WS_CLIPSIBLINGS Or %WS_VISIBLE Or %DS_MODALFRAME Or %DS_3DLOOK Or _
            %DS_NOFAILCREATE Or %DS_SETFONT, %WS_EX_CONTROLPARENT Or %WS_EX_LEFT _
            Or %WS_EX_LTRREADING Or %WS_EX_RIGHTSCROLLBAR, To hDlg
    
        Control Add Button,  hDlg, %SaveBtn, "&Save", 141, 134, 32, 14
        Control Add Button,  hDlg, %ChkBtn, "&Check", 180, 134, 32, 14
    
        Control Add TextBox, hDlg, %Txt, "", 0, 0, 212, 124, %WS_CHILD Or _
            %WS_VISIBLE Or %WS_TABSTOP Or %WS_HSCROLL Or %WS_VSCROLL Or %ES_LEFT _
            Or %ES_MULTILINE Or %ES_AUTOHSCROLL Or %ES_AUTOVSCROLL Or _
            %ES_WANTRETURN, %WS_EX_CLIENTEDGE Or %WS_EX_LEFT Or _
            %WS_EX_LTRREADING Or %WS_EX_RIGHTSCROLLBAR
    
        Control Add Option,  hDlg, %SndOpt, "Sounde&x", 2, 127, 84, 10, %WS_CHILD _
            Or %WS_VISIBLE Or %WS_GROUP Or %WS_TABSTOP Or %BS_TEXT Or _
            %BS_AUTORADIOBUTTON Or %BS_LEFT Or %BS_VCENTER, %WS_EX_LEFT Or _
            %WS_EX_LTRREADING
        Control Add Option,  hDlg, %MetaOpt, "Double &Metaphone", 2, 137, 84, 10
        Control Set Option hDlg, %SndOpt, %SndOpt, %MetaOpt
    
        Dialog Show Modeless hDlg, Call ShowDlgProc To lRslt
        Do
            Dialog DoEvents To lRslt
        Loop While lRslt
    
        If gID Then PostMessage(hWnd, NotID, %KNT_MSG_PLUGIN_SHUTDOWN, gID)
        'Function = 0
    
    End Function ' KNTPluginExecute
    
    '**************************************
    'Here's a chance to clean up before unloading
    Function KNTPluginCleanup() Export As Long
    
        'Function = 0
    
    End Function ' KNTPluginCleanup
    
    '**************************************
    
    CallBack Function ShowDlgProc()
    Static ck   As Long
    
        Select Case As Long CbMsg
            Case %WM_INITDIALOG
                Control Set Text CbHndl, %Txt, s
    
            Case %WM_NCACTIVATE
                Static hWndSaveFocus As Dword
                If IsFalse CbWParam Then
                    hWndSaveFocus = GetFocus()
                ElseIf hWndSaveFocus Then
                    SetFocus(hWndSaveFocus)
                    hWndSaveFocus = 0
                End If
    
            Case %WM_COMMAND
    
                Select Case As Long CbCtl
    
                    Case %ChkBtn    'check spelling
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            GetText()
                            Control Set Text hDlg, %Txt, s
                            Dialog Set Text hDlg, $BusyCaption
                            Control Get Check hDlg, %SndOpt To ck
                            ck = IIf&(ck, %Soundex, %DoubleMeta)
                            s = SpellCheck(hDlg, s, $Class, 0, ck)
                            Dialog Set Text hDlg, $Caption & " --- Spell-check is complete"
                            Control Set Text hDlg, %Txt, s
    
                        End If
    
                    Case %SaveBtn   'save results
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            If MsgBox("Are you sure? All formatting will be lost !", _
                                    %MB_ICONWARNING Or %MB_OKCANCEL, "Warning!") = %IDOK Then
                                Control Get Text hDlg, %Txt To s
                                SendText()
                            End If
                        End If
    
                End Select
    
        End Select
    
    End Function
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    'get plain text from a richedit
    Sub GetText()
    
        gtlx.flags = %GTL_DEFAULT
        gtlx.codepage = -1
        gt.cb = SendMessage(ghRichEd, %EM_GETTEXTLENGTHEX, VarPtr(gtlx), 0)
        If gt.cb <> %E_INVALIDARG Then s = Space$(gt.cb) Else Exit Sub
        gt.flags = %GT_DEFAULT
        gt.codepage = -1
        SendMessage(ghRichEd, %EM_GETTEXTEX, VarPtr(gt), StrPtr(s))
    
        'sometimes it has $Cr's without $Lf's, so...
        Replace $Cr With $CrLf In s
        Replace $Cr & $Cr With $Cr In s
    
    End Sub 'GetText
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    'send text to a richedit
    Sub SendText()
        SendMessage(ghRichEd, %WM_SETTEXT, 0, StrPtr(s))
    End Sub 'SendText
    
    '**************************************
    
    Function LibMain( _
            ByVal hInstance As Long, _
            ByVal fwdReason As Long, _
            ByVal lpvReserved As Long) _
            As Long
    
        Select Case fwdReason
    
            Case %DLL_PROCESS_ATTACH
                ghInst = hInstance
                Function = 1 'success!
    
            Case %DLL_PROCESS_DETACH
                Function = 1 'success!
    
            Case %DLL_THREAD_ATTACH
                Function = 1 'success!
    
            Case %DLL_THREAD_DETACH
                Function = 1 'success!
    
        End Select
    
    End Function
    
    '**************************************

    ------------------
    Tony Burcham
    TheirCorp


    [This message has been edited by Tony Burcham (edited January 31, 2006).]

    Leave a comment:


  • Tony Burcham
    replied
    "KeyNoteResPlugIn.bas"
    Code:
    '**************************************
    '   "KeyNoteResPlugIn.bas"
    '**************************************
    
    'Purpose:
    'The start of a resident plugIn DLL for KeyNote v 1.6.5.
    
    'KeyNote can be found at the following three sites:
    'http://keynote.prv.pl
    'http://www.tranglos.com
    'http://sourceforge.net/projects/keynote/
    
    
    '**************************************
    'Procedures required to be present and exported for resident plugins:
    '   KNTConfigurePlugin
    '   KNTGetPluginDescription
    '   KNTGetPluginFeatures
    '   KNTGetPluginName
    '   KNTGetPluginVersion
    '   KNTSetPluginID
    '   KNTPluginExecute
    '   KNTPluginCleanup
    
    '**************************************
    'Notes:
    'All of the procedures listed above must be present and exported
    'or KeyNote won't run it. Some don't even have to do anything,
    'they just have to be there.
    'The capitalization must also be exactly as shown. This is why
    '"FixPlugin" was written. You will need to run it each time you
    'compile this DLL, to: properly capitalize the export names,
    'change the internal reference to the DLL to "DllName.KNL" and
    'change the extension to "KNL".
    
    'For the functions:
    '   KNTConfigurePlugin
    '   KNTGetPluginDescription
    '   KNTGetPluginName
    '   KNTPluginCleanup
    '...returning any value except zero, indicates an error.
    
    
    '**************************************
    'Other procedures:
    '    TextToClip
    '    TextFromClip
    '    IsRtf
    '    RtfStreamProc
    '    GetRTF
    '    SendRTF
    '    GetText
    '    SendText
    '    PasteText
    '    PasteRtf
    '    InsertRtf
    '    PerformKey
    '    MoveCaret
    '    ShowDlgProc 'CallBack
    
    
    'Public domain by TheirWare Corporation 2005
    '**************************************
    
    
    'Set this path to KeyNote's "plugins"
    #Compile Dll "PowerResid.dll"
    #Dim All
    #Register All
    '#Debug Error On
    '#Tools On
    
    %NOANIMATE         = 1  ' Animate control
    %NOBUTTON          = 1  ' Button
    %NOCOMBO           = 1  ' Combo box
    %NOCOMBOEX         = 1  ' ComboBoxEx
    %NODATETIMEPICK    = 1  ' Date/time picker
    %NODRAGLIST        = 1  ' Drag list control
    %NOEDIT            = 1  ' Edit control
    %NOFLATSBAPIS      = 1  ' Flat scroll bar
    %NOHEADER          = 1  ' Header control
    '%NOHOTKEY          = 1  ' HotKey control
    %NOIMAGELIST       = 1  ' Image APIs
    %NOIPADDRESS       = 1  ' IP Address edit control
    %NOLIST            = 1  ' List box control
    %NOLISTVIEW        = 1  ' ListView control
    %NOMENUHELP        = 1  ' Menu help
    %NOMONTHCAL        = 1  ' MonthCal
    %NOMUI             = 1  ' MUI
    %NONATIVEFONTCTL   = 1  ' Native Font control
    %NOPAGESCROLLER    = 1  ' Pager
    %NOPROGRESS        = 1  ' Progress control
    %NOREBAR           = 1  ' Rebar control
    %NOSTATUSBAR       = 1  ' Status bar
    %NOTABCONTROL      = 1  ' Tab control
    %NOTOOLBAR         = 1  ' Tool bar
    %NOTOOLTIPS        = 1  ' Tool tips
    %NOTRACKBAR        = 1  ' Track bar
    %NOTRACKMOUSEEVENT = 1  ' Track Mouse Event
    %NOTREEVIEW        = 1  ' TreeView
    %NOUPDOWN          = 1  ' Up Down arrow control
    
    
    '**************************************
    '   equates for dialog and controls
    %Dlg     =  101
    %HotBtn  = 1001
    %SendBtn = 1002
    %RcvBtn  = 1003
    %TextOpt = 1004
    %RtfOpt  = 1005
    %Hot     = 1006
    %Txt     = 1007
    
    '**************************************
    'equates for plugin
    
    $Caption = "Resident Plugin for KeyNote"
    $PlugName = "PowerBASIC Resident Plugin Demo" & $Nul
    $Desc   = "This is to test the use of PowerBASIC DLLs with KeyNote" & $Nul
    
    %Include_Copy   = 1
    '%Include_Paste  = 1
    
    'plugin features bit-masks
    %plOK                = 1&
    %plGetsData          = 2&
    %plGetsRTF           = 4&
    %plGetsSelection     = 8&
    %plReturnsData       = 16&
    %plReturnsRTF        = 32&
    %plReturnsClipboard  = 64&
    %plNeedsSelection    = 128&
    '%plWantsNewNote      = 256& ' not implemented
    %plWantsDlgBox       = 512&
    '%plWantsSavedFile    = 1024& ' not implemented
    '%plReloadFile        = 2048& ' not implemented
    %plStaysResident     = 4096&
    
        '**************************************
        'Explanation of the "features" equates:
        '**************************************
    
    'Note:  Some of this is based on testing the effects of various
    '       settings, and does not necessarily agree with the official
    '       documentation.
    
    '%plOK
    ' plugin MUST ALWAYS set "plOK", otherwie KeyNote will not run it.
    ' You could perform some status checking here, and NOT set "plOK"
    ' if the plugin decides that it cannot be executed for some reason,
    
    '%plGetsData
    'tells KeyNote the plugin wants to receive text. This must also be
    'set to receive RTF data
    
    '%plGetsRTF
    'tells KeyNote the plugin wants to receive data in richtext format
    '(requires %plGetsData)
    
    '%plGetsSelection
    ' tell KeyNote the plugin wants selected text (that is, not ALL
    'of the note's text)
    
    '%plReturnsData
    'tells KeyNote the plugin will return plain text. This must also be
    'set to send RTF data
    
    '%plReturnsRTF
    'tells KeyNote the plugin will return data in richtext format
    '(requires %plReturnsData)
    
    '%plReturnsClipboard
    'tells KeyNote the plugin will return data on the clipboard
    
    '%plNeedsSelection
    'tells KeyNote not to run the plugin unless there is some text selected
    
    '%plWantsDlgBox
    'tells KeyNote the plugin wants the returned text to be
    'displayed in a dialog box
    
        '**************************************
    
    'arbitrary, maximum length of text that KeyNote will
    'display in a dialog box. If plugin wants KeyNote
    'to show its output in a dialog box, output will be
    'truncated to this length
    %MAX_DLGBOX_MSG_LEN = 512
    
    
    $KeyNote_WinMsgIDStr = "KeyNote1_WinMsgIdStr"
    
    ' Message IDs for resident plugins
    %KNT_MSG_PERFORMKEY         = 100 ' pass a key to TRichEdit
    %KNT_MSG_INSERTTEXT         = 101 ' insert plain text in active note
    %KNT_MSG_INSERTRTFTEXT      = 102 ' not implemented (0.999)
    %KNT_MSG_MOVECARET          = 103 ' move caret (use direction constants, below)
    %KNT_MSG_PLUGIN_SHUTDOWN    = 1000 ' notify KeyNote that plugin is about to shut down
    
      ' caret motion direction constants
    %CARET_RIGHT = 1
    %CARET_LEFT  = 2
    %CARET_UP    = 3
    %CARET_DOWN  = 4
    
    $NO_FILENAME_TO_LOAD = "?"
    
    'custom structure for passing information with %WM_COPYDATA
    Type KeyNoteMsg Byte
        intData1    As Dword    'the KeyNote-message to send
        intData2    As Dword    'length of data being sent
        strData     As String * 256
    End Type
    
    
    '----------------------------------------------------------
    'Here's the feature set being used in this demo:
    '%Features = 0
    %Features = %plGetsData Or %plGetsSelection 'Or %plReturnsData
    
    '----------------------------------------------------------
    '   Some handy feature-set equates (no guarantee that they'll
    '   work, but they seem to agree with the documentation):
    
    'Get and return text
    '%Features = %plGetsData Or %plReturnsData Or %plGetsSelection 'Or %plNeedsSelection
    
    'Get and return RTF
    '%Features = %plGetsData or %plGetsRTF Or %plReturnsData Or %plReturnsRTF Or %plGetsSelection 'Or %plNeedsSelection
    
    'Get text then return text through the clipboard
    '%Features = %plGetsData or %plReturnsData Or %plGetsSelection or %plReturnsClipboard
    
    'Get RTF then return RTF through the clipboard
    '%Features = %plGetsData or %plGetsRTF Or %plReturnsData Or %plReturnsRTF Or %plGetsSelection or %plReturnsClipboard 'Or %plNeedsSelection
    
    '----------------------------------------------------------
    'For your convenience, the following equate "%Features" has all
    'of the implemented features. Remove the equates for features you
    'don't want.
    '%Features = %plGetsData Or %plReturnsData Or %plGetsRTF Or %plReturnsRTF Or %plGetsSelection Or %plNeedsSelection Or %plReturnsClipboard Or %plWantsDlgBox
    
    '----------------------------------------------------------
    
    '**************************************
    '   includes
    %USEMACROS      = 1
    #Include "WIN32API.INC"
    #Include "COMMCTRL.INC"
    #Include "RichEdit.inc"
    #Include "PBForms.INC"
    
    '**************************************
    'De-REM-ing this equate enables all the spell-checker code in the file
    '%SpellCheck     = 1
    #If %Def(%SpellCheck)
    
    '   Be sure "PwrSpell.DLL", "SQLite.DLL" and "words.db" are in the
    '   same folder as "KeyNote.EXE".
    '   PwrSpell can be obtained from ZCureIT Tech at:
    '   [url="http://www.zcureit.com/"]http://www.zcureit.com/[/url] 
    
        %SoundexValue             = 0   'Soundex value
        %DoubleMetaphone          = 1   'Double Metaphone
        $SpellCaption = "PowerSpell is working, please wait..."
        $Class = "PwrSpell"
        #Include "PwrSpell.INC"
    
    '   Select one of these spell-check modes
    %SpellMode = %SoundexValue
    '%SpellMode = %DoubleMetaphone
    
        Global hSpell   As Dword
        Global pCheck   As Dword
        Global hIcon    As Dword
    
    #EndIf
    
    '**************************************
    '   globals
    Global hDlg  As Dword
    Global gID      As Long
    Global ghInst   As Dword
    Global ghApp    As Dword
    Global ghWnd    As Dword
    Global ghRichEd As Dword
    Global s        As String
    Global fs       As String   'file name
    Global ns       As String   'note name
    
    Global NotID    As Word
    Global cds      As COPYDATASTRUCT
    Global msg      As KeyNoteMsg
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    '   richedit
    'Global hREInst     As Dword   'Richedit instance
    'Global ChrRng       As CHARRANGE
    'Global TxtRng       As TEXTRANGE
    Global gt           As GETTEXTEX
    Global gtlx         As GETTEXTLENGTHEX
    Global edstr        As EDITSTREAM
    %GetFromRichEdit    = 0
    %SendToRichEdit     = 1
    %fCanUndo           = 1
    
    '**************************************
    '   declares
    Declare Function KNTGetPluginName Alias "KNTGetPluginName"(ByVal buf As Byte Ptr, ByVal sz As Long) As Long
    Declare Function KNTGetPluginVersion Alias "KNTGetPluginVersion"() As Long
    Declare Function KNTGetPluginDescription Alias "KNTGetPluginDescription"(ByVal buf As Byte Ptr, ByVal sz As Long) As Long
    Declare Function KNTConfigurePlugin Alias "KNTConfigurePlugin"(ByVal hWnd As Dword) As Long
    Declare Function KNTGetPluginFeatures Alias "KNTGetPluginFeatures"() As Long
    Declare Sub KNTSetPluginID Alias "KNTSetPluginID"(ByVal ID As Dword)
    Declare Function KNTPluginExecute Alias "KNTPluginExecute"(ByVal hApp As Dword, ByVal hWnd As Dword, ByVal hRichEd As Dword, ByRef FileName As Asciz, ByRef NoteName As Asciz, ByRef InText As Asciz, ByRef OutText As Dword) As Long
    Declare Function KNTPluginCleanup Alias "KNTPluginCleanup"() As Long
    
    Declare Sub TextToClip(st As String)
    Declare Sub TextFromClip(st As String)
    Declare Function IsRtf(s As String) As Long
    Declare Function RtfStreamProc(ByVal dwCookie As Dword, ByVal pBuff As Byte Ptr, ByVal cb As Dword, ByVal pc As Dword) As Long
    Declare Sub GetRTF()
    Declare Sub SendRTF()
    Declare Sub GetText()
    Declare Sub SendText()
    Declare Sub PasteText(s As String)
    Declare Sub PasteRtf(s As String)
    Declare Sub InsertRtf(s As String)
    Declare Sub PerformKey(n As Long)
    Declare Sub MoveCaret(n As Long)
    Declare CallBack Function ShowDlgProc()
    
    '**************************************
    'Send KeyNote the name of the plugin
    'sz is the maximum length of the name
    Function KNTGetPluginName( _
        ByVal buf As Byte Ptr, _ 'pointer to asciiz string
        ByVal sz As Long _       'length of the asciiz string
        ) Export As Long
    
        'pass the plugin's name to KeyNote.
        Poke$ buf, Left$($PlugName, sz - 1)
    
        'Function = 0
    
    End Function 'KNTGetPluginName
    
    '**************************************
    'Send KeyNote the version of the plugin
    '(must be 1 for now)
    Function KNTGetPluginVersion() Export As Long
    
        Function = 1
    
    End Function
    
    '**************************************
    'Send KeyNote the description of the plugin
    'sz is the maximum length of the description
    Function KNTGetPluginDescription( _
        ByVal buf As Byte Ptr, _ 'pointer to asciiz string
        ByVal sz As Long _      'length of the asciiz string
        ) Export As Long
    
    
        'pass plugin description to KeyNote.
        Poke$ buf, Left$($Desc, sz - 1)
    
        'Function = 0
    
    End Function 'KNTGetPluginDescription
    
    '**************************************
    'Let the user configure the plugin
    Function KNTConfigurePlugin(ByVal hWnd As Dword) Export As Long
    
      ' This is one place where you can get the handle of KeyNote's
      ' main window:
        If hWnd = 0 Then hWnd = FindWindow("GFKeyNote10", "")
    
        ghWnd = hWnd 'save a global copy
    
        'There's no configuration code yet,
        'so just show a messagebox.
        MessageBox(hWnd, _
            "KeyNote 2.0 by General Frenetics", _
            "TheirWare's resident KeyNote PlugIn, written in PowerBASIC", _
            %MB_OK Or %MB_ICONASTERISK Or _
            %MB_DEFBUTTON1 Or %MB_APPLMODAL)
    
        'Function = 0
    
    End Function ' KNTConfigurePlugin
    
    '**************************************
    'Returns a bit mask to tell KeyNote what
    'the plugin wants and what it does.
    Function KNTGetPluginFeatures() Export As Long
    
        'you can test for error conditions here, and return zero
        'if there are any problems, to abort the plugin.
    
        '----------------------------------
        'The "plStaysResident" bit tells KeyNote the plugin will stay resident
        'When set, KeyNote will NOT free the DLL after executing the plugin.
        '(Note that the cleanup procedure will still be called.) KeyNote will
        'ignore any flags related to the data returned by the plugin.
        'Further, KeyNote will call "KNTSetPluginID" BEFORE calling the
        '"KNTPluginExecute" procedure.
    
        Function = %Features Or %plOK Or %plStaysResident
    
    End Function ' KNTGetPluginFeatures
    
    '**************************************
    'Get ID for communicating with KeyNote
    'The plugin must record the ID which KeyNote
    'will pass to it, in order to identify itself
    'to KeyNote when it shuts down.
    Sub KNTSetPluginID(ByVal ID As Dword) Export
    
        gID = ID
    
    End Sub 'KNTSetPluginID
    
    '**************************************
    'Returns the length of the data placed at the
    'address referenced by the pointer named "OutText"
    
    'This performs the the plugin's primary function ---
    'it is the function KeyNote calls when you '"run"
    'the plugin
    
    'This function must change the value of OutText
    'to point to the data being returned.
    Function KNTPluginExecute( _
        ByVal hApp As Dword,  _
        ByVal hWnd As Dword,  _     'KeyNote's window handle
        ByVal hRichEd As Dword,  _  'current richedit control's handle
        ByRef FileName As Asciz,  _ 'name of the file currently open in KeyNote
        ByRef NoteName As Asciz,  _ 'name of the note currently open in KeyNote
        ByRef InText As Asciz,  _   'the text currently selected in KeyNote
        ByRef OutText As Dword _    'a pointer (ByRef) to the data you want to send back
        ) Export As Long
    
        'save global copies of these
        ghApp    = hApp
        ghWnd    = hWnd
        ghRichEd = hRichEd
        fs = FileName
        ns = NoteName
    
        NotID = RegisterWindowMessage($KeyNote_WinMsgIDStr)
    
        s = "Hello, KeyNote Plugin World !" & $CrLf &  _
            "Notification ID = " & Str$(NotID) & _
            " Plugin ID = " & Str$(gID) & $CrLf  & $CrLf & _
            "Text received from KeyNote: " & $CrLf & _
            RTrim$(InText, $Nul)
    
        Local lRslt As Long
    
        Dialog New ghWnd, $Caption, 269, 70, 213, 149, _
            %WS_POPUP Or %WS_BORDER Or %WS_DLGFRAME Or %WS_CAPTION Or _
            %WS_SYSMENU Or %WS_CLIPSIBLINGS Or %WS_VISIBLE Or %DS_MODALFRAME Or _
            %DS_3DLOOK Or %DS_NOFAILCREATE Or %DS_SETFONT, %WS_EX_CONTROLPARENT _
            Or %WS_EX_LEFT Or %WS_EX_LTRREADING Or %WS_EX_RIGHTSCROLLBAR, To hDlg
    
        Control Add "msctls_hotkey32", hDlg, %Hot, "", 1, 134, 56, 14, %WS_CHILD _
            Or %WS_VISIBLE Or %WS_TABSTOP, %WS_EX_CLIENTEDGE Or %WS_EX_LEFT Or _
            %WS_EX_LTRREADING
        Control Add Button,  hDlg, %HotBtn, "&HotKey", 59, 134, 32, 14
    
        Control Add Option,  hDlg, %TextOpt, "Text", 109, 131, 30, 8, %WS_CHILD _
            Or %WS_VISIBLE Or %WS_GROUP Or %WS_TABSTOP Or %BS_TEXT Or _
            %BS_AUTORADIOBUTTON Or %BS_LEFT Or %BS_VCENTER, %WS_EX_LEFT Or _
            %WS_EX_LTRREADING
        Control Add Option,  hDlg, %RtfOpt, "RTF", 109, 140, 30, 8
        Control Set Option hDlg, %TextOpt, %TextOpt, %RtfOpt
    
        Control Add Button,  hDlg, %SendBtn, "&Send", 143, 134, 32, 14
        Control Add Button,  hDlg, %RcvBtn, "&Receive", 179, 134, 32, 14
        Control Add TextBox, hDlg, %Txt, "", 0, 0, 212, 128, %WS_CHILD Or _
            %WS_VISIBLE Or %WS_TABSTOP Or %WS_HSCROLL Or %WS_VSCROLL Or %ES_LEFT _
            Or %ES_MULTILINE Or %ES_AUTOHSCROLL Or %ES_AUTOVSCROLL Or _
            %ES_WANTRETURN, %WS_EX_CLIENTEDGE Or %WS_EX_LEFT Or _
            %WS_EX_LTRREADING Or %WS_EX_RIGHTSCROLLBAR
    
        Dialog Show Modeless hDlg, Call ShowDlgProc To lRslt
        Do
            Dialog DoEvents To lRslt
        Loop While lRslt
    
        If gID Then PostMessage(hWnd, NotID, %KNT_MSG_PLUGIN_SHUTDOWN, gID)
        Function = 0
    
    End Function ' KNTPluginExecute
    
    '**************************************
    'Here's a chance to clean up before unloading
    Function KNTPluginCleanup() Export As Long
    
        'Function = 0
    
    End Function ' KNTPluginCleanup
    
    '**************************************
    
    #If %Def(%Include_Copy)
    ' Puts the contents of a text string
    ' on the clipboard.
    ' Example:
    ' SomeString = "This string will be placed on the clipboard"
    ' TextToClip(SomeString)
    Sub TextToClip(st As String)
    Dim hMem    As Dword  'handle to globally allocated memory
    Dim pMem    As Dword  'pointer to globally allocated memory
    
        If OpenClipboard(0) Then
            EmptyClipboard
            hMem = GlobalAlloc(%GMEM_MOVEABLE Or %GMEM_DDESHARE, Len(st) + 1)
            If hMem Then
                pMem = GlobalLock(hMem)
                If pMem Then
                    Poke$ pMem, st & $Nul
                    GlobalUnlock hMem
                    SetClipboardData %CF_TEXT, hMem
                End If
            End If 'pMem
            CloseClipboard
        End If 'OpenClipBoard
    
    End Sub 'TextToClip
    #EndIf
    
    '**************************************
    
    #If %Def(%Include_Paste)
    Sub TextFromClip(st As String)
    Dim hMem    As Dword 'handle to clipboard object
    Dim pMem    As Dword 'pointer to globally allocated memory
    
        st = ""
        If IsClipboardFormatAvailable(%CF_TEXT) Then
            If OpenClipboard(0) Then
                hMem = GetClipboardData(%CF_TEXT)
                pMem = GlobalLock(hMem)
                If pMem Then st = Peek$(pMem, lstrlen(ByVal pMem))
                GlobalUnlock hMem
                CloseClipboard
            End If
        End If
    
    End Sub ' TextFromClip
    #EndIf
    
    '**************************************
    'checks to see if "s" contains RTF instead
    'of plain text
    Function IsRtf(s As String) As Long
    Local n     As Long
    Local r     As Double
    
    Data "{\rtf1\"
    Data "\ansi\"
    Data "\deflang"
    Data "{\fonttbl{\"
    Data "{\colortbl"
    Data "\red"
    Data "\green"
    Data "\blue"
    Data "\viewkind"
    Data "\par"
    
        For n = 1 To DataCount
            r = r + (1 * Tally(s, Read$(n)))
        Next n
    
        Function = r + (Tally(s, Any "{\;}")  * 100# / Len(s))
    
    End Function 'IsRtf
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    
    Function RtfStreamProc( _
        ByVal dwCookie As Dword, _  'dwCookie member of EditStream
        ByVal pBuff As Byte Ptr, _  'pointer to RTF data buffer
        ByVal cb As Dword, _        'count of bytes to read or write
        ByVal pc As Dword _         'pointer to number of bytes actually written or read
        ) As Long
    
    
        Select Case edstr.dwCookie
    
            Case %GetFromRichEdit
                s = s & Peek$(pBuff, cb)
                pc = cb
    
            Case %SendToRichEdit
                Poke$ pBuff, Left$(s, cb)
                s = Mid$(s, cb + 1)
                pc = Len(s)
    
        End Select
    
    End Function 'RtfStreamProc
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    'get rtf from richedit
    Sub GetRTF()
    
        s = ""
        edstr.dwCookie = %GetFromRichEdit
        edstr.pfnCallback = CodePtr(RtfStreamProc)
    
        'returns the number of characters written to the data stream
        SendMessage(ghRichEd, %EM_STREAMOUT, %SF_RTF, ByCopy VarPtr(edstr))
        'Err = edstr.dwError
    
    End Sub 'GetRTF
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    'send rtf to richedit
    Sub SendRTF()
    
        edstr.dwCookie = %SendToRichEdit
        edstr.pfnCallback = CodePtr(RtfStreamProc)
    
        'returns the number of characters written to the data stream
        SendMessage(ghRichEd, %EM_STREAMIN, %SF_RTF, ByCopy VarPtr(edstr))
        'Err = edstr.dwError
    
    End Sub 'SendRTF
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    'get plain text from a richedit
    Sub GetText()
    
        gtlx.flags = %GTL_DEFAULT
        gtlx.codepage = -1
        gt.cb = SendMessage(ghRichEd, %EM_GETTEXTLENGTHEX, VarPtr(gtlx), 0)
        If gt.cb <> %E_INVALIDARG Then s = Space$(gt.cb) Else Exit Sub
        gt.flags = %GT_DEFAULT
        gt.codepage = -1
        SendMessage(ghRichEd, %EM_GETTEXTEX, VarPtr(gt), StrPtr(s))
    
        'sometimes it has $Cr's without $Lf's, so...
        Replace $Cr With $CrLf In s
        Replace $Cr & $Cr With $Cr In s
    
    End Sub 'GetText
    
    '¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤¤
    'send text to a richedit
    Sub SendText()
        SendMessage(ghRichEd, %WM_SETTEXT, 0, StrPtr(s))
    End Sub 'SendText
    
    '**************************************
    
    Sub PasteText(s As String)
    
        'ExtractText(s)
        TextToClip(s)
        SendMessage(ghRichEd, %WM_PASTE, 0, 0)
    
    End Sub
    
    '**************************************
    
    Sub PasteRtf(s As String)
    
        TextToClip(s)
        SendMessage(ghRichEd, %WM_PASTE, 0, 0)
    
    End Sub 'PasteRtf
    
    '**************************************
    'a way to replace any currently selected text
    Sub InsertRtf(s As String)
    
        SendMessage(ghRichEd, %EM_REPLACESEL, %fCanUndo, ByVal StrPtr(s))
    
    End Sub 'InsertRtf
    
    '**************************************
    'sends the value from the hotkey control
    Sub PerformKey(n As Long)
    
        msg.intData1 = n
        msg.strData = s
        cds.dwData = %KNT_MSG_PERFORMKEY
        cds.cbData = SizeOf(msg)
        cds.lpData = VarPtr(msg)
        msg.intData1 = n
        SendMessage(ghWnd, %WM_COPYDATA, hDlg, ByCopy VarPtr(cds))
    
    End Sub 'PerformKey
    
    '**************************************
    
    Sub MoveCaret(n As Long)
    Local m     As Long
    
        m = n
        msg.intData1 = %CARET_RIGHT
        'msg.intData1 = %CARET_LEFT
        'msg.intData1 = %CARET_UP
        'msg.intData1 = %CARET_DOWN
        cds.dwData = %KNT_MSG_MOVECARET
        cds.cbData = SizeOf(msg)
        cds.lpData = VarPtr(msg)
        For m = 1 To m
            SendMessage(ghWnd, %WM_COPYDATA, hDlg, ByCopy VarPtr(cds))
            Sleep 100
        Next m
    
    End Sub
    
    '**************************************
    
    CallBack Function ShowDlgProc()
    Static ck   As Long
    
        Select Case As Long CbMsg
            Case %WM_INITDIALOG
                Control Set Text CbHndl, %Txt, s
    
    #If %Def(%SpellCheck)
                Control Show State hDlg, %Hot, %SW_HIDE
                Control Set Text hDlg, %HotBtn, "Spe&lling"
    #EndIf
    
            Case %WM_NCACTIVATE
                Static hWndSaveFocus As Dword
                If IsFalse CbWParam Then
                    hWndSaveFocus = GetFocus()
                ElseIf hWndSaveFocus Then
                    SetFocus(hWndSaveFocus)
                    hWndSaveFocus = 0
                End If
    
            Case %WM_COMMAND
    
                Select Case As Long CbCtl
    
                    Case %RcvBtn
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            Control Get Check hDlg, %TextOpt To ck
                            If ck Then GetText() Else GetRtf()
                            Control Set Text hDlg, %Txt, s
                        End If
    
                    Case %SendBtn
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
                            Control Get Text hDlg, %Txt To s
                            Control Get Check hDlg, %TextOpt To ck
                            If ck Then SendText() Else SendRTF()
                        End If
    
                    Case %HotBtn 'this doubles as the spell-checker button
                        If CbCtlMsg = %BN_CLICKED Or CbCtlMsg = 1 Then
    
    #If %Def(%SpellCheck)
                            Control Get Text hDlg, %Txt To s
                            If IsRtf(s) > 10 Then
                                MsgBox "The text appears to be in RTF format, which is" & _
                                    $CrLf & "more trouble to spell-check than it's worth    [img]http://www.powerbasic.com/support/forums/smile.gif[/img]"
                                Exit Function
                            End If
                            Dialog Set Text hDlg, $SpellCaption
                            s = SpellCheck(hDlg, s, $Class, 0, %SpellMode)
                            Dialog Set Text hDlg, $Caption & " --- Spell-check is complete"
                            Control Set Text hDlg, %Txt, s
    
    #Else                   'send the hotkey
                            Control Handle hDlg, %Hot To ck
                            PerformKey(SendMessage(ck, %HKM_GETHOTKEY, 0, 0))
    
                            'here are some others to try out
                            'PasteText(s)
                            'PasteRtf(s)
                            'MoveCaret(10)
    
    #EndIf
                        End If
    
                End Select
    
        End Select
    
    End Function
    
    '**************************************
    ' Main DLL entry point called by Windows...
    Function LibMain( _
            ByVal hInstance As Long, _
            ByVal fwdReason As Long, _
            ByVal lpvReserved As Long) _
            As Long
    
        Select Case fwdReason
    
            Case %DLL_PROCESS_ATTACH
                'Indicates that the DLL is being loaded by another process (a DLL
                'or EXE is loading the DLL).  DLLs can use this opportunity to
                'initialize any instance or global data, such as arrays.
                ghInst = hInstance
    
                'for the hotkey control
                PBFormsInitComCtls (%ICC_WIN95_CLASSES Or %ICC_DATE_CLASSES Or %ICC_INTERNET_CLASSES)
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!  This will prevent the EXE from running.
    
            Case %DLL_PROCESS_DETACH
                'Indicates that the DLL is being unloaded or detached from the
                'calling application.  DLLs can take this opportunity to clean
                'up all resources for all threads attached and known to the DLL.
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!
    
            Case %DLL_THREAD_ATTACH
                'Indicates that the DLL is being loaded by a new thread in the
                'calling application.  DLLs can use this opportunity to
                'initialize any thread local storage (TLS).
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!
    
            Case %DLL_THREAD_DETACH
                'Indicates that the thread is exiting cleanly.  If the DLL has
                'allocated any thread local storage, it should be released.
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!
    
        End Select
    
    End Function
    
    '**************************************

    ------------------
    Tony Burcham
    TheirCorp


    [This message has been edited by Tony Burcham (edited January 31, 2006).]

    Leave a comment:


  • Tony Burcham
    replied
    "KeyNotePlugIn.bas"
    Code:
    '**************************************
    '   "KeyNotePlugIn.bas"
    '**************************************
    
    'Purpose:
    'The start of a PlugIn DLL for KeyNote v 1.6.5.
    
    'KeyNote can be found at the following three sites:
    'http://keynote.prv.pl
    'http://www.tranglos.com
    'http://sourceforge.net/projects/keynote/
    
    
    '**************************************
    'Procedures (all of these are required
    'to be present and exported):
    '   KNTConfigurePlugin
    '   KNTGetPluginDescription
    '   KNTGetPluginFeatures
    '   KNTGetPluginName
    '   KNTGetPluginVersion
    '   KNTPluginExecute
    '   KNTPluginCleanup
    
    '**************************************
    'Notes:
    'All of the procedures listed above must be present and exported
    'or KeyNote won't run it. Some don't even have to do anything,
    'they just have to be there.
    '"FixPlugin" was written to change the extension to "KNL" and change
    'the internal reference to itself to "DllName.KNL" (not sure that it
    'matters, but it can't hurt).
    
    'For the functions:
    '   KNTConfigurePlugin
    '   KNTGetPluginDescription
    '   KNTGetPluginName
    '   KNTPluginCleanup
    
    '...returning any value except zero, indicates an error.
    
    
    'Public domain by TheirWare Corporation 2005
    '**************************************
    
    'Set this path to KeyNote's "plugins"
    #Compile Dll "PowerNote.dll"
    #Dim All
    #Register All
    '#Debug Error On
    '#Tools On
    
    '**************************************
    'equates for plugin
    
    
    $PlugName = "PowerBASIC Plugin Demo" & $Nul
    $Desc   = "This is to test the use of PowerBASIC DLLs with KeyNote" & $Nul
    
    'plugin features bit-masks
    %plOK                = 1&
    %plGetsData          = 2&
    %plGetsRTF           = 4&
    %plGetsSelection     = 8&
    %plReturnsData       = 16&
    %plReturnsRTF        = 32&
    %plReturnsClipboard  = 64&
    %plNeedsSelection    = 128&
    '%plWantsNewNote      = 256& ' not implemented
    %plWantsDlgBox       = 512&
    '%plWantsSavedFile    = 1024& ' not implemented
    '%plReloadFile        = 2048& ' not implemented
    '%plStaysResident     = 4096&
    
    
        '**************************************
    
    'Here's the feature set being used in this demo:
    %Features = %plGetsData Or %plGetsSelection Or %plReturnsData Or %plNeedsSelection
    
    'For your convenience, the following equate "%Features" has all of the implemented features
    'which can be used in a non-resident plugin. Remove the equates for features you don't want.
    
    '%Features = %plGetsData Or %plGetsRTF Or %plGetsSelection Or %plReturnsData Or %plReturnsRTF Or %plReturnsClipboard Or %plNeedsSelection Or %plWantsDlgBox
    
    
        '**************************************
        'Explanation of the "features" equates:
        '**************************************
    
    '%plOK
    ' plugin MUST ALWAYS set "plOK", otherwise KeyNote will not run it.
    ' You could perform some status checking here, and NOT set "plOK"
    ' if the plugin decides that it cannot be executed for some reason,
    
    '%plGetsData
    'tells KeyNote the plugin wants to receive text
    
    '%plGetsRTF
    'tells KeyNote the plugin wants to receive data in richtext format
    
    '%plGetsSelection
    ' tell KeyNote the plugin wants selected text (that is, not ALL
    'of the note's text)
    
    '%plReturnsData
    'tells KeyNote the plugin will return plain text
    
    '%plReturnsRTF
    'tells KeyNote the plugin will return data in richtext format
    
    '%plReturnsClipboard
    'tells KeyNote the plugin will return data on the clipboard
    
    '%plNeedsSelection
    'tells KeyNote not to run the plugin unless there is some text selected
    
    '%plWantsDlgBox
    'tells KeyNote the plugin wants the returned text to be
    'displayed in a dialog box
    
    '**************************************
    
    %USEMACROS = 1
    #Include "WIN32API.INC"
    
    Global ghInst   As Dword
    Global ghApp    As Dword
    Global ghWnd    As Dword
    Global ghRichEd As Dword
    Global s        As String
    
    '**************************************
    'Send KeyNote the name of the plugin
    'sz is the maximum length of the name
    Function KNTGetPluginName Alias "KNTGetPluginName" (  _
        ByVal buf As Byte Ptr, _ 'pointer to asciiz string
        ByVal sz As Long _  'length of the asciiz string
        ) Export As Long
    
        'pass the plugin's description to KeyNote.
        Poke$ buf, Left$($PlugName, sz - 1)
    
        'Function = 0
    
    End Function 'KNTGetPluginName
    
    '**************************************
    'Send KeyNote the version of the plugin
    '(must be 1 for now)
    Function KNTGetPluginVersion Alias "KNTGetPluginVersion" () Export As Long
    
        Function = 1
    
    End Function
    
    '**************************************
    'Send KeyNote the description of the plugin
    'sz is the maximum length of the description
    Function KNTGetPluginDescription Alias "KNTGetPluginDescription" ( _
        ByVal buf As Byte Ptr, _ 'pointer to asciiz string
        ByVal sz As Long _      'length of the asciiz string
        ) Export As Long
    
        'pass plugin description to KeyNote.
        Poke$ buf, Left$($Desc, sz - 1)
    
        'Function = 0
    
    End Function 'KNTGetPluginDescription
    
    '**************************************
    'Let the user configure the plugin
    Function KNTConfigurePlugin Alias "KNTConfigurePlugin" ( _
        ByVal hWnd As Dword) Export As Long
    
        'get the handle of KeyNote's main window
        If hWnd = 0 Then hWnd = FindWindow("GFKeyNote10", "")
        ghWnd = hWnd 'save a global copy
    
        'There's no configuration code yet,
        'so just show a messagebox.
        MessageBox(hWnd, _
            "KeyNote 2.0 by General Frenetics", _
            "TheirWare's KeyNote PlugIn, written in PowerBASIC", _
            %MB_OK Or %MB_ICONASTERISK Or _
            %MB_DEFBUTTON1 Or %MB_APPLMODAL)
    
        'Function = 0
    
    End Function ' KNTConfigurePlugin
    
    '**************************************
    'Returns a bit mask to tell KeyNote what
    'the plugin wants and what it does.
    Function KNTGetPluginFeatures Alias "KNTGetPluginFeatures" () Export As Long
    
        'you can test for error conditions here, and return zero
        'if there are any problems, to abort the plugin.
        Function = %Features Or %plOK
    
    End Function ' KNTGetPluginFeatures
    
    '**************************************
    'Returns the length of the data placed at the
    'address referenced by the pointer named "OutText"
    
    'This performs the the plugin's primary function ---
    'it is the function KeyNote calls when you '"run"
    'the plugin
    
    'This function must change the value of OutText
    'to point to the data being returned.
    Function KNTPluginExecute Alias "KNTPluginExecute" ( _
        ByVal hApp As Dword,  _
        ByVal hWnd As Dword,  _     'KeyNote's window handle
        ByVal hRichEd As Dword,  _  'current richedit control's handle
        ByRef FileName As Asciz,  _ 'name of the file currently open in KeyNote
        ByRef NoteName As Asciz,  _ 'name of the note currently open in KeyNote
        ByRef InText As Asciz,  _   'the text currently selected in KeyNote
        ByRef OutText As Dword _    'a pointer (ByRef) to the data you want to send back
        ) Export As Long
    
        'save global copies of these
        ghApp    = hApp
        ghWnd    = hWnd
        ghRichEd = hRichEd
    
        'this upper-cases InText before appending it to
        'OutText, so you can see the change in KeyNote
        s = "Hello, KeyNote Plugin World !" & $CrLf & $CrLf & _
            "Text received: " & $CrLf & _
            UCase$(InText)
    
        OutText = StrPtr(s) 'set KeyNote's pointer to the string's data
        Function = Len(s) 'tell KeyNote how many bytes it will receive
    
    End Function ' KNTPluginExecute
    
    '**************************************
    'Here's a chance to clean up before unloading
    Function KNTPluginCleanup Alias "KNTPluginCleanup" () Export As Long
    
        'Function = 0
    
    End Function ' KNTPluginCleanup
    
    '**************************************
    ' Main DLL entry point called by Windows...
    Function LibMain( _
            ByVal hInstance As Long, _
            ByVal fwdReason As Long, _
            ByVal lpvReserved As Long) _
            As Long
    
        Select Case fwdReason
    
            Case %DLL_PROCESS_ATTACH
                'Indicates that the DLL is being loaded by another process (a DLL
                'or EXE is loading the DLL).  DLLs can use this opportunity to
                'initialize any instance or global data, such as arrays.
                ghInst = hInstance
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!  This will prevent the EXE from running.
    
            Case %DLL_PROCESS_DETACH
                'Indicates that the DLL is being unloaded or detached from the
                'calling application.  DLLs can take this opportunity to clean
                'up all resources for all threads attached and known to the DLL.
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!
    
            Case %DLL_THREAD_ATTACH
                'Indicates that the DLL is being loaded by a new thread in the
                'calling application.  DLLs can use this opportunity to
                'initialize any thread local storage (TLS).
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!
    
            Case %DLL_THREAD_DETACH
                'Indicates that the thread is exiting cleanly.  If the DLL has
                'allocated any thread local storage, it should be released.
    
                Function = 1 'success!
                'FUNCTION = 0   'failure!
    
        End Select
    
    End Function
    
    '**************************************
    ------------------
    Tony Burcham
    TheirCorp


    [This message has been edited by Tony Burcham (edited January 31, 2006).]

    Leave a comment:


  • KeyNote PlugIn Kit for PBWin7 (with Spell-Checker Demo)

    KeyNote is a free, tree-based, tabbed notebook with RichText support.
    It imports and exports HJT (TreePad), HTML, RTF and TXT files. Notes
    don't all have to have trees. It is open source and is written in Delphi.


    • Some of the more notable features are:
    • Clipboard capture
    • Picture and object insertion
    • Macro recording
    • Plugin support
    • Templates
    • Bookmarks
    • Configurable keyboard
    • Very easy tree editing
    • Auto backup to another folder
    • It is open source under Mozilla Public License (MPL).
    • (no built-in spell-checker yet)

    [list=1]
    KeyNote locations:
    [*]http://keynote.prv.pl[*]http://www.tranglos.com/free/keynote.html[*]http://sourceforge.net/projects/keynote/[/list=a]

    Code:
    [b]
        Notes:[/b]
     KeyNote plugins are DLLs with their extensions changed to "KNL".
    This allows one to run a plugin by double-clicking it in Windows
    Explorer after file associations are made between them and KeyNote.
    
     They must be located in KeyNote's "plugins" folder.
    
     They are required to have certain exported functions present, or
    KeyNote will refuse to run them.
    
     "FixPlugIn" verifies the required exports are present, fixes the
    file extension in its internal reference to itself and copies it to
    the "plugins" folder. You need to run this every time you compile a
    plugin.
     Besides that, "FixPlugin" locates KeyNote's "plugins" folder on its
    own. It also finds any plugin DLLs in its own folder and puts the names
    of up to two of them in the appropriate boxes (the rest are shown in
    the messages box). It saves its settings between uses.
    
     To run a plugin: press F9 to open the resource panel, then go to the
    "Plugins" tab.
     You can refresh the list using the right-click menu. This can take
    a few seconds if you have many of the standard, KeyNote plugins (many
    of them are from 226KB to 498KB).
    
     For more information, download the plugins SDK from the keyNote
    website.
    [list=1]
    The posted files are:[*]KeyNotePlugIn.bas[*]KeyNoteResPlugIn.bas[*]SpellChecker.bas (a demonstration)[*]FixPlugin.bas[*]FixPlugin.ini[/list=a]

    ------------------
    Tony Burcham
    TheirCorp


    [This message has been edited by Tony Burcham (edited January 31, 2006).]
Working...
X