Consulting

Results 1 to 13 of 13

Thread: Solved: Disable X and Stop Shutdown

  1. #1

    Solved: Disable X and Stop Shutdown

    High everyone,
    I am new to this and would like to know if this is even possible.
    I am trying to disable the x button in a Citrix ICA Window. I would like to do this on client side but if need be I can put something in the users termserv login script or even run something on the server.

    Secondly I would like to be able to check to see if a Citrix Client is running if someone tries to shutdown or logoff the local pc. If Citrix is running then I would like it to pause the shutdown and inform the user to log out of Citrix. This would be on the same principal when you have a Office App open when trying to shutdown. The proccess stops and tells you to close the Office app first.

    The first one I have tried using the different snipplets (if that is the correct term) found on the web and using a FindWindow Function and that didn't work. I used the code from the MSDN site (http://support.microsoft.com/default...b;en-us;818361) as a guide to disabling the close button.

    If this is possible could someone please guide me in the right direction.

    Right now from trying this using the code above I believe the problem is that I cannot control a menu item on a window that is not created by script. In other words because the Citrix Window is created befor or after the script runs it cannot modify the menu. I am thinking I need to open the Citrix window from within the module itself to accomplish this.

  2. #2
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Hi Eric,

    A couple of questions for you.. Are you the systems administrator on your Citrix server?

    Rather than spend the time trying to work this out, why not just set the properties of the Citrix connection so that when a client disconnects their session (either via the X or by shutting down their PC), it is automatically disconnected, or disconnected after about 15 minutes.

    I've found that the above works very well without having to code anything.

    I'm sure you have your reasons, but just a thought...
    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!





  3. #3
    Yes
    The problem is on the disconnected session they leave open another program called Syteline. Well what happens is even if I have Citrix clear the disconnect after a time period the process from the db connection is still active. Therefor when we run rebalance utilities and nightly tasks the databases end up hanging during the shutdown process. We have tried everything from Citrix Settings to db Utils to try to help fix this situation. The only true way is to make sure the users log off properly and something like this would definately be a help. Definately not fix but help will the problem.

  4. #4
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Hmm. Okay, that makes sense. I've never tried this, but I'm assuming that we'd have to leverage an API call to see if the Citrix process is running. I'm at home right now, but I think it's ICA.exe. I'll see if I can find anything tomorrow.
    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. #5
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Hey there,

    The process name is actually wfica32.exe

    I'm going to try and call in a VB programmer, though, as the only way I could really even hope to control this is through Excel, which wouldn't really work.
    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!





  6. #6
    BoardCoder
    Licensed Coder
    VBAX Expert mark007's Avatar
    Joined
    May 2004
    Location
    Leeds, UK
    Posts
    622
    Location
    To stop windows closing and get tell them to logout of Citrix create a vb app that starts using a sub main then loads but doesn't show the form. Then within the form place the following code:

    [vba]
    Option Explicit

    Const TH32CS_SNAPHEAPLIST = &H1
    Const TH32CS_SNAPPROCESS = &H2
    Const TH32CS_SNAPTHREAD = &H4
    Const TH32CS_SNAPMODULE = &H8
    Const TH32CS_SNAPALL = (TH32CS_SNAPHEAPLIST Or TH32CS_SNAPPROCESS Or TH32CS_SNAPTHREAD Or TH32CS_SNAPMODULE)
    Const TH32CS_INHERIT = &H80000000
    Const MAX_PATH As Integer = 260
    Private Type PROCESSENTRY32
    dwSize As Long
    cntUsage As Long
    th32ProcessID As Long
    th32DefaultHeapID As Long
    th32ModuleID As Long
    cntThreads As Long
    th32ParentProcessID As Long
    pcPriClassBase As Long
    dwFlags As Long
    szExeFile As String * MAX_PATH
    End Type
    Private Declare Function CreateToolhelp32Snapshot Lib "Kernel32" (ByVal lFlags As Long, ByVal lProcessID As Long) As Long
    Private Declare Function Process32First Lib "Kernel32" (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long
    Private Declare Function Process32Next Lib "Kernel32" (ByVal hSnapShot As Long, uProcess As PROCESSENTRY32) As Long
    Private Declare Sub CloseHandle Lib "Kernel32" (ByVal hPass As Long)

    Function CheckProcess(strEXEName As String) As Boolean
    Dim hSnapShot As Long, uProcess As PROCESSENTRY32, r As Long
    'Takes a snapshot of the processes and the heaps, modules, and threads used by the processes
    hSnapShot = CreateToolhelp32Snapshot(TH32CS_SNAPALL, 0&)
    'set the length of our ProcessEntry-type
    uProcess.dwSize = Len(uProcess)
    'Retrieve information about the first process encountered in our system snapshot
    r = Process32First(hSnapShot, uProcess)

    Do While r > 0
    If LCase$(strEXEName) = _
    LCase$(Left$(uProcess.szExeFile, IIf(InStr(1, uProcess.szExeFile, Chr$(0)) > 0, InStr(1, uProcess.szExeFile, Chr$(0)) - 1, 0))) _
    Then CheckProcess = True
    'Retrieve information about the next process recorded in our system snapshot
    r = Process32Next(hSnapShot, uProcess)
    Loop
    'close our snapshot handle
    CloseHandle hSnapShot
    End Function

    Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
    If UnloadMode = vbAppWindows Then
    If CheckProcess("wfica32.exe") Then
    MsgBox "Please logout of citrix!"
    Cancel = 1
    End If
    End If
    End Sub
    [/vba]

    The app can then be loaded on start up as part of the login script and will run in the background.

    To remove the close button you need to use a combinaion of FindWindow, GetWindowLong and SetWindowLong.

    Use FindWindow to get a handle to the window. Now use:


    [VBA]Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" _
    (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
    Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" _
    (ByVal hwnd As Long, ByVal nIndex As Long) As Long

    Private Const GWL_STYLE As Long = (-16)
    Private Const WS_SYSMENU = &H80000


    Sub RemoveClose(hWnd as Long)

    Dim lngCurrent As Long
    lngCurrent = GetWindowLong(hwnd, GWL_EXSTYLE)
    lngCurrent=lngCurrent AND (NOT WS_SYSMENU)
    Dim ret As Long
    ret = SetWindowLong(hwnd, GWL_STYLE, lngCurrent)
    End Sub
    [/vba]

    This will also remove the maximise and minimise boxes though.

    Hope that helps.

    "Computers are useless. They can only give you answers." - Pablo Picasso
    Mark Rowlinson FIA | The Code Net

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

    Just in case I haven't told you lately... You rule!
    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!





  8. #8
    Thank You very much. IT works great. I just need to figure out how to get the program not responding message from poping up during the shutdown if the wfica32.exe is running. But this does exactly what I wanted it to do. I am glad I stumbled across this board and found such a helpful group of people.

  9. #9
    BoardCoder
    Licensed Coder VBAX Expert mark007's Avatar
    Joined
    May 2004
    Location
    Leeds, UK
    Posts
    622
    Location
    No problem - glad I could help!

    "Computers are useless. They can only give you answers." - Pablo Picasso
    Mark Rowlinson FIA | The Code Net

  10. #10
    Moderator VBAX Guru Ken Puls's Avatar
    Joined
    Aug 2004
    Location
    Nanaimo, BC, Canada
    Posts
    4,001
    Location
    Quote Originally Posted by EricM
    I just need to figure out how to get the program not responding message from poping up during the shutdown if the wfica32.exe is running.
    I'm thinking that you need a message to berate your user instead! If they got that far, doesn't that mean that they didn't log off properly?
    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!





  11. #11
    Yes I know. The message is just something I noticed and wanted to see if I could iliminate it myself. I am not concerned with it because users shouldn't get that far.

  12. #12
    Well I figured out how to do this by editing a dll with RH. I was able to edit the popup screen that says you are about to disconnect and delete the ok option. Then I editi the text to say something like Please log out properly. Now whenever they click the X or menu close it pops up the message and they can only cancel the disconnect. If they altF4 it will bring up the logout screen. SO they are not upset about a no responce X click and we are happy because it is a polite way to remind them not to disconnect.

    Thanks Everyone

  13. #13

    I'm a Real Dummy

    hi,

    i don't know how i implementing this script. could any one help me.

    best regards oliver

Posting Permissions

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