ProgressIndicator.st
author Claus Gittinger <cg@exept.de>
Sat, 18 May 1996 13:09:56 +0200
changeset 183 c63a4f284a6d
parent 86 4d7dbb5f1719
child 184 13a2f3677c68
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1995 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

View subclass:#ProgressIndicator
	instanceVariableNames:'percentage showPercentage fgColor connectedTop connectedLabel'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Misc'
!

!ProgressIndicator class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    a view showing a rectangle filled according the percentage value.
    Can be used as a progress indicator a la MSwindows.

    [author:]
        Claus Gittinger

    [see also:]
        ActionWaitBox AnimatedLabel
"
!

examples
"
    basic (internal) interface
    (if progress indicator is to be used in a complex box ...):

    Before you get frustrated - see the convenient-interface examples
    at the end ;-)

                                                                        [exBegin]
      |top p h|

      top := ModalBox new.
      top extent:300@100.
      top label:'Progress'.
      p := ProgressIndicator in:top.
      p origin:(0.0@0.5) corner:(1.0@0.5).
      p level:-1.
      h := p preferredExtent y.
      p topInset:(h // 2) negated; 
        bottomInset:(h // 2) negated;
        leftInset:5;
        rightInset:5.

      [
          1 to:100 do:[:val |
              (Delay forSeconds:0.05) wait.
              p percentage:val 
          ].
          top hide.
      ] fork.
      top open.
                                                                        [exEnd]

    changing colors, turning percentage display off:
                                                                        [exBegin]
      |top p h|

      top := StandardSystemView new.
      top extent:300@100.
      top label:'Progress'.
      p := ProgressIndicator in:top.
      p origin:(0.0@0.5) corner:(1.0@0.5).
      p level:-1.
      p showPercentage:false.
      p foregroundColor:(Color red).
      h := 10.
      p topInset:(h // 2) negated; 
        bottomInset:(h // 2) negated;
        leftInset:5;
        rightInset:5.
      top open.
      [
          1 to:100 do:[:val |
              (Delay forSeconds:0.05) wait.
              p percentage:val 
          ]
      ] fork
                                                                        [exEnd]

    with border (2D look):
                                                                        [exBegin]
      |top p h|

      top := StandardSystemView new.
      top extent:300@100.
      top label:'Progress'.
      p := ProgressIndicator in:top.
      p origin:(0.0@0.5) corner:(1.0@0.5).
      p borderWidth:1.
      h := p preferredExtent y.
      p topInset:(h // 2) negated; 
        bottomInset:(h // 2) negated;
        leftInset:5;
        rightInset:5.
      top open.
      [
          1 to:100 do:[:val |
              (Delay forSeconds:0.05) wait.
              p percentage:val 
          ]
      ] fork
                                                                        [exEnd]


    getting progress from a model:
                                                                        [exBegin]
      |model top p h|

      model := 0 asValue.

      top := StandardSystemView new.
      top extent:300@100.
      top label:'Progress'.
      p := ProgressIndicator in:top.
      p model:model.
      p origin:(0.0@0.5) corner:(1.0@0.5).
      p level:-1.
      h := p preferredExtent y.
      p topInset:(h // 2) negated; 
        bottomInset:(h // 2) negated;
        leftInset:5;
        rightInset:5.
      top open.

      [
          1 to:100 do:[:val |
              (Delay forSeconds:0.05) wait.
              model value:val 
          ]
      ] fork
                                                                        [exEnd]


    concrete example:
      search all files in the source directory for a string
      using grep. Show progress while doing so.
                                                                        [exBegin]
      |top p h names done|

      top := StandardSystemView new.
      top extent:300@100.
      top label:'Searching ...'.
      p := ProgressIndicator in:top.
      p origin:(0.0@0.5) corner:(1.0@0.5).
      p level:-1.
      h := p preferredExtent y.
      p topInset:(h // 2) negated; 
        bottomInset:(h // 2) negated;
        leftInset:5;
        rightInset:5.
      top openWithPriority:(Processor activePriority + 1).

      names := 'source' asFilename directoryContents.
      done := 0.
      names do:[:aName |
        |fn stream line|

        p percentage:(done / names size * 100).
        fn := ('source/' , aName) asFilename.
        fn isDirectory ifFalse:[
            stream := fn readStream.
            [stream atEnd] whileFalse:[
                line := stream nextLine.
                (line findString:'subclass:') ~~ 0 ifTrue:[
                    Transcript showCr:line
                ].
            ].
            stream close.
        ].
        done := done + 1
      ].

      top destroy
                                                                        [exEnd]


   using the convenient inBox-interface

   (this creates a box and an activity label and evaluates a block
    to indicate ...)

    basic interface demonstration:
                                                                        [exBegin]
      |p|

      p := ProgressIndicator 
                inBoxWithLabel:'doing something  ...'
                abortable:true.
      p showProgressOf:
            [:progressValue :currentAction |

              1 to:100 do:[:val |
                  (Delay forSeconds:0.05) wait.
                  val == 25 ifTrue:[
                      currentAction value:'still going ...'
                  ].
                  val == 50 ifTrue:[
                      currentAction value:'halfway through ...'
                  ].
                  val == 75 ifTrue:[
                      currentAction value:'almost finished ...'
                  ].
                  progressValue value:val 
              ]
            ]
                                                                        [exEnd]


    above search example using this convenient interface:
                                                                        [exBegin]
      |p|

      p := ProgressIndicator 
                inBoxWithLabel:'searching files ...'
                abortable:false.
      p showProgressOf:
            [:progressValue :currentAction |
                |names nDone|

                names := 'source' asFilename directoryContents.
                nDone := 0.
                names do:[:aName |
                  |fn stream line|

                  progressValue value:(nDone / names size * 100).
                  currentAction value:'searching ' , 'source/' , aName , ' ...'.

                  fn := ('source/' , aName) asFilename.
                  fn isDirectory ifFalse:[
                      stream := fn readStream.
                      [stream atEnd] whileFalse:[
                          line := stream nextLine.
                          (line findString:'subclass:') ~~ 0 ifTrue:[
                              Transcript showCr:line
                          ].
                      ].
                      stream close.
                  ].
                  nDone := nDone + 1
                ].
            ].
                                                                        [exEnd]


    a nice example: copying files a la windows ...
    the following copies all files to /dev/null.
                                                                        [exBegin]
      |p|

      (ProgressIndicator 
                inBoxWithLabel:'copy files to /dev/null ...'
                abortable:true)
         showProgressOf:
            [:progressValue :currentAction |
                |files nFiles nDone|

                files := '.' asFilename directoryContents.
                nFiles := files size.
                nDone := 0.
                files do:[:aFileName |
                    |percent|

                    nDone := nDone + 1.
                    percent := nDone / nFiles * 100.
                    progressValue value:percent. 
                    aFileName asFilename isDirectory ifTrue:[
                        Transcript showCr:('skipping ' , aFileName , ' ...'). 
                        currentAction value:('skipping ' , aFileName , ' ...'). 
                    ] ifFalse:[
                        Transcript showCr:('copying ' , aFileName , ' ...').
                        currentAction value:('copying ' , aFileName , ' ...').
                        Object errorSignal handle:[:ex |
                            self warn:'an error occurred while copying ' , aFileName.
                            ex return
                        ] do:[
                            aFileName asFilename copyTo:'/dev/null'.
                        ]
                    ].
                ].
            ].
                                                                        [exEnd]
"
! !

!ProgressIndicator class methodsFor:'instance creation'!

inBox
    ^ self inBoxWithLabel:'executing ...' abortable:false 
!

inBoxWithLabel:aLabel
    "create a topView containing an instance of myself,
     for later use with #showProgressOf:"

    ^ self inBoxWithLabel:aLabel abortable:false 
!

inBoxWithLabel:aLabel abortable:abortable
    "create a topView containing an instance of myself,
     for later use with #showProgressOf:"

    |top p l h|

    top := Dialog new.
    top extent:300@100; sizeFixed:true.
    top label:aLabel.
    top cursor:(Cursor wait).

    l := top addTextLabel:''.
    l borderWidth:0.
    l adjust:#left.
    l cursor:(Cursor wait).

    top addVerticalSpace.

    p := ProgressIndicator new.
    p extent:(1.0 @ p preferredExtent y).
    p level:-1.
    p leftInset:5;
      rightInset:5.
    p cursor:(Cursor wait).
    p connectToTop:top label:l.

    top addComponent:p.

    abortable ifTrue:[
	top addVerticalSpace.
	top addAbortButton
    ].

    ^ p
! !

!ProgressIndicator methodsFor:'accessing'!

foregroundColor:aColor 
    fgColor := aColor
!

percentage:aNumber
    |newPercentage|

    newPercentage := ((aNumber max:0) min:100) rounded.
    newPercentage ~~ percentage ifTrue:[
	percentage := newPercentage.
	shown ifTrue:[self redraw].
    ]
!

showPercentage:aBoolean
    showPercentage := aBoolean
! !

!ProgressIndicator methodsFor:'change & update'!

update:aspect with:aParameter from:changedObject
    (aspect == aspectMsg
    and:[changedObject == model]) ifTrue:[
	self percentage:(model perform:aspectMsg).
	^ self
    ].
    ^ super update:aspect with:aParameter from:changedObject
! !

!ProgressIndicator methodsFor:'drawing'!

redraw
    |s rx sx sy sw m w h|

    m := margin + 1.
    w := width - (m*2).
    h := height - (m*2).

    s := percentage printString , ' %'.
    sw := font widthOf:s.
    sx := (width - sw) // 2.
    sy := height // 2 + font descent + 2.

    rx := (w * percentage / 100) rounded.

    self paint:Color white.
    self fillRectangleX:m y:m width:w height:h.

    showPercentage ifTrue:[
	rx <= (sx+sw) ifTrue:[
	    self paint:Color black.
	    self displayString:s x:sx y:sy.
	]
    ].

    self paint:fgColor.
    self fillRectangleX:m y:m width:rx height:h.

    showPercentage ifTrue:[
	rx >= sx ifTrue:[
	    self clipRect:(m@m corner:rx+1 @ h).
	    self paint:Color white.
	    self displayString:s x:sx y:sy.
	    self clipRect:nil
	]
    ]
! !

!ProgressIndicator methodsFor:'initialization'!

initialize
    super initialize.
    viewBackground := styleSheet colorAt:'progressIndicatorViewBackground' default:Color white.
    fgColor := styleSheet colorAt:'progressIndicatorForegroundColor' default:Color blue.
    percentage := 0.
    showPercentage := true.
! !

!ProgressIndicator methodsFor:'queries'!

preferredExtent
    ^ 100 @ (font height + font descent + ((margin + 1) * 2))
! !

!ProgressIndicator methodsFor:'showing progress'!

connectToTop:top label:label
    connectedTop := top.
    connectedLabel := label
!

showProgressOf:aBlock
    "show progress, while evaluating aBlock.
     If the receiver has been created with inBox, show the
     box centered on the screen. If not, the view is assumed to
     be contained in another view, and no special startup actions
     are performed.

     The block is passed two arguments, the progressValue,
     which should be set to the percentage from time-to-time
     within the block and an action value, which should be set to
     the currently performed action (a string) from time to time.
     The second valueHolder can be left unchanged.

     Caveat: cannot (currently) suppress close of the box ..."

    |progressValue labelValue p|

    progressValue := 0 asValue.
    labelValue := '' asValue.

    connectedLabel notNil ifTrue:[
	connectedLabel 
	    model:labelValue;
	    aspect:#value;
	    labelMessage:#value.
    ].

    self model:progressValue.

    p := [
	[
	    aBlock value:progressValue value:labelValue
	] valueNowOrOnUnwindDo:[
	    p := nil.
	    connectedTop notNil ifTrue:[
		connectedTop hide
	    ]
	]
    ] fork.

    connectedTop notNil ifTrue:[
	Processor activeProcess 
	    withPriority:(Processor activePriority + 1)
	    do:[
		self topView show.
	    ].
	p notNil ifTrue:[p terminate].
    ] ifFalse:[
	self halt:'not yet implemented'.
    ]


    "
      |p|

      p := ProgressIndicator inBox.
      p showProgressOf:
	    [:progressValue :currentAction |
		1 to:100 do:[:percent |
		    (Delay forSeconds:0.05) wait.
		    progressValue value:percent 
		].
	    ].

      'it can be reused ...'.  
      p showProgressOf:
	    [:progressValue :currentAction |
		1 to:100 by:5 do:[:percent |
		    (Delay forSeconds:0.05) wait.
		    progressValue value:percent 
		].
	    ].

    "
! !

!ProgressIndicator class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ProgressIndicator.st,v 1.5 1996-05-18 11:09:56 cg Exp $'
! !