ProgressIndicator.st
author Claus Gittinger <cg@exept.de>
Mon, 15 Dec 1997 12:13:28 +0100
changeset 634 cee0d1f706e1
parent 575 9279151db8f5
child 826 d8470e26754d
permissions -rw-r--r--
*** empty log message ***

"
 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
		collector finishAction closeTopWhenDone'
	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.
    Can be used as a widget within an application, or
    via the convenient #inBox: instance creation messages,
    which shows a progressDisplay in a modalBox, while some
    action is performed.
    See examples.

    [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
    "create a topView containing an instance of myself,
     for later use with #showProgressOf:"

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

    "Modified: 22.10.1997 / 21:08:37 / cg"
!

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:"

    ^ self
	inBoxWithLabel:aLabel   
	text:''
	abortable:abortable

    "Modified: 17.7.1996 / 15:14:58 / cg"
!

inBoxWithLabel:aLabel icon:anIcon text:text abortable:abortable view:additionalView closeWhenDone:closeWhenDoneBoolean
    "create a topView containing an instance of myself,
     for later use with #showProgressOf:"

    |top p l h y y2|

    top := Dialog new.
    top label:aLabel.
    top cursor:(Cursor wait).

    anIcon notNil ifTrue:[
	y := top yPosition.
	l := top addTextLabel:anIcon.
	l borderWidth:0.
	l adjust:#left.
	l cursor:(Cursor wait).
	y2 := top yPosition.
	top yPosition:y.
    ].

    l := top addTextLabel:text.
    l borderWidth:0.
    l adjust:#left.
    l cursor:(Cursor wait).
    l leftInset:(anIcon width + 10).

    top yPosition:(top yPosition max:y2).

    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 closeTopWhenDone:closeWhenDoneBoolean.
    p connectToTop:top label:l.

    top addComponent:p.

    additionalView notNil ifTrue:[
	top addComponent:additionalView.
	additionalView extent:(1.0 @ additionalView preferredExtent y).
    ].

    abortable ifTrue:[
	top addVerticalSpace.
	top addAbortButton
    ].

    ^ p

    "Created: 17.7.1996 / 15:14:33 / cg"
    "Modified: 17.7.1996 / 15:16:58 / cg"
!

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

    ^ self
	inBoxWithLabel:aLabel 
	text:text 
	abortable:abortable 
	view:nil

!

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

    ^ self
	inBoxWithLabel:aLabel 
	text:text 
	abortable:abortable 
	view:additionalView 
	closeWhenDone:true

!

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

    ^ self
	inBoxWithLabel:aLabel 
	icon:nil
	text:text 
	abortable:abortable 
	view:additionalView 
	closeWhenDone:closeWhenDoneBoolean

! !

!ProgressIndicator methodsFor:'accessing'!

percentage:aNumber
    "set the percentage"

    |newPercentage|

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

    "Modified: 29.3.1997 / 16:08:00 / cg"
! !

!ProgressIndicator methodsFor:'accessing - behavior'!

closeTopWhenDone:aBoolean
    "set/clear the close-topView-when-done flag"

    closeTopWhenDone := aBoolean

    "Created: 3.9.1996 / 14:22:03 / cg"
    "Modified: 29.3.1997 / 16:08:19 / cg"
!

finishAction:aBlock 
    "define an action to be performed when finished"

    finishAction := aBlock

    "Created: 3.9.1996 / 14:15:15 / cg"
    "Modified: 29.3.1997 / 16:08:35 / cg"
! !

!ProgressIndicator methodsFor:'accessing - look'!

foregroundColor 
    "return the percentage displays foreground color"

    ^ fgColor

    "Created: 29.3.1997 / 16:12:28 / cg"
!

foregroundColor:aColor 
    "set the percentage displays foreground color"

    aColor ~~ fgColor ifTrue:[
	fgColor := aColor.

	shown ifTrue:[
	    self invalidate
	]
    ].

    "Modified: 3.4.1997 / 21:14:32 / cg"
!

showPercentage
    "return the flag controlling if the percentage is to be shown numerically"

    ^ showPercentage

    "Created: 29.3.1997 / 16:12:39 / cg"
!

showPercentage:aBoolean
    "set/clear the flag controlling if the percentage is to be shown numerically"

    showPercentage := aBoolean.
    shown ifTrue:[
	self invalidate
    ].

    "Modified: 29.3.1997 / 16:27:37 / cg"
! !

!ProgressIndicator methodsFor:'change & update'!

update:aspect with:aParameter from:changedObject
    "react upon value changes of my model"

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

    "Modified: 22.10.1997 / 21:05:11 / cg"
! !

!ProgressIndicator methodsFor:'drawing'!

redraw
    "redraw the percentage bar and optional percentage string"

    |s rx sx sy sw m w h|

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

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

    self paint:viewBackground.
    self fillRectangleX:m y:m width:w height:h.

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

	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 clippingRectangle:(m@m corner:rx+1 @ h).
	    self paint:Color white.
	    self displayString:s x:sx y:sy.
	    self clippingRectangle:nil
	]
    ]

    "Modified: 22.10.1997 / 21:05:31 / cg"
! !

!ProgressIndicator methodsFor:'initialization'!

initStyle
    "initialize styleSheet values"

    <resource: #style (#'progressIndicator.viewBackground'
		      #'progressIndicator.foregroundColor')>

    super initStyle.

    self is3D ifTrue:[
	self level:-1
    ].
    viewBackground := styleSheet colorAt:'progressIndicator.viewBackground' default:Color white.

    fgColor := styleSheet colorAt:'progressIndicator.foregroundColor' default:Color blue.
    fgColor := fgColor onDevice:device.

    showPercentage := true.

    "Created: 22.10.1997 / 21:06:48 / cg"
!

initialize
    super initialize.
    percentage := 0.

    "Modified: 22.10.1997 / 21:07:06 / cg"
! !

!ProgressIndicator methodsFor:'private'!

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

!ProgressIndicator methodsFor:'queries'!

preferredExtent
    "return my preferred extent"

    preferredExtent notNil ifTrue:[
	^ preferredExtent
    ].
    ^ 100 @ (font height + font descent + ((margin + 1) * 2))

    "Modified: 22.10.1997 / 21:07:17 / cg"
! !

!ProgressIndicator methodsFor:'showing progress'!

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.

    "/ the worker process

    p := [
	[
	    WindowGroup windowGroupQuerySignal handle:[:ex |
		ex proceedWith:self topView windowGroup
	    ] do:[
		aBlock value:progressValue value:labelValue
	    ]
	] valueNowOrOnUnwindDo:[
	    p := nil.
	    closeTopWhenDone ifTrue:[
		connectedTop hide
	    ].
	    finishAction notNil ifTrue:[
		finishAction value
	    ]
	]
    ] fork.

    Processor activeProcess 
	withPriority:(Processor activePriority + 1)
	do:[
	    self topView show.
	].
    p notNil ifTrue:[p terminate].

    "
      |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 
		].
	    ].

    "

    "Modified: 3.9.1996 / 14:22:43 / cg"
! !

!ProgressIndicator class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/ProgressIndicator.st,v 1.18 1997-12-15 11:13:28 cg Exp $'
! !