Notifications
Clear all

macro para gravar ip da máquina que acessou a planilha

11 Posts
2 Usuários
0 Reactions
4,049 Visualizações
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Bom dia a todos,

Recentemente, lendo assuntos relacionados a macros e vba na net, descobri que tem como criar uma rotina para gravar o endereço de ip da máquina ao acessar uma planilha.
Alguem pode me ajudar????

Desde ja, agradeço-lhes!!!!

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 17/10/2012 8:29 am
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Encontrei na net e adaptei o código abaixo para ler a pasta temp da máquina:

Ele escreve na célula A1 da aba ativa

Option Explicit
 
Sub IPtest()
    Dim wsh As Object
    Dim RegEx As Object, RegM As Object
    Dim FSO As Object, fil As Object
    Dim ts As Object, txtAll As String, TempFil As String
    Set wsh = CreateObject("WScript.Shell")
    Set FSO = CreateObject("Scripting.FileSystemObject")
    Set RegEx = CreateObject("vbscript.regexp")
    TempFil = Environ$("TEMP")
    If Right(TempFil, 1) <> "" Then TempFil = TempFil & ""
    TempFil = TempFil & "myip.txt"
     ' Save ipconfig info to temporary file
    wsh.Run "%comspec% /c ipconfig > " & TempFil, 0, True
    With RegEx
        .Pattern = "(d{1,3}.){3}d{1,3}"
        .Global = False
    End With
    Set fil = FSO.GetFile(TempFil)
     ' Access temporary file
    Set ts = fil.OpenAsTextStream(1)
    txtAll = ts.ReadAll
    Set RegM = RegEx.Execute(txtAll)
     ' Return IP address to Activesheet cell A1 by parsing text
    ActiveSheet.Range("A1").Value = RegM(0)
    ActiveSheet.Range("A1").EntireColumn.AutoFit
    ts.Close
     ' Remove temp file
    Kill TempFil
     
    Set ts = Nothing
    Set wsh = Nothing
    Set fil = Nothing
    Set FSO = Nothing
    Set RegM = Nothing
    Set RegEx = Nothing
End Sub

http://www.vbaexpress.com/kb/getarticle.php?kb_id=537

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 17/10/2012 8:46 am
(@wilmarleal)
Posts: 186
Estimable Member
 

ve se te ajuda
http://www.exceldoseujeito.com.br/2009/ ... na-celula/

*** Espero ter Ajudado ***
Se a mensagem foi útil Favor Clicar na [MÃOZINHA].
Se Finalizou, lembre se de marcar o tópico como [RESOLVIDO].

Wilmar Borges Leal Junior
http://wilmarborges.com

 
Postado : 17/10/2012 8:49 am
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

ve se te ajuda
<span><a href="" http://www.exceldoseujeito.com.br/2009/03/14/exibir-o-endereco-de-ip-do-usuario-na-celula/" ;" class="smarterwiki-linkify"> http://www.exceldoseujeito.com.br/2009/03/14/exibir-o-endereco-de-ip-do-usuario-na-celula/</a></span>

o link que o wilmarleal postou tem uma rotina que me fornece o ip da maquina, porem copiei a macro e deu erro em tempo de execução nas duas linhas abaixo

CopyMemory HOST, lpHost, Len(HOST)
CopyMemory dwIPAddr, HOST.hAddrList, 4

Alguém pode me dar um help??

Obrigado!!

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 18/10/2012 8:09 am
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Wagner,

Você tem que copiar TODO aquele código ... não existe um código simplificado para fazer o que vc quer.

Para retornar o número do IP, use a função: GetIPAddress()

Ou seja, depois de colar todo aquele código no seu vba, segue um exemplo do uso para escrever na célula E4 da aba Plan1:

worksheet("Plan1").range("E4")=GetIPAddress()

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 18/10/2012 8:33 am
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Desculpem-me pela minha falha, segue abaixo o código completo

Option Explicit

Public Const MAX_WSADescription As Long = 256
Public Const MAX_WSASYSStatus As Long = 128
Public Const ERROR_SUCCESS As Long = 0
Public Const WS_VERSION_REQD As Long = &H101
Public Const WS_VERSION_MAJOR As Long = WS_VERSION_REQD  &H100 And &HFF&
Public Const WS_VERSION_MINOR As Long = WS_VERSION_REQD And &HFF&
Public Const MIN_SOCKETS_REQD As Long = 1
Public Const SOCKET_ERROR As Long = -1

Public Type HOSTENT
hName As Long
hAliases As Long
hAddrType As Integer
hLen As Integer
hAddrList As Long
End Type

Public Type WSADATA
wVersion As Integer
wHighVersion As Integer
szDescription(0 To MAX_WSADescription) As Byte
szSystemStatus(0 To MAX_WSASYSStatus) As Byte
wMaxSockets As Integer
wMaxUDPDG As Integer
dwVendorInfo As Long
End Type

Public Declare Function WSAGetLastError Lib "wsock32" () As Long

Public Declare Function WSAStartup Lib "wsock32" (ByVal wVersionRequired As Long, lpWSADATA As WSADATA) As Long

Public Declare Function WSACleanup Lib "wsock32" () As Long

Public Declare Function gethostname Lib "wsock32" (ByVal szHost As String, ByVal dwHostLen As Long) As Long

Public Declare Function gethostbyname Lib "wsock32" (ByVal szHost As String) As Long

Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)

Public Function GetIPAddress() As String

Dim sHostName As String * 256
Dim lpHost As Long
Dim HOST As HOSTENT
Dim dwIPAddr As Long
Dim tmpIPAddr() As Byte
Dim i As Integer
Dim sIPAddr As String

If Not SocketsInitialize() Then
    GetIPAddress = ""
    Exit Function
End If

If gethostname(sHostName, 256) = SOCKET_ERROR Then
   GetIPAddress = ""
   MsgBox "Ocorre um erro de Socket : " & Str$(WSAGetLastError()) & " , não é possivel obter nome do Host."
   SocketsCleanup
   Exit Function
End If

sHostName = Trim$(sHostName)
lpHost = gethostbyname(sHostName)

If lpHost = 0 Then
  GetIPAddress = ""
  MsgBox "Windows Sockets não está respondendo. " & vbCrLf & "Não foi possivel obter nome do Host"
  SocketsCleanup
  Exit Function
End If

CopyMemory HOST, lpHost, Len(HOST)
CopyMemory dwIPAddr, HOST.hAddrList, 4

ReDim tmpIPAddr(1 To HOST.hLen)
CopyMemory tmpIPAddr(1), dwIPAddr, HOST.hLen

For i = 1 To HOST.hLen
  sIPAddr = sIPAddr & tmpIPAddr(i) & "."
Next

GetIPAddress = Mid$(sIPAddr, 1, Len(sIPAddr) - 1)

SocketsCleanup

End Function

Public Function GetIPHostName() As String

Dim sHostName As String * 256

If Not SocketsInitialize() Then
  GetIPHostName = ""
  Exit Function
End If

If gethostname(sHostName, 256) = SOCKET_ERROR Then
  GetIPHostName = ""
  MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) & " não é possivel obter nome do Host."
  SocketsCleanup
  Exit Function
End If

GetIPHostName = Left$(sHostName, InStr(sHostName, Chr(0)) - 1)
SocketsCleanup

End Function

Public Function HiByte(ByVal wParam As Integer) As Byte

HiByte = (wParam And &HFF00&)  (&H100)

End Function

Public Function LoByte(ByVal wParam As Integer) As Byte

  LoByte = wParam And &HFF&

End Function

Public Sub SocketsCleanup()

If WSACleanup() <> ERROR_SUCCESS Then
  MsgBox " Erro de Socket."
End If

End Sub

Public Function SocketsInitialize() As Boolean

Dim WSAD As WSADATA
Dim sLoByte As String
Dim sHiByte As String

If WSAStartup(WS_VERSION_REQD, WSAD) <> ERROR_SUCCESS Then
  MsgBox "32-bit Windows Socket não está respondendo."
  SocketsInitialize = False
  Exit Function
End If

If WSAD.wMaxSockets < MIN_SOCKETS_REQD Then
MsgBox " Esta aplicação requer um minimo de " & _
CStr(MIN_SOCKETS_REQD) & " sockets suportados."

SocketsInitialize = False
Exit Function
End If

If LoByte(WSAD.wVersion) < WS_VERSION_MAJOR Or (LoByte(WSAD.wVersion) = WS_VERSION_MAJOR And HiByte(WSAD.wVersion) < WS_VERSION_MINOR) Then

  sHiByte = CStr(HiByte(WSAD.wVersion))
  sLoByte = CStr(LoByte(WSAD.wVersion))

  MsgBox "A versao Sockets " & sLoByte & "." & sHiByte & " não é suportada por 32-bit Windows Sockets."

  SocketsInitialize = False
Exit Function

End If

SocketsInitialize = True

End Function

Conforme Reynaldo Coral, editor do código:
"Após isso, salve o projeto e retorne à sua planilha.

Como nós criamos uma função personalizada, podemos chamá-la diretamente dentro da célula desejada. Para tanto, se quiser mostrar o endereço de IP do usuário da planilha, selecione uma célula e digite:

=GetIPAddress()

Irá exibir algo como 10.2.2.185.

Caso queira mostrar o nome do Host (Computador) então digite:

=GetIPHostName()

O resultado seria parecido com EDSJeito-Suporte01."

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 18/10/2012 8:39 am
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Desculpem-me pela minha falha, segue abaixo o código completo

Option Explicit

Public Const MAX_WSADescription As Long = 256
Public Const MAX_WSASYSStatus As Long = 128
Public Const ERROR_SUCCESS As Long = 0
Public Const WS_VERSION_REQD As Long = &H101
Public Const WS_VERSION_MAJOR As Long = WS_VERSION_REQD  &H100 And &HFF&
Public Const WS_VERSION_MINOR As Long = WS_VERSION_REQD And &HFF&
Public Const MIN_SOCKETS_REQD As Long = 1
Public Const SOCKET_ERROR As Long = -1

Public Type HOSTENT
hName As Long
hAliases As Long
hAddrType As Integer
hLen As Integer
hAddrList As Long
End Type

Public Type WSADATA
wVersion As Integer
wHighVersion As Integer
szDescription(0 To MAX_WSADescription) As Byte
szSystemStatus(0 To MAX_WSASYSStatus) As Byte
wMaxSockets As Integer
wMaxUDPDG As Integer
dwVendorInfo As Long
End Type

Public Declare Function WSAGetLastError Lib "wsock32" () As Long

Public Declare Function WSAStartup Lib "wsock32" (ByVal wVersionRequired As Long, lpWSADATA As WSADATA) As Long

Public Declare Function WSACleanup Lib "wsock32" () As Long

Public Declare Function gethostname Lib "wsock32" (ByVal szHost As String, ByVal dwHostLen As Long) As Long

Public Declare Function gethostbyname Lib "wsock32" (ByVal szHost As String) As Long

Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)

Public Function GetIPAddress() As String

Dim sHostName As String * 256
Dim lpHost As Long
Dim HOST As HOSTENT
Dim dwIPAddr As Long
Dim tmpIPAddr() As Byte
Dim i As Integer
Dim sIPAddr As String

If Not SocketsInitialize() Then
    GetIPAddress = ""
    Exit Function
End If

If gethostname(sHostName, 256) = SOCKET_ERROR Then
   GetIPAddress = ""
   MsgBox "Ocorre um erro de Socket : " & Str$(WSAGetLastError()) & " , não é possivel obter nome do Host."
   SocketsCleanup
   Exit Function
End If

sHostName = Trim$(sHostName)
lpHost = gethostbyname(sHostName)

If lpHost = 0 Then
  GetIPAddress = ""
  MsgBox "Windows Sockets não está respondendo. " & vbCrLf & "Não foi possivel obter nome do Host"
  SocketsCleanup
  Exit Function
End If

CopyMemory HOST, lpHost, Len(HOST)
CopyMemory dwIPAddr, HOST.hAddrList, 4

ReDim tmpIPAddr(1 To HOST.hLen)
CopyMemory tmpIPAddr(1), dwIPAddr, HOST.hLen

For i = 1 To HOST.hLen
  sIPAddr = sIPAddr & tmpIPAddr(i) & "."
Next

GetIPAddress = Mid$(sIPAddr, 1, Len(sIPAddr) - 1)

SocketsCleanup

End Function

Public Function GetIPHostName() As String

Dim sHostName As String * 256

If Not SocketsInitialize() Then
  GetIPHostName = ""
  Exit Function
End If

If gethostname(sHostName, 256) = SOCKET_ERROR Then
  GetIPHostName = ""
  MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) & " não é possivel obter nome do Host."
  SocketsCleanup
  Exit Function
End If

GetIPHostName = Left$(sHostName, InStr(sHostName, Chr(0)) - 1)
SocketsCleanup

End Function

Public Function HiByte(ByVal wParam As Integer) As Byte

HiByte = (wParam And &HFF00&)  (&H100)

End Function

Public Function LoByte(ByVal wParam As Integer) As Byte

  LoByte = wParam And &HFF&

End Function

Public Sub SocketsCleanup()

If WSACleanup() <> ERROR_SUCCESS Then
  MsgBox " Erro de Socket."
End If

End Sub

Public Function SocketsInitialize() As Boolean

Dim WSAD As WSADATA
Dim sLoByte As String
Dim sHiByte As String

If WSAStartup(WS_VERSION_REQD, WSAD) <> ERROR_SUCCESS Then
  MsgBox "32-bit Windows Socket não está respondendo."
  SocketsInitialize = False
  Exit Function
End If

If WSAD.wMaxSockets < MIN_SOCKETS_REQD Then
MsgBox " Esta aplicação requer um minimo de " & _
CStr(MIN_SOCKETS_REQD) & " sockets suportados."

SocketsInitialize = False
Exit Function
End If

If LoByte(WSAD.wVersion) < WS_VERSION_MAJOR Or (LoByte(WSAD.wVersion) = WS_VERSION_MAJOR And HiByte(WSAD.wVersion) < WS_VERSION_MINOR) Then

  sHiByte = CStr(HiByte(WSAD.wVersion))
  sLoByte = CStr(LoByte(WSAD.wVersion))

  MsgBox "A versao Sockets " & sLoByte & "." & sHiByte & " não é suportada por 32-bit Windows Sockets."

  SocketsInitialize = False
Exit Function

End If

SocketsInitialize = True

End Function

Conforme Reynaldo Coral, editor do código:
"Após isso, salve o projeto e retorne à sua planilha.

Como nós criamos uma função personalizada, podemos chamá-la diretamente dentro da célula desejada. Para tanto, se quiser mostrar o endereço de IP do usuário da planilha, selecione uma célula e digite:

=GetIPAddress()

Irá exibir algo como 10.2.2.185.

Caso queira mostrar o nome do Host (Computador) então digite:

=GetIPHostName()

O resultado seria parecido com EDSJeito-Suporte01."

Eu inseri a fórmula numa célula qualquer, no entanto não surtiu efeito, resolvi executar a fórmula no vba para verificar se havia algum erro. Como ja informei num post anterior, as linhas

CopyMemory HOST, lpHost, Len(HOST)
CopyMemory dwIPAddr, HOST.hAddrList, 4

deram erro em tempo de execução. Valor de propriedade incorreto.
O que pode ter acontecido para o programa dar essa msg????

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 18/10/2012 8:50 am
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Wagner, testei a function tanto no excel 2003 como no 2007 e funcionou perfeitamente.

Você tem de copiar toda a rotina criar um novo Modulo e cola-la, então é só ir em qq celula e digitar os comandos conforme o Alexandre passou:

=GetIPAddress() ou

=GetIPHostName()

No outro link, tem um exemplo pronto, é só baixar:
http://www.vbaexpress.com/kb/getarticle.php?kb_id=537

Por via de duvidas montei um exemplo com as dicas acima com uma msgbox ao iniciar o aplicativo, uma opção de preenchimento em Textboxs e outro jogando para celulas na planilha e outra utilizando somente a formula, veja se ajuda.

Retornando IP e Host da maquina

[]s

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 18/10/2012 7:52 pm
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Boa tarde,

Quero agradecer a todos que me ajudaram, pois consegui fazer exatamente o que precisava.
O tópico já pode ser fechado!

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 22/10/2012 12:04 pm
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Boa tarde Amigos,

Fazendo alguns testes no código abaixo, percebi que ao alterar o usuario, alterava todas as outras ocorrências
O q eu qero fazer é por exemplo: SE(A7>"";GetIPAddress();""), entretanto, qdo acessei a planilha de outra maquina as outras células alteravam para o ip atual. Existe alguma forma de travar a fórmula citada acima????

Option Explicit

Public Const MAX_WSADescription As Long = 256
Public Const MAX_WSASYSStatus As Long = 128
Public Const ERROR_SUCCESS As Long = 0
Public Const WS_VERSION_REQD As Long = &H101
Public Const WS_VERSION_MAJOR As Long = WS_VERSION_REQD  &H100 And &HFF&
Public Const WS_VERSION_MINOR As Long = WS_VERSION_REQD And &HFF&
Public Const MIN_SOCKETS_REQD As Long = 1
Public Const SOCKET_ERROR As Long = -1

Public Type HOSTENT
hName As Long
hAliases As Long
hAddrType As Integer
hLen As Integer
hAddrList As Long
End Type

Public Type WSADATA
wVersion As Integer
wHighVersion As Integer
szDescription(0 To MAX_WSADescription) As Byte
szSystemStatus(0 To MAX_WSASYSStatus) As Byte
wMaxSockets As Integer
wMaxUDPDG As Integer
dwVendorInfo As Long
End Type

Public Declare Function WSAGetLastError Lib "wsock32" () As Long

Public Declare Function WSAStartup Lib "wsock32" (ByVal wVersionRequired As Long, lpWSADATA As WSADATA) As Long

Public Declare Function WSACleanup Lib "wsock32" () As Long

Public Declare Function gethostname Lib "wsock32" (ByVal szHost As String, ByVal dwHostLen As Long) As Long

Public Declare Function gethostbyname Lib "wsock32" (ByVal szHost As String) As Long

Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)

Public Function GetIPAddress() As String

Dim sHostName As String * 256
Dim lpHost As Long
Dim HOST As HOSTENT
Dim dwIPAddr As Long
Dim tmpIPAddr() As Byte
Dim i As Integer
Dim sIPAddr As String

If Not SocketsInitialize() Then
    GetIPAddress = ""
    Exit Function
End If

If gethostname(sHostName, 256) = SOCKET_ERROR Then
   GetIPAddress = ""
   MsgBox "Ocorre um erro de Socket : " & Str$(WSAGetLastError()) & " , não é possivel obter nome do Host."
   SocketsCleanup
   Exit Function
End If

sHostName = Trim$(sHostName)
lpHost = gethostbyname(sHostName)

If lpHost = 0 Then
  GetIPAddress = ""
  MsgBox "Windows Sockets não está respondendo. " & vbCrLf & "Não foi possivel obter nome do Host"
  SocketsCleanup
  Exit Function
End If

CopyMemory HOST, lpHost, Len(HOST)
CopyMemory dwIPAddr, HOST.hAddrList, 4

ReDim tmpIPAddr(1 To HOST.hLen)
CopyMemory tmpIPAddr(1), dwIPAddr, HOST.hLen

For i = 1 To HOST.hLen
  sIPAddr = sIPAddr & tmpIPAddr(i) & "."
Next

GetIPAddress = Mid$(sIPAddr, 1, Len(sIPAddr) - 1)

SocketsCleanup

End Function

Public Function GetIPHostName() As String

Dim sHostName As String * 256

If Not SocketsInitialize() Then
  GetIPHostName = ""
  Exit Function
End If

If gethostname(sHostName, 256) = SOCKET_ERROR Then
  GetIPHostName = ""
  MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) & " não é possivel obter nome do Host."
  SocketsCleanup
  Exit Function
End If

GetIPHostName = Left$(sHostName, InStr(sHostName, Chr(0)) - 1)
SocketsCleanup

End Function

Public Function HiByte(ByVal wParam As Integer) As Byte

HiByte = (wParam And &HFF00&)  (&H100)

End Function

Public Function LoByte(ByVal wParam As Integer) As Byte

  LoByte = wParam And &HFF&

End Function

Public Sub SocketsCleanup()

If WSACleanup() <> ERROR_SUCCESS Then
  MsgBox " Erro de Socket."
End If

End Sub

Public Function SocketsInitialize() As Boolean

Dim WSAD As WSADATA
Dim sLoByte As String
Dim sHiByte As String

If WSAStartup(WS_VERSION_REQD, WSAD) <> ERROR_SUCCESS Then
  MsgBox "32-bit Windows Socket não está respondendo."
  SocketsInitialize = False
  Exit Function
End If

If WSAD.wMaxSockets < MIN_SOCKETS_REQD Then
MsgBox " Esta aplicação requer um minimo de " & _
CStr(MIN_SOCKETS_REQD) & " sockets suportados."

SocketsInitialize = False
Exit Function
End If

If LoByte(WSAD.wVersion) < WS_VERSION_MAJOR Or (LoByte(WSAD.wVersion) = WS_VERSION_MAJOR And HiByte(WSAD.wVersion) < WS_VERSION_MINOR) Then

  sHiByte = CStr(HiByte(WSAD.wVersion))
  sLoByte = CStr(LoByte(WSAD.wVersion))

  MsgBox "A versao Sockets " & sLoByte & "." & sHiByte & " não é suportada por 32-bit Windows Sockets."

  SocketsInitialize = False
Exit Function

End If

SocketsInitialize = True

End Function

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 23/10/2012 2:54 pm
Fernando Fernandes
(@fernandofernandes)
Posts: 43750
Illustrious Member
Topic starter
 

Wagner, mesmo utilizando uma Função Personalizada a mesma funciona igual as funções do Excel, ou seja elas são atualizadas automaticamente.

Se quer criar uma relação dos IPs que acessaram o arquivo, o ideal seria criar uma coluna de "IPs" em alguma aba e atraves de uma rotina lançar um abaixo do outro, ou seja sem fixar a formula na celula.
No exemplo que disponibilizei, tem um Formulário com um botão para lançar o IP na planilha sem a formula, é só adapta-lo para lançar na coluna que criar e lançar sequencialmente, da até para por o dia e hora que foi acessado tambem.

No Forum abaixo tem um exemplo que gera um arquivo de Log com as informações dos usuarios, datas e alterações efetuadas nas planilhas, de uma olhada e veja se ajuda.

Log com as Alterações nas Planilhas v 2003 - v 2007
http://www.tomasvasquez.com.br/forum/vi ... IcpT2_A9-J

[]s

Existem mil maneiras de preparar Neston. Invente a sua!
http://www.youtube.com/ExpressoExcel

 
Postado : 23/10/2012 5:09 pm