Durchsuchbare Dokumentation aufrufen | Zurück zur Dokumentationsübersicht
Navigation: Dokumentationen agorum core > Übersicht tags
In dieser Dokumentation erfahren Sie, wie Sie mit einem Makro in Word eine Aktion aus dem agorum core explorer aufrufen. Ein Beispielmakro können Sie unter undefined>CheckInWord.bas herunterladen.
Attribute VB_Name = "NewMacros"
' Attribute VB_Name = "NewMacros"
' Attribute VB_Name = "NewMacros"
Option Explicit
#If VBA7 Then
Private Declare PtrSafe Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" _
(ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long
#Else
Private Declare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" _
(ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long
#End If
'Public Declare Function ShellExecute Lib "shell32.dll" Alias _
"ShellExecuteA" (ByVal hWnd As Long, _
ByVal lpOperation As String, _
ByVal lpFile As String, _
ByVal lpParameters As String, _
ByVal lpDirectory As String, _
ByVal nshowcmd As Long) As Long
Public hwnd As Long
Public Const SW_HIDE = 0 ' Versteckt öffnen
Public Const SW_MAXIMIZE = 3 ' Maximiert öffnen
Public Const SW_MINIMIZE = 6 ' Minimiert öffnen
Public Const SW_NORMAL = 1
Public Const SW_RESTORE = 9
Public Const SW_SHOWMAXIMIZED = 3
Public Const SW_SHOWMINIMIZED = 2
Public Const SW_SHOWMINNOACTIVE = 7
Public Const SW_SHOWNOACTIVATE = 4
Public Function Execute(Aktion As String, pfad As String, Params As String, Ansicht As Long) As Boolean
Call ShellExecute(hwnd, Aktion, pfad, Params, "", Ansicht)
End Function
Sub agorumASACheckIn()
'
' agorumASACheckIn - Speichert das Dokument ab und öffnet den CheckIn-Dialog aus dem ASA
'
'
' On Error GoTo errormessage
Dim id As String
id = getId()
ActiveDocument.Close SaveChanges:=True
' Jetzt CheckIn-Action starten
Execute "open", "agorum:action:Check-In(Word):" + id, "", SW_NORMAL
If Documents.Count = 0 Then
Application.Quit
End If
GoTo endesub
errormessage:
MsgBox "CheckIn - geht nur mit einem agorum core Pro - Objekt über das DMS-Laufwerk"
endesub:
End Sub
Function getId() As String
Dim xml As String
Dim iFile As Integer: iFile = FreeFile
Dim abc As String
' SMB2
Dim f, fs
Set fs = CreateObject("Scripting.FileSystemObject")
Set f = fs.OpenTextFile(ActiveDocument.FullName + ".$$go$$", 1, True)
xml = f.ReadAll()
f.Close
' SMB1
' Open ActiveDocument.FullName + ".$$go$$" For Input As #iFile
' xml = Input(LOF(iFile), iFile)
' Close #iFile
Dim pos1 As Integer
Dim pos2 As Integer
pos1 = InStr(xml, "<ObjectId>")
pos2 = InStr(xml, "</ObjectId>")
Dim id As String
getId = Mid(xml, pos1 + 10, pos2 - pos1 - 10)
End Function
Hinweis: Geben Sie einen Namen ohne Spaces ein.