اذهب الي المحتوي
أوفيسنا

كيف يمكنني نسخ الصورة من المرفقات


الردود الموصى بها

السلام عليكم ورحمة الله وبركاته

اسعد الله اوقاتكم

اخواني الكرام

عندي جدول فيه عمود مرفق وقد وضعت بداخله صورة وعرضت الصورة في النموذج ، اريد اضافة زر يقوم بنسخ الصورة الموجودة في المرفق حيث استطيع لصقها في الواتساب او على اي برنامج اخر

 

وشكرا جزيلا

رابط هذا التعليق
شارك

اخي جعفر جزاك الله كل خير

لا اريد حفظ الصورة في مجلد

المطلوب ان اقوم بعمل نسخ للصورة حتى استطيع اضعها لصق في الواتساب او التلغرام مباشرة

 

رابط هذا التعليق
شارك

في احد برامجي ، انقر نقرتين على الصورة ، وهذا الكود خلف النقرتين :

Private Sub Pic_DblClick(Cancel As Integer)

    'use irfan view to copy the picture in clipboard
    dim A as string 

    A = "C:\Program Files\IrfanView\"  'location of i_view32.exe file
    Shell (A & "i_view32.exe " & Me.Pic.Picture & "/ClipCopy /killmesoftly")
    
    MsgBox "تم عمل نسخة من هذه الصورة في الذاكرة ، يمكنك الصاقها في اي برنامج" & vbCrLf & _
           "This image is copied in the clipboard, you can paste it in any program"
           
End Sub

.

ثم الصق الصورة في اي برنامج ، مثل الوورد 🙂

 

لإستعمال الكود ، استخدم برنامج IrfanView المجاني من هنا: https://www.irfanview.com/

وضبط المسار ، والنسخة سواء 64 او 32 بت ،

واسم حقل الصورة هو Pic ،

 

فيقوم الكود بحفظ الصورة في الذاكرة ، وبدون اي واجهة 🙂

 

جعفر

  • Like 1
رابط هذا التعليق
شارك

مشاركة مع اخي جعفر

ومن باب اثراء الموضوع

عثرت على وظيفة تنسخ الصورة من النموذج ويمكن لصقها في برامج التواصل كــ الوتساب

للصق استخدم   ctrl+v

 

photo.rar

  • Like 3
رابط هذا التعليق
شارك

6 ساعات مضت, jjafferr said:

في احد برامجي ، انقر نقرتين على الصورة ، وهذا الكود خلف النقرتين :

 

52 دقائق مضت, ابوخليل said:

عثرت على وظيفة تنسخ الصورة من النموذج ويمكن لصقها في برامج التواصل كــ الوتساب

للصق استخدم   ctrl+v

اعتقد يوجد اشخاص لديهم نظام اكسس بدل الوندوز  عند تشغيل الحاسوب

رابط هذا التعليق
شارك

في 4‏/3‏/2022 at 16:35, ابوخليل said:

مشاركة مع اخي جعفر

ومن باب اثراء الموضوع

عثرت على وظيفة تنسخ الصورة من النموذج ويمكن لصقها في برامج التواصل كــ الوتساب

للصق استخدم   ctrl+v

السلام عليكم

جزاكم الله كل خير

لكن اخي الكريم لم يفلح الامر

 

الصورة عندي في عمود مرفق وليست خارج القاعدة

 

رابط هذا التعليق
شارك


اخي عبدالله آمل ان تعذرني لعدم  وصولي الى طريقة سهلة من خلال اكسس

اتضح لي ان حقل المرفقات يتضمن في الخلفية ثلاث حقول اخرى : اسم الصوره ، ونوعها ، وبياناتها

حاولت وبحثت واخيرا توصلت الى صفحة تتحدث بالتفصيل عن الموضوع .. وهذا رابطها

رابط هذا التعليق
شارك

السلام عليكم 🙂

 

الحل اللي توصلت اليه هو:

1. حفظ الصورة في مجلد الوندوز المؤقت ،

2. ثم قراءته وحفظه في الذاكرة ،

وعن طريق Ctrl + V تستطيع لصقه في معظم البرامج (هناك برنامج لم يقبل اللصق فيه) 

1484.gif.0f9b044401c69983d8658d4ee12f0d49.gif

.

والاكواد :

1.

Public Function Export_Attached_Pictures(TQ_Name As String, Record_ID, fld_Name As String, img_Name As String, Export_Folder_Name As String)
On Error GoTo err_Export_Attached_Pictures

    ' TQ_Name = Table or Query Name
    ' fld_Name = Attachement field name
    ' Export_Folder_Name = where to export the picture

    Dim db As dao.Database
    Dim rst_TQ As dao.Recordset
    Dim rst_Pictures As dao.Recordset
    Dim mySQL As String
    
    Set db = CurrentDb
    
    ' the parent recordset.
    mySQL = "Select "
    mySQL = mySQL & fld_Name
    mySQL = mySQL & " From "
    mySQL = mySQL & TQ_Name
    mySQL = mySQL & " Where ID=" & Record_ID
    
    Set rst_TQ = db.OpenRecordset(mySQL)
  
    ' loop through it
    While Not rst_TQ.EOF
  
     
        ' the child recordset.
        Set rst_Pictures = rst_TQ.Fields(fld_Name).Value
 
        '  Loop through the attachments.
        While Not rst_Pictures.EOF
  
            If rst_Pictures.Fields("FileName") = img_Name Then
                ' Save current attachment to disk, with their original names
                rst_Pictures.Fields("FileData").SaveToFile Export_Folder_Name
                GoTo Exit_Export_Attached_Pictures
            End If
            
            rst_Pictures.MoveNext
        Wend
    
        rst_TQ.MoveNext
   Wend
   
   
Exit_Export_Attached_Pictures:

    rst_TQ.Close: Set rst_TQ = Nothing
    rst_Pictures.Close: Set rst_Pictures = Nothing
    
    Exit Function
    
err_Export_Attached_Pictures:

    If err.Number = 3839 Then
        'file exists
        Resume Next
    ElseIf err.Number = 91 Or err.Number = 3420 Then
        Resume Next
    Else
        MsgBox err.Number & vbCrLf & err.Description
        Resume Exit_Export_Attached_Pictures
    End If
    
End Function

.

2.

Option Compare Database
Option Explicit

' Required data structures
Private Type POINTAPI
x As Long
y As Long
End Type

#If Win64 And VBA7 Then

    ' Clipboard Manager Functions
    Private Declare PtrSafe Function EmptyClipboard Lib "user32" () As Long
    Private Declare PtrSafe Function OpenClipboard Lib "user32" (ByVal hwnd As LongPtr) As Long
    Private Declare PtrSafe Function CloseClipboard Lib "user32" () As Long
    Private Declare PtrSafe Function SetClipboardData Lib "user32" (ByVal wFormat As Long, ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As LongPtr
    Private Declare PtrSafe Function IsClipboardFormatAvailable Lib "user32" (ByVal wFormat As Long) As Long
    
    ' Other required Win32 APIs
    Private Declare PtrSafe Function DragQueryFile Lib "shell32.dll" Alias "DragQueryFileA" (ByVal HDROP As LongPtr, ByVal UINT As Long, ByVal lpStr As String, ByVal ch As Long) As Long
    Private Declare PtrSafe Function DragQueryPoint Lib "shell32.dll" (ByVal HDROP As LongPtr, lpPoint As POINTAPI) As Long
    Private Declare PtrSafe Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalFree Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalLock Lib "kernel32" (ByVal hMem As LongPtr) As LongPtr
    Private Declare PtrSafe Function GlobalUnlock Lib "kernel32" (ByVal hMem As LongPtr) As Long
    Private Declare PtrSafe Sub CopyMem Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As LongPtr)

    Dim hGlobal As LongPtr
    Dim lpGlobal As LongPtr
    Dim HDROP As LongPtr

#Else

    ' Clipboard Manager Functions
    Private Declare Function EmptyClipboard Lib "user32" () As Long
    Private Declare Function OpenClipboard Lib "user32" (ByVal hwnd As Long) As Long
    Private Declare Function CloseClipboard Lib "user32" () As Long
    Private Declare Function SetClipboardData Lib "user32" (ByVal wFormat As Long, ByVal hMem As Long) As Long
    Private Declare Function GetClipboardData Lib "user32" (ByVal wFormat As Long) As Long
    Private Declare Function IsClipboardFormatAvailable Lib "user32" (ByVal wFormat As Long) As Long
    
    ' Other required Win32 APIs
    Private Declare Function DragQueryFile Lib "shell32.dll" Alias "DragQueryFileA" (ByVal HDROP As Long, ByVal UINT As Long, ByVal lpStr As String, ByVal ch As Long) As Long
    Private Declare Function DragQueryPoint Lib "shell32.dll" (ByVal HDROP As Long, lpPoint As POINTAPI) As Long
    Private Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
    Private Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function GlobalLock Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Function GlobalUnlock Lib "kernel32" (ByVal hMem As Long) As Long
    Private Declare Sub CopyMem Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)

    Dim hGlobal As Long
    Dim lpGlobal As Long
    Dim HDROP As Long

#End If

' Predefined Clipboard Formats
Private Const CF_TEXT = 1
Private Const CF_BITMAP = 2
Private Const CF_METAFILEPICT = 3
Private Const CF_SYLK = 4
Private Const CF_DIF = 5
Private Const CF_TIFF = 6
Private Const CF_OEMTEXT = 7
Private Const CF_DIB = 8
Private Const CF_PALETTE = 9
Private Const CF_PENDATA = 10
Private Const CF_RIFF = 11
Private Const CF_WAVE = 12
Private Const CF_UNICODETEXT = 13
Private Const CF_ENHMETAFILE = 14
Private Const CF_HDROP = 15
Private Const CF_LOCALE = 16
Private Const CF_MAX = 17

' New shell-oriented clipboard formats
Private Const CFSTR_SHELLIDLIST As String = "Shell IDList Array"
Private Const CFSTR_SHELLIDLISTOFFSET As String = "Shell Object Offsets"
Private Const CFSTR_NETRESOURCES As String = "Net Resource"
Private Const CFSTR_FILEDESCRIPTOR As String = "FileGroupDescriptor"
Private Const CFSTR_FILECONTENTS As String = "FileContents"
Private Const CFSTR_FILENAME As String = "FileName"
Private Const CFSTR_PRINTERGROUP As String = "PrinterFriendlyName"
Private Const CFSTR_FILENAMEMAP As String = "FileNameMap"

' Global Memory Flags
Private Const GMEM_FIXED = &H0
Private Const GMEM_MOVEABLE = &H2
Private Const GMEM_NOCOMPACT = &H10
Private Const GMEM_NODISCARD = &H20
Private Const GMEM_ZEROINIT = &H40
Private Const GMEM_MODIFY = &H80
Private Const GMEM_DISCARDABLE = &H100
Private Const GMEM_NOT_BANKED = &H1000
Private Const GMEM_SHARE = &H2000
Private Const GMEM_DDESHARE = &H2000
Private Const GMEM_NOTIFY = &H4000
Private Const GMEM_LOWER = GMEM_NOT_BANKED
Private Const GMEM_VALID_FLAGS = &H7F72
Private Const GMEM_INVALID_HANDLE = &H8000
Private Const GHND = (GMEM_MOVEABLE Or GMEM_ZEROINIT)
Private Const GPTR = (GMEM_FIXED Or GMEM_ZEROINIT)

Private Type DROPFILES
pFiles As Long
pt As POINTAPI
fNC As Long
fWide As Long
End Type


Public Function ClipboardCopyFiles(File As String) As Boolean

'
'From: https://www.developerfusion.com/code/224/copy-files-to-clipboard/
'

'modified by jjafferr
'Copy one file to clipboad
'call it like this: ClipboardCopyFiles("D:\Les-fruits.jpg")
'

Dim data As String
Dim df As DROPFILES
'Dim hGlobal As Long
'Dim lpGlobal As Long
Dim i As Long


' Open and clear existing crud off clipboard.
If OpenClipboard(0&) Then
Call EmptyClipboard

' Build double-null terminated list of files.
data = File & vbNullChar

' Allocate and get pointer to global memory,
' then copy file list to it.
hGlobal = GlobalAlloc(GHND, Len(df) + Len(data))
If hGlobal Then
lpGlobal = GlobalLock(hGlobal)

' Build DROPFILES structure in global memory.
df.pFiles = Len(df)
Call CopyMem(ByVal lpGlobal, df, Len(df))
Call CopyMem(ByVal (lpGlobal + Len(df)), ByVal data, Len(data))
Call GlobalUnlock(hGlobal)

' Copy data to clipboard, and return success.
If SetClipboardData(CF_HDROP, hGlobal) Then
ClipboardCopyFiles = True
End If
End If

' Clean up
Call CloseClipboard
End If

End Function

Public Function ClipboardPasteFiles(Files() As String) As Long

'Dim HDROP As Long
Dim nFiles As Long
Dim i As Long
Dim desc As String
Dim filename As String
Dim pt As POINTAPI
Const MAX_PATH As Long = 260

' Insure desired format is there, and open clipboard.
If IsClipboardFormatAvailable(CF_HDROP) Then
If OpenClipboard(0&) Then

' Get handle to Dropped Filelist data, and number of files.
HDROP = GetClipboardData(CF_HDROP)
nFiles = DragQueryFile(HDROP, -1&, "", 0)

' Allocate space for return and working variables.
ReDim Files(0 To nFiles - 1) As String
filename = Space(MAX_PATH)

' Retrieve each filename in Dropped Filelist.
For i = 0 To nFiles - 1
Call DragQueryFile(HDROP, i, filename, Len(filename))
Files(i) = TrimNull(filename)
Next

' Clean up
Call CloseClipboard
End If

' Assign return value equal to number of files dropped.
ClipboardPasteFiles = nFiles
End If

End Function

Private Function TrimNull(ByVal sTmp As String) As String

Dim nNul As Long

'
' Truncate input sTmpg at first Null.
' If no Nulls, perform ordinary Trim.
'
nNul = InStr(sTmp, vbNullChar)
Select Case nNul
Case Is > 1
TrimNull = Left(sTmp, nNul - 1)
Case 1
TrimNull = ""
Case 0
TrimNull = Trim(sTmp)
End Select

End Function

.

والحدث على نقر الزر :

Private Sub cmd_Attachment_image_to_Clipboard_Click()

    Dim myFile As String
    
    'make folder tmp_File in Windows TEMP Directory
    myFile = Environ("TEMP") & "\tmp_File\"
    If Dir(myFile) = "" Then
        MkDir myFile
    End If
    
    'Save the image to folder
    Call Export_Attached_Pictures("Query1", Me.ID, "img", Me.img.filename, myFile)
    
    'Copy the image to Clipboard
    Call ClipboardCopyFiles(myFile & Me.img.filename)
    
End Sub

Private Sub cmd_Copy_file_to_Clipboard_with_irfan_view_Click()
    
    'use irfan view to copy the picture in clipboard
    Dim IV_Path As String, Source_File As String

    IV_Path = "C:\Program Files\IrfanView\"  'location of i_view32.exe file
    Source_File = "D:\Les-fruits.jpg"
    'Source_File = Me.img.Picture
    
    Shell (IV_Path & "i_view64.exe " & Source_File & "/ClipCopy /killmesoftly")
    
    MsgBox "This image is copied in the clipboard, you can paste it in any program"
     
End Sub

 

جعفر

1484.Copy attached image to clipboard.accdb.zip

رابط هذا التعليق
شارك

Join the conversation

You can post now and register later. If you have an account, sign in now to post with your account.

زائر
اضف رد علي هذا الموضوع....

×   Pasted as rich text.   Paste as plain text instead

  Only 75 emoji are allowed.

×   Your link has been automatically embedded.   Display as a link instead

×   Your previous content has been restored.   Clear editor

×   You cannot paste images directly. Upload or insert images from URL.

  • تصفح هذا الموضوع مؤخراً   0 اعضاء متواجدين الان

    • لايوجد اعضاء مسجلون يتصفحون هذه الصفحه
×
×
  • اضف...

Important Information