Click here to Skip to main content
15,867,568 members
Articles / Desktop Programming / WPF

The Explorer Imperative - Partie Trois

Rate me:
Please Sign up or sign in to vote.
0.00/5 (No votes)
20 Mar 2012CPOL21 min read 18.6K   330   2   3
Restoring UI Responsiveness FromContinuations (Asynch file IO)

Search Menu, ProgressBar and Status Message.

Screen Print showing Search Menu, ProgressBar and Directory currently being processed in the Background Thread displayed in the TextBox.

Searching for a Responsive UI

Previously in the Explorer Imperative, I added a directory search function and enabled the menu selection for it. I had tested it and it looked quite cool on My XP. It worked very quickly on My XP. And in my myopic perspective of reality, I thought everyone would have the same awesme user experience as I. Then I got a modern computer with a modern operating system running on it, (Windows 7) and when I could find some time, I downloaded the latest version of F# and .NET and fired up my little toy program. It looked even better on Windows 7 until I did a search, and then, OH MY GaG, It froze up! Let me fix this, I thought. I could not move the Window to check the Console output underneath it and when I switched to the Console, the MainWindow disappeared. I couldn't tab back to it.

But then I was interrupted by other matters and when I returned the Window had re-appeared. I had just experienced an Unresponsive UI caused by a long-running IO process blocking the GUI Thread. To anyone who's opinion of F# was down-graded by this experience I offer my sincere apology. If you will give me the opportunity, I will strive to up-grade your opinion of F# and it's capabilities. But I must deviate from the strictly Imperative Paradigm and introduce some of the more powerful, and therefore naybe not so easily understood, Functional Constructs that give F# it's power and versatility.

This article is a face-saving device(my face) in which I will attempt to explain how I used a type extension to add Asynchronus processing to the long-running IO routine that was blocking the GUI Thread. The Code fot the type extension is the copyrighted property of Microsoft Corporation and can be found in the Microsoft Help Library under the haeding of 'Async.FromContinuations<'T> method (F#)'. You must consult that document as the official and correct description of the BackgroundWorker class. My comments should be viewed as an explanation of why I constructed the code that uses it in the way I did. This is not a claim to be the best or only way but only as a possible way of integrating a BackgroundWorker into a program. The F# Type Definition is an Extension of the BackgroundWorker class in 'System.ComponentModel.BackgroundWorker'. The 'with' keyword identifies this type definition as an 'extension' of the type 'BackgroundWorker'. This 'extension' creates an asynchronous computation that encapulates, in the RunWorkerCompletedEventHandler, the 'cont'(success continuation), the 'econt'(exception continuation) and 'ccont'(cancelation continuation). The callback will eventually call one of them. My interpretation of this process is that 'handler' will choose 'From' the three 'Continuations' depending on the 'RunWorkerCompletedEventHandler' event 'args' when 'RunWorkerCompleted' is(completed, that is, RunWorkerCompleted event occurs). While 'AsyncRunWorker' is computing your 'computation' your 'worker' routine 'ReportsProgress' as well as tracking Error and Cancellation Requests.

Here is the code for the type extension

F#
type BackgroundWorker with
  member this.AsyncRunWorker (computation, argument : 'T, progressChangedHandler) : Async<'U> =
    let workerAsync =
      Async.FromContinuations (fun (cont, econt, ccont) ->
        let handler = new RunWorkerCompletedEventHandler (fun sender args ->
          if args.Cancelled then
            ccont (new OperationCanceledException()) 
          elif args.Error <> null then
            econt args.Error
          else
            cont (args.Result :?> 'U))
        this.WorkerSupportsCancellation <- true
        this.WorkerReportsProgress <- true
        this.DoWork.AddHandler(new DoWorkEventHandler(fun sender args ->
          args.Result <- computation(argument, this, args)))
        this.ProgressChanged.AddHandler(progressChangedHandler)
        this.RunWorkerCompleted.AddHandler(handler)
        this.RunWorkerAsync(argument)
        )

    async { 
      use! holder = Async.OnCancel(fun _ -> this.CancelAsync())
      return! workerAsync
      }

In short, this type extension restores responsiveness to the GUI by executing in the background, allows the task to be cancelled and also allows exception handling and progress reporting to the GUI Thread. To take advantage of these possibilties, I have added a Cancel Search Selection to the Search Menu and a Progress Bar above the TextBox. The Search Status output is displayed in the TextBox.

Background

All of the Major IDE's have an excellent Search Function built-in, usually with a Replace capability as well. Windows 7 has an awesome Search Function built into the Operating System itself. You can use it from the Start Menu or Windows Explorer. It is fantastic!

But sometimes it is not exactly what I want. Sometimes I almost want to grep! Unfortunately (or maybe, fortunately) it doesn't happen often enough for me to remember all those switches and what they do or even where I put that book. Usually what I want to see is the line where some string or keyword occurs but I also want to see the line before and the line after. And, although I may want to browse the entire file, I don't want to open it in my Editor or IDE because it changes the list of 'recent' files or projects. Before long the list doesn't even contain anything I'm actually working on. So I open them in Notepad and use it's Find Function. Usually the three line 'context' output in the Console Window shows me what I'm looking for. Previously, I had added the File Search and 'context' output functionality to the Explorer Imperative and I intended to add a 'find' function to the TextBox when I could 'find' the time. Then I discovered that on a Windows 7 machine the file search Blocked the UI. Therefore in this episode, I will cover both of these issues.

The Background Worker

The 'type extension' shown above provides the member 'this.AsyncRunWorker' with return type of Async<'U>(generic Async type), whose parameters are 'computation'(which you must provide), 'argument'(generic type, 'T) and the 'progressChangedHandler'. The 'argument' type must be the the same type as the parameter named in the let binding that defines the 'computation'. In this case it is "let parseDirsAsync (path, worker: BackgroundWorker, eventArgs: DoWorkEventArgs) = ". To clarify the connections, 'parseDirsAsync' is the 'computation', 'path' is the 'argument' and 'worker' is a lambda expression defined in the code that calls the BackgroundWorker routine. Here's the code for the computation.

F#
let parseDirsAsync (path, worker: BackgroundWorker, eventArgs: DoWorkEventArgs) =
   // Define the computation 
   let mutable root = ""
   if File.Exists(path) then do // it's a file.extract the directory and fname
       fname <- path.Substring(path.LastIndexOf("\\") + 1)
       root  <- path.Substring(0,path.LastIndexOf("\\"))
   else // it's a directory. use it and current fname
       root <- path
   printfn "Searching for %s in %s and it's subdirectories." fname root
   // create 3 empty string arrays on the heap
   let fileList:string[] ref = ref (Array.create 1 "")
   let files:string[] ref = ref (Array.create 1 "")
   let subDirs:string[] ref = ref (Array.create 1 "")
   let gotIt = ref false //create a bool on the heap
   let rec fileSearch root = //Define the recursive function
       gotIt := false //':=' operator puts a value in the ref cell
       try
         files := Directory.GetFiles(root, fname, SearchOption.AllDirectories)
         gotIt := true // only happens when getfiles succeeds
       with
         | :? System.UnauthorizedAccessException -> ()
         | _  as oops -> invalidOp <| sprintf "%O" oops
       if (worker.CancellationPending) then
          eventArgs.Cancel <- true
       elif !gotIt = true then do // '!' operator dereferebces a ref cell
          let mutable count = 0
          fileList := Array.append !fileList !files // build the fileList
          let len = files.Value.Length //number of array elements
          if len > 0 then printfn "\nIn %s" root
          for fi in !files do
             printfn "    found %s" fi
             count <- count + 1 // builds from 0 to len
             let percentComplete = int ( ((float count) / (float (len))) * 100.0)
             worker.ReportProgress(percentComplete, fi)
       else do
          gotIt := false //make sure it's false now
          try
              files := Directory.GetFiles(root, fname) //, SearchOption.TopDirectoryOnly)
              gotIt := true
          with
              | :? System.UnauthorizedAccessException -> ()
              | _  as e -> invalidOp <| sprintf "%O" e
          if (worker.CancellationPending) then
              eventArgs.Cancel <- true
          elif !gotIt = true then do
              let mutable count = 0
              fileList := Array.append !fileList !files  //|>ignore
              let len = files.Value.Length
              if len > 0 then printfn "\nIn %s" root
              for fi in !files do
                 printfn "    found %s" fi
                 count <- count + 1
                 let percentComplete = int ( ((float count) / (float (len))) * 100.0)
                 worker.ReportProgress(percentComplete, fi)
          try
              subDirs := Directory.GetDirectories(root)  //, "*", SearchOption.TopDirectoryOnly)
              gotIt := true
          with
              | :? System.UnauthorizedAccessException -> ()
              | e -> invalidOp <| sprintf "%O" e
          if (worker.CancellationPending) then
              eventArgs.Cancel <- true
          else do
              if !gotIt = true then do
                 let mutable count = 0
                 let len = subDirs.Value.Length
                 for di in !subDirs do
                    count <- count + 1
                    let percentComplete = int ( ((float count) / (float (len))) * 100.0)
                    worker.ReportProgress(percentComplete, di)
                    fileSearch di
   fileSearch root  //Execute the file search function
   !fileList        //return fileList as the result

To clarify the intent of the routine, we will recursively get all of the files matching the pattern in fname. If we can we getfiles from all directories. If successful then we are through otherwise we getfiles from top directory and then recurse with all of the sub directories in the top directory. Since the fileSearch expression is a closure we can not trap a mutable value within it. We have to pass everything on the heap. This is why we must use 'ref', '!' and ':='. Since we defined 'fileSearch' within another function, we have to call it in that same function. Then we return the list of files we have built, '!fileList'.

Calling the BackgroundWorker

The short snippet below defimes the expression 'computation' and all of it's parts. To relate the snippet to the let binding defining parseDirsAsync, 'value' is the 'path' parameter. The lambda expression '(fun sender eventArgs -> ...)' is the 'worker' in the parameter list. In effect, the value 'parseDirsAsync' is a function passed to worker and worker is a parameter of parseDirsAsync. The F# Compiler understands this but I'm still thinking about it.

The second and third lines safely update the UI, reporting the current directory being processed and the percentage of that directory that has been completed. Since we don't really know the final number of files or directories that will be processed, we have arbitrarily chosen to report the progress for the directory we are processing rather than the entire job.

The fourth line, 'Async.StartWithContinuations(...)' starts the computation in the Background and feeds the result of success to the first continuation, the result of an exception to the seconnd continuation and the result of cancellation to the third continuation. Note that this snippet is preceded by some initialization code and is followed by code that finishes the processing on the GUI Thread, in other words, the three continuations.

F#
let computation value = worker.AsyncRunWorker(parseDirsAsync, value, (fun sender eventArgs ->
  textBox1.Text <- "Scanning ... " + eventArgs.UserState.ToString()
  myProgressBar.Value <- (float (eventArgs.ProgressPercentage)) ))
Async.StartWithContinuations( computation value, (fun result ->

The lines that follow this snippet contain the body of the success continuation which terminates with a closing parentheses, a comma and an opening parentheses and the token 'fun' which is the beginning of the lambda expression for the exception continuation. This lambda terminates with the same pattern, Lparen, comma, Rparen followed by the fun keyword to begin the third continuation to process a cancellation. The cancellation continuation is terminated by a closing parentheses which is followed by another closing parentheses which terminates the Async.StartWithContinuations lambda expression itself. In the success continuation I have added the code necessary to Enqueue the fileList and strip out any blank strings that were embedded in the list by appending to an array with a blank string. Then I position the Queue to the next available item to match the current item if the current item is in the Queue so that the next match can be found. If the current item is not in the Queue, we position to the beginning of the Queue. We find the item and attempt to position it in the middle of the Viewport. This is done in a function called 'updateMyScreen'. The other two continuations put a message in the TextBox indicating an Error or cancellation has occurred and sets the 'fileSearchStarted' flag to 'false' so that the next Search Menu constructed can enable all of the Asynchronous Search Clicks and disable the Cancellation Click. When certain conditions are met the Asynchrinius File Search is not executed. The only thing we need to do is to call the findNextFile() and updateMyScreen() routines.

Here is the Menu Request Handler for the Async File Search

F#
let findFileReq (myProgressBar:ProgressBar) (textBox1:TextBox) value =
  try
     let mutable currentDir = ""
     let mutable currentfname = ""
     let temp = focusItem.Tag.ToString()
     if File.Exists(temp) then do
        currentDir  <- temp.Substring(0,temp.LastIndexOf("\\"))
        if fname = "???" || fname = "" then do
            currentfname <- temp.Substring(temp.LastIndexOf("\\") + 1)
     else
        currentDir <- temp
     if fname <> "" then
       fSfname <- fname
     elif currentfname <> "" then
       fname <- currentfname
       fSfname <-currentfname
     else
       fSfname <- "???"
     //endif
     if (fQue.Count = 0) || (fSfname <> fTfname) then
        fname <- fSfname
        let targetFile = currentDir + "\\" + fname
        printfn "\nCurrent File is: %s." targetFile
        fQue.Clear()
        mainWindow.Title <- "Searching for  " + fname
        let worker = new BackgroundWorker()
        fQue.Clear()
        fileSearchStarted <- true
        textBox1.Text <- "Computing..."
        let computation value = worker.AsyncRunWorker(parseDirsAsync, value, (fun sender eventArgs ->
            textBox1.Text <- "Scanning ... " + eventArgs.UserState.ToString()
            myProgressBar.Value <- (float (eventArgs.ProgressPercentage)) ))
        Async.StartWithContinuations( computation value, (fun result -> 
            printfn "\nThe following files have been Enquwued:"
            Array.iter (fun elem -> (printfn "%s" elem;fQue.Enqueue elem)) result
            fileSearchStarted <- false
            startInDir <- fQue.Dequeue()
            while startInDir = "" && fQue.Count <> 0  do
               startInDir <- fQue.Dequeue()
            fQue.Enqueue(startInDir)
            if fQue.Contains(targetFile) then
               while startInDir <> targetFile do
                  startInDir <- fQue.Dequeue()
                  fQue.Enqueue(startInDir)
            let mutable qItem = new TreeViewItem()
            let mutable pItem = new TreeViewItem()
            for i in 0 .. (treeTrunk.Items.Count) - 1 do
               pItem <- treeTrunk.Items.[i]:?>TreeViewItem
               if startInDir.Contains(pItem.Tag.ToString()) then 
                  findIt pItem
                  textBox1.Text <- (focusItem.Tag.ToString())
               done
            mainWindow.Title <- focusItem.Tag.ToString()
            myProgressBar.Value <- 0.0
            findNextFile()
            printfn "Current File is:\n%s" (startInDir)
            updateMyScreen()
            // the end of the success continuation
            ),
            (fun exn -> 
               textBox1.Text <- "Operation failed with error:" + exn.Message
               fileSearchStarted <- false
               // the end of the exception continuation
               ),
            (fun _ -> 
               textBox1.Text <- "Operation canceled."
               fileSearchStarted <- false
               // the end of the cancellation continuation 
            )  // the end of StartWithContinuations
     else
        findNextFile()
        printfn "Current File is:%s\n" (startInDir)
        updateMyScreen()
  with
     |e -> eprintf "Error: "

The 'startHereReq' request calls the 'findFileReq' but passes it the current Directory instead of the default Root Directory of the Drive. This enables the user to search anywhere, on any Drive. The 'findString' routine itself is the same as in Partie Deux of the Explorer Imperative but the file search embeded in the 'findStringReq' has been changed to a Background version. The string search itself is not asynchronous but is fast enough to avoid blocking the GUI for long periods of time. I recognize that some may disagree but rather than argue the point, I invite them to write a new Background String Search using this type extension or any other technique they want to use.

The Menu. Starting an Asynchronous File Search

Popup Menu with Search Submenu

Screen Print showing Search Menu with File Name taken from Screen and Invitation to "Hit Me!" to start search for "???".

To prevent the user from accidently starting a search while a search is in progress it is necessary to disable the selections when a search starts. We also need to keep the Popup Menu open so that the user can cancel the search if they wish. But we need to close the Popup Menu when the Search has completed in order to construct a new Popup Menu with the selections re-enabled. This mean we have to close the Popup Menu. Therefore the Popup must be defined at the module level. This allows us to close it when we need to. Note that only the Popup is created at the module level. It is named 'menuPopup'. The Menu is put into the Popup at the end of the Menu Builder Routine. We will close the Popup in the 'updateMyScreen()' function. We do this by setting it's 'IsOpen' flag to false. This is the code.

menuPopup.IsOpen <- false

We also must set a flag to indicate that the search has completed. It is named 'fileSearchStarted' and it is set to false at the Module level and in the success, exception and cancellation continuations of the async invocations. It is set to true just before the invocations. It is tested in the Search Menu Item during the construction of the menu. This is necessary because the user can force the Menu to close by clicking outside of the Menu when it is open When this occurs and the user decides that it is necessary to cancel the search, the menu is built with only the Cancel selection enabled. The Screen Print at the beginning of this article shows a Menu with a search in progress. Notice that everything is greyed-out except for the Cancel Selection. Notice also, the Find Next File and Find Next ... String selections with the 'F3' and 'F4' in parentheses. Pressing the 'F3' or 'F4' keys will do the same thing as hitting one of these selections. These functions will cycle through the Queue. The function invoked by the 'F4' key has been updated to find the string in the TextBox. Event Handlers have been added to high light the selected word when the cursur hovers over the TextBox. I originally 'Added' a routine and a trigger for it but when I saw how short the routines were I changed it to a lambda expression. I left the original code in the program however. Here'sthe code for one of the lambda's.

F#
textBox1.MouseEnter.Add(fun _ ->
   textBox1.Focus()|>ignore
   )

This expression fires whenever the Mouae Pointer is over the TextBox. All it does is switch focus to the TextBox and throw away the type information. The other lambda is just below this one. All it does is switch focus to the TreeView when the Mouse Leaves. They are both at the end of the mainWindow.Loaded lambda expression This isn't really a part of the menu but is pertinent here because the 'F3' key will find the next occurrence of string in the TextBox. If you are looking at the TreeView and the Mouse Pointer happens to be over the TextBox You could miss what is happening.

And now back to the menu. I discussed the menu in Partie Deux so I am only going to cover the new code. We have already created the menuPopup Popup, so don't be mystified when the menu is added to it. Here's the code for the Search Menu. It is in the form of snippets of code to shorten the article.

F#
let menuReq(e:MouseButtonEventArgs) =
  try
     //let menuPopup = new Popup() - now created at module level, Line 291
     .....
     let pmS = new MenuItem()
     pmS.Header <- "Search"
     let pmSfF = new MenuItem()     // We create 
     let pmSfFsH = new MenuItem()   // all of the
     let pmSfS = new MenuItem()     // MenuItems
     let pmSfFsN = new MenuItem()   // in order to
     let pmSfFsS = new MenuItem()   // enable or 
     let pmSasynCan = new MenuItem()// disable them enmass
     if fileSearchStarted = true then
        pmSfF.IsEnabled <- false
        pmSfFsH.IsEnabled <- false
        pmSfS.IsEnabled <- false
        pmSfFsN.IsEnabled <- false
        pmSfFsS.IsEnabled <- false
        pmSasynCan.IsEnabled <- true
     else
        pmSfF.IsEnabled <- true
        pmSfFsH.IsEnabled <- true
        pmSfS.IsEnabled <- true
        pmSfFsN.IsEnabled <- true
        pmSfFsS.IsEnabled <- true
        pmSasynCan.IsEnabled <- false        
     let pmSfFHeader = new TextBox()
     pmSfFHeader.Text  <- "Search For File"
     ... 
     pmSfF.Tag <- thisItem.Tag.ToString()
     pmSfF.StaysOpenOnClick <- true
     pmSfF.Click.Add(fun args -> 
        findFileReq myProgressBar textBox1 (Directory.GetDirectoryRoot(thisItem.Tag.ToString()))
        pmSfF.IsEnabled <- false   // In the line above we are passing the progressBar,
        pmSfFsH.IsEnabled <- false // textBox1 and the root of the directory.
        pmSfS.IsEnabled <- false   
        pmSfFsN.IsEnabled <- false
        pmSfFsS.IsEnabled <- false
        pmSasynCan.IsEnabled <- true
        ) 
     pmSfF.Header <- pmSfFs
     let pmSfFToolTip = new ToolTip()
     pmSfFToolTip.FontSize <- sizeOfFont * 2.0
     pmSfFToolTip.FontWeight <- FontWeights.ExtraBold
     pmSfFToolTip.Content <- "HIT ME ! (To Start File Search)"
     pmSfF.ToolTip <- pmSfFToolTip
     let _ = pmS.Items.Add(pmSfF)
     pmSfFsH.Header <- "Start File Search Here"
     pmSfFsH.Tag <- thisItem.Tag.ToString()
     pmSfFsH.StaysOpenOnClick <- true
     pmSfFsH.Click.Add(fun args -> 
        fTfname <- "..." // Here we set the values to force an asynchronous file search 
        fSfname <- "???" // Note below we are passing the progressBar, textBox1 and the current directory
        findFileReq myProgressBar textBox1 (thisItem.Tag.ToString())
        pmSfFsH.IsEnabled <- false
        pmSfF.IsEnabled <- false
        pmSfS.IsEnabled <- false
        pmSfFsN.IsEnabled <- false
        pmSfFsS.IsEnabled <- false
        pmSasynCan.IsEnabled <- true
        ) 
     let pmSfFsHToolTip = new ToolTip()
     pmSfFsHToolTip.FontSize <- sizeOfFont * 2.0
     pmSfFsHToolTip.FontWeight <- FontWeights.ExtraBold
     pmSfFsHToolTip.Content <- "HIT ME ! (To Search this Directory and it's SubDirectories for File)"
     pmSfFsH.ToolTip <- pmSfFsHToolTip
     let _ = pmS.Items.Add(pmSfFsH)
     let cfilePan = new StackPanel()
     cfilePan.Orientation <- Orientation.Horizontal
     let mutable cargBox = new TextBox()
     cargBox.Text <- "Sratch For String"
     cargBox.Margin <- new Thickness(10.0,2.0,2.0,2.0)
     cargBox.MinWidth <- 15.0
     cargBox.IsReadOnly <- true
     ...
     cfileBox.LostFocus.Add(validateFileBox)
     cfileBox.IsReadOnly <- false
     ...
     let mutable argBox = new TextBox()
     argBox.Margin <- new Thickness(10.0,2.0,2.0,2.0)
     argBox.MinWidth <- 40.0
     let fndStrToolTip = new ToolTip()
     fndStrToolTip.FontSize <- sizeOfFont
     fndStrToolTip.FontWeight <- FontWeights.Bold
     fndStrToolTip.Content <- "Enter or change the string to search for"
     argBox.ToolTip <- fndStrToolTip
     if fndStr = "" then
      argBox.Text <- "???"
      fndStr <- "???"
     else
      argBox.Text <- fndStr
     argBox.LostFocus.Add(validateArgBox)
     argBox.IsReadOnly <- false
     let mutable inBox = new TextBox()
     inBox.Text <- " in "
     inBox.Margin <- new Thickness(10.0,2.0,2.0,2.0)
     inBox.MinWidth <- 15.0
     inBox.IsReadOnly <- true
     let _ = cfilePan.Children.Add(cargBox)
     let _ = cfilePan.Children.Add(argBox)
     let _ = cfilePan.Children.Add(inBox)
     let _ = cfilePan.Children.Add(cfileBox)
     pmSfS.Header <- cfilePan
     pmSfS.Tag <- thisItem.Tag.ToString()
     pmSfS.StaysOpenOnClick <- true
     pmSfS.Click.Add(fun args -> 
        findStrReq myProgressBar textBox1 (Directory.GetDirectoryRoot(thisItem.Tag.ToString()))
        pmSfS.IsEnabled <- false // Here we are passing the progressBar, the TextBox1 
        pmSfF.IsEnabled <- false // and the root of the directory
        pmSfFsH.IsEnabled <- false
        pmSfFsN.IsEnabled <- false
        pmSfFsS.IsEnabled <- false
        pmSasynCan.IsEnabled <- true
        ) 
     let pmSfSToolTip = new ToolTip()
     pmSfSToolTip.FontSize <- sizeOfFont * 2.0
     pmSfSToolTip.FontWeight <- FontWeights.ExtraBold
     pmSfSToolTip.Content <- "HIT ME ! (To Find File with this String in the Queue)"
     pmSfS.ToolTip <- pmSfSToolTip
     let _ = pmS.Items.Add(pmSfS)
     pmSfFsN.Header <- "Find Next File in Queue(F3)"
     pmSfFsN.Click.Add(findNextReq) // Here we are passing nothing
     let pmSfFsNToolTip = new ToolTip()
     pmSfFsNToolTip.FontSize <- sizeOfFont * 2.0
     pmSfFsNToolTip.FontWeight <- FontWeights.ExtraBold
     pmSfFsNToolTip.Content <- "HIT ME ! (Or HIT PF3 To FIND NEXT File in the Queue)"
     pmSfFsN.ToolTip <- pmSfFsNToolTip
     let _ = pmS.Items.Add(pmSfFsN)
     pmSfFsS.Header <- "Find Next File with this String(F4)"
     pmSfFsS.Click.Add(findNextStrReq) // Here we are passing nothing
     let pmSfFsSToolTip = new ToolTip()
     pmSfFsSToolTip.FontSize <- sizeOfFont * 2.0
     pmSfFsSToolTip.FontWeight <- FontWeights.ExtraBold
     pmSfFsSToolTip.Content <- "HIT ME ! (Or HIT PF4 To Find Next File with this String in the Queue)"
     pmSfFsS.ToolTip <- pmSfFsSToolTip
     let _ = pmS.Items.Add(pmSfFsS)
     pmSasynCan.Header <- "Cancel Search in Progress"
     pmSasynCan.Click.Add(fun args -> Async.CancelDefaultToken() )
     let pmSasynCanToolTip = new ToolTip() // The lambda function above cancels any search that might be running
     pmSasynCanToolTip.FontSize <- sizeOfFont * 2.0
     pmSasynCanToolTip.FontWeight <- FontWeights.ExtraBold
     pmSasynCanToolTip.Content <- "HIT ME ! (To Cancel the Asynchronous Search mow in Progress)"
     pmSasynCan.ToolTip <- pmSasynCanToolTip
     let _ = pmS.Items.Add(pmSasynCan)
     let _ = popupMenu.Items.Add(pmS)
     .....

The TextBox FindString Function

Now for something else, that is to say, completely not the same. The TextBox 'Find String' routine. It doesn't have a Menu Selection or even an event handler. Or at least, not an event handler that is specifically for a 'find'. Instead it is in the 'textBoxKeyUpDetected' handler routine. Currently it recognizes only the 'F3' function key but could be coded to respond to any key. I leave the analysis to those who are interested in understanding it.

The code for the TextBox FindString Function
F#
let textBoxKeyUpDetected(e:KeyEventArgs) =
 try
   if foundAt = -1 then
     foundAt <- textBox1.Text.IndexOf(fndStr, foundAt + 1)
   if e.Key.ToString() = "F3" then
     foundAt <- textBox1.Text.IndexOf(fndStr, foundAt + 1)
     if foundAt = -1 then
       foundAt <- textBox1.Text.IndexOf(fndStr, foundAt + 1)
     fndStrInd <- textBox1.GetLineIndexFromCharacterIndex(foundAt)
     mainWindow.Title <- sprintf "Line #:%d" fndStrInd
     textBox1.Select(foundAt, fndStr.Length)
 with
  |e -> eprintf "\n\n Error: %O\n" e

Using the Asynchronous File Search and FindString functions

Context Menu with Search Submenu

Screen Print showing the the alternate menu format of the Context Menu. This results in the same routines being called as with the PopupMenu format.

In the Screen Print above the Context Menu is shown. The selections are the same for both formats, even though they are constructed in different routines. The Popup Format is invoked when the Right Mouse Button is depressed. The menu will capture the Mouse Pointer if it is over the menu, otherwise the Context Menu will be invoked when the Right Mouse Button is released and it will capture the Mouse Pointer. The PreviewRightMouseButton<Down|Up> Event Handlers can be changed to both call the same menu or one of them can be commented out.

Search String hit hi-lited in expanded TextBox

Screen Print showing the results of a successful Search for the string "???". The selected string is high lighted when the Mouse Pointer is over the TextBox.

In the Screen Print above we have conducted an asynchronous file search from the 'Search For String ... in File ...' Menu Selection. If the Mouse Pointer is over the TreeView the File that was found will be high lighted. If the Mouse Pointer is over the TextBox the selected string(the string that was found) will be high lighted. The Splitter Bar below the Textbox can be moved up or down to decrease or increase the height of the TextBox. In the TextBoxF3 will find the next occurrence of the search string, F4 will do nothing. In the TreeView F3 will go to the next file in the Queue and F4 will find the next file in the Queue that contains the search string.

Console output of file search

Screen Print showing the Console Output of an astnchronous file search and how deep the search was when it got a hit.

In the Screen Print above we have the output showing the files that were found and how deep the search was when the file was found. You can tell if it was found in the top directory by comparing the Group Heading, which begins with 'In ...' and the 'found ...' as in the MyPdfes Directory it found one file in the top directory. This information may or may not be of interest to you. Following this Group of infornation is the list of files that were enqueued.

Console output of string search

Screen Print showing the lines where the string argument was found as well as the previous line and the line that follows it in the proper order.

In the Screen Print above the list of enqueued file is followed by messages showing which files were searched for the string. This group is followed by the Context of each occurrence, that is, the line before, the line itself and the line after. Using this output you can quickly see how a word is used in a file and determine which occurrence you want to examine more closely in the TextBox. The TextBox can be expanded to full screen and with the find function you may want to use it instead of, or in combination with Notepad.

Matching TextBox and Console

Screen Print showing Mouse Pointer hovering over an expanded TextBox, the selected word, "???", the 'Line #:592' in the Window Title and the Console Output showung lines where the string argument was found, including 592.

In the Screen Print above the 'Line #:592' in the Window Title refers to the line where the selected word was found, not the first line visible in the Viewport. Using this output you can quickly see how a word is used in a file and determine which occurrence you want to examine more closely in the TextBox, matching the line numbers in the Console output with the line number shown in the Window Title. The TextBox can be expanded to full screen and with the find function you may want to use it instead of, or in combination with Notepad. A Quick Reminder - On the File Menu, the Open, Execute and CMD.EXE Selections can be used to 'OPEN' a file. In most cases, 'Open' and 'Execute' are equivalent since 'Opening' a file EXECUTES the program defined to OPEN it(i.e. '.doc' is opened by Word, '.pdf' is opened by Adobe Reader). This includes 'Opening' a folder because Windows Explorer is the program that 'opens' a folder. The Menu Item 'CMD.EXE' has the same result as 'Open' and 'Execute' but will accept additional parameters. The intent of this is to allow you to execute batch files, passing parameters to it or passing the file name in the TreeView to a batch file. For instance, Right Click on a file with a .txt extension. In the File Menu, you can 'open' it with the OPEN, EXECUTE or CMD.EXE Menu Selections. On the other hand, using the OPEN Menu Seletion with a .bat file will 'execute' the file but will not pass amything to it as you could do with the EXECUTE Menu Selection. With the CMD.EXE Menu Selection you can, for instance, enter 'type' or 'notepad' in the first entry field to see the contents of it or enter the parameters for it in the last entry and run it from within the Explorer Imperative. You can also use the NEW Menu Selection to create a batch file, in place, that required no parameters and OPEN it. Just remember to 'Save As' and change the file type to '*.*'. One last thing, OPEN and EXECUTE use a Comspec Instance but they close it on completion while CMD.EXE leaves it open.

History

History Partie Trois

The intended purpose of the third episode of this series was to add a find string for inside the TextBox. Then I saw how long it could block the User Interface when searching a large Directory Tree. I realized this was very bad from a Users perspective. I found a solution that not only leaves the UI unblocked but also provides a little entertainment for the User to keep them interested watching the ProgressBar and text flashing by, and the Window will re-draw itself if you flip over to the Internet and then flip back. If this collection of snippets had been intended to have a specific purpose then this would be a bug-fix, but there was no planned purpose except wondering around, exploring F Sharp and asking myself, 'I wonder if I can do this', whatever this happened to be. It just happened that a Grid seemed to belong in a Window and a Tree belonged in a Grid. And it just grokked from there. And having grokked itself into being, it grokked forward in fullness. In other words, it kinda invented itself.

Here is a summary of the changes for this article.

  • Added a 'type extension' for BackgroundWorker. This enables Asynchronous processing of long-running functions, freeing blocked UI, feeding back ProgressBar Updates and Status Info, enables cancellation request and exception handling in the background thread.
  • Changed Directory Parsing Routine from a recursive function to a function containing a recursive expression which is a closure that uses mutable values from the outer scope, requiring the use of ref cells to pass those values.
  • Moved code to create popup for menu to module level so that it could be closed outside of menu routine.
  • Changed Search Menu and it's handlers to handle invocation of async processing and prevent simultaneaus execution of async processes, causing unpredictable results
  • Added routine to switch focus to TextBox when Mouse Enters it and back to TreeView when Mouse Leaves.
  • Added 'find string' function to TextBox. Invoked by 'F3', it will hi-lite the 'string' with 'SelectionBrush' and show the line number in the Window Title. This allows User to match line number from Console Window Context Output,
  • Added 'find next file in queue with this string'. Invoked by 'F4', it will cycle through the queued up files searching for the next file that contains the current search string.
  • Added routine, 'updateMyScreen' to move the TreeViewItem with focus to the middle of the screen if possible.
  • Commented out code to handle Mouse Wheel Tilt because it caused Scrolling to be stuck in Horizontal Only if Mouse Driver did not produce proper Delta Values.
  • Changed Initial Window Size to fit in physical screen on Windows 7 as well as Windows XP.
  • Updated the #I and #r Interactive Directives to include only the WPF V4.0 Search Path and reference ony the necessary Libraries. This was also necessary for the WPFEventLoop.fsx to prevent fsi.exe from using the WPF V3.0 Libraries from the WPF Event Loop Installation instead of the WPF V4.0 referenced in the script, causing undefined names in the Interactive execution that were defined in the compiled version. Also, the same script did not have undefined names if the WPF Event Loop was not installed. With the current #I and #r directives the script runs on Windows 7 and XP, producing the same output whether it is a compiled program or a script.
  • Added two semicolons to end of script for pasting into the Interactive Console.

History Partie Deux

This article is devoted to a discussion of the new functionality added to the Explorer Imperative, specifically the SEARCH functions, concentrating on the find string function for illustration purposes. The popup and context menu are discussed as they are required to invoke the search methods. I regard all of the code for the menues, including the functions that increase and decrease the font size for the menus as new code even if it was in the original program because it was not discussed at that time. Akthough the menues themselves were working as they do now the code was not showing up in the article. That's okay because I also did not provide any explanation of the code involved. For that reason I won't list any code chamges unless thay are bug fixes or noticable changes in functionality.

Here are the changes you should be aware of;

  • The 'File>New>File' function contained a bug in the code that extracted the parameters from the menu item. This bug has been corrected in this version.
  • The 'File>New>Folder' function contained a bug in the code that extracted the parameters from the menu item. This bug has been corrected in this version.
  • The 'View>Increase Font Size' function was changed to increase the size of the menu instaead of the size of the treeview.
  • The 'View>Decrease Font Size' function was changed to decrease the size of the menu instaead of the size of the treeview.
  • The 'Search' Menu has been enabled and functions added to 'Find a File', 'Start the search from a specific Directory', 'Find a String' and print out the context in which it is used and 'Find the Next File' using either the menu or the F3 Key.

License

This article, along with any associated source code and files, is licensed under The Code Project Open License (CPOL)


Written By
United States United States
This member has not yet provided a Biography. Assume it's interesting and varied, and probably something to do with programming.

Comments and Discussions

 
QuestionMessage Closed Pin
15-Nov-21 11:32
marry julia15-Nov-21 11:32 
SuggestionSave Images as PNG Pin
AspDotNetDev20-Mar-12 6:27
protectorAspDotNetDev20-Mar-12 6:27 
GeneralRe: Save Images as PNG Pin
Jaxon720-Mar-12 7:57
Jaxon720-Mar-12 7:57 
AnswerRe: Save Images as PNG Pin
AspDotNetDev20-Mar-12 8:23
protectorAspDotNetDev20-Mar-12 8:23 

General General    News News    Suggestion Suggestion    Question Question    Bug Bug    Answer Answer    Joke Joke    Praise Praise    Rant Rant    Admin Admin   

Use Ctrl+Left/Right to switch messages, Ctrl+Up/Down to switch threads, Ctrl+Shift+Left/Right to switch pages.