Consulting

Page 4 of 5 FirstFirst ... 2 3 4 5 LastLast
Results 61 to 80 of 97

Thread: Solved: Only running MyExcel.xls on named machine?

  1. #61
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Hey Simon,

    Okay, new zip attached with all the following files:
    -Control.xla
    -Auth.mdb
    -TestBook1.xls
    -TestBook2.xls

    Open TestBook1.xls with macros disabled. Update the path in the ThisWorkbook module to where you'll store the xla file. (Does not have to be in the standard locale, I don't believe. Haven't tested this completely through.) Save it and reopen it.

    You should now get a message about not working from home, and the workbook should close. This is a good thing. Check your addins, and a new one should be installed. Go into the code of the Control.xla and update the database path.

    I've converted the Control workbook to an xla, and added the class module to monitor events. I've converted the old Workbook_Open routine to a separate re-usable routine, and made the addin to ensure that it is installed.

    Once it's running, open TestBook2.xls. If you're all authorized, you're good to go, else it should kick you out. There is no code in there, it's all controlled by the Control.xla class module code.

    Thing is, you need to add the ThisWorkbook code to all 27 workbooks to ensure that they kick the home users.

    It's not perfect, but it should do the trick to get you started.

    One issue now remains... if the user disables macros the first time, they won't get the add-in installed. We need to give you a way to ensure macros are enabled, and there's tricks for that.

    Review this first, though, and ask your questions.
    Ken Puls, CMA - Microsoft MVP (Excel)
    I hate it when my computer does what I tell it to, and not what I want it to.

    Learn how to use our KB tags! -||- Ken's Excel Website -||- Ken's Excel Forums -||- My Blog -||- Excel Training Calendar

    This is a shameless plug for my new book "RibbonX - Customizing the Office 2007 Ribbon". Find out more about it here!

    Help keep VBAX clean! Use the 'Thread Tools' menu to mark your own threads solved!





  2. #62
    Administrator
    Chat VP
    VBAX Guru johnske's Avatar
    Joined
    Jul 2004
    Location
    Townsville, Australia
    Posts
    2,872
    Location
    Put all the workbooks that need the new ThisWorkbook procedures into a folder with the book containing the new procedure.

    Put this code into a standard module in the book that contains the new procedure and run it (make sure all the other workbooks are closed as I didn't add code to check if thay're open) - this is basically a 'copy and paste' for a VBE module

    [vba]Option Explicit

    Sub ReplaceThisWorkbookProcedures()

    Dim N As Long
    Dim NewCode As String

    'ThisWorkbook is the file containing the new ThisWorkbook procedures
    With ThisWorkbook.VBProject.VBComponents("ThisWorkbook").CodeModule
    NewCode = .Lines(1, .countoflines)
    End With

    'open all files you want the new procs in
    With Application
    .ScreenUpdating = False
    .DisplayAlerts = False
    With .FileSearch
    .LookIn = ThisWorkbook.Path
    .Filename = "*.xls"
    If .Execute > 0 Then
    For N = 1 To .FoundFiles.Count
    If .FoundFiles(N) <> ThisWorkbook.FullName Then
    Workbooks.Open(.FoundFiles(N)).Activate

    '--------Delete old procedures and replace with new--------
    With ActiveWorkbook.VBProject.VBComponents("ThisWorkbook").CodeModule
    .DeleteLines 1, .countoflines
    .InsertLines 1, NewCode
    End With
    '-----------------------------------------------------------------

    ActiveWorkbook.Close savechanges:=True
    End If
    Next
    End If
    End With
    .ScreenUpdating = True
    .DisplayAlerts = True
    End With

    End Sub[/vba]
    You know you're really in trouble when the light at the end of the tunnel turns out to be the headlight of a train hurtling towards you

    The major part of getting the right answer lies in asking the right question...


    Made your code more readable, use VBA tags (this automatically inserts [vba] at the start of your code, and [/vba ] at the end of your code) | Help those helping you by marking your thread solved when it is.

  3. #63
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Ken, thanks!

    1. Confused?, how does the Control.xla monitor TestBook2? I understand that we have set the workbook name in the xla but we dont set a path, do i have to set the path for each and every workbook? does it monitor files only in its own folder?............im finding it hard to grasp that there is no code in it. Testbook1 did throw me out until i changed the path of the xla so i understand how this one works because there is code in the ThisWorkBook module.

    2. Xla? im not sure what this is i assume it like a template, although it doesn't have any work sheets but i can view the code.....strange!

    3. You say check my add in's well ichecked in the testbook1 just excels add ins available, in testbook2 just Excel add in's (no vba add ins in either). Where did you mean?

    its a bit tougher following the flow of this one as it doesnt react the same using F8 to step through it but i see what is happening but testbook2....?

    Regards,
    Simon
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  4. #64
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    LOL!

    First, John, nice work!

    Okay, Simon, here's the deal.

    The xla is an Excel Add-in file, not a regular workbook any more. What happens with an xla file is that it hides all the worksheets from view. The same is true of the personal.xls workbook, which you may know. Sheets are still there, but as soon as you set the IsAddin property on the workbook to True, they cease being visible. So how do you know if your add-in is open? Well, if you coded a menu structure, the menus will still be visible. In this case, though, we have no menus. Go to Tools|Add-ins. Look for "Control". It should be checked in the list now.

    Now, why does the add-in work with Testbook 2, even though it has no code...

    Remember how I said I'd add a Class Module to monitor events? The deal is this... the new class module is linked to by the Add-ins Workbook_Open event. Once that is done, EVERY workbook that is opened triggers the event in the Class Module. It examines the name of the workbook that was opened, and if it is in our list, it fires the code to check if the user is authorized to be there.

    The only reason that there is code in the TestBook1.xls is that we need to be able to check if the user is allowed to use that main workbook. That code checks if the add-in is installed. If it's not, it tries to install the add-in. If it can't the user must be at work. If it can, it triggers the add-in code. If the add-in is already installed, it was doing it's thing already.

    Does that make more sense?
    Ken Puls, CMA - Microsoft MVP (Excel)
    I hate it when my computer does what I tell it to, and not what I want it to.

    Learn how to use our KB tags! -||- Ken's Excel Website -||- Ken's Excel Forums -||- My Blog -||- Excel Training Calendar

    This is a shameless plug for my new book "RibbonX - Customizing the Office 2007 Ribbon". Find out more about it here!

    Help keep VBAX clean! Use the 'Thread Tools' menu to mark your own threads solved!





  5. #65
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Hi Ken thanks for the explanation it clears it up for me....but do all the workbooks have to be in the same folder for the xla to work? does the xla file have to be open? i cant imagine every workbook on the drive its located on will be checked!

    For clarity....i have to list all of my workbooks where currently testbook1 & 2 are?

    When i ran testbook1 i got "Error 52" Bad filename or number...and the code stopped here.
    Workbooks.Open strAddinPath
    Until i changed the Auth path in the controls workbook.

    And i checked both workbooks again and there wasn't a Control in Add In's in either workbook!

    John thanks for that work on procedure for adding stuff to the workbooks!

    Regards,
    Simon

    P.S if dont sound compus mentus its because i have been working nights last night and im reading this at 8:30 am so i may have more questions when i can see straight.
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  6. #66
    Distinguished Lord of VBAX VBAX Grand Master Bob Phillips's Avatar
    Joined
    Apr 2005
    Posts
    25,453
    Location
    John,

    Time to stop providing solutions with FileSearch. In Excel 2007, FileSearch is gone, so for forward compatibility ...

  7. #67
    Administrator
    Chat VP VBAX Guru johnske's Avatar
    Joined
    Jul 2004
    Location
    Townsville, Australia
    Posts
    2,872
    Location
    Quote Originally Posted by xld
    John,

    Time to stop providing solutions with FileSearch. In Excel 2007, FileSearch is gone, so for forward compatibility ...
    Really? Oh well, this is shorter anyway.

    Scrap the previous Simon and use this instead (same instructions) [vba]
    Option Explicit

    Sub ReplaceThisWorkbookProcedures()

    Dim FileFound As Object
    Dim NewCode As String

    'ThisWorkbook is the file containing all the new ThisWorkbook procedures
    With ThisWorkbook.VBProject.VBComponents("ThisWorkbook").CodeModule
    NewCode = .Lines(1, .countoflines) '< "copy" the code
    End With

    'open all files you want the new procs in
    With Application
    .ScreenUpdating = False
    .DisplayAlerts = False

    For Each FileFound In CreateObject("Scripting.FileSystemObject") _
    .GetFolder(ThisWorkbook.Path).Files
    If Right(FileFound.Name, 4) = ".xls" _
    And Not FileFound.Name = ThisWorkbook.Name Then
    Workbooks.Open(FileFound).Activate

    '--------Delete old procedures and replace with new--------
    With ActiveWorkbook.VBProject.VBComponents("ThisWorkbook").CodeModule
    .DeleteLines 1, .countoflines
    .InsertLines 1, NewCode '< "paste" the code
    End With
    '-----------------------------------------------------------------

    ActiveWorkbook.Close savechanges:=True
    End If
    Next

    .ScreenUpdating = True
    .DisplayAlerts = True
    End With
    End Sub
    [/vba]
    You know you're really in trouble when the light at the end of the tunnel turns out to be the headlight of a train hurtling towards you

    The major part of getting the right answer lies in asking the right question...


    Made your code more readable, use VBA tags (this automatically inserts [vba] at the start of your code, and [/vba ] at the end of your code) | Help those helping you by marking your thread solved when it is.

  8. #68
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    El Xid, im probably grasping the wrong end of the stick but i dont have Xl2007 as im sure many others dont and probably wont for a while........so not wanting to take sides but i for one would still like solutions i could use comfortbly!

    Regards,
    Simon

    John thanks for the revised code
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  9. #69
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Quote Originally Posted by Simon Lloyd
    Hi Ken thanks for the explanation it clears it up for me....but do all the workbooks have to be in the same folder for the xla to work?
    Nope. When you place the code in the ThisWorkbook module, you need make sure that the following line points to where you are going to save the add-in file:

    [vba]Private Const strAddinPath = ...[/vba]

    In addition, make sure that the path to the database is set in the actuall add-in.

    Those 2 keys control how the file finds the add-in and the database, and they can be anywhere. They should point to a location that will always be accesible though. I can't remember... did your drive letters change? If so, we may need to make it relevant to the "ThisWorkbook.Path", but if we can avoid that, it would be better. Those paths should be able to accept UNC paths too, if the logical drive mappings (letters) are different.

    Quote Originally Posted by Simon Lloyd
    does the xla file have to be open? i cant imagine every workbook on the drive its located on will be checked!
    The Xla file is automagically installed when you open one of the 27 workbooks. After that, it just checks if it was instaleld. Provided Excel does not crash, the setting will be placed in the registry to register the addin, and Excel will start with it installed the next time it opens. Your users will be none the wiser, and this really shouldn't slow them down much at all.

    Does it check every workbook on the drive? Heck no! That would take forever! What is checked is every workbook that is opened, if it's stored on the drive or not.

    Quote Originally Posted by Simon Lloyd
    For clarity....i have to list all of my workbooks where currently testbook1 & 2 are?
    That's correct, and that's how the test works. When a workbook is opened, the event is fired. It looks to see if the name of the opened workbook is in your list. If it's not, it just ends the event, and lets the user continue on as normal. If it is in the list, though, the credential checking starts.

    Quote Originally Posted by Simon Lloyd
    When i ran testbook1 i got "Error 52" Bad filename or number...and the code stopped here.
    Workbooks.Open strAddinPath
    Until i changed the Auth path in the controls workbook.
    Hmm... will have to look into that one. I doubt your users will see that once the path is set to the db. Shoudln't affect the home user, either, as they won't have the db, so will never get there.

    Quote Originally Posted by Simon Lloyd
    And i checked both workbooks again and there wasn't a Control in Add In's in either workbook!
    Methinks you didn't quite follow on that part. The Add-in is an Application level thing, not a workbook level thing. Go to Tools|Add-ins. Look down the list until you find "Control". It should be checked. This signifies that the add-in was correctly installed.

    Quote Originally Posted by Simon Lloyd
    El Xid, im probably grasping the wrong end of the stick but i dont have Xl2007 as im sure many others dont and probably wont for a while........so not wanting to take sides but i for one would still like solutions i could use comfortbly!
    RE this point. Bob was just pointing out that the method John used will not work in 2007. It will still work fine in this case. The reason though, is just to get us in the habit of using methods that will work now and forward. There's nothing worse than upgrading to a new version, and finding out that the code broke. Just imagine trying to explain all of this to someone in a help forum 3 years from now. John's code will be a one timer, but it's still good practice to think of the future anyway.
    Ken Puls, CMA - Microsoft MVP (Excel)
    I hate it when my computer does what I tell it to, and not what I want it to.

    Learn how to use our KB tags! -||- Ken's Excel Website -||- Ken's Excel Forums -||- My Blog -||- Excel Training Calendar

    This is a shameless plug for my new book "RibbonX - Customizing the Office 2007 Ribbon". Find out more about it here!

    Help keep VBAX clean! Use the 'Thread Tools' menu to mark your own threads solved!





  10. #70
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Ken, i understand your point about Xl2007.....just being abit dim there!

    As for the Add-Ins i mus be missing the point somewhere......on both workbooks i went to Tools | Add In's and just excel standard add ins were available, i checked VBA Add-In Manager no items, i checked Control.XLA Tools |Add In's just excels standard, i checked VBA Add In Manager no items!

    I know i have probably misunderstood, so if you could explain kinda idiot fashion for me i would appreciate it!

    In testbook1 and Control.xla thisworkbook module i dont have
    [VBA]
    Private Const strAddinPath = ...
    [/VBA]Regards,
    Simon
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  11. #71
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Sorry, Simon, my gaff. I must have already had the add-in installed when I tested, although I was sure I didn't. You can't remove an add-in from the collection easily, so it messed me up a bit.

    New zip attached with a new copy of the Control.xla file. This one uses a proper method to install the add-in. I've also modified the code in TestBook1.xls a bit. Go to the ThisWorkbook module there. Right at the very top is the code that I eluded to above. That path needs to be the same as the path to your add-in (wherever you store it).

    PS, update the file paths as usual.
    Ken Puls, CMA - Microsoft MVP (Excel)
    I hate it when my computer does what I tell it to, and not what I want it to.

    Learn how to use our KB tags! -||- Ken's Excel Website -||- Ken's Excel Forums -||- My Blog -||- Excel Training Calendar

    This is a shameless plug for my new book "RibbonX - Customizing the Office 2007 Ribbon". Find out more about it here!

    Help keep VBAX clean! Use the 'Thread Tools' menu to mark your own threads solved!





  12. #72
    Administrator
    Chat VP VBAX Guru johnske's Avatar
    Joined
    Jul 2004
    Location
    Townsville, Australia
    Posts
    2,872
    Location
    Quote Originally Posted by Ken Puls
    ...RE this point. Bob was just pointing out that the method John used will not work in 2007. It will still work fine in this case. The reason though, is just to get us in the habit of using methods that will work now and forward. There's nothing worse than upgrading to a new version, and finding out that the code broke. Just imagine trying to explain all of this to someone in a help forum 3 years from now. John's code will be a one timer, but it's still good practice to think of the future anyway.
    Ken, Simon,

    It's not just the future, some ppl have 2007 now and maybe they've been Googling to find something that does what you want to do...

    Regards,
    John
    You know you're really in trouble when the light at the end of the tunnel turns out to be the headlight of a train hurtling towards you

    The major part of getting the right answer lies in asking the right question...


    Made your code more readable, use VBA tags (this automatically inserts [vba] at the start of your code, and [/vba ] at the end of your code) | Help those helping you by marking your thread solved when it is.

  13. #73
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    True enough, John, true enough.

    Oh! And Simon, btw... before you copy all that code into each workbook, remember that we still need to deal with a user who disables macros. There is a trick for doing this where we make all sheets except our "Welcome" sheet VeryHidden. Then, at workbook open, if the file is authorized, we unhide everything and hide the "Welcome" sheet.

    I believe that there is some code in the KB to do this.
    Ken Puls, CMA - Microsoft MVP (Excel)
    I hate it when my computer does what I tell it to, and not what I want it to.

    Learn how to use our KB tags! -||- Ken's Excel Website -||- Ken's Excel Forums -||- My Blog -||- Excel Training Calendar

    This is a shameless plug for my new book "RibbonX - Customizing the Office 2007 Ribbon". Find out more about it here!

    Help keep VBAX clean! Use the 'Thread Tools' menu to mark your own threads solved!





  14. #74
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Thamks Ken.....I believe the code you refer to was posted by Johnske!

    I did research it and found that, i will test out your revised code then incorporate the Macro force code.

    Thanks....to both of you

    Regards,
    Simon

    P.S as for gaffs, i've got a million of 'em!
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  15. #75
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Cool! Let us know how you make out with it.
    Ken Puls, CMA - Microsoft MVP (Excel)
    I hate it when my computer does what I tell it to, and not what I want it to.

    Learn how to use our KB tags! -||- Ken's Excel Website -||- Ken's Excel Forums -||- My Blog -||- Excel Training Calendar

    This is a shameless plug for my new book "RibbonX - Customizing the Office 2007 Ribbon". Find out more about it here!

    Help keep VBAX clean! Use the 'Thread Tools' menu to mark your own threads solved!





  16. #76
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    BINGO!!!!!!!!!!!

    I opened the file made the adjustments...worked great opened TestBook1 code already installed, authentication worked if xla path was wrong or Auth path was wrong, change them and everything was cool........next i went to TextBook2 (which is on the same path just one folder down, Xla is stored in F:\Kens Work\Final and Testbook2 is stored in F:\Kens Work) i opened it saw nothing..checked Add-Ins and Hey Presto! there it was checked, again change the path of Auth and i was denied access!

    Brilliant!

    So as long as i list the workbooks whether the Add In is already installed or not authentication takes place..........so cool!

    Ken i'm going to mark this epic thread Solved, and if i ever get to visit Canada i'll look you up i think you've earned a beer or 12!

    Best regards,
    Simon

    Here's the code i found in the kb
    Johnske could you explain the use of .[A100] please, as for the rest of the code i already use something similar in my workbooks, i have a front sheet which is visible and all others are just xlHidden if they dont have macros enabled they only see the front page, i take it that xlVeryHidden means they aren't available in Format | Sheets | Unhide

    [VBA]Private Sub Workbook_Open()

    Dim Sheet As Worksheet
    'make all sheets visible
    For Each Sheet In Worksheets
    If Sheet.Name <> "Prompt" Then
    Sheet.Visible = xlSheetVisible
    End If
    Next Sheet
    'hide the prompt and go to A1 on sheet1
    Sheets("Prompt").Visible = xlSheetVeryHidden
    Application.Goto Sheet1.[A1], scroll:=True
    'clean up
    Set Sheet = Nothing
    ActiveWorkbook.Saved = True

    End Sub

    Private Sub Workbook_BeforeClose(Cancel As Boolean)

    With Sheets("Prompt")
    'if book is already saved, make a note of it
    If ActiveWorkbook.Saved = True Then .[A100] = "Saved"

    'make prompt sheet visible
    Dim Sheet As Worksheet
    .Visible = xlSheetVisible
    'hide all other sheets
    For Each Sheet In Worksheets
    If Sheet.Name <> "Prompt" Then
    Sheet.Visible = xlSheetVeryHidden
    End If
    Next Sheet
    'if the book is already saved, delete
    'the previous note and close the book
    If .[A100] = "Saved" Then
    .[A100].ClearContents
    ActiveWorkbook.Save
    End If
    'clean up
    Set Sheet = Nothing
    End With

    End Sub [/VBA]
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  17. #77
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Quick question Ken, the database, can i password protect it? would it still be able to be read? I just dont want anyone who finds it to be able to change anything.

    Regards,
    Simon
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  18. #78
    Administrator
    Chat VP VBAX Guru johnske's Avatar
    Joined
    Jul 2004
    Location
    Townsville, Australia
    Posts
    2,872
    Location
    Simon,

    That bit was put in because - although you may've saved the workbook, the changes made when closing it forced another "Save?" prompt when you really hadn't made any changes, that bit means you're only prompted to save if it hasn't already been saved.

    Here's what the Help file says about xlSheetVeryHidden "This hides the object so that the only way for you to make it visible again is by setting this property to True (the user cannot make the object visible)."

    However, if the VBA Project is unlocked the user can make it visible in the VBE window by going to "Properties" and changing it to visible there - but not if it's locked.

    Regards,
    John
    You know you're really in trouble when the light at the end of the tunnel turns out to be the headlight of a train hurtling towards you

    The major part of getting the right answer lies in asking the right question...


    Made your code more readable, use VBA tags (this automatically inserts [vba] at the start of your code, and [/vba ] at the end of your code) | Help those helping you by marking your thread solved when it is.

  19. #79
    Moderator VBAX Guru Simon Lloyd's Avatar
    Joined
    Sep 2005
    Location
    UK
    Posts
    3,003
    Location
    Got it!, thanks the user has no way of viewing the sheets unless coded to do so, i think i will make great use of that in my workbooks.

    So the.[A100] is that VBA and are there other similar statements that have that kind of control if so where can they be seen?

    Thanks,
    Simon
    Regards,
    Simon
    Please read this before cross posting!
    In the unlikely event you didn't get your answer here try Microsoft Office Discussion @ The Code Cage
    If I have seen further it is by standing on the shoulders of giants.
    Isaac Newton, Letter to Robert Hooke, February 5, 1675 English mathematician & physicist (1642 - 1727)

  20. #80
    Administrator
    Chat VP VBAX Guru johnske's Avatar
    Joined
    Jul 2004
    Location
    Townsville, Australia
    Posts
    2,872
    Location
    No, that's just shortcut notation i.e. [A100] = Range("A100").Value the pertinent bit is...
    [vba]
    'if book is already saved, make a note of it
    If ActiveWorkbook.Saved = True Then .[A100] = "Saved"

    'more code here

    'if it's already been saved, remove this note
    If .[A100] = "Saved" Then
    .[A100].ClearContents
    ActiveWorkbook.Save
    End If

    'if it hasn't been saved you'll now get the "Save?" prompt
    [/vba]
    You know you're really in trouble when the light at the end of the tunnel turns out to be the headlight of a train hurtling towards you

    The major part of getting the right answer lies in asking the right question...


    Made your code more readable, use VBA tags (this automatically inserts [vba] at the start of your code, and [/vba ] at the end of your code) | Help those helping you by marking your thread solved when it is.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •